Re: Instance checking and phantom types

2003-09-15 Thread Sven Panne
Nick Name wrote:
Hi all, I have an example wich I don't understand:
First of all, let's rename the constructors and types a bit to make
things clearer add the instance in question, and remove the type
signatures:

module Main where
class C t
data T = MkT
instance C T
instance C ()
data C t = T1 t = MkT1

f1 = MkT1

data C t = T2 t = MkT2 t

f2 = MkT2 ()

Then we can easily ask GHC:


[EMAIL PROTECTED]:~ ghci -v0 Main.hs
*Main :i T1 MkT1 f1 T2 MkT2 f2
-- T1 is a type constructor, defined at Main.hs:8
data (C t) = T1 t = MkT1
-- MkT1 is a data constructor, defined at Main.hs:8
MkT1 :: forall t. T1 t
-- f1 is a variable, defined at Main.hs:10
f1 :: forall t. T1 t
-- T2 is a type constructor, defined at Main.hs:12
data (C t) = T2 t = MkT2 t
-- MkT2 is a data constructor, defined at Main.hs:12
MkT2 :: forall t. (C t) = t - T2 t
-- f2 is a variable, defined at Main.hs:14
f2 :: T2 ()

The first function, f1, is accepted both by hugs and ghc, unlike the 
second wich is rejected.

Why does this happen? Shouldn't f1 be rejected with no instance C ()
The reason is buried in

   http://haskell.org/onlinereport/decls.html#sect4.2.1

In a nutshell: The context in datatype declarations has only an effect for
the *data* constructors of that type which use the type variables mentioned
in the context. Contexts have no effect for the *type* constructor. IIRC the
reason for this design decision was that contexts in type signatures should
always be explicit.
Cheers,
   S.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Instance checking and phantom types

2003-09-15 Thread Sven Panne
Nick Name wrote:
Got it ;) Thanks for prompt reply. What does should always be explicit 
mean? Is there a notion of explicit context that I should know?
What I meant was the fact that you always have to write down *all* contexts
involved in a type signature. Nothing is inherited under the hood by
contexts in datatype declarations.
Cheers,
   S.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe