[Haskell] boilerplate boilerplate

Lennart Augustsson lennart at augustsson.net
Tue May 22 19:26:53 EDT 2007


Oh, so you want the original behaviour of type declarations back. :)
In Haskell 1.0, if you didn't specify any deriving, you got as much 
derived as possible.  I quite liked it, but it was changed.

 	-- Lennart

On Tue, 22 May 2007, Alex Jacobson wrote:

> Date: Tue, 22 May 2007 19:07:26 -0400
> From: Alex Jacobson <alex at alexjacobson.com>
> To: haskell at CS.YALE.EDU
> Subject: [Haskell] boilerplate boilerplate
> 
> 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 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?
>
>  {-# 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?
>
> -Alex-
>
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>


 	-- Lennart


More information about the Haskell mailing list