Re: Fun with 3.00

1998-01-30 Thread Sigbjorn Finne


> For some reason there's no flag to switch off the update analyser.
> It does very little good anyway, so just switch it off by force
> in ghc/driver/ghc.lprl (look for -fupdate-anal).
> 

-fno-update-analysis turns it off.

--Sigbjorn



bug report

1998-01-30 Thread Marc van Dongen=

Dear all,



While compiling some stuff I came across the following:
 compiling with -O did failed without any error message
  at all.
 compiling with -O2 succeeded

?


Any idea what could have caused it? I can tell you how to
reproduce this if wanted.


Regards,



Marc



Query on multi-param type classes

1998-01-30 Thread Jon Mountjoy


Hello,

I decided to try and get my old multi-param. parser to work,
and got told-off by Haskell's parser:

Please tell me what I am doing wrong.  The following program:

> module A where
>  
> class (Monad m, Monad (t m)) => AMonadT t m where
>   lift :: m a -> t m a

Gives me:

(lambda o) ghc -fglasgow-exts A.hs  
A.hs:3:23: parse error on input: "("

Thanks,
Jon
--

The Glorious Glasgow Haskell Compilation System, version 3.00, patchlevel 0

Effective command line: -fglasgow-exts -v

Ineffective C pre-processor:
echo '{-# LINE 1 "A.hs" -}' > /tmp/ghc19403.cpp && cat A.hs >> 
/tmp/ghc19403.cpp

real0.0
user0.0
sys 0.0
ghc:compile:Output file A.o doesn't exist
ghc:recompile:Input file A.hs newer than A.o

Haskell compiler:
/home/jon/FunctionalLanguages/GHC-3.00//lib/hsc ,-N ,-W ,/tmp/ghc19403.cpp  
-fglasgow-exts -fignore-interface-pragmas -fomit-interface-pragmas -fsimplify [  
-ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -fdo-case-elim 
-freuse-con -fpedantic-bottoms -fsimpl-uf-use-threshold3 -fmax-simplifier-iterations4  
]   -fwarn-overlapping-patterns -fwarn-missing-methods -fwarn-duplicate-exports 
-himap=.%.hi:/home/jon/FunctionalLanguages/GHC-3.00//lib/imports%.hi   -v 
-hifile=/tmp/ghc19403.hi -S=/tmp/ghc19403.s +RTS -H600 -K100
Glasgow Haskell Compiler, version 3.00, for Haskell 1.4
A.hs:3:23: parse error on input: "("

real0.1
user0.0
sys 0.1
deleting... /tmp/ghc19403.cpp /tmp/ghc19403.hi /tmp/ghc19403.s

rm -f /tmp/ghc19403*



NGC bug (?), canonicalised.

1998-01-30 Thread Alex Ferguson


SOF:
> install-sh is the fallback script used if the configure script is
> unable to find an OK looking `install' somewhere along your PATH.

Oops, I confess to not knowing this.  Configure doesn't seem to moan too
loudly about the lack of an "install", so I assumed that it was The
Real Program.


Getting back to the first problem I reported, the code-gen crunch:
here's as simple an instance as ever I can possibly construct:

module R where

data NumVal = RealNum Float

isZero (RealNum 0.0) = True


This is the Sun NCG, of course.  Doesn't happen without the constructor,
or with Int's, or with -fvia-C...

Slainte,
Alex.
--

ghc-3.00 -c R.hs -H30m  -K2M -recomp -fglasgow-exts -cpp -syslib ghc 
-syslib hbc -Rgc-stats -dshow-passes -fmax-simplifier-iterations4 
-funfolding-use-threshold-0 
*** Reader:
*** Renamer:
*** TypeCheck:
*** DeSugar:
*** Core2Core:
*** Core2Core: Simplify
*** Core2Stg:
*** Stg2Stg:
*** CodeGen:
*** CodeOutput:
ghc-3.00: module version changed to 6; reason: usages changed
/usr/ccs/bin/as: "/tmp/ghc24667.s", line 188: error: statement syntax
make: *** [R.o] Error 1
swift.ucc.ie:~/filt4: make R.o OPT=-v
ghc-3.00 -c R.hs -H30m  -K2M -recomp -fglasgow-exts -cpp -syslib ghc 
-syslib hbc -Rgc-stats -dshow-passes -fmax-simplifier-iterations4 
-funfolding-use-threshold-0 -v
The Glorious Glasgow Haskell Compilation System, version 3.00, patchlevel 0

Effective command line: -c -H30m -K2M -recomp -fglasgow-exts -cpp -syslib ghc 
-syslib hbc -Rgc-stats -dshow-passes -fmax-simplifier-iterations4 
-funfolding-use-threshold-0 -v

Haskellised C pre-processor:
echo '{-# LINE 1 "R.hs" -}' > /tmp/ghc24692.cpp && 
/usr/local/ghc-3.00/lib/hscpp -v   -D__HASKELL1__=4 -D__GLASGOW_HASKELL__=300 
-I. -I/usr/local/ghc-3.00/lib/includes -I/usr/local/ghc-3.00/lib/includes R.hs 
>> /tmp/ghc24692.cpp

real0.0
user0.0
sys 0.0
hscpp:CPP invoked: /usr/local/lib/gcc-lib/sparc-sun-solaris2.5/2.7.2.3/cpp 
-traditional -D__HASKELL1__=4 -D__GLASGOW_HASKELL__=300 -I. 
-I/usr/local/ghc-3.00/lib/includes -I/usr/local/ghc-3.00/lib/includes R.hs
ghc-3.00:compile:Output file R.o doesn't exist
ghc-3.00:recompile:Input file R.hs newer than R.o

Haskell compiler:
/usr/local/ghc-3.00/lib/hsc ,-N ,-W ,/tmp/ghc24692.cpp  -fglasgow-exts 
-dshow-passes -fignore-interface-pragmas -fomit-interface-pragmas -fsimplify [  
-ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -fdo-case-elim 
-freuse-con -fpedantic-bottoms -funfolding-use-threshold-0 
-fmax-simplifier-iterations4  ]   -fwarn-overlapping-patterns 
-fwarn-missing-methods -fwarn-duplicate-exports 
-himap=.%.hi:/usr/local/ghc-3.00/lib/hslibs/hbc/imports%.hi:/usr/local/ghc-3.00/
lib/hslibs/ghc/imports%.hi:/usr/local/ghc-3.00/lib/hslibs/hbc/imports%.hi:/usr/l
ocal/ghc-3.00/lib/hslibs/ghc/imports%.hi:/usr/local/ghc-3.00/lib/imports%.hi   
-v -hifile=/tmp/ghc24692.hi -S=/tmp/ghc24692.s +RTS -H3000 -K200 
-SR.stat
Glasgow Haskell Compiler, version 3.00, for Haskell 1.4
*** Reader:
*** Renamer:
*** TypeCheck:
*** DeSugar:
*** Core2Core:
*** Core2Core: Simplify
*** Core2Stg:
*** Stg2Stg:
*** CodeGen:
*** CodeOutput:

real3.8
user3.3
sys 0.3

Pin on Haskell consistency info:
echo '
.text
hsc.R.hs.33.0..:' >> /tmp/ghc24692.s

real0.0
user0.0
sys 0.0
*** New hi file follows...
{-# GHC_PRAGMA INTERFACE VERSION 20 #-}
_interface_ R
_instance_modules_
Addr ArrBase CCall Foreign IO PrelBounded PrelNum

_usages_
PrelBase 1 :: $d1 1 $d10 1 $d11 1 $d12 1 $d13 1 $d15 1 $d2 1 $d20 1 $d21 1 $d24 
1 $d25 1 $d26 1 $d27 1 $d28 1 $d29 1 $d3 1 $d30 1 $d31 1 $d32 1 $d33 1 $d34 1 
$d36 1 $d37 1 $d38 1 $d39 1 $d4 1 $d40 1 $d41 1 $d42 1 $d43 1 $d5 1 $d6 1 $d7 1 
$d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $menumFromThenTo 
1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 Enum 1 Eq 1 Eval 1 Num 
1 Ord 1 Ordering 1 Show 1 String 1;
PrelNum 1 :: $d1 1 $d10 1 $d14 1 $d15 1 $d16 1 $d17 1 $d18 1 $d19 1 $d2 1 $d23 1 
$d24 1 $d25 1 $d26 1 $d27 1 $d29 1 $d30 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 
$d36 1 $d37 1 $d38 1 $d39 1 $d4 1 $d5 1 $d6 1 $d7 1 $d8 1 $d9 1 $mdiv 1 $mdivMod 
1 $mmod 1 $mquot 1 $mrecip 1 $mrem 1 Fractional 1 Integral 1 Ratio 1 Rational 1 
Real 1;
PrelTup 1 :: $d13 1 $d4 1 $d49 1 $d9 1;
_exports_
R isZero NumVal(RealNum);
_instances_
instance {PrelBase.Eval NumVal} = $d1;
_declarations_
data NumVal = RealNum PrelBase.Float ;
$d1 _:_ {PrelBase.Eval NumVal} ;;
isZero _:_ NumVal -> PrelBase.Bool ;;


ghc-3.00: module version unchanged at 6

Replace .hi file, if changed:
cmp -s R.hi /tmp/ghc24692.hi-new || ( rm -f R.hi && cp 
/tmp/ghc24692.hi-new R.hi )

real0.0
user0.0
sys 0.0

Unix assembler:
gcc -o R.o -c  /tmp/ghc24692.s
/usr/ccs/bin/as: "/tmp/ghc24692.s", line 188: error: statement syntax

real0.0
user0.0
sys 0.0
deleting... /tmp/ghc24692.cpp /tmp/ghc24692.hi /tmp/ghc24692.s

Re: Fun with 3.00

1998-01-30 Thread Simon Marlow

Sven Panne <[EMAIL PROTECTED]> writes:

> One can play funny games with GHC-3.00 and the following program
> (a small fragment of a Happy-generated parser):
> 
> --
> module Foo ( happyParse ) where
> 
> action_0 1 = \j tk _ -> action_1 j j tk (HappyState action_1)
> 
> action_1 3 = error "Bar"
> action_1 _ = \i tk st@(HappyState action) sts stk -> action (-1) (-1) tk st sts 
>(Just i : stk)
> 
> happyParse = action_0 2 2 '-' (HappyState action_0) [] [] 2
> 
> newtype HappyState b c =
>HappyState (Int -> Int -> b -> HappyState b c -> [HappyState b c] -> c)
> --

Just one more thing to add: if you compile a Happy-generated parser
with -O, you probably have porridge for brains anyway :-)  It tends to
increase the size of the object file without having much effect on the
speed of the parser.

Recommended flags for compiling Happy parsers: 

-Onot -funfolding-use-threshold0

There are some even more fun games to play with Happy parsers: you can
get rid of the HappyAbsSyn datatype altogether by defining a function
'cooerce' of type a -> b and replacing all HappyAbsSyn constructors
with applications of it.  I've tried this in Hugs, and it works (but
doesn't improve things) - it should have quite a bit effect with GHC,
though.  How do you define coerce?  Like this :-)

_interface_ Coerce 1
_exports_
Coerce coerce;
_declarations_
1 coerce _:_ _forall_ [a b] => a -> b ;; _A_ 1 _S_ L _U_ _/\_ $x0 $x1 -> \ $x2 :: $x0 
-> $x2 ;;

And make sure you don't have -dcore-lint turned on.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



test for ghc

1998-01-30 Thread S.D.Mechveliani

Hellow,

ftp.botik.ru/pub/local/Mechveliani/docon/1.06/

contains the test for ghc:  it is a large computer algebra system.

The test is Makefile to compile this system correct.
It works under  linux-i386-unknown,  but i doubt how it will do
on other platforms.
In particular,  Marc van Dongen <[EMAIL PROTECTED]>
writes:

> I am in the process of installing doCon ...
> after successfully having compiled IParse.hsa and OPTab_.hs the
> compilation of DPrelude.hs fails with a misterious:

> [snip]
>  nativeGen/MachCode.lhs:1017: Non-exhaustive patterns in case
> ...
>  make: *** [source/DPrelude.o] Error 1

> I've tried to find a directory nativeGen and a file MachCode but
> can't find them. Do you have any suggestions on how to solve this?


nativeGen/MachCode.lhs  
is, probably, of ghc system. Looks like a ghc bug.

Marc,  DoCon provides  hi files only for  ghc-2.10, 2.08.
If you have other version, then this Makefile may not go as it is.
Also consult sometimes  [EMAIL PROTECTED]
  ..users@..

--
Sergey Mechveliani
[EMAIL PROTECTED]




Re: Query on multi-param type classes

1998-01-30 Thread Ralf Hinze

Dear Jon, dear Simon,

> > > class (Monad m, Monad (t m)) => AMonadT t m where
> > >   lift :: m a -> t m a

> I'm frankly unsure of the consequences of lifting the 
> restriction.  Can you give a compact summary of why you want
> to?  Our multi-parameter type-class paper gives none, and if
> you've got one I'd like to add it.

I would suspect that the context `only' lists an invariant which
should hold and that one can do with `class (Monad m) =>' alone.
Give it a try (it worked for me all (most?) of the time).

Cheers, Ralf



Re: Query on multi-param type classes

1998-01-30 Thread Keith S. Wansbrough

> >  A.hs:3:23: parse error on input: "("
> 
> I should have said that I've implemented the choices given
> on the Standard Haskell web discussion page.  In particular:
> 
> ===
> Choice 7a
> ~
> 
> The context in a class declaration (which introduces superclasses)
> must constrain only type variables.  For example, this is legal:
> 
> class (Foo a b, Baz b b) => Flob a b where ...
> but not
> class (Foo [a] b, Baz (a,b) b) => Flob a b where ...
> 
> It might be possible to relax this restriction (which is the same
> as in current Haskell) without losing decideability, but we're not
> sure.  Choice 7a is conservative, and we don't know of any examples
> that motivate relaxing the restriction.
> ===
> 
> I'm frankly unsure of the consequences of lifting the 
> restriction.  Can you give a compact summary of why you want
> to?  Our multi-parameter type-class paper gives none, and if
> you've got one I'd like to add it.
> 
> In the short term, you're stuck.  Damn!  First customer too!

I ran into *exactly* the same problem with my own monad transformer
code, but haven't reported it yet because there's a lot of other stuff
I need to do to massage it into GHC-friendly form.

The problem is, the above parens appear in the standard definition of
a monad transformer, the motivating example for MPCs in the first
place!

Consider the state monad transformer:

> type StateT s m v = s -> m (v,s)
> 
> instance Monad m => Monad (StateT s m) where
>   return v = \s -> return (v,s)
>   m >>= f  = \s -> m s  >>= \(v,s') -> 
>(f v) s
> 
> instance (Monad m, Monad (StateT s m))   -- here is the problem
>   => MonadT (StateT s) m where
>   lift m = \s -> m >>= \v ->
>  return (v,s)
> 
> class Monad m => StateMonad s m where
>   getS :: m s
>   setS :: s -> m ()
> 
> instance Monad m => StateMonad s (StateT s m) where
>   getS   = \s -> return (s ,s)
>   setS s = \_ -> return ((),s)
> 
> instance (StateMonad s m, MonadT t m)
>   => StateMonad s (t m) where
>   getS   = lift getS
>   setS s = lift (setS s)

Note we assume here the definition of MonadT:

> class (Monad m, Monad (t m)) => MonadT t m where  -- here again
>   liftM :: m a -> t m a

You can see the two lines that violate 7a.

> Simon

--KW 8-)
-- 
: Keith Wansbrough, MSc, BSc(Hons) (Auckland) -:
: PhD Student, Computing Science, University of Glasgow, Scotland. :
: Native of Antipodean Auckland, New Zealand: 174d47' E, 36d55' S. :
: http://www.dcs.gla.ac.uk/~keithw/  mailto:[EMAIL PROTECTED]   :
:--:



Re: Query on multi-param type classes

1998-01-30 Thread Jon Mountjoy


Hi

Simon says:
 > Can you give a compact summary of why you want
 > to?  Our multi-parameter type-class paper gives none, and if
 > you've got one I'd like to add it.

Essentially, many of the examples in the paper by Liang, Hudak and
Jones: "Monad Transformers and Modular Interpreters" will fail.  The
examples, and motivation behind them are all there.

Regards,
Jon



Re: bug report

1998-01-30 Thread Simon Marlow

Marc van Dongen= <[EMAIL PROTECTED]> writes:

> While compiling some stuff I came across the following:
>  compiling with -O did failed without any error message
>   at all.
>  compiling with -O2 succeeded
> 
> ?
> 
> Any idea what could have caused it? I can tell you how to
> reproduce this if wanted.

No idea, could you provide a test case please?

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: test for ghc

1998-01-30 Thread Sigbjorn Finne


Thanks for the report, the native code generator fails to handle
a primop. We'll track this one down, but as a temporary solution,
try compiling the module with -fvia-C

--Sigbjorn

S.D.Mechveliani writes:
> Hellow,
> 
> ftp.botik.ru/pub/local/Mechveliani/docon/1.06/
> 
> contains the test for ghc:  it is a large computer algebra system.
> 
> The test is Makefile to compile this system correct.
> It works under  linux-i386-unknown,  but i doubt how it will do
> on other platforms.
> In particular,  Marc van Dongen <[EMAIL PROTECTED]>
> writes:
> 
> > I am in the process of installing doCon ...
> > after successfully having compiled IParse.hsa and OPTab_.hs the
> > compilation of DPrelude.hs fails with a misterious:
> 
> > [snip]
> >  nativeGen/MachCode.lhs:1017: Non-exhaustive patterns in case
> > ...
> >  make: *** [source/DPrelude.o] Error 1
> 
> > I've tried to find a directory nativeGen and a file MachCode but
> > can't find them. Do you have any suggestions on how to solve this?
> 
> 
> nativeGen/MachCode.lhs  
> is, probably, of ghc system. Looks like a ghc bug.
> 
> Marc,  DoCon provides  hi files only for  ghc-2.10, 2.08.
> If you have other version, then this Makefile may not go as it is.
> Also consult sometimes  [EMAIL PROTECTED]
>   ..users@..
> 
> --
> Sergey Mechveliani
> [EMAIL PROTECTED]



Re: Query on multi-param type classes

1998-01-30 Thread Simon L Peyton Jones


> I decided to try and get my old multi-param. parser to work,
> and got told-off by Haskell's parser:
> 
> Please tell me what I am doing wrong.  The following program:
> 
> > module A where
> >  
> > class (Monad m, Monad (t m)) => AMonadT t m where
> >   lift :: m a -> t m a
> 
> Gives me:
> 
> (lambda o) ghc -fglasgow-exts A.hs
>  A.hs:3:23: parse error on input: "("

I should have said that I've implemented the choices given
on the Standard Haskell web discussion page.  In particular:

===
Choice 7a
~

The context in a class declaration (which introduces superclasses)
must constrain only type variables.  For example, this is legal:

class (Foo a b, Baz b b) => Flob a b where ...
but not
class (Foo [a] b, Baz (a,b) b) => Flob a b where ...

It might be possible to relax this restriction (which is the same
as in current Haskell) without losing decideability, but we're not
sure.  Choice 7a is conservative, and we don't know of any examples
that motivate relaxing the restriction.
===

I'm frankly unsure of the consequences of lifting the 
restriction.  Can you give a compact summary of why you want
to?  Our multi-parameter type-class paper gives none, and if
you've got one I'd like to add it.

In the short term, you're stuck.  Damn!  First customer too!

Simon





Re: NGC bug (?), canonicalised.

1998-01-30 Thread Sigbjorn Finne


Alex Ferguson writes:
> 
> module R where
> 
> data NumVal = RealNum Float
> 
> isZero (RealNum 0.0) = True
> 
> 
> This is the Sun NCG, of course.  Doesn't happen without the constructor,
> or with Int's, or with -fvia-C...
> 

Thanks for narrowing this down, here's the offending line

.double 0r<>

One line fix at the end - Death to 'instance Show (->)'!

--Sigbjorn

*** ghc/compiler/nativeGen/MachRegs.lhs.~1~ 1998/01/08 18:06:32
--- ghc/compiler/nativeGen/MachRegs.lhs 1998/01/30 11:50:09
***
*** 95,99 
,IF_ARCH_i386( '0' : 'd' :
,IF_ARCH_sparc('0' : 'r' :,)))
!   show (rational r))
  \end{code}
  
--- 95,99 
,IF_ARCH_i386( '0' : 'd' :
,IF_ARCH_sparc('0' : 'r' :,)))
!   showSDoc (rational r))
  \end{code}



is this a bug?

1998-01-30 Thread Marc van Dongen=

Hi there,



While using mkdependHS, I am getting errors because the
tool can not find .hi files for modules which are imported
from a library in some other directory than the one I'm
making in.

Is this an error, and if not, how do I solve this?



Thanks in advance,


Marc van Dongen



Re: is this a bug? (fwd)

1998-01-30 Thread Marc van Dongen=

: Hi there,
: 
: 
: 
: While using mkdependHS, I am getting errors because the
: tool can not find .hi files for modules which are imported
: from a library in some other directory than the one I'm
: making in.
: 
: Is this an error, and if not, how do I solve this?
: 

This is embarrassing. As soon as I had submitted the message
I knew the answer to it. Sorry.

Marc



HBC/contrib libraries

1998-01-30 Thread Simon Marlow


Does anyone use the hbc or contrib libraries?  I'd like to move them
out of the standard binary distributions, but keep them as
'contributed code' in the source tree.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key