[Haskell] RE: Implicit parameters:
Simon Peyton-Jones
simonpj at microsoft.com
Fri Feb 4 08:38:58 EST 2005
| Sent: 19 January 2005 14:42
| Unbound implicit parameter (?global_counter::IORef a)
| arising from use of `get_unique' at Test.hs:17:13-22
|
| Is this a bug? Is there some reason why this is not possible? (and if
it
| is not possible
| shouldn't the documentation be changed to reflect this)...
Keean's program has made me realise (yet again) that implicit parameters
are a bit different to class constraints.
Consider
module Main where
main = let ?x = 5 in print foo
foo = woggle 3
woggle :: (?x :: Int) => Int -> Int
woggle y = ?x + y
GHC's current rules say that 'foo' is monomorphic, so we get
foo :: Int
but we also get an unbound top-level constraint (?x::Int). GHC emits a
message like:
Unbound implicit parameter (?x::Int)
arising from use of `woggle' at ...
The point is that THERE IS NO WAY FOR THIS CONSTRAINT TO GET BOUND,
because we don't have a top-level binding form for implicit parameters.
So it's stupid for 'foo' to be monomorphic.
The situation is a bit different for class constraints:
module Main where
main = print fooC
fooC = woggleC 3
woggleC :: Num a => a -> a
wogglec y = y+1
'fooC' is monomorphic, so we get foo :: a, with a top-level constraint
(Num a); and the defaulting mechanism fixes a=Integer, so all is well.
Even in the absence of monomorphism, we might get some other use of
'fooC' in the module which fixes fooC's type. So it's *not* stupid for
foo to be monomorphic.
Possible conclusions
A) Emit an error message at the definition of foo, saying that it needs
a type signature.
B) Change the rule so that we always generalise over the implicit
parameters of *top-level* definitions, even in definitions that fall
under the MR.
C) Change the rule so that we always generalise over implicit
parameters, whether top-level or nested.
I'll do (A) for now, I think, since it improves the error message.
For those that care, there are quite extensive notes about
generalisation and implicit parameters in GHC's source code, here:
http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/typecheck
/TcSimplify.lhs?rev=1.144
(search for "Notes on implicit parameters"). Interestingly, the notes
argue for (C), but that's not what is currently implemented in GHC, for
reasons I don't remember. Perhaps compatibility with other
implementations.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Keean Schupke
| Sent: 19 January 2005 14:42
| To: glasgow-haskell-users at haskell.org
| Subject: Implicit parameters:
|
| Question regarding implicit parameters... The GHC manual says:
|
| "Dynamic binding constraints behave just like other type class
| constraints in that they are automatically propagated."
|
| But the following code produces an error:
|
|
------------------------------------------------------------------------
---------------------------------
|
| main = do
| var <- newIORef (0::Int)
| let ?global_counter = var in f
|
|
| f = do
| a <- get_unique
| putStr (showInt a "\n")
| b <- get_unique
| putStr (showInt b "\n")
| c <- get_unique
| putStr (showInt c "\n")
|
|
| get_unique :: (?global_counter :: IORef Int) => IO Int
| get_unique = readIORef ?global_counter
|
|
------------------------------------------------------------------------
----------------------------------
|
| If "(?global_counter :: IORef Int)" were a class constraint the type
| signature
| for 'f' could be derived automatically... but we get:
|
| Unbound implicit parameter (?global_counter::IORef a)
| arising from use of `get_unique' at Test.hs:17:13-22
|
| Is this a bug? Is there some reason why this is not possible? (and if
it
| is not possible
| shouldn't the documentation be changed to reflect this)...
|
| Keean.
|
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Haskell
mailing list