Leif Willerts
Leif Willerts

Reputation: 205

Can I avoid explicitly deriving built-in Haskell typeclasses over and over again?

I have a large type hierarchy in Haskell. Counting family instances, which (can) have separate class membership after all, there are hundreds of data types.

Since the top-most type needs to implement built-in classes like Generic,Eq,Ord,Show, every single type in the hierarchy has to as well for a meaningful implementation overall. So my specification contains hundreds of times deriving (Generic,Eq,Ord,Show), which I would like to avoid cluttering the files.

A solution involving a single typeclass to attach everywhere like deriving GEOS with a single automatic derivation from that to the usual set in a centralized place would already help a lot with readability.

Another question asking for similar conciseness in constraints is solved by using constraint synonyms (so my GEOS would be not just linked to but explicitly made up of exactly the classes I want), which however apparently are currently prevented from being instantiated.

(A side question of mine would be why that is so. It seems to me like the reason @simonpj gives about the renamer not knowing what the type checker knows the synonym really to be would only apply to explicitly written out instance implementations.)

Maybe GHC.Generic itself (and something like generic-deriving) could help here?

Upvotes: 2

Views: 148

Answers (1)

leftaroundabout
leftaroundabout

Reputation: 120751

You could of course use Template Haskell, to generate the deriving-clauses as -XStandaloneDeriving.

{-# LANGUAGE QuasiQuotes #-}

module GEOSDerive where

import Language.Haskell.TH
import Control.Monad
import GHC.Generics

deriveGEOS :: Q Type -> DecsQ
deriveGEOS t = do
   t' <- t
   forM [ [t|Generic|], [t|Eq|], [t|Ord|], [t|Show|] ] $ \c -> do
      c' <- c
      return $ StandaloneDerivD Nothing [] (AppT c' t')

Then,

{-# LANGUAGE TemplateHaskell, StandaloneDeriving, QuasiQuotes, DeriveGeneric #-}

import GEOSDerive

data Foo = Foo

deriveGEOS [t|Foo|]

But, I find it somewhat dubious that you need so many types in the first place, or rather that you have so many types but each of them has so little code associated with it that you're bothered about mentioning those four classes for each of them. It's not like there's anything to be concerned about regarding refactoring or so with those, so I'd rather recommend simply keeping with deriving (Generic, Eq, Ord, Show) for each of them.

Upvotes: 1

Related Questions