RE: Can't compile HaskellDirect with GHC

1999-06-23 Thread Sigbjorn Finne (Intl Vendor)


George Russell [EMAIL PROTECTED] writes: 
 
..
 ../../ghc/driver/ghc -fglasgow-exts -Rghc-timing -H16m -W 
 -recomp-O -O2-for-C -H30m -c Utils.lhs -o Utils.o -osuf o
 ghc: ignoring heap-size-setting option (-H16m)...not the largest seen
 Utils.lhs:22: parse error on input `(#'
 
 Compilation had errors
 

"s|(#|( #|g" - the parser thinks it's the start of an unboxed
tuple, which is not the case here.

--sigbjorn



Can't compile HaskellDirect with GHC

1999-06-23 Thread George Russell

The latest GHC chokes on the latest HaskellDirect file src/Utils.lhs.
Here is a copy of error message and attached is the src/Utils.lhs file.
It will be seen from the file that ghc is objecting to an explicit
universal quantification.  What should I do?


===fptools== Recursively making `all' in src lib examples doc ...
PWD = /export/ger/fptools/hdirect


==fptools== gmake all -r;
 in /export/ger/fptools/hdirect/src

../../ghc/driver/ghc -syslib exts -Rghc-timing -H16m -W -recomp-O -O2-for-C -H30m 
-c Utils.lhs -o Utils.o -osuf o
ghc: ignoring heap-size-setting option (-H16m)...not the largest seen
Utils.lhs:345: parse error on input `.'

Compilation had errors

%
% @(#) $Docid: May. 24th 1999  17:42  Sigbjorn Finne $
% @(#) $Contactid: [EMAIL PROTECTED] $
%

\begin{code}
module Utils 
   ( showOct
   , showHex
   , mapFromMb
   , mapMb
   , mapMbM
   , concMaybe
   , split
   , prefix
   , traceIf
   , elemBy
   , mapUnzip
   , diff

   , deEscapeString
   , (#)

   --,UNUSED: catMapMaybes
   
   , dropSuffix

 -- re-exported
   , trace
   
   , tryOpen
   
   , basename
   , prefixDir

   , hdirect_root
   , bailIf
   
   , decons
   , safe_init
   
   , mapAccumLM
   
   , readTaggedFields
   , read_int
   , read_string
   , read_bool
   , read_qid
   , FieldInfo(..)
   
   ) where

--import NumExts
import Char (chr, ord, readLitChar, isSpace, isAlphaNum)
import IOExts
import IO
{- BEGIN_GHC_ONLY
import Directory
   END_GHC_ONLY -}
import Monad ( when )
import List  ( mapAccumL, nub, isPrefixOf )

infixl 1 #
\end{code}

A convenience operator for invoking methods on objects:

\begin{code}
obj # meth  = meth obj
\end{code}


Until NumExts is commonly available, we define the following show functions here:

\begin{code}
showIntAtBase :: Integral a = a - (a - Char) - a - ShowS
showIntAtBase base toChr n r
  | n  0 = '-':showIntAtBase 10 toChr (negate n) r
  | otherwise = 
case quotRem n base of { (n', d) -
case toChr dof { ch -
let
r' = ch : r
in
if n' == 0 then r' else showIntAtBase base toChr n' r'
}}

showHex :: Integral a = a - ShowS
showHex n r = 
 showString "0x" $
 showIntAtBase 16 (toChrHex) n r
 where  
  toChrHex d
| d  10= chr (ord_0   + fromIntegral d)
| otherwise = chr (ord 'a' + fromIntegral (d - 10))

showOct :: Integral a = a - ShowS
showOct n r = 
 showString "0o" $
 showIntAtBase 8 (toChrOct) n r
 where toChrOct d = chr (ord_0   + fromIntegral d)

ord_0 :: Num a = a
ord_0 = fromInt (ord '0')
\end{code}

Mapping from a Maybe:

\begin{code}
mapFromMb :: b - (a - b) - Maybe a - b
mapFromMb d f mb = case mb of  Nothing - d ; Just v  - f v
\end{code}

\begin{code}
split :: Eq a = a - [a] - [[a]]
split a [] = []
split a as = 
 case break (==a) as of
   (xs,[])   - [xs]
   (xs,_:ys) - xs:split a ys

\end{code}

\begin{code}
prefix :: Eq a = [a] - [a] - Maybe [a] -- what's left
prefix [] ls = Just ls
prefix ls [] = Nothing
prefix (x:xs) (y:ys)
 | x == y= prefix xs ys
 | otherwise = Nothing
\end{code}

\begin{code}
traceIf :: Bool - String - a - a
traceIf True str v = trace str v
traceIf _ _ v = v

elemBy :: (a - Bool) - [a] - Bool
elemBy isEqual []   =  False
elemBy isEqual (y:ys)   =  isEqual y || elemBy isEqual ys

mapUnzip :: (a - (b,c)) - [a] - ([b],[c])
mapUnzip f [] = ([],[])
mapUnzip f (x:xs) =
  let
   (a, b)  = f x
   (as,bs) = mapUnzip f xs
  in
  (a:as,b:bs)
\end{code}

Returns list of deltas, i.e,

@
  diff [x0,x1..xp,xn] = [x0, x1-x0, .., xp - xn]
@

\begin{code}
diff :: Num a = [a] - [a]
diff ls = snd (mapAccumL ( \ acc v - (v, v - acc)) 0 ls)
\end{code}

\begin{code}
catMapMaybes :: (a - b) - [Maybe a] - [b]
catMapMaybes f ls = [f x | Just x - ls]
\end{code}

Dropping the extension off of a filename:

\begin{code}
dropSuffix :: String - String
dropSuffix str = 
 case dropWhile (\ch - ch /= '.'  ch /= '/'  ch /= '\\' ) 
(reverse str) of
  ('.':rs) - reverse rs
  _- str
  -- give up if we reach a separator (/ or \) or end of list.

dropPrefix :: Eq a = [a] - [a] - [a]
dropPrefix [] ys = ys
dropPrefix xs [] = []
dropPrefix (x:xs) (y:ys) 
  | x == y   = dropPrefix xs ys
  | otherwise= y:ys
\end{code}

Slightly generalised version of code found in Green Card's front end:

\begin{code}
tryOpen ::   Bool 
 - [FilePath] 
 - [String] 
 - FilePath
 - IO (Maybe FilePath)
tryOpen verbose path exts name = 
  doUntil (mbOpenFile verbose) (allFileNames path name exts)


RE: compiling CVS of June 99

1999-06-23 Thread Simon Marlow

 --
 -
   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:profiling:parser:usageSP:cprAnalysis:nativeGen 
 -recomp 
 -optCrts-G3 -optCrts-F1.5 -optCrts-M112m  -Onot -H45m 
 -dcore-lint -fno-warn-incomplete-patterns -dcore-lint  
 -c parser/Parser.hs  -o parser/Parser.o -osuf o
   ghc: 2896826300 bytes, 2495 GCs, 20862924/58736116 avg/max bytes 
residency (25 samples), 96M in use, 0.02 INIT (0.00 elapsed), 
 93.62 MUT (1541.24 elapsed), 93.58 GC (3792.84 elapsed) :ghc
   ghc: module version unchanged at 1
   make[2]: *** [parser/Parser.o] Error 1
   make[1]: *** [all] Error 1
   make: *** [all] Error 1
   -
 
 
 What might this mean?

It means your machine is thrashing, for a start.  Buy some more memory ;-)

Seriously, it looks like something crashed.  The fact that you got the stats
from the compiler means it probably wasn't the compiler, so it could have
been perl.  Try compiling again with EXTRA_HC_OPTS=-v, to see exactly where
the compilation got to.

I'm a bit concerned that the mem in use figure is 96M, and yet the maximum
residency is reported as 58M - I'd expect the in use figure to be at least
twice the maximum residency.  Very strange.

Cheers, 
Simon



RE: Can't compile HaskellDirect with GHC

1999-06-23 Thread Sigbjorn Finne (Intl Vendor)


Untested, but changing the occurrence of '-syslib exts'
to '-fglasgow-exts' in the first setting of
SRC_HC_OPTS in src/Makefile may just take you past this
one..

--sigbjorn

George Russell [EMAIL PROTECTED] writes: 
 
 The latest GHC chokes on the latest HaskellDirect file src/Utils.lhs.
 Here is a copy of error message and attached is the 
 src/Utils.lhs file.
 It will be seen from the file that ghc is objecting to an explicit
 universal quantification.  What should I do?
 
 --
 --
 ===fptools== Recursively making `all' in src lib examples doc ...
 PWD = /export/ger/fptools/hdirect
 --
 --
 --
 --
 ==fptools== gmake all -r;
  in /export/ger/fptools/hdirect/src
 --
 --
 ../../ghc/driver/ghc -syslib exts -Rghc-timing -H16m -W 
 -recomp-O -O2-for-C -H30m -c Utils.lhs -o Utils.o -osuf o
 ghc: ignoring heap-size-setting option (-H16m)...not the largest seen
 Utils.lhs:345: parse error on input `.'
 
 Compilation had errors
 



Re: Can't compile HaskellDirect with GHC

1999-06-23 Thread George Russell

George Russell wrote:
 
 "Sigbjorn Finne (Intl Vendor)" wrote:
 
  Untested, but changing the occurrence of '-syslib exts'
  to '-fglasgow-exts' in the first setting of
  SRC_HC_OPTS in src/Makefile may just take you past this
  one..
 In that case I get another error message:
 
 ===fptools== Recursively making `all' in src lib examples doc ...
 PWD = /export/ger/fptools/hdirect
 
 
 ==fptools== gmake all -r;
  in /export/ger/fptools/hdirect/src
 
 ../../ghc/driver/ghc -fglasgow-exts -Rghc-timing -H16m -W -recomp-O -O2-for-C 
-H30m -c Utils.lhs -o Utils.o -osuf o
 ghc: ignoring heap-size-setting option (-H16m)...not the largest seen
 Utils.lhs:22: parse error on input `(#'
 
 Compilation had errors
. . . but if (as well as Sigborn's change to the Makefile) I
replace  "(#)" by "( # )" on line 22 of Utils.lhs, it goes through!



Re: Can't compile HaskellDirect with GHC

1999-06-23 Thread George Russell

The struggle continues . . .
after the hacks suggested by Sigborn and myself, Utils went through,
as did a lot of other HaskellDirect files, but now I get the following
messages.  So we have a bug in GHC itself, with a non-exhaustive match
in ghc/compiler/typecheck/TcMatches.lhs.   The version of GHC is up to date
(as of last night) from the CVS sources.


===fptools== Recursively making `all' in src lib examples doc ...
PWD = /export/ger/fptools/hdirect


==fptools== gmake all -r;
 in /export/ger/fptools/hdirect/src

../../ghc/driver/ghc -fglasgow-exts -Rghc-timing -H16m -W -recomp-O -O2-for-C 
-H30m -c CodeGen.lhs -o CodeGen.o -osuf o
ghc: ignoring heap-size-setting option (-H16m)...not the largest seen

TcMatches.lhs:274: Non-exhaustive patterns in function tcStmts


gmake[1]: *** [CodeGen.o] Error 1
gmake: *** [all] Error 1



Re: Can't compile HaskellDirect with GHC

1999-06-23 Thread George Russell

"Sigbjorn Finne (Intl Vendor)" wrote:
 
 Untested, but changing the occurrence of '-syslib exts'
 to '-fglasgow-exts' in the first setting of
 SRC_HC_OPTS in src/Makefile may just take you past this
 one..
In that case I get another error message:

===fptools== Recursively making `all' in src lib examples doc ...
PWD = /export/ger/fptools/hdirect


==fptools== gmake all -r;
 in /export/ger/fptools/hdirect/src

../../ghc/driver/ghc -fglasgow-exts -Rghc-timing -H16m -W -recomp-O -O2-for-C 
-H30m -c Utils.lhs -o Utils.o -osuf o
ghc: ignoring heap-size-setting option (-H16m)...not the largest seen
Utils.lhs:22: parse error on input `(#'

Compilation had errors



Re: Integer - Int conversion

1999-06-23 Thread Marc van Dongen

Sigbjorn:

:  The question is what should 0x8000 :: Integer
:  become when its coerced into an int. 
:  
:  GHC takes the lowest 32 bits.
:   Advantage: Equality above maxBound still "works" aka above.
:   Disadvantage: 0x + 1 == 0 !
:  
:  Perhaps constant Int's larger than maxBound (or smaller
:  than minBound) should be a compile time error? 
:  
: 
: Int arithmetic is modulo maxBound (at least that's what
: ghc and Hugs implements), so making the Integer-Int conversion
: fall into line with that, has some merit.

On my machine the following program:

 main = do putStr "According to ghc-4.02 (1-maxBound)^2 = "
   putStr $ show mult1
   putStr "\nAccording to ghc-4.02 (maxBound-1)^2 = "
   putStr $ show mult2
  where mult1, mult2 :: Int
mult1 = (1-maxBound)*(1-maxBound)
mult2 = (maxBound-1)*(maxBound-1)

outputs:

According to ghc-4.02 (1-maxBound)^2 = 4
According to ghc-4.02 (maxBound-1)^2 = 4

Mod maxBound the result of both multiplication should have been 1.

Maybe it is better to rely on Integers.

Regards,


Marc van Dongen



RE: Integer - Int conversion

1999-06-23 Thread Simon Marlow

 On my machine the following program:
 
  main = do putStr "According to ghc-4.02 (1-maxBound)^2 = "
putStr $ show mult1
putStr "\nAccording to ghc-4.02 (maxBound-1)^2 = "
putStr $ show mult2
   where mult1, mult2 :: Int
 mult1 = (1-maxBound)*(1-maxBound)
 mult2 = (maxBound-1)*(maxBound-1)
 
 outputs:
 
 According to ghc-4.02 (1-maxBound)^2 = 4
 According to ghc-4.02 (maxBound-1)^2 = 4
 
 Mod maxBound the result of both multiplication should have been 1.

Int arithmetic on GHC and Hugs is modulo 2^32, i.e. maxBound + 1.

Cheers,
Simon



GHC panic when building prelude

1999-06-23 Thread George Russell

When building the GHC prelude (latest sources again), the following happened:

rm -f Weak.o ; if [ ! -d Weak ]; then mkdir Weak; else find Weak -name '*.o' -print | 
xargs rm -f __rm_food ; fi ;
../../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing -O 
-split-objs -odir Weak -H20m -static-O -O2-for-C -H30m -Onot -c Weak.lhs -o Weak.o 
-osuf o
ghc: ignoring heap-size-setting option (-H20m)...not the largest seen

panic! (the `impossible' happened):
cgEvalAlts: dodgy case of unboxed tuple type

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



Re: Can't compile HaskellDirect with GHC

1999-06-23 Thread Sven Panne

George Russell wrote:
 [...] So we have a bug in GHC itself, with a non-exhaustive match
 in ghc/compiler/typecheck/TcMatches.lhs. The version of GHC is up
 to date (as of last night) from the CVS sources. [...]

The same happens during the compilation of Green Card:

   [...]
   ghc -fvia-C -fglasgow-exts -recomp -Rghc-timing -O  -H10m  -c Lex.lhs -o Lex.o 
-osuf o

   TcMatches.lhs:274: Non-exhaustive patterns in function tcStmts

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.informatik.uni-muenchen.de/~Sven.Panne



Re: Integer - Int conversion

1999-06-23 Thread Lennart Augustsson

Lennart Augustsson wrote:

 Simon Marlow wrote:

 
  Int arithmetic on GHC and Hugs is modulo 2^32, i.e. maxBound + 1.
 

 Actually, if we are in nit-picking mode, arithmetic is modulo (maxBound+1)*2.

PS. I.e., if we interpret "modulo" in the right way since the result is interpreted
as a signed number.  Int arithmetic in all Haskell implementations I know of
operate in the same way as C usually does.  It has the advantage that you have
the ring properties of + and *, which arithmetic with exceptions would not give you.

-- Lennart