Hi Uri,
Here's how it might look.
{-# LANGUAGE DeriveDataTypeable, DataKinds, KindSignatures,
ScopedTypeVariables #-}
module Example where
import Data.Typeable
import Data.Proxy
data Tag = TagV | TagE | TagA | TagL
deriving Typeable
class TypeableTag (t :: Tag) where
tagRep :: Proxy t -> TypeRep
instance TypeableTag TagV where
tagRep _ = mkTyConApp (mkTyCon3 "mypkg" "Example" "'TagV") []
-- ... same for the other tags
newtype TaggedVar (t :: Tag) = TaggedVar Int
instance TypeableTag t => Typeable (TaggedVar t) where
typeOf _ =
mkTyConApp
(mkTyCon3 "mkpkg" "Example" "TaggedVar")
[tagRep (Proxy :: Proxy t)]
Roman
* Uri Braun <[email protected]> [2013-01-24 16:14:53-0500]
> I've read the recent posting titled "Non-derivable Typeable"
> (http://www.mail-archive.com/[email protected]/msg103616.html) which
> explains that Typeable cannot be automatically derived for cases where the
> kind is constrained.
>
> I'm very impressed that a solution is imminent. In the interim, can
> somebody kindly suggest a workaround? I'm okay with a manual instance, but
> I'd appreciate some help as to how to write one. I'm looking for a Typeable
> instance for TaggedVar for the following example below (extracted from my
> code).
>
> Thank you in advance!
>
> +Uri
>
> {-# LANGUAGE DeriveDataTypeable, DataKinds, KindSignatures #-}
> module Example where
>
> import Data.Typeable
>
> data Tag = TagV | TagE | TagA | TagL
> deriving Typeable
>
> newtype TaggedVar (t :: Tag) = TaggedVar Int
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe