[Haskell-cafe] Would it be evil to add "deriving Typeable" to newtype Q?

Neil Mitchell ndmitchell at gmail.com
Fri May 7 15:32:57 EDT 2010


Hi Leonel,

You might want to try Derive
(http://community.haskell.org/~ndm/derive) if DrIFT doesn't work for
you. They do roughly the same jobs, but Derive has more output formats
(it can be spliced in as Template Haskell, generate #include files,
output text etc) more derivations (but not quite overlapping -
although both have Typeable), and is fully cabal-friendly on all
platforms.

Thanks, Neil

On Thu, May 6, 2010 at 3:42 PM, Leonel Fonseca <leonelfl at gmail.com> wrote:
> Hey, the hint provided by Ben worked like a charm.
>
> I've also tried Ivan suggestions both on my windows and linux installations.
> DrIFT-cabalized couldn't install at all at windows since I don't use MinGW.
> So, I ghc'ed --make  DrIFT.
>
> Both, windows and linux, refused to complete work with this error:
> drift: can't find module Control/Monad
>
> Thank you.
>
>> {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
>>
>> import Data.Typeable
>> import Language.Haskell.TH
>>
>> deriving instance Typeable1 Q
>
>
>
> --
>
> Leonel Fonseca.
> _______________________________________________
> 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