[Haskell-cafe] Deriving

Martin Huschenbett huschi at gmx.org
Tue Dec 2 17:18:09 EST 2008


If you use a newtype the answer to the second question is yes. Just put

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

in the first line of your module or pass -XGeneralizedNewtypeDeriving to 
ghc or ghci.

Daryoush Mehrtash schrieb:
> What happens when a type adds driving such as:
> 
> newtype SupplyT s m a = SupplyT (StateT [s] m a)
> 
>     deriving (Functor <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Functor>, Monad <http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Monad>, MonadTrans, MonadIO)
> 
> 
> Two questions:
> 
> How does the deriving implement the instance?
> 
> Is there a way for me to add  my own classes in the deriving?  for example
> 
> newtype .....
>    deriving( xyz)
> 
> 
> Thanks
> 
> 
> 
> ------------------------------------------------------------------------
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list