I allege that this is a Hugs bug!  Yes, delayTrans is
monomorphic, so it can only be used at one type.
And indeed, it *is* used at one type, namely Bool.

We use the defaults when the situation is ambiguous;
here it isn't.

Perhaps I should add a clarifying para to the report?

Simon

> -----Original Message-----
> From: Jeffrey R. Lewis [mailto:[EMAIL PROTECTED]]
> Sent: Tuesday, November 10, 1998 5:12 PM
> To: [EMAIL PROTECTED]
> Subject: monomorphism wierdness
> 
> 
> 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
> 
> 

Reply via email to