With GHC 4.00, the enclosed program successully compiles. Hugs reports
the following (expected) type error (line 11 is the one that contains
`delayTrans memOut'):
ERROR "qh.hs" (line 11): Type error in application
*** expression : delayTrans memOut
*** term : memOut
*** type : [Maybe Bool]
*** does not match : [Maybe Int]
If I look at the .hi file GHC produces, I see:
MuHawk.hi:57 delayTrans _:_ [PrelMaybe.Maybe PrelBase.Bool] ->
[PrelMaybe.Maybe PrelBase.Bool] ;;
The correct type for delayTrans should be `[Maybe Int]' because of the
monomorphism restriction. It's as if the `default' for Num were
suddenly `Bool'. If I add the following two signatures, everything
types properly:
nopTrans :: Num a => Maybe a
delayTrans :: Num a => [Maybe a] -> [Maybe a]
------------------
module MuHawk where
delay = (:)
nopTrans = Just 0
delayTrans = delay nopTrans
memOut :: [Maybe Bool]
memOut = error "memOut"
writeback = delayTrans memOut
instance Num Bool where
(+) = (||)
(*) = (&&)
negate = not
fromInteger n = if even n then False else True