NHC98 and GHC 4.08.1 differ on monad related functions

José Romildo Malaquias romildo@urano.iceb.ufop.br
Sat, 14 Oct 2000 05:49:52 -0200


--4Ckj6UjgE2iN1+kY
Content-Type: text/plain; charset=iso-8859-1
Content-Disposition: inline
Content-Transfer-Encoding: 8bit

Hello.

While porting Haskore to NHC98 I got an error
I am not understanding. I have attached a test
module that shows the error message:

$ nhc98 -c Test.hs

====================================
        Error after type deriving/checking:
No default for  Monad.MonadPlus at 7:1.(171,[(2,209)])
No default for  Monad.MonadPlus at 6:1.(174,[(2,208)])

GHC 4.08.1 and Hugs98 accepts the code without
complaining.

Any hints?

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

--4Ckj6UjgE2iN1+kY
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="Test.hs"

module Test where

import Monad

zeroOrMore, oneOrMore :: MonadPlus m => m a -> m [a]
zeroOrMore m      = return [] `mplus` oneOrMore m
oneOrMore  m      = do { a <- m; as <- zeroOrMore m; return (a:as) }


--4Ckj6UjgE2iN1+kY--