undocumented feature in GHC-4.00?

1998-10-13 Thread Jeffrey R. Lewis

When attempting to reconstruct the syntax for existential
quantification, I tried:

newtype Groo a = Groo (Either a b)

To my surprise, using ghc-4.00, this worked - without even using
`-fglasgow-exts'.  (it doesn't work, with or without `-fglasgow-exts'
under 3.02)

Then I read the release notes ;-)  These told me about using `forall' on
`data' declarations.  But the above works, and yields the type I was
expecting, i.e. the .hi file sez:

newtype Groo $r3r = Groo (_forall_ [$r3u] = PrelEither.Either $r3r
$r3u) ;

Is this a feature or a bug?

--Jeff




panic with existential types

1998-10-13 Thread Erik Rozendaal

System: Redhat 5.1 with all updates, Linux 2.1.125, glibc 2.0.7,
Dual Pentium II 300Mhz, egcs 1.1b compiler with PGCC patches.
GHC: GHC-4.00 binary distribution installed in /opt/ghc-4.00.

Trying to compile the following Haskell program

--
module Main where

data Foo = forall a. MkFoo a (a - Bool)

foo_list = [MkFoo 7 even, MkFoo True id]

f :: Foo - Bool
f (MkFoo e p) = p e

main :: IO ()
main = putStrLn (show (map f foo_list))
--

resulted in the following compiler output using the command
`ghc -fglasgow-exts -c Main.hs':

-
panic! (the `impossible' happened):
 applyTypeToArgs Main.MkFoo{-r1l,x-} {B1 PrelBase.True{-6y,w-}}

Please report it as a compiler bug to
[EMAIL PROTECTED]
-

A minor modification for this program:


module Main where

data Foo = forall a. MkFoo a (a - Bool)

foo1 = MkFoo 7 even

main = putStrLn "foo"


resulted in this compiler error (same command as before):


panic! (the `impossible' happened):
 lookupBindC:no info!
 for: B1
(probably: data dependencies broken by an optimisation pass)
static binds for:
local binds for:
cZx

Please report it as a compiler bug to
[EMAIL PROTECTED]



Erik





GHC 4.00 bugs

1998-10-13 Thread Sven Panne

Here the latest bug news on GHC 4.00 from Munich...   :-)

My installation went the usual path: First compile quick-and-dirty GHC-4.00
with GHC-3.03, then test the whole thing by bootstrapping.
Platform: Linux (libc5)

   * Some "classic" warnings in ghc/rts:
/usr/include/stdlib.h:149: warning: no previous prototype for `strtold'
 Hmm, perhaps I should better not mention my fix, otherwise Simon
 gets pale again...  (see Sep 1st)

   * Some warnings about (almost) nested comments in gum/{HLComms,ParInit}.c:
gum/HLComms.c:125: warning: `/*' within comment
 Perhaps use #ifdef 0...#endif instead of /*...*/

   * Compiling ghc/compiler/rename/ParseIface.hs with GHC 4.00 itself
 needs 40MB instead of the 30MB given in ghc/compiler/Makefile.
 Hmmm, 30MB was enough when compiling 4.00 with 3.03. Even stranger:
 What about the promised self-adjusting heap in the new RTS? I hoped
 no -H/-K has to be used with the shiny new RTS...   :-(

   * In the boostrapping phase (4.00 with 4.00), there are some strange
 warnings from gcc, but only on some files, e.g.
basicTypes/Var.lhs
types/Type.lhs
typecheck/TcEnv.lhs
typecheck/TcHsSyn.lhs
typecheck/Inst.lhs
 gcc complained:
/home/inst/glasgow/linux/bin/ghc -cpp -fglasgow-exts -Rghc-timing -I. 
-IcodeGen -InativeGen -Iparser 
-iutils:basicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:stranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen
 -recomp   -H10m  -c typecheck/TcEnv.lhs -o typecheck/TcEnv.o -osuf o
ghc: 271383260 bytes, 95 GCs, 2432854/3116888 avg/max bytes residency (5 
samples), 0.03 INIT (0.00 elapsed), 13.31 MUT (15.00 elapsed), 4.39 GC (4.72 elapsed) 
:ghc
ghc: module version changed to 1; reason: no old .hi file
/tmp/ghc6681.hc:3700: warning: `c6BS_closure' was declared `extern' and later 
`static'
/tmp/ghc6681.hc:4010: warning: `c6C2_closure' was declared `extern' and later 
`static'
/tmp/ghc6681.hc:4163: warning: `c6C7_closure' was declared `extern' and later 
`static'

   * foreign is a little bit buggy:
module Test where
foreign export _ccall "bar" myBar :: IO ()
myBar = putStrLn "Hi!"
 leads to
panne:~/tst  ghc -c -fglasgow-exts Test.hs
ghc: module version changed to 1; reason: no old .hi file
/tmp/ghc7265.hc:118: macro `STK_CHK' used with too many (7) args
 Test_stub.h contains another surprise:
#include "rtsdefs.h"
extern void bar (void* _a0) ;
 Where is the void* coming from? I expected: extern void bar(void);

Cheers,
   Sven

P.S.: I'm slowly getting old, this is *not* the first bug report on
  4.00...  :'-(

-- 
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



[Fwd: GHC 4.00 bugs]

1998-10-13 Thread Sven Panne

[ I've only replied Sigbjorn, so here's it again... ]




Sigbjorn Finne wrote:
 'foreign export' doesn't work with ghc-4.00 just yet, use ghc-3.03
 if you need it.

Aargl...  Versionitis at its worst:

panne:~/tst  linux-303/bin/ghc --version
The Glorious Glasgow Haskell Compilation System, version 3.03, patchlevel 0
panne:~/tst  linux-303/bin/ghc -c -fglasgow-exts Test.hs

DsCCall.lhs:279: Irrefutable pattern failed for pattern [ioOkDataCon, ioFailDataCon]


panne:~/tst  /soft/bin/ghc --version
The Glorious Glasgow Haskell Compilation System, version proto-3.03-2-Aug, patchlevel 0
panne:~/tst  /soft/bin/ghc -c -fglasgow-exts Test.hs 
Test.hs:11:35: parse error on input: "::"


panne:~/tst  linux-400/bin/ghc --version
The Glorious Glasgow Haskell Compilation System, version 4.00, patchlevel 0
panne:~/tst  linux-400/bin/ghc -c -fglasgow-exts Test.hs
ghc: module version changed to 1; reason: no old .hi file
/tmp/ghc15405.hc:118: macro `STK_CHK' used with too many (7) args


I *really* want a single, all-in-one GHC! :'-(  I don't dare to test
which one of the above systems supports MPC, the new RTS, ... At least I
have the choice which part should fail: Desugarer, parser or gcc.   :-}

\begin{sarcasm}
   Hmm, this strongly reminds me of the current Java situation: "For
   these classes you need at least JDK 1.1.4 or higher, but on Linux
   1.1.6 does not work under KDE. On Solaris, 1.1.5 is highly recommended.
   Blah blah..." It seems that the GHC people have learned their lessons
   from the commercially successful languages...
\end{sarcasm}

Totally confused,
   Sven

-- 
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




Re: GHC 4.00 bugs

1998-10-13 Thread Sven Panne

Simon Marlow wrote:
 
 Sven Panne [EMAIL PROTECTED] writes:
 [...]
   What about the promised self-adjusting heap in the new RTS? I hoped
   no -H/-K has to be used with the shiny new RTS...   :-(
 [...]
 Remember, you compiled 4.00 with 3.03 - that's why the -H option is
 still needed.
 [...]

Uh oh, I forgot...  :-}

 I was expecting a bug report about CgBindery.hi-boot - you have to
 replace some () with {} to bootstrap.

Yep, and a "!" should probably read ".". CgRetConv.hi-boot looks wrong,
too, but strangely enough there's no complaint from GHC here!?

And another one: The compilation of ghc/lib/misc/ByteOps.lhs yields the
following warnings from gcc:

   /tmp/ghc8040.hc:292: warning: implicit declaration of function `double2bytes__'
   /tmp/ghc8040.hc:428: warning: implicit declaration of function `float2bytes__'
   /tmp/ghc8040.hc:563: warning: implicit declaration of function `short2bytes__'
   /tmp/ghc8040.hc:698: warning: implicit declaration of function `int2bytes__'
   /tmp/ghc8040.hc:833: warning: implicit declaration of function `long2bytes__'
   /tmp/ghc8040.hc:1207: warning: implicit declaration of function `bytes2double__'
   /tmp/ghc8040.hc:1431: warning: implicit declaration of function `bytes2float__'
   /tmp/ghc8040.hc:1623: warning: implicit declaration of function `bytes2short__'
   /tmp/ghc8040.hc:1814: warning: implicit declaration of function `bytes2int__'
   /tmp/ghc8040.hc:2005: warning: implicit declaration of function `bytes2long__'

I don't think that they are all harmless, especially the float one. Easy
cure: Add
   ByteOps_HC_OPTS  += '-\#include"cbits/ByteOps.h"'
to ghc/lib/misc/Makefile.

Cheers,
   Sven

-- 
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



Eval and seq

1998-10-13 Thread Ralf Hinze

High,

it seems that the class `Eval' has vanished and `seq' is now truely
polymorphic. Right? Perhaps worth mentioning in the Release notes as
the change may affect some programs ((Eval a) = is no longer a valid
context).

Cheers, Ralf



Re: GHC 4.00 bugs

1998-10-13 Thread Simon Marlow

Sven Panne [EMAIL PROTECTED] writes:

* Some "classic" warnings in ghc/rts:
 /usr/include/stdlib.h:149: warning: no previous prototype for `strtold'
  Hmm, perhaps I should better not mention my fix, otherwise Simon
  gets pale again...  (see Sep 1st)

These go away w/ a glibc version of Linux.

* Some warnings about (almost) nested comments in gum/{HLComms,ParInit}.c:
 gum/HLComms.c:125: warning: `/*' within comment
  Perhaps use #ifdef 0...#endif instead of /*...*/

Harmless.

* Compiling ghc/compiler/rename/ParseIface.hs with GHC 4.00 itself
  needs 40MB instead of the 30MB given in ghc/compiler/Makefile.
  Hmmm, 30MB was enough when compiling 4.00 with 3.03. Even stranger:
  What about the promised self-adjusting heap in the new RTS? I hoped
  no -H/-K has to be used with the shiny new RTS...   :-(

using -dcore-lint cuts down the residency.  This is a space leak we're
looking into.

Remember, you compiled 4.00 with 3.03 - that's why the -H option is
still needed.  In the bootstrapped version you can forget about -H,
unless you need more than 64M heap!

* In the boostrapping phase (4.00 with 4.00), there are some strange
  warnings from gcc, but only on some files, e.g.
 basicTypes/Var.lhs
 types/Type.lhs
 typecheck/TcEnv.lhs
 typecheck/TcHsSyn.lhs
 typecheck/Inst.lhs
  gcc complained:
 /home/inst/glasgow/linux/bin/ghc -cpp -fglasgow-exts -Rghc-timing -I. 
-IcodeGen -InativeGen -Iparser 
-iutils:basicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:stranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen
 -recomp   -H10m  -c typecheck/TcEnv.lhs -o typecheck/TcEnv.o -osuf o
 ghc: 271383260 bytes, 95 GCs, 2432854/3116888 avg/max bytes residency (5 
samples), 0.03 INIT (0.00 elapsed), 13.31 MUT (15.00 elapsed), 4.39 GC (4.72 elapsed) 
:ghc
 ghc: module version changed to 1; reason: no old .hi file
 /tmp/ghc6681.hc:3700: warning: `c6BS_closure' was declared `extern' and 
later `static'
 /tmp/ghc6681.hc:4010: warning: `c6C2_closure' was declared `extern' and 
later `static'
 /tmp/ghc6681.hc:4163: warning: `c6C7_closure' was declared `extern' and 
later `static'
 

Hmm, should be harmless, but I'll look into it.

I was expecting a bug report about CgBindery.hi-boot - you have to
replace some () with {} to bootstrap.

Sorry for the terse message, I'm on a *really* slow dialup link at the
moment.

Cheers,
Simon

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



relocate_TSO

1998-10-13 Thread Ralf Hinze

--
X-Sun-Data-Type: text
X-Sun-Data-Description: text
X-Sun-Data-Name: text
X-Sun-Charset: us-ascii
X-Sun-Content-Lines: 108

High again,

the build was successful ;-). Unfortunately, the first test program
which aims at stressing the new RTS dies with a fatal error. Here
is a transcript of the session ...

jod 76 uname -a
SunOS jod 5.6 Generic_105181-08 sun4u sparc SUNW,Ultra-1
jod 77 ghc -v EDigits.lhs
The Glorious Glasgow Haskell Compilation System, version 4.00, patchlevel 0

literate pre-processor:
	/home/III/a/ralf/FP/ghc/lib/unlit  EDigits.lhs -   /tmp/ghc25291.lpp

real0.0
user0.0
sys 0.0

Effective command line: -v

Ineffective C pre-processor:
	echo '{-# LINE 1 "EDigits.lhs" -}'  /tmp/ghc25291.cpp  cat /tmp/ghc25291.lpp  /tmp/ghc25291.cpp

real0.0
user0.0
sys 0.0
ghc:compile:Output file EDigits.o doesn't exist
ghc:compile:Interface file EDigits.hi doesn't exist
ghc:recompile:Input file EDigits.lhs newer than EDigits.o

Haskell compiler:
	/home/III/a/ralf/FP/ghc/lib/hsc ,-W ,/tmp/ghc25291.cpp  -fignore-interface-pragmas -fomit-interface-pragmas -fsimplify [  -ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -fdo-case-elim -freuse-con -fpedantic-bottoms -fclone-binds -fmax-simplifier-iterations4  ]   -fwarn-overlapping-patterns -fwarn-missing-methods -fwarn-duplicate-exports -fhi-version=400 -himap=.%.hi:/home/III/a/ralf/FP/ghc/lib/imports/std%.hi   -v -hifile=/tmp/ghc25291.hi -S=/tmp/ghc25291.s -F= -FH= +RTS -H600 -K100
Glasgow Haskell Compiler, version 4.00, for Haskell 1.4

real5.7
user5.3
sys 0.2

Pin on Haskell consistency info:
	echo '
	.text
hsc.EDigits.lhs.40.0..:'  /tmp/ghc25291.s

real0.0
user0.0
sys 0.0
*** New hi file follows...
_interface_ Main 400
_instance_modules_
IO PrelAddr PrelArr PrelBounded PrelCCall PrelForeign PrelIOBase PrelNum PrelNumExtra PrelTup

_usages_
IO 1 :: putChar 1;
Monad 1 :: sequence 1;
PrelBase 1 :: $dEnum0 1 $dEnumBool0 1 $dEnumChar0 1 $dEnumInt0 1 $dEnumOrdering0 1 $dEq0 1 $dEq1 1 $dEqBool0 1 $dEqChar0 1 $dEqInt0 1 $dEqInteger0 1 $dEqOrdering0 1 $dMonad0 1 $dMonadPlus0 1 $dMonadZero0 1 $dNumInt0 1 $dOrd0 1 $dOrd1 1 $dOrdBool0 1 $dOrdChar0 1 $dOrdInt0 1 $dOrdOrdering0 1 $dShow0 1 $dShow1 1 $dShow2 1 $dShowBool0 1 $dShowChar0 1 $dShowInt0 1 $dShowOrdering0 1 $m- 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 addr2Integer 1 foldr 1 int2Integer 1 integer_0 1 integer_1 1 integer_2 1 integer_m1 1 otherwise 1 Enum 1 Eq 1 Monad 1 MonadPlus 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Show 1 String 1;
PrelIOBase 1 :: $dMonadIO0 1 IO 1;
PrelList 1 :: repeat 1;
PrelNum 1 :: $dEnumInteger0 1 $dEqRatio0 1 $dIntegralInt0 1 $dIntegralInteger0 1 $dNumInteger0 1 $dOrdInteger0 1 $dRealInt0 1 $dRealInteger0 1 $dShowInteger0 1 $mdiv 1 $mdivMod 1 $mmod 1 $mquot 1 $mrem 1 Integral 1 Ratio 1 Rational 1 Real 1;
PrelNumExtra 1 :: $dEnumDouble0 1 $dEnumRatio0 1 $dEqDouble0 1 $dNumDouble0 1 $dNumRatio0 1 $dOrdDouble0 1 $dOrdRatio0 1 $dRealDouble0 1 $dRealRatio0 1 $dShowDouble0 1 $dShowRatio0 1;
PrelPack 1 :: packCString# 1 unpackAppendCString# 1 unpackCString# 1 unpackFoldrCString# 1 unpackNBytes# 1;
PrelTup 1 :: $dEq0 1 $dOrd0 1 $dShow3 1;
_exports_
Main convert edigits main mkdigit norm;
_declarations_
main _:_ PrelIOBase.IO PrelBase.() ;;
edigits _:_ [PrelBase.Char] ;;
convert _:_ [PrelBase.Int] - [PrelBase.Char] ;;
mkdigit _:_ PrelBase.Int - PrelBase.Char ;;
norm _:_ _forall_ [$a] {PrelNum.Integral $a, PrelBase.Num $a, PrelBase.Ord $a} = $a - [$a] - ($a, [$a]) ;;


ghc: module version changed to 1; reason: no old .hi file

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

real0.0
user0.0
sys 0.0

Unix assembler:
	gcc -o EDigits.o -c  -I. -I/home/III/a/ralf/FP/ghc/lib/includes -I/home/III/a/ralf/FP/ghc/lib/includes /tmp/ghc25291.s

real0.2
user0.1
sys 0.0

Linker:
	gcc -v -u PrelBase_IZh_static_info -u PrelBase_CZh_static_info -u PrelBase_False_static_closure -u PrelBase_True_static_closure -u PrelMain_mainIO_closure  EDigits.o  -L/home/III/a/ralf/FP/ghc/lib  -lHS -lHS_cbits -lHSrts -lgmp -lm
Reading specs from /usr/local/gnu/gcc-2.7.2.3/lib/gcc-lib/sparc-sun-solaris2.6/2.7.2.3/specs
gcc version 2.7.2.3
 /usr/ccs/bin/ld -V -Y P,/usr/ccs/lib:/usr/lib -Qy -u PrelBase_IZh_static_info -u PrelBase_CZh_static_info -u PrelBase_False_static_closure -u PrelBase_True_static_closure -u PrelMain_mainIO_closure /usr/local/gnu/gcc-2.7.2.3/lib/gcc-lib/sparc-sun-solaris2.6/2.7.2.3/crt1.o /usr/local/gnu/gcc-2.7.2.3/lib/gcc-lib/sparc-sun-solaris2.6/2.7.2.3/crti.o /usr/ccs/lib/values-Xa.o /usr/local/gnu/gcc-2.7.2.3/lib/gcc-lib/sparc-sun-solaris2.6/2.7.2.3/crtbegin.o -L/home/III/a/ralf/FP/ghc/lib -L/usr/local/gnu/gcc-2.7.2.3/lib/gcc-lib/sparc-sun-solaris2.6/2.7.2.3 -L/usr/ccs/bin -L/usr/ccs/lib 

YAB (yet another bug)

1998-10-13 Thread Ralf Hinze

--
X-Sun-Data-Type: text
X-Sun-Data-Description: text
X-Sun-Data-Name: text
X-Sun-Encoding-Info: uuencode
X-Sun-Content-Lines: 69

begin 600 text
M25R92!IR!T:4@;F5X="!O;F4Z(=H8R=S(]N;'D@8V]M;65N="!IR!@
M=6YI;7!L96UE;G1E9"!C:5C:RN(%1H90ID971A:6QS(%R92!G:79E;B!B
M96QO=R!A;F0@22=V92!A='1A8VAE9"!T:4@;V9F96YD:6YG(9I;4@*IU
MW0@:6X*8V%S92!3=F5N(QI:V5S('1O('-P96YD($@9F5W($-052!C6-L
M97,I+@H*0VAE97)S+"!286QF"@H*:F]D(#DW/B!G:,@+78@+6,@+4\@+5@
M+69G;%S9V]W+65X=',@+7)E8V]M"!1=6EC:U-OG1);E!L86-E+FQHR M
M;R!1=6EC:U-OG1);E!L86-E+F\*5AE($=L;W)I;W5S($=L87-G;W@2%S
M:V5L;"!#;VUP:6QA=EO;B!37-T96TL('9EG-I;VX@-"XP,"P@%T8VAL
M979E;" P"@IL:71EF%T92!PF4M')O8V5SV]R.@H)+VAO;64O24E)+V$O
MF%L9B]4"]G:,O;EB+W5N;ET("!1=6EC:U-OG1);E!L86-E+FQHR M
M(" ^/B O=UP+V=H8S(V,3(V+FQP H*F5A;" @(" @(" @,"XP"G5S97(@
M(" @(" @(# N, IS7,@(" @(" @(" P+C *"D5F9F5C=EV92!C;VUM86YD
M(QI;F4Z("UV("UC("U/("U7("UF9VQAV=O=RUE'1S("UR96-O;7 @+6\@
M475I8VM3;W)T26Y0;%C92YO"@I);F5F9F5C=EV92!#('!R92UPF]C97-S
M;W(Z"@EE8VAO("=[+2,@3$E.12 Q(")1=6EC:U-OG1);E!L86-E+FQHR(@
M+7TG(#X@+W1M"]G:,R-C$R-BYC' @)B8@8V%T("]T;7 O9VAC,C8Q,C8N
M;'!P(#X^("]T;7 O9VAC,C8Q,C8N8W!P"@IR96%L(" @(" @(" P+C *=7-E
MB @(" @(" @,"XP"G-YR @(" @(" @(# N, IG:,Z8V]MEL93I/=71P
M=70@9FEL92!1=6EC:U-OG1);E!L86-E+F\@9]EVXG="!EES= IG:,Z
M8V]MEL93I);G1EF9A8V4@9FEL92!1=6EC:U-OG1);E!L86-E+FAI(1O
M97-N)W0@97AIW0*9VAC.G)E8V]MEL93I);G!U="!F:6QE(%%U:6-K4V]R
M=$EN4QA8V4N;AS(YE=V5R('1H86X@475I8VM3;W)T26Y0;%C92YO"@I(
M87-K96QL(-O;7!I;5R.@H)+VAO;64O24E)+V$OF%L9B]4"]G:,O;EB
M+VAS8R L+4X@+"U7("PO=UP+V=H8S(V,3(V+F-P" @+69W87)N+6]V97)L
M87!P:6YG+7!A='1EFYS("UF=V%R;BUM:7-S:6YG+6UE=AO9',@+69W87)N
M+61UQI8V%T92UE'!OG1S("UF=V%R;BUI;F-O;7!L971E+7!A='1EFYS
M("UF=V%R;BUU;G5S960M8FEN9',@+69W87)N+75N=7-E9"UI;7!OG1S("UF
M9VQAV=O=RUE'1S("UF9\M971A+7)E9'5C=EO;B M9G-I;7!L:69Y(%L@
M("UF:V5E"US5C+7!R86=M82UI9',@+69EW-E;G1I86PM=6YF;VQD:6YG
MRUO;FQY("UFVEMPM=68M=7-E+71HF5S:]L9# @+69C;]N92UB:6YD
MR M9FUA"US:6UP;EF:65R+6ET97)A=EO;G,Q("UF5D86YT:6,M8F]T
M=]MR!=("UFW!E8VEA;ES92UO=F5R;]A95D(" M9G-P96-I86QIV4@
M+69S:6UP;EF2!;(" M9F9L;V%T+6QE=',M97AP;W-I;FM=VAN9B M9F9L
M;V%T+7!R:6UO',M;VL@+69C87-E+6]F+6-AV4@+69D;RUC87-E+65L:6T@
M+69C87-E+6UEF=E("UF9\M;%M8F1A+65T82UE'!A;G-I;VX@+69R975S
M92UC;VX@+69P961A;G1I8RUB;W1T;VUS(" M9FUA"US:6UP;EF:65R+6ET
M97)A=EO;G,T(" M9F-L;VYE+6)I;F1S(%T@+69F=6QL+6QAFEN97-S("UF
M9FQO870M:6YW87)DR M9G-I;7!L:69Y(%L@("UF9FQO870M;5TRUE'!O
MVEN9RUW:YF("UF9FQO870M')I;6]PRUO:R M9F-AV4M;V8M8V%S92 M
M9F1O+6-AV4M96QI;2 M9F-AV4M;65R9V4@+69D;RUE=$MF5D=6-T:6]N
M("UF9\M;%M8F1A+65T82UE'!A;G-I;VX@+69R975S92UC;VX@("UF5D
M86YT:6,M8F]T=]MR @+69M87@MVEMQI9FEEBUI=5R871I;VYS-" @
M72 M9G-TFEC=YEW,@+69S:6UP;EF2!;(" M9F9L;V%T+6QE=',M97AP
M;W-I;FM=VAN9B M9F9L;V%T+7!R:6UO',M;VL@+69C87-E+6]F+6-AV4@
M+69D;RUC87-E+65L:6T@+69C87-E+6UEF=E("UF9\M;%M8F1A+65T82UE
M'!A;G-I;VX@+69R975S92UC;VX@+69L970M=\M8V%S92 M9G!E9%N=EC
M+6)O='1O;7,@("UF;6%X+7-I;7!L:69I97(M:71EF%T:6]NS0@(%T@+69F
M;]A="UI;G=AF1S("UFVEMQI9GD@6R @+69F;]A="UL971S+65X]S
M:6YG+7=H;F8@+69F;]A="UPFEM;W!S+6]K("UF8V%S92UO9BUC87-E("UF
M9\M8V%S92UE;EM("UF8V%S92UM97)G92 M9F1O+6QA;6)D82UE=$M97AP
M86YS:6]N("UFF5UV4M8V]N("UF;5T+71O+6-AV4@+69I9VYOF4M:6YL
M:6YE+7!R86=M82 @+69P961A;G1I8RUB;W1T;VUS(" M9FUA"US:6UP;EF
M:65R+6ET97)A=EO;G,T("!=("UF;%M8F1A+6QI9G0@(" M9FQE="UN;RUE
MV-A4@+69W87)N+6]V97)L87!P:6YG+7!A='1EFYS("UF=V%R;BUM:7-S
M:6YG+6UE=AO9',@+69W87)N+61UQI8V%T92UE'!OG1S("UF:DM=F5R
MVEO;CTT,# @+6AI;6%P/2XE+FAI.B]H;VUE+TE)22]A+W)A;8O1E O9VAC
M+VQI8B]I;7!OG1S+V5X=',E+FAI.B]H;VUE+TE)22]A+W)A;8O1E O9VAC
M+VQI8B]I;7!OG1S+V5X=',E+FAI.B]H;VUE+TE)22]A+W)A;8O1E O9VAC
M+VQI8B]I;7!OG1S+W-T9"4N:D@(" M=B M:EF:6QE/2]T;7 O9VAC,C8Q
M,C8N:D@+5,]+W1M"]G:,R-C$R-BYS("U/2 M1D@]("M25%,@+4@V,# P
M,# P("U+,3 P,# P, I';%S9V]W($AAVME;P@0V]MEL97(L('9EG-I
M;VX@-"XP,"P@9F]R($AAVME;P@,2XT"@IU;FEMQE;65N=5D(-H96-K
M"G)E86P@(" @(" @,3$N,0IUV5R(" @(" @(#$P+C4*WES(" @(" @(" @
M,"XR"F1E;5T:6YG+BXN("]T;7 O9VAC,C8Q,C8N;'!P("]T;7 O9VAC,C8Q
M,C8N8W!P("]T;7 O9VAC,C8Q,C8N:D@+W1M"]G:,R-C$R-BYS(" *"G)M
3("UF("]T;7 O9VAC,C8Q,C8J"C8N
 
end
--
X-Sun-Data-Type: default
X-Sun-Data-Name: QuickSortInPlace.lhs
X-Sun-Charset: us-ascii
X-Sun-Content-Lines: 86

%---=  
\chapter{In place quick sort}
%---=  

%align

 module QuickSortInPlace (module QuickSortInPlace)
 where
 import Array
 import ST
 import LibBase

%align 33

%---=  
\section{Median of three quick sort}
%---=  

 swap a i j			=  do { v - readSTArray a i
  	  ; w - readSTArray a j
 ; writeSTArray a i w
 ; writeSTArray a j v }

 qsortInPlace			:: Rel a - STArray s Int a - (Int, Int) - ST s ()
 qsortInPlace (=) a (l, r)
   | l = r			=  return ()
   | otherwise			=  do { m - median3 l ((l + r) 

Re: relocate_TSO

1998-10-13 Thread Antony Bowers


On Tue, 13 Oct 1998, Sven Panne wrote:
 Ralf Hinze wrote:
  High again,
  
  the build was successful ;-). Unfortunately, the first test program
  which aims at stressing the new RTS dies with a fatal error. Here
  is a transcript of the session ...
  [...]
  jod 78 a.out
  a.out: fatal error: relocate_TSO
 
 Hmm, this works for me with the bootstrapped 4.00:
 
 panne:~  uname -a
 Linux august 2.0.32 #10 Wed Jun 3 11:12:47 CEST 1998 i686
 
 panne:~  ./a.out 
 2.71828182845904523536028747135266249775724709369995957496696762772... CTRL-C
 
 Solaris problem?

Looks like it.

I just tried Ralf's EDigits program with my newly built ghc 4.00, and got
exactly the same result:

kii:compiler$ uname -a
SunOS kii 5.5.1 Generic sun4u sparc SUNW,Ultra-1
kii:compiler$ a.out
a.out: fatal error: relocate_TSO
kii:compiler$ 

"Hello world" works for me too.

   Tony

Antony Bowers, Department of Computer Science, University of Bristol, UK.
http://www.cs.bris.ac.uk/~bowers/




Re: YAB (yet another bug)

1998-10-13 Thread Sven Panne

Ralf Hinze wrote:
 Here is the next one: ghc's only comment is `unimplemented check'. The
 details are given below and I've attached the offending file (just in
 case Sven likes to spend a few CPU cycles). [...]

Needless to say that your example works here...  :-)
Only change: Removed "import LibBase", inserted "type Rel a = a - a - Bool"

Much fun,
   Sven

-- 
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



Re: relocate_TSO

1998-10-13 Thread Sven Panne

Ralf Hinze wrote:
 High again,
 
 the build was successful ;-). Unfortunately, the first test program
 which aims at stressing the new RTS dies with a fatal error. Here
 is a transcript of the session ...
 [...]
 jod 78 a.out
 a.out: fatal error: relocate_TSO

Hmm, this works for me with the bootstrapped 4.00:

panne:~  uname -a
Linux august 2.0.32 #10 Wed Jun 3 11:12:47 CEST 1998 i686

panne:~  ./a.out 
2.71828182845904523536028747135266249775724709369995957496696762772... CTRL-C

Solaris problem?

In wonder,
   Sven

-- 
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



RE: panic with existential types

1998-10-13 Thread Simon Peyton-Jones

 resulted in the following compiler output using the command
 `ghc -fglasgow-exts -c Main.hs':
 
 -
 panic! (the `impossible' happened):
  applyTypeToArgs Main.MkFoo{-r1l,x-} {B1 PrelBase.True{-6y,w-}}

Thanks for a fine report.  Talk about falling at the first fence.
The inlining for constructors was totally broken.

I've fixed this, and checked it into the main new-rts CVS tree.
You can grab it from there or wait for a new release..

Simon



GHC 4.00 bug

1998-10-13 Thread edward barry jr

The following bug occurred while compiling GHC-4.00 on a Linux
platform, using ghc-3.03, gcc-2.7.3.2

Thanks
Ed
-

ghc-3.03 -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen
-Iparser
-iutils:basicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:stranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen
-recomp -O -H32m-c hsSyn/HsDecls.lhs -o hsSyn/HsDecls.o -osuf o

HsDecls.lhs:10: Warning:
Failed to find (optional) interface decl for
`s6CV'
desired at
HsBinds.hi:60

HsDecls.lhs:10: Warning:
Failed to find (optional) interface decl for
`s6CV'
desired at
HsBinds.hi:60

HsDecls.lhs:10: Warning:
Failed to find (optional) interface decl for
`s6CV'
desired at
HsBinds.hi:60


panic! (the `impossible' happened):
tcLookupTyVar: HsBinds.s6CV{-r3qc-}

Please report it as a compiler bug to
[EMAIL PROTECTED]

make[2]: *** [hsSyn/HsDecls.o] Error 1






Re: undocumented feature in GHC-4.00?

1998-10-13 Thread Jeffrey R. Lewis

Simon Peyton-Jones wrote:

  When attempting to reconstruct the syntax for existential
  quantification, I tried:
 
  newtype Groo a = Groo (Either a b)
 
  To my surprise, using ghc-4.00, this worked - without even using
  `-fglasgow-exts'.  (it doesn't work, with or without `-fglasgow-exts'
  under 3.02)

 Nothing about existentials here.   GHC is universally quantifying
 over the 'b'.  It's just as if you'd written

 newtype Groo a = Groo (forall b. Either a b)


Indeed - it wasn't the type I was casting about for - I was looking for
how to express:
newtype Groo a = forall b. Groo (Either a b)

This form of quantification seems to only be supported for `data' decls -
is there a reason we can't also do it with `newtype'?


 Perhaps we shouldn't do implicit universal quantification here?

  Is this a feature or a bug?



The confusion on my part was that this form of implicit universal
quantification seems to be an undocumented feature.  In the release notes,
the only comment about implicit quantification is this:


 Notice that you don't need to use a forall if there's an
 explicit context. For example in the first argument of the
 constructor MkSwizzle, an implicit "forall a." is prefixed to
 the argument type. The implicit forall quantifies all type
 variables that are not already in scope, and are mentioned in
 the type quantified over

--Jeff