Re: ghc-2.04 compiling problems

1997-06-11 Thread Sigbjorn Finne


> 
> I downloaded ghc-2.04 patch level 2. I then tried compiling it. I'm
> using an i386-unknown-solaris2 machine. I get the error shown below.
> I tried compiling using ghc-0.29. I was trying for profiled, concurrent
> and concurrent profiled builds.

 ...[compiling ArrBase]..

> /tmp/ghc27445.hc:953: fixed or forbidden register was spilled.
> This may be due to a compiler bug or to impossible asm
> statements or clauses.

Hi,

you'll need to compile ArrBase with -monly-3-regs, the backend is
trying to steal more x86 registers than gcc can handle. If you're still
getting the same error, try -monly-2-regs

hope that helps,

--Sigbjorn




ghc-2.04 compiling problems

1997-06-11 Thread Meurig Sage

I downloaded ghc-2.04 patch level 2. I then tried compiling it. I'm
using an i386-unknown-solaris2 machine. I get the error shown below.
I tried compiling using ghc-0.29. I was trying for profiled, concurrent
and concurrent profiled builds.

Cheers 
 Meurig

rm -f ghc/ArrBase.o ; if [ ! -d ghc/ArrBase ]; then mkdir ghc/ArrBase ;
else exit 0; fi; find ghc/ArrBase -name '*.o' -print | xargs rm -f
__rm_food;
../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing
-split-objs -odir ghc/ArrBase   -H20m -c ghc/ArrBase.lhs -o
ghc/ArrBase.o -osuf o
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS array a{~,Int,IPr} b{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS (!) a{~,Int,IPr} b{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS (//) a{~,Int,IPr} b{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS accum a{~,Int,IPr} b{} c{} #-}
Warning: GENERATE_SPECS pre-processing pragma ignored:
  {-# GENERATE_SPECS accumArray a{~,Int,IPr} b{} c{} #-}
Warning: InitTime not found in stats file
Warning: InitElapsed not found in stats file
<>
ghc: module version changed to 1; reason: no old .hi file
/tmp/ghc27445.hc:953: fixed or forbidden register was spilled.
This may be due to a compiler bug or to impossible asm
statements or clauses.
make[2]: *** [ghc/ArrBase.o] Error 1
make[1]: *** [all] Error 2  

--
Meurig Sage
Dept of Computing Science
University of Glasgow
http://www.dcs.gla.ac.uk/~meurig
mailto:[EMAIL PROTECTED]



Re: ghc-2.04-pl2 on Linux/HP-UX

1997-06-11 Thread Sigbjorn Finne

> 
> Yesterday I successfully installed ghc-2.04-pl2 on Linux and HP-UX10.
> Just a few remarks:
> 
>* autoheader complains:
> Symbol `HAVE_ALTZONE' is not covered by
/soft/share/autoconf/acconfig.h
>  Ignoring this didn't hurt, but I was just wondering if our
autoheader
>  is too old (from autoconf 2.12, latest version, I think)?
> 

autoheader needs some help with that one as it is a custom autoconf macro,
I've
appended the necessary acconfig.h stub (which should have been included in
the distrib..)

>* fptools/ghc/lib/cbits/timezone.h still makes some trouble on HPs.
>  After commenting out line 31 ('extern time_t timezone;'),
>  everything went smooth. The problem seems to be the OS-dependent
>  type of timezone: Some OS declare it as long, others as time_t.
>  But either way, timezone.h already includes the relevant header
>  files, so this redeclaration seems unneccessary.
> 

Thanks for the HPUX info, I'll take another stab at getting it Right.

>* makeinfo, ugen and hp2ps are compiled without -O. Not that these
>  are the most important and time-consuming commands, but anyway...
> 

No good reason why they shouldn't be, let's got for broke :-)

--Sigbjorn

--acconfig.h--

/* Leave this blank line here -- autoheader needs it! */


/* Define this if your time.h defines altzone */
#undef HAVE_ALTZONE




bind error in decl (2)

1997-06-11 Thread Ralf Hinze

[Sorry for sending this message twice but I accidentally hit
the deliver button.]

Dear bug chasers,

ghc's latest version sometimes misses conflicting function definitions.
Consider the following *wrong* program:

%--

> module Small  (  module Small  )
> where

> data MinView t a  =  Min a (t a)
>   |  Infty

> newtype ToppedTree a  =  P (MinView BinTree a)
> data BinTree a=  Bin a (BinTree a) (BinTree a)
>   |  Empty

> P Infty /\ u  =  P Infty
> t@(P (Min _ _)) /\ P Infty=  P Infty
> P (Min a t) /\ P (Min b u)
> | a <= b  =  P (Min a (Bin b u t))
> | otherwise   =  P (Min b (Bin a t u))

> data Tree a   =  Root a (Forest a)
>   |  Void
> type Forest a =  [Tree a]

> Void  /\ u=  Void
> t@(Root _ _)  /\ Void =  Void
> t@(Root a ts) /\ u@(Root b us)
> | a <= b  =  Root a (u : ts)
> | otherwise   =  Root b (t : us)

%--

Note that /\ is defined twice at different types. ghc replies

bind error in decl (2)
bind error in decl (2)
bind error in decl (2)
Module version unchanged at 3

Ralf

P.S.: Here is the verbose compiler output:

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

literate pre-processor:
echo '#line 1 "Small.lhs"' > /tmp/ghc23960.lpp && 
/home/III/a/ralf/FP/ghc-2.04/lib/unlit  Small.lhs -  >> /tmp/ghc23960.lpp

real0.0
user0.0
sys 0.0

Effective command line: -i/home/III/a/ralf/TBoA/GHC/Import 
-L/home/III/a/ralf/TBoA/GHC/lib -lbn -v -c

Ineffective C pre-processor:
echo '#line 1 "Small.lhs"' > /tmp/ghc23960.cpp && cat /tmp/ghc23960.lpp >> 
/tmp/ghc23960.cpp

real0.0
user0.0
sys 0.0

Haskell compiler:
/home/III/a/ralf/FP/ghc-2.04/lib/hsc ,-W ,/tmp/ghc23960.cpp  
-fignore-interface-pragmas -fomit-interface-pragmas -fsimplify \(  
-ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -freuse-con 
-fpedantic-bottoms -fsimpl-uf-use-threshold3 -fmax-simplifier-iterations4 \)   
-himap=/home/III/a/ralf/TBoA/GHC/Import%.hi:.%.hi:/home/III/a/ralf/FP/ghc-2.04/lib/imports%.hi
   -v -hifile=/tmp/ghc23960.hi -S=/tmp/ghc23960.s +RTS -H600 -K100



Glasgow Haskell Compiler, version 2.03, for Haskell 1.4

bind error in decl (2)
bind error in decl (2)
bind error in decl (2)

real2.3
user1.9
sys 0.1

Pin on Haskell consistency info:
echo '
.text
hsc.Small.lhs.33.0..:' >> /tmp/ghc23960.s

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

_usages_
PrelBase 1 :: $d14 1 $d15 1 $d26 1 $d27 1 $d32 1 $d34 1 $d37 1 $d39 1 $d41 1 $d44 1 
$d45 1 $d46 1 $d49 1 $d51 1 $d6 1 $d7 1 otherwise 1 Eq 1 Eval 1 Ord 1 Ordering 1;
PrelNum 1 :: $d17 1 $d18 1;
_exports_
Small /\ BinTree(Bin Empty) Forest MinView(Min Infty) ToppedTree(P) Tree(Root Void);
_instances_
instance _forall_ [a] => {PrelBase.Eval (Tree a)} = $d1;
instance _forall_ [a] => {PrelBase.Eval (BinTree a)} = $d2;
instance _forall_ [a] => {PrelBase.Eval (ToppedTree a)} = $d3;
instance _forall_ [a :: (* -> *) b] => {PrelBase.Eval (MinView a b)} = $d4;
_declarations_
type Forest r3H = [Tree r3H] ;
data Tree r3J = Root r3J (Forest r3J) |  Void ;
data BinTree r3L = Bin r3L (BinTree r3L) (BinTree r3L) |  Empty ;
newtype ToppedTree r3N = P (MinView BinTree r3N) ;
data MinView r3P :: (* -> *) r3Q = Min r3Q (r3P r3Q) |  Infty ;
/\ _:_ _forall_ [a] {PrelBase.Ord a} => ToppedTree a -> ToppedTree a -> ToppedTree a ;;
$d1 _:_ _forall_ [a] => {PrelBase.Eval (Tree a)} ;;
$d2 _:_ _forall_ [a] => {PrelBase.Eval (BinTree a)} ;;
$d3 _:_ _forall_ [a] => {PrelBase.Eval (ToppedTree a)} ;;
$d4 _:_ _forall_ [a :: (* -> *) b] => {PrelBase.Eval (MinView a b)} ;;


Module version unchanged at 3

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

real0.0
user0.0
sys 0.0

Unix assembler:
gcc -o Small.o -c  /tmp/ghc23960.s

real0.2
user0.0
sys 0.0

rm -f /tmp/ghc23960*



bind error in decl (2)

1997-06-11 Thread Ralf Hinze

Dear bug chasers,

ghc's latest version sometimes misses conflicting function definitions.
Consider the following *wrong* program:

%--

> module Small  (  module Small  )
> where

> data MinView t a  =  Min a (t a)
>   |  Infty

> newtype ToppedTree a  =  P (MinView BinTree a)
> data BinTree a=  Bin a (BinTree a) (BinTree a)
>   |  Empty

> P Infty /\ u  =  P Infty
> t@(P (Min _ _)) /\ P Infty=  P Infty
> P (Min a t) /\ P (Min b u)
> | a <= b  =  P (Min a (Bin b u t))
> | otherwise   =  P (Min b (Bin a t u))

> data Tree a   =  Root a (Forest a)
>   |  Void
> type Forest a =  [Tree a]

> Void  /\ u=  Void
> t@(Root _ _)  /\ Void =  Void
> t@(Root a ts) /\ u@(Root b us)
> | a <= b  =  Root a (u : ts)
> | otherwise   =  Root b (t : us)

%--

Note that /\ is defined twice at different types. 



Re: Pattern-matching error within GHC

1997-06-11 Thread Sigbjorn Finne

Thanks for chasing this down, Einar - this (mis)behaviour is
reproducable. Fixed in the next release.

--Sigbjorn

> 
> The module that caused GHC to fail attempted to reexport a name
> from a module that was imported as a qualified module, i.e.: 
> 
>   module Silly (
>   Posix.dupTo,
>   ...
> 
>   )
>   import qualified Posix
>   ..
> 
> Lesson to be learned: dont reexport names that are imported as
> qualified names. The following works better:
> 
> 
>   module Silly (
>   dupTo,
>   ...
> 
>   )
>   import qualified Posix
>   import Posix(dupTo)
>   ..
> 
> Einar



Re: Pattern-matching error within GHC

1997-06-11 Thread Sigbjorn Finne

> 
> While compiling a larger configuration of GHC code (30 KLOC's) with
> the brand new compiler 2.04 on a Ultra-Sparc, I got the following 
> 
> *** Pattern-matching error within GHC!
> 
> This is a compiler bug; please report it to
[EMAIL PROTECTED]
> 
> Fail: "rename/RnNames.lhs", line 453: pattern-match failed on an
irrefutable pattern
> 
> I will see if I can reconstruct the error on a smaller configuration of
> Haskell code.
> 

Hi,

if you recompile rename/RnNames.o with EXTRA_HC_OPTS=-DDEBUG set, this
should at least give you the name of the thing in the export list it is
processing
at the point of failure.

It may help to turn off the pruning of type constructors for the module
that it is
failing on, i.e., add the option -fno-prune-tydecls

--Sigbjorn




ghc-2.04-pl2 on Linux/HP-UX

1997-06-11 Thread Sven Panne

Yesterday I successfully installed ghc-2.04-pl2 on Linux and HP-UX10.
Just a few remarks:

   * autoheader complains:
Symbol `HAVE_ALTZONE' is not covered by /soft/share/autoconf/acconfig.h
 Ignoring this didn't hurt, but I was just wondering if our autoheader
 is too old (from autoconf 2.12, latest version, I think)?

   * fptools/ghc/lib/cbits/timezone.h still makes some trouble on HPs.
 After commenting out line 31 ('extern time_t timezone;'),
 everything went smooth. The problem seems to be the OS-dependent
 type of timezone: Some OS declare it as long, others as time_t.
 But either way, timezone.h already includes the relevant header
 files, so this redeclaration seems unneccessary.

   * makeinfo, ugen and hp2ps are compiled without -O. Not that these
 are the most important and time-consuming commands, but anyway...

Apart from these really minor glitches, this was the most painless and
easy installation of ghc I had. Moving away from Jmakefiles to GNU make
was clearly the right decision!

Today I will give ghc-2.04-pl2 a try compiling itself, so stay tuned!
:-)

-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne