For ghc6.0.1 on Linux

# ghc Test1.hs -c -fglasgow-exts -fallow-undecidable-instances 
-fallow-overlapping-instances
# ghc Test2.hs -c -fglasgow-exts -fallow-undecidable-instances 
-fallow-overlapping-instances

works.

But for ghc6.3.20031201 the second compilation produces the message:

> Test2.hs:6:
>     No instance for (FormValue (Maybe [Char]))
>       arising from use of `isFormValue' at Test2.hs:6
>     In the definition of `is': is = isFormValue (Just "")

Oddly enough the compilation works if you do it in one step
using

# ghc --make Test2.hs -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances

module Test1 where

class FormValue value where
   isFormValue :: value -> ()
   isFormValue _ = () 

class FormTextField value

instance FormTextField String

instance FormTextField value => FormTextFieldIO value

class FormTextFieldIO value

instance FormTextFieldIO value => FormValue value

instance FormTextFieldIO value => FormTextFieldIO (Maybe value)
module Test2 where

import Test1

is :: ()
is = isFormValue (Just "")
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to