[Haskell-cafe] Type Constraints on Data Constructors
Daniel Schüssler
anotheraddress at gmx.de
Thu Jun 9 16:18:19 CEST 2011
You could do something like this, but admittedly it appears slightly clunky:
newtype Baz f a = Baz (Foo f => BazInner f a)
data BazInner f a = BazInner { baz :: f a, baz2 :: f a }
instance Foo (Baz f) where
foo a = Baz (let b = foo a in BazInner b b)
Cheers,
Daniel
On 2011-June-09 Thursday 15:25:40 Guy wrote:
> 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
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list