I've found a much shorter example (without imports) that does not compile. The error displayed is:

Ambiguous type variable `a' in the top-level constraint:
`ATermConvertibleSML a'
arising from use of `las' at /home/maeder/haskell/examples/NoMonoRestr.hs:29


(comenting out the initial "OPTIONS" line, will make it go through)

Cheers Christian
{-# OPTIONS -fno-monomorphism-restriction #-}
module NoMonoRestr where

data ShATerm = ShAAppl String [Int] [Int]

data ATermTable = ATermTable

getATerm :: ATermTable -> ShATerm
getATerm = undefined

data Annotation = Annotation

data Annoted a = Annoted a [Annotation]

from_sml_ATermAnnotedBasic_Items :: 
    ATermConvertibleSML a => ATermTable -> (a,[Annotation])
from_sml_ATermAnnotedBasic_Items = undefined

class ATermConvertibleSML t where
    from_sml_ShATerm     :: ATermTable -> t

instance (ATermConvertibleSML a) => ATermConvertibleSML (Annoted a) where
    from_sml_ShATerm att =
        case aterm of
         (ShAAppl con as _)  ->
             (case con of
                "pos-BASIC-ITEMS" -> 
                      let (bi,las) = from_sml_ATermAnnotedBasic_Items att
                      in Annoted bi las )
       where
            aterm = getATerm att
_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to