On Thu, May 6, 2010 at 4:05 AM, Ivan Miljenovic
<[email protected]> wrote:
> Re-CC'ing -cafe:
>
> On 6 May 2010 12:54, Leonel Fonseca <[email protected]> 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 :)
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to