[Haskell] boilerplate boilerplate

Isaac Dupree isaacdupree at charter.net
Tue May 22 19:26:45 EDT 2007


Alex Jacobson wrote:
> Consider this module for a blog entry that I will want to put in various
> generic collections that require Ord
> 
>   {-# OPTIONS -fglasgow-exts #-}
>   module Blog.Types where
>   import Data.Typeable
>   import Data.Generics
> 
>   data BlogEntry = Entry EpochSeconds Name Email Title Body
>                    deriving (Eq,Ord,Read,Show,Typeable)
> 
>   newtype Name = Name String deriving (Eq,Ord,Read,Show,Typeable)
>   newtype Title = Title String deriving (Eq,Ord,Read,Show,Typeable)
>   newtype Body = Body String deriving (Eq,Ord,Read,Show,Typeable)
> 
> 
> It seems really unnecessarily verbose.  Having to add the OPTION header
> AND import Data.Typeable and Data.Generics just to derive Typeable is a
> beat-down.

It works for me removing the Data.Generics import - I think that's just
for generics/deriving Data, which is different from Typeable.

> It is even more of a beat-down to have to add a deriving
> clause for every newtype to make this all work nicely.  Is there a way
> to make all types automatically derive everything unless there is an
> explicit instance declaration otherwise?

No, not with separate compilation, not in a practical way anyway.  And
sometimes you don't _want_ a newtype to be an instance of those classes
that the inside type is instances of (for abstraction/encapsulation).

> 
>   {-# OPTIONS -fglasgow-exts -fgenerics -fderiving#-}
>   module Blog.Types where
> 
>   data BlogEntry = Entry EpochSeconds Name Email Title Body 
>   newtype Name = Name String   newtype Title = Title String   newtype
> Body = Body String
> Isn't that much nicer?

A little nicer, but wouldn't you like to get rid of those words
"newtype" and duplicate names too? >:)

(For your second, desired code sample, I have a feeling this is where
DrIFT or Data.Derive are going to come in... I'm not going to mention
those external things!)

Isaac


More information about the Haskell mailing list