[This bug report may be related to SimonPJ's question about implicit
parameters and the monomorphism restriction - I'm not sure.]

The attached program contains two definitions of "ident" - a function
that uses implicit parameters.

The only difference between them is that the first (which works) binds
the implicit parameter to a normal variable and the second (which
gives a type error uses the implicit parameter directly).

$ rm -f T.o && ghc -c -fglasgow-exts T.hs -cpp -DOK=1
$ rm -f T.o && ghc -c -fglasgow-exts T.hs -cpp -DOK=2

T.hs:20:
    Could not deduce `?env :: ([(String, b)], b1)' from the context ()
    Probable fix:
        Add `?env :: ([(String, b)], b1)' to the banding(s) for {y}
        Or add an instance declaration for `?env :: ([(String, b)], b1)'
    arising from use of implicit parameter `?env' at T.hs:20
    In the first argument of `fst', namely `env'
    In the second argument of `lookup', namely `(fst env)'

Interestingly, both versions work if I remove the 2nd component of Env:

  type Env = ([(String,Int)])

and delete the calls to fst.  This makes the somewhat mysterious
behaviour of the typechecker even more mysterious.

-- 
Alastair Reid        [EMAIL PROTECTED]        http://www.cs.utah.edu/~reid/



module T where

import Maybe

type Env = ([(String,Int)],Int)

ident :: (?env :: Env) => String -> Int

#if OK==1

ident x = y
 where
  env = ?env
  y   = fromJust (lookup x (fst env))

#elif OK==2

ident x = y
 where
  y   = fromJust (lookup x (fst ?env))

#endif

_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to