[Haskell-cafe] Type Constraints on Data Constructors
Guy
guytsalmaves-h at yahoo.com
Thu Jun 9 15:25:40 CEST 2011
Can this be extended to records, without redundant repetition?
data Baz f a = Baz {baz :: Foo f => f a, baz2 :: Foo f => f a}
The type constraint for baz2 adds no information, as it's the same f as baz, but I can't leave it out.
----- Original Message -----
> From: Daniel Schüssler <danlex at gmx.de>
> To: haskell-cafe at haskell.org
> Cc: Guy <guytsalmaves-h at yahoo.com>
> Sent: Thursday, 9 June 2011, 2:06
> Subject: Re: [Haskell-cafe] Type Constraints on Data Constructors
>
> Hello,
>
> you might be thinking of this type?
>
> {-# LANGUAGE Rank2Types #-}
>
> class Foo f where
> foo :: a -> f a
>
> data Baz f a = Baz (forall f. Foo f => f a)
>
> instance Foo (Baz f) where
> foo a = Baz (foo a)
>
> Maybe the difference between Bar and Baz ist best explained by writing it with
> an explicit class dictionary for Foo:
>
> {-# LANGUAGE Rank2Types #-}
>
> data FooDict f = FooDict {
> foo :: forall a. a -> f a
> }
>
> data Bar f a = Bar (FooDict f) (f a)
>
> data Baz f a = Baz (FooDict f -> f a)
>
> fooDict_Baz :: FooDict (Baz f)
> fooDict_Baz = FooDict (\a -> Baz (\d -> foo d a))
>
> -- fooDict_Bar :: FooDict (Bar f)
> -- fooDict_Bar = FooDict (\a -> Bar ? ?)
> -- Doesn't work - you'd have to create a 'FooDict f' and a
> 'f a' out of just
> an 'a'
>
>
>
> Cheers,
> Daniel
More information about the Haskell-Cafe
mailing list