[Yhc] Inconsistent compilation when type context is involved
Dimitry Golubovsky
golubovsky at gmail.com
Wed Mar 21 23:34:29 EDT 2007
Hi,
The following program:
=============
module Main where
import Data.Maybe
fun :: Show a => String -> Maybe a -> IO ()
fun s mb = do
putStrLn s
case mb of
Nothing -> return ()
Just a -> do putStrLn (show a)
return ()
main = do fun "bla" Nothing
fun "foo" (Just "bar")
=============
compiles with Yhc and runs fine (even with only the first line of
main, so there is no mentioning that a String is wrapped in Maybe).
However another example (shortened mainly to type signatures):
================
putLine :: CNode a => String -> Maybe a -> CPS b ()
putLine s mbb k = getHTMLDocument $ \doc ->
...
let iac = case mbb of
Nothing -> addChild dv -- dv is also
some instance of TNode, basically
Just b -> insertChild b dv -- almost
anything in DOM is a node.
in ....
...
main = putLine "bla" (Nothing {-- :: Maybe TNode --}) $ id
....
addChild :: (CNode newChild, CNode zz) =>
newChild -> zz -> CPS b zz
insertChild :: (CNode refChild, CNode newChild, CNode parent) =>
refChild -> newChild -> parent -> CPS b parent
================
results in error:
-- during after type inference/checking
Error: No default for DOM.Level1.Dom.CNode at 23:1-23:91.(Id 348,[(Id
1,Id 350)])
If I uncomment ::Maybe TNode then compilation succeeds.
The class CNode is defined without any methods:
class CNode a
data TNode = TNode
instance CNode TNode
Is there any difference between these two examples, or is it a bug? Or
too much context is involved in addChild and insertChild?
Thanks.
PS I haven't tried to compile the above code with Ghc, and I am
specifically interested in compilation by Yhc: this is a part of the
DOM/Javascript stuff.
--
Dimitry Golubovsky
Anywhere on the Web
More information about the Yhc
mailing list