[Haskell-cafe] Would it be evil to add "deriving Typeable" to
newtype Q?
Ben Millwood
haskell at benmachine.co.uk
Thu May 6 06:40:33 EDT 2010
On Thu, May 6, 2010 at 4:05 AM, Ivan Miljenovic
<ivan.miljenovic at gmail.com> wrote:
> Re-CC'ing -cafe:
>
> On 6 May 2010 12:54, Leonel Fonseca <leonelfl at gmail.com> wrote:
>> I wasn't aware of GeneralizedNewtypeDeriving.
>> I just edited the source file Language.Haskell.TH.Syntax
>> and left:
>>
>> newtype Q a = Q { unQ :: forall m. Quasi m => m a }
>> deriving Typeable
>
> Hang on, is Q something actually in the template-haskell library? In
> that case, you can't just do "deriving (Typeable)" .
>
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
import Data.Typeable
import Language.Haskell.TH
deriving instance Typeable1 Q
-- Sorted :)
More information about the Haskell-Cafe
mailing list