[Haskell-cafe] Fwd: The Typeable class is changing
Thomas DuBuisson
thomas.dubuisson at gmail.com
Mon Jul 11 22:53:47 CEST 2011
Alberto G. Corona <agocorona at gmail.com> wrote:
> What to do when the data has been defined in other package and provides no
> Typeable instance?
You'd have to use standalone deriving, which I hope gets into Haskell 201X.
----
module A where
data A = A
----
{-# LANGUAGE StandaloneDeriving, DeriveDataTypeable #-}
module B where
import A
import Data.Typeable
deriving instance Typeable A
----
Cheers,
Thomas
>
> 2011/7/11 Yitzchak Gale <gale at sefer.org>
>>
>> Simon Marlow has announced[1] on the Haskell Libraries
>> list that the Typeable class is changing.
>>
>> The standard way to create a Typeable instance is
>> just to derive it. If you do that, you will not be affected
>> by this change.
>>
>> But it seems that many packages create Typeable
>> instances by explicitly using mkTyCon. If your package
>> does this, it will eventually break, after a deprecation
>> period.
>>
>> Please respond to this thread if you own a package
>> that will be affected by this change.
>>
>> Can someone who has quick access to the entire contents
>> of Hackage please do a grep and find out exactly which
>> packages on Hackage will be affected? Thanks.
>>
>> -Yitz
>>
>> [1] http://www.haskell.org/pipermail/libraries/2011-July/016546.html
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
> _______________________________________________
> 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