[Haskell-cafe] interesting type families problem

Anthony Cowley acowley at seas.upenn.edu
Wed Sep 8 13:15:20 EDT 2010


2010/9/8 Gábor Lehel <illissius at gmail.com>:
> Oh. Hmm. That makes sense. So I gather there's absolutely no way to
> specify which instance you mean, and hence to use `value` as any
> concrete type?

Here's one way to indicate which value you are referring to.

Anthony

{-# LANGUAGE EmptyDataDecls, TypeFamilies #-}
data True
data False

class TypeValue a where
    type ValueTypeOf a
    value :: a -> ValueTypeOf a

instance TypeValue True where
    type ValueTypeOf True = Bool
    value _ = True

instance TypeValue False where
    type ValueTypeOf False = Bool
    value _ = False

main = print (value (undefined::True))


More information about the Haskell-Cafe mailing list