[Hugs-users] bug in WinHugs Version 20051031?

Bulat Ziganshin bulatz at HotPOP.com
Fri Jan 6 05:52:23 EST 2006


Hello

the following program fails to load in Hugs2005 with all Haskell
extensions enabled:

{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
class (Monad m) => Stream m h where
class (Stream m h) => CharStream m h where
    vGetChar :: h -> m Char
    vGetContents :: h -> m String
    vGetContents h  =  func
                where func = do vGetChar h
                                return ""
class (Stream m h) => ByteStream m h where
    vGetByte :: h -> m ()
instance (CharStream m h) => ByteStream m h where
    vGetByte h = undefined
instance (ByteStream m h) => CharStream m h where
    vGetChar = undefined


message printed is:

ERROR file:.\SystemStreamClasses.hs -
*** The type checker has reached the cutoff limit while trying to
*** determine whether:
***     CharStream a b
*** can be deduced from:
***     ()
*** This may indicate that the problem is undecidable.  However,
*** you may still try to increase the cutoff limit using the -c
*** option and then try again.  (The current setting is -c40)


this program compiles ok in GHC 6.4.1. if call to `func` is replaced
with its body, then program loads ok:

    vGetContents h  =  do vGetChar h
                          return ""



can problem with loading my code in Hugs be resolved by giving to
`func` some type signmature? i can't replace call with its body
because code in real program is much more complicated:

    vGetContents h =
        let loop =
                let func = do c <- vGetChar h
                              next <- loop
                              c `seq` return (c : next)
                    handler e = if isEOFError e then return []
                                else mError e
                    in mCatch func handler
            in
            do firstchar <- vGetChar h
               rest <- loop
               return (firstchar : rest)

class (Monad m) => MonadHelper m where
    mError  :: IOError -> m a
    mCatch  :: m a -> (IOError -> m a) -> m a

class (Show h, MonadHelper m) => Stream m h | h -> m where
    ....

-- 
Best regards,
 Bulat                          mailto:bulatz at HotPOP.com





More information about the Hugs-Users mailing list