[Haskell-cafe] question about GADT and deriving automatically a Show instance
TP
paratribulations at free.fr
Sat May 18 11:16:23 CEST 2013
Chris Wong wrote:
>> data Person :: Gender -> * where
>> Dead :: Person Gender -- WHAT DO I PUT HERE
>> Alive :: { name :: String
>> , weight :: Float
>> , father :: Person Gender } -> Person Gender
>
> Here's the problem. In the line:
>
> Dead :: Person Gender
>
> you are referring to the Gender *type*, not the Gender kind.
>
> To refer to the kind instead, change this to:
>
> Dead :: forall (a :: Gender). Person a
>
> This means "for all types A which have the kind Gender, I can give you
> a Person with that type." The Alive declaration and deriving clause
> can be fixed in a similar way.
>
> Also, to enable the "forall" syntax, you need to add
>
> {-# LANGUAGE ExplicitForAll #-}
>
> at the top of the file.
Thanks a lot for your help. I did not realize the possible usage of "a::b"
to indicate "any type a of kind b". So I have adapted my code, and the
following version is working correctly:
----------------------------
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
data Gender = Male | Female
data Person :: Gender -> * where
Dead :: Person (a :: Gender)
Alive :: { name :: String
, weight :: Float
, father :: Person (a::Gender) } -> Person (b :: Gender)
deriving instance Show (Person (a::Gender))
main = do
let a = Alive "Joe" 60 Dead :: Person Female
let b = Alive "Jim" 70 a :: Person Male
----------------------------
However, I have not managed to make the version with forall work. Below, the
first occurrence of forall is ok, but the three following yield error.
----------------------------
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ExplicitForAll #-}
data Gender = Male | Female
data Person :: Gender -> * where
Dead :: forall (a :: Gender). Person a
Alive :: { name :: String
, weight :: Float
, father :: forall (a :: Gender). Person a } -> forall (b ::
Gender). Person b
deriving instance Show (forall (a :: Gender). Person a)
main = do
let a = Alive "Joe" 60 Dead :: Person Female
let b = Alive "Jim" 70 a :: Person Male
----------------------------
Thanks,
TP
More information about the Haskell-Cafe
mailing list