monomorphism/hugs98/ghc-5.02.3

Matt Fairtlough Matt Fairtlough <m.fairtlough@dcs.shef.ac.uk>
Thu, 30 May 2002 19:08:52 +0100 (BST)


Hello Haskellers, I've just joined this email group because I am
teaching Haskell to our 2nd year students.  I'm not a Haskell expert
but I do enjoy functional programming.

I don't know if anyone can help with this; I've checked the FAQs and
the bug-reports on SourceForge and found nothing but I'd have thought
it might be a common problem for folks migrating from hugs to ghci.

I'm used to using hugs in
haskell 98 mode but it seems that functions need not be monomorphic
in where clauses in that case (is this a departure from the standard?).

However, in ghc-5.02.3 for Haskell 98 (without glasgow extensions) it
seems that is not the case.  I _guessed_ that I need to use the flag
-fno-monomorphism-restriction
but I don't know whether I've failed to turn it on or if the
problem is to be found somewhere else.  A related problem I've found
is that if I try to specify that flag in a pragma, I get an error
message stating that static flags may not be specified in pragmas,
and yet the flag is supposed to be dynamic.

Here is a simple instance of a program that runs under Hugs but not
ghc(i)-5.02.3 :

module Test where

class Bounded a => Testit a where
    test1 :: a

data Test a = Test {f1::[a], f2::[Char]}

class Super a where
    sup1 :: a -> Maybe a

instance (Eq a, Testit a) => Super (Test a) where
    sup1 (Test{f1=x, f2=y}) = Just Test{f1=x, f2=y}
    where
    y' = top y
    x' = top x
    top :: [a] -> a
    top (s:st) = s

is it possible to compile this program in ghc-5.02.3?

Any advice much appreciated,

Matt.

---------------------------------------------------------------------------
Matt Fairtlough					m.fairtlough@dcs.shef.ac.uk
Verification and Testing Group			Room 115
Department of Computer Science			
University of Sheffield
Regent Court, 211 Portobello Street
Sheffield  S1 4DP			Tel:	(0)114-22-21826
UK					Fax:	(0)114-22-21810
WWW:	http://www.dcs.shef.ac.uk/~matt/
----------------------------------------------------------------------------