[Haskell-cafe] Manually instantiating Typeable w/DataKinds

Uri Braun uribraun at eecs.harvard.edu
Thu Jan 24 22:14:53 CET 2013


I've read the recent posting titled "Non-derivable Typeable"
(http://www.mail-archive.com/haskell-cafe@haskell.org/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





More information about the Haskell-Cafe mailing list