[Haskell-cafe] Type Constraints on Data Constructors

Daniel Schüssler anotheraddress at gmx.de
Thu Jun 9 01:07:13 CEST 2011


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

On 2011-June-08 Wednesday 20:45:56 Guy wrote:
> {- continuing discussion from beginners@ -}
> 
> I have code such as
> 
> class Foo f where
>      foo :: a -> f a
> 
> data Bar f a = Foo f => Bar {bar :: f a}
> 
> instance Foo (Bar f) where
>      foo a = Bar $ foo a
> 
> GHC insists that I put Foo f => on the instance declaration, even though
> the constructor for Bar implies this.
> 
> Is there any reason why GHC cannot infer this constraint from the Bar
> constructor? One issue raised in the beginners thread is that
> undefined :: Bar f a
> is not Foo f, but as undefined cannot be evaluated, this would not appear
> to be a problem.
> 
> 
> _______________________________________________
> 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