- 20 Nov, 2001 1 commit
-
-
simonpj authored
Add constant-folding rules for Float# and Double#
-
- 14 Sep, 2001 1 commit
-
-
simonpj authored
Add comments
-
- 29 Aug, 2001 1 commit
-
-
simonmar authored
Fix *two* bugs in formatRealFloat: The first one is in the Haskell 98 errata, namely that negative exponents cause an infinite loop in the FFFixed case when no precision is specified. eg. `Numeric.showFFloat Nothing 0.02 ""' I've modified the code in the errata to properly handle the e == 0 case and to be slightly more efficient when e > 0. The second bug is this: Prelude> Numeric.showFFloat (Just 0) 0.02 "" "0."
-
- 28 Feb, 2001 1 commit
-
-
qrczak authored
* Add {intToInt,wordToWord}{8,16,32}# primops. WARNING: Not implemented in ncg for Alpha and Sparc. But -O -fasm is not going to go far anyway because of other omissions. * Have full repertoire of 8,16,32-bit signed and unsigned MachMisc.Size values. Again only x86 is fully supported. They are used for {index,read,write}{Int,Word}{8,16,32}{OffAddr,Array}# and {intToInt,wordToWord}{8,16,32}# primops. * Have full repertoire of {index,read,write}\ {Char,WideChar,Int,Word,Addr,Float,Double,StablePtr,\ {Int,Word}{8,16,32,64}}\ {OffAddr,Array} primops and appropriate instances. There were various omissions in various places. * Add {plus,minus,times}Word# primops to avoid so many Word# <-> Int# coercions. * Rewrite modules PrelWord and PrelInt almost from scratch. * Simplify fromInteger and realToFrac rules. For each of {Int,Word}{8,16,32} there is just a pair of fromInteger rules replacing the source or target type with Int or Word. For {Int,Word,Int64,Word64} there are rules from any to any. Don't include rules which are derivable from inlining anyway, e.g. those mentioning Integer. Old explicit coercions are simply defined as appropriately typed fromInteger. * Various old coercion functions marked as deprecated. * Add instance Bits Int, and instance {Show,Num,Real,Enum,Integral,Bounded,Ix,Read,Bits} Word. * Coercions to sized integer types consistently behave as cutting the right amount of bits from the infinite two-complement representation. For example (fromIntegral (-1 :: Int8) :: Word64) == maxBound. * ghc/tests/numeric/should_run/arith011 tests {Int,Word}64 and instance Bits Int, and does not try to use overflowing toEnum. arith011.stdout is not updated yet because of a problem I will tell about soon. * Move fromInteger and realToFrac from Prelude to PrelReal. Move fromInt from PrelNum to PrelReal and define as fromInteger. Define toInt as fromInteger. fromInteger is the place to write integer conversion rules for. * Remove ArrayBase.newInitialisedArray, use default definition of newArray instead. * Bugs fixed: - {quot,rem}Word# primop attributes. - integerToInt64# for small negative values. - {min,max}Bound::Int on 64-bit platforms. - iShiftRL64#. - Various Bits instances. * Polishing: - Use 'ppr' instead of 'pprPrimOp' and 'text . showPrimRep'. - PrimRep.{primRepString,showPrimRepToUser} removed. - MachMisc.sizeOf returns Int instead of Integer. - Some eta reduction, parens, spacing, and reordering cleanups - sorry, couldn't resist. * Questions: - Should iShiftRL and iShiftRL64 be removed? IMHO they should, s/iShiftRA/iShiftR/, s/shiftRL/shiftR/. The behaviour on shifting is a property of the signedness of the type, not the operation! I haven't done this change.
-
- 22 Feb, 2001 1 commit
-
-
simonpj authored
fromInt Remove fromInt from class Num, though it is retained as an overloaded operation (with unchanged type) in PrelNum. There are quite a few consequential changes in the Prelude. I hope I got them all correct! Also fix a bug that meant Integer (and its instances) wasn't getting slurped in by the renamer, even though it was needed for defaulting.
-
- 29 Aug, 2000 1 commit
-
-
simonpj authored
Remove redundant imports and dead code
-
- 30 Jun, 2000 1 commit
-
-
simonmar authored
- fix copyrights - remove some unused imports - comment formatting fixes
-
- 09 Jun, 2000 1 commit
-
-
simonmar authored
ieee-flpt.h is in ../../includes, not ../includes.
-
- 10 May, 2000 1 commit
-
-
panne authored
More RULES for coercions and truncate.
-
- 14 Apr, 2000 1 commit
-
-
rrt authored
Removed -fcompiling-prelude flag (now removed from compiler)
-
- 10 Apr, 2000 1 commit
-
-
simonpj authored
Make it so that -fcompiling-prelude applies only for Prelude modules (i.e. ones called Prelxxx). I've done this with an {-# OPTIONS #-} line in each such module (they all has -fno-implicit-prelude anyway) but a less repetitive approach in the Makefile would be welcome.
-
- 23 Mar, 2000 1 commit
-
-
simonpj authored
This utterly gigantic commit is what I've been up to in background mode in the last couple of months. Originally the main goal was to get rid of Con (staturated constant applications) in the CoreExpr type, but one thing led to another, and I kept postponing actually committing. Sorry. Simon, 23 March 2000 I've tested it pretty thoroughly, but doubtless things will break. Here are the highlights * Con is gone; the CoreExpr type is simpler * NoRepLits have gone * Better usage info in interface files => less recompilation * Result type signatures work * CCall primop is tidied up * Constant folding now done by Rules * Lots of hackery in the simplifier * Improvements in CPR and strictness analysis Many bug fixes including * Sergey's DoCon compiles OK; no loop in the strictness analyser * Volker Wysk's programs don't crash the CPR analyser I have not done much on measuring compilation times and binary sizes; they could have got worse. I think performance has got significantly better, though, in most cases. Removing the Con form of Core expressions ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The big thing is that For every constructor C there are now *two* Ids: C is the constructor's *wrapper*. It evaluates and unboxes arguments before calling $wC. It has a perfectly ordinary top-level defn in the module defining the data type. $wC is the constructor's *worker*. It is like a primop that simply allocates and builds the constructor value. Its arguments are the actual representation arguments of the constructor. Its type may be different to C, because: - useless dict args are dropped - strict args may be flattened For every primop P there is *one* Id, its (curried) Id Neither contructor worker Id nor the primop Id have a defminition anywhere. Instead they are saturated during the core-to-STG pass, and the code generator generates code for them directly. The STG language still has saturated primops and constructor applications. * The Const type disappears, along with Const.lhs. The literal part of Const.lhs reappears as Literal.lhs. Much tidying up in here, to bring all the range checking into this one module. * I got rid of NoRep literals entirely. They just seem to be too much trouble. * Because Con's don't exist any more, the funny C { args } syntax disappears from inteface files. Parsing ~~~~~~~ * Result type signatures now work f :: Int -> Int = \x -> x -- The Int->Int is the type of f g x y :: Int = x+y -- The Int is the type of the result of (g x y) Recompilation checking and make ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * The .hi file for a modules is not touched if it doesn't change. (It used to be touched regardless, forcing a chain of recompilations.) The penalty for this is that we record exported things just as if they were mentioned in the body of the module. And the penalty for that is that we may recompile a module when the only things that have changed are the things it is passing on without using. But it seems like a good trade. * -recomp is on by default Foreign declarations ~~~~~~~~~~~~~~~~~~~~ * If you say foreign export zoo :: Int -> IO Int then you get a C produre called 'zoo', not 'zzoo' as before. I've also added a check that complains if you export (or import) a C procedure whose name isn't legal C. Code generation and labels ~~~~~~~~~~~~~~~~~~~~~~~~~~ * Now that constructor workers and wrappers have distinct names, there's no need to have a Foo_static_closure and a Foo_closure for constructor Foo. I nuked the entire StaticClosure story. This has effects in some of the RTS headers (i.e. s/static_closure/closure/g) Rules, constant folding ~~~~~~~~~~~~~~~~~~~~~~~ * Constant folding becomes just another rewrite rule, attached to the Id for the PrimOp. To achieve this, there's a new form of Rule, a BuiltinRule (see CoreSyn.lhs). The prelude rules are in prelude/PrelRules.lhs, while simplCore/ConFold.lhs has gone. * Appending of constant strings now works, using fold/build fusion, plus the rewrite rule unpack "foo" c (unpack "baz" c n) = unpack "foobaz" c n Implemented in PrelRules.lhs * The CCall primop is tidied up quite a bit. There is now a data type CCall, defined in PrimOp, that packages up the info needed for a particular CCall. There is a new Id for each new ccall, with an big "occurrence name" {__ccall "foo" gc Int# -> Int#} In interface files, this is parsed as a single Id, which is what it is, really. Miscellaneous ~~~~~~~~~~~~~ * There were numerous places where the host compiler's minInt/maxInt was being used as the target machine's minInt/maxInt. I nuked all of these; everything is localised to inIntRange and inWordRange, in Literal.lhs * Desugaring record updates was broken: it didn't generate correct matches when used withe records with fancy unboxing etc. It now uses matchWrapper. * Significant tidying up in codeGen/SMRep.lhs * Add __word, __word64, __int64 terminals to signal the obvious types in interface files. Add the ability to print word values in hex into C code. * PrimOp.lhs is no longer part of a loop. Remove PrimOp.hi-boot* Types ~~~~~ * isProductTyCon no longer returns False for recursive products, nor for unboxed products; you have to test for these separately. There's no reason not to do CPR for recursive product types, for example. Ditto splitProductType_maybe. Simplification ~~~~~~~~~~~~~~~ * New -fno-case-of-case flag for the simplifier. We use this in the first run of the simplifier, where it helps to stop messing up expressions that the (subsequent) full laziness pass would otherwise find float out. It's much more effective than previous half-baked hacks in inlining. Actually, it turned out that there were three places in Simplify.lhs that needed to know use this flag. * Make the float-in pass push duplicatable bindings into the branches of a case expression, in the hope that we never have to allocate them. (see FloatIn.sepBindsByDropPoint) * Arrange that top-level bottoming Ids get a NOINLINE pragma This reduced gratuitous inlining of error messages. But arrange that such things still get w/w'd. * Arrange that a strict argument position is regarded as an 'interesting' context, so that if we see foldr k z (g x) then we'll be inclined to inline g; this can expose a build. * There was a missing case in CoreUtils.exprEtaExpandArity that meant we were missing some obvious cases for eta expansion Also improve the code when handling applications. * Make record selectors (identifiable by their IdFlavour) into "cheap" operations. [The change is a 2-liner in CoreUtils.exprIsCheap] This means that record selection may be inlined into function bodies, which greatly improves the arities of overloaded functions. * Make a cleaner job of inlining "lone variables". There was some distributed cunning, but I've centralised it all now in SimplUtils.analyseCont, which analyses the context of a call to decide whether it is "interesting". * Don't specialise very small functions in Specialise.specDefn It's better to inline it. Rather like the worker/wrapper case. * Be just a little more aggressive when floating out of let rhss. See comments with Simplify.wantToExpose A small change with an occasional big effect. * Make the inline-size computation think that case x of I# x -> ... is *free*. CPR analysis ~~~~~~~~~~~~ * Fix what was essentially a bug in CPR analysis. Consider letrec f x = let g y = let ... in f e1 in if ... then (a,b) else g x g has the CPR property if f does; so when generating the final annotated RHS for f, we must use an envt in which f is bound to its final abstract value. This wasn't happening. Instead, f was given the CPR tag but g wasn't; but of course the w/w pass gives rotten results in that case!! (Because f's CPR-ness relied on g's.) On they way I tidied up the code in CprAnalyse. It's quite a bit shorter. The fact that some data constructors return a constructed product shows up in their CPR info (MkId.mkDataConId) not in CprAnalyse.lhs Strictness analysis and worker/wrapper ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * BIG THING: pass in the demand to StrictAnal.saExpr. This affects situations like f (let x = e1 in (x,x)) where f turns out to have strictness u(SS), say. In this case we can mark x as demanded, and use a case expression for it. The situation before is that we didn't "know" that there is the u(SS) demand on the argument, so we simply computed that the body of the let expression is lazy in x, and marked x as lazily-demanded. Then even after f was w/w'd we got let x = e1 in case (x,x) of (a,b) -> $wf a b and hence let x = e1 in $wf a b I found a much more complicated situation in spectral/sphere/Main.shade, which improved quite a bit with this change. * Moved the StrictnessInfo type from IdInfo to Demand. It's the logical place for it, and helps avoid module loops * Do worker/wrapper for coerces even if the arity is zero. Thus: stdout = coerce Handle (..blurg..) ==> wibble = (...blurg...) stdout = coerce Handle wibble This is good because I found places where we were saying case coerce t stdout of { MVar a -> ... case coerce t stdout of { MVar b -> ... and the redundant case wasn't getting eliminated because of the coerce.
-
- 22 Mar, 2000 1 commit
-
-
simonpj authored
Make Enum for Ratio behave like the Report says
-
- 20 Dec, 1999 1 commit
-
-
simonpj authored
This commit implements a substantial re-organisation of the Prelude It also fixes a couple of small renamer bugs that were reported recently (notably, Sven pointed out that we weren't reporting unused imports properly) My original goal was to get rid of all "orphan" modules (i.e. ones with instance decls that don't belong either to a tycon or a class defined in the same module). This should reduce the number of interface files that have to be read when compiling small Haskell modules. But like most expeditions into the Prelude Swamp, it spiraled out of control. The result is quite satisfactory, though. GONE AWAY: PrelCCall, PrelNumExtra NEW: PrelReal, PrelFloat, PrelByteArr, PrelNum.hi-boot (The extra PrelNum.hi-boot is because of a tiresome thin-air Id, addr2Integer, which used to be in PrelBase.) Quite a lot of types have moved from one module to another, which entails some changes to part of the compiler (PrelInfo, PrelMods) etc, and there are a few places in the RTS includes and even in the driver that know about these home modules (alas). So the rough structure is as follows, in (linearised) dependency order [this list now appears in PrelBase.lhs] PrelGHC Has no implementation. It defines built-in things, and by importing it you bring them into scope. The source file is PrelGHC.hi-boot, which is just copied to make PrelGHC.hi Classes: CCallable, CReturnable PrelBase Classes: Eq, Ord, Functor, Monad Types: list, (), Int, Bool, Ordering, Char, String PrelTup Types: tuples, plus instances for PrelBase classes PrelShow Class: Show, plus instances for PrelBase/PrelTup types PrelEnum Class: Enum, plus instances for PrelBase/PrelTup types PrelMaybe Type: Maybe, plus instances for PrelBase classes PrelNum Class: Num, plus instances for Int Type: Integer, plus instances for all classes so far (Eq, Ord, Num, Show) Integer is needed here because it is mentioned in the signature of 'fromInteger' in class Num PrelReal Classes: Real, Integral, Fractional, RealFrac plus instances for Int, Integer Types: Ratio, Rational plus intances for classes so far Rational is needed here because it is mentioned in the signature of 'toRational' in class Real Ix Classes: Ix, plus instances for Int, Bool, Char, Integer, Ordering, tuples PrelArr Types: Array, MutableArray, MutableVar Does *not* contain any ByteArray stuff (see PrelByteArr) Arrays are used by a function in PrelFloat PrelFloat Classes: Floating, RealFloat Types: Float, Double, plus instances of all classes so far This module contains everything to do with floating point. It is a big module (900 lines) With a bit of luck, many modules can be compiled without ever reading PrelFloat.hi PrelByteArr Types: ByteArray, MutableByteArray We want this one to be after PrelFloat, because it defines arrays of unboxed floats. Other Prelude modules are much easier with fewer complex dependencies.
-
- 01 Nov, 1999 2 commits
-
-
simonpj authored
A regrettably-gigantic commit that puts in place what Simon PJ has been up to for the last month or so, on and off. The basic idea was to restore unfoldings to *occurrences* of variables without introducing a space leak. I wanted to make sure things improved relative to 4.04, and that proved depressingly hard. On the way I discovered several quite serious bugs in the simplifier. Here's a summary of what's gone on. ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * No commas between for-alls in RULES. This makes the for-alls have the same syntax as in types. * Arrange that simplConArgs works in one less pass than before. This exposed a bug: a bogus call to completeBeta. * Add a top-level flag in CoreUnfolding, used in callSiteInline * Extend w/w to use etaExpandArity, so it does eta/coerce expansion * Implement inline phases. The meaning of the inline pragmas is described in CoreUnfold.lhs. You can say things like {#- INLINE 2 build #-} to mean "inline build in phase 2" * Don't float anything out of an INLINE. Don't float things to top level unless they also escape a value lambda. [see comments with SetLevels.lvlMFE Without at least one of these changes, I found that {-# INLINE concat #-} concat = __inline (/\a -> foldr (++) []) was getting floated to concat = __inline( /\a -> lvl a ) lvl = ...inlined version of foldr... Subsequently I found that not floating constants out of an INLINE gave really bad code like __inline (let x = e in \y -> ...) so I now let things float out of INLINE * Implement the "reverse-mapping" idea for CSE; actually it turned out to be easier to implement it in SetLevels, and may benefit full laziness too. * It's a good idea to inline inRange. Consider index (l,h) i = case inRange (l,h) i of True -> l+i False -> error inRange itself isn't strict in h, but if it't inlined then 'index' *does* become strict in h. Interesting! * Big change to the way unfoldings and occurrence info is propagated in the simplifier The plan is described in Subst.lhs with the Subst type Occurrence info is now in a separate IdInfo field than user pragmas * I found that (coerce T (coerce S (\x.e))) y didn't simplify in one round. First we get to (\x.e) y and only then do the beta. Solution: cancel the coerces in the continuation * Amazingly, CoreUnfold wasn't counting the cost of a function an application. * Disable rules in initial simplifier run. Otherwise full laziness doesn't get a chance to lift out a MFE before a rule (e.g. fusion) zaps it. queens is a case in point * Improve float-out stuff significantly. The big change is that if we have \x -> ... /\a -> ...let p = ..a.. in let q = ...p... where p's rhs doesn't x, we abstract a from p, so that we can get p past x. (We did that before.) But we also substitute (p a) for p in q, and then we can do the same thing for q. (We didn't do that, so q got stuck.) This is much better. It involves doing a substitution "as we go" in SetLevels, though.
-
sof authored
formatRealFloat: Fixed some e==0 confusion in the default case for FFExponent
-
- 19 Sep, 1999 1 commit
-
-
sof authored
Drop the use of _ccall_, _casm_ and lit-lits in std/, "foreign import" is the future.
-
- 14 Jul, 1999 1 commit
-
-
simonmar authored
USE_REPORT_PRELUDE patches from Wolfram Kahl.
-
- 09 Jun, 1999 1 commit
-
-
simonmar authored
Add a few SPECIALISE/INLINE pragmas.
-
- 18 May, 1999 1 commit
-
-
simonpj authored
../compiler/msg_prel
-
- 01 Mar, 1999 1 commit
-
-
sof authored
wibble
-
- 18 Feb, 1999 1 commit
-
-
simonm authored
Add two new operations to StgPrimFloat.c: __int_encodeFloat __int_encodeDouble for encoding floats/doubles from small integers. This avoids having to convert small integers to large ones before an encodeFloat operation, and fixes the two cases of slowdown in nofib after the small integer changes. Also: - remove encodeFloat and decodeFloat as primops - use foreign import for encode{Float,Double} and the various isNaN etc. ccalls in PrelNumExtra.
-
- 17 Feb, 1999 2 commits
-
-
simonpj authored
Reinstate specialisations for fromIntegral and realToFrac
-
simonm authored
Fast Integers. The rep. of Integers is now data Integer = S# Int# | J# Int# ByteArray# - several new primops added for overflow-detecting arithmetic - negateInteger# removed; it can be done directly - integer_0, integer_1 etc. removed. - the compiler now uses S# where it previously used int2Integer. - the compiler generates small integers for -2^32 .. 2^32-1, instead of -2^29 .. -2^29-1. - PrelST.State datatype moved to LazyST (its only use). - some library code (in Time.lhs) still needs cleaning up, it depends on the Integer rep.
-
- 02 Feb, 1999 1 commit
-
-
simonm authored
Optimise take a little.
-
- 01 Feb, 1999 2 commits
- 21 Jan, 1999 1 commit
-
-
sof authored
Enum instances updated to comply with the behaviour that Haskell 98 specifies. Notable changes, * [a..b] is not the empty list when a>b any longer. * [x..] and [x,y..] for Enum Int are now bounded lists. The first change is might be worth bearing in mind when converting 1.4 code to Haskell 98; functions may have made use of the old behaviour.
-
- 19 Jan, 1999 1 commit
-
-
sof authored
The Fight against needless use of (++) continues.
-
- 14 Jan, 1999 1 commit
-
-
sof authored
Changes to make the Prelude comply with Haskell 98. I claim that this completes GHC's implementation of Haskell 98 (at least feature-wise, but there's bound to be some bugs lurking..)
-
- 02 Dec, 1998 1 commit
-
-
simonm authored
Move 4.01 onto the main trunk.
-
- 21 Oct, 1998 1 commit
-
-
sof authored
Removed commented-out Haskell-1.2 methods
-
- 30 Sep, 1998 1 commit
-
-
sof authored
tweaked Integral.Int.div to cope with overflows
-
- 27 Aug, 1998 1 commit
-
-
sof authored
floatToDigits bugfix
-
- 02 Jul, 1998 1 commit
-
-
simonm authored
Add specialise pragmas (which don't work at the moment, due to an unidentified bug in the specialiser/simplifier).
-
- 22 May, 1998 1 commit
-
-
simonm authored
- Add NOINLINE pragmas to the unsafe things (unsafe*IO, unsafe*ST, runST etc.) - Move unsafe function back into the proper modules - Remove PrelUnsafe*.lhs
-
- 06 May, 1998 1 commit
-
-
simonm authored
- one `quotRem` is faster than separate `quot` and `rem` on Integers.
-
- 11 Mar, 1998 1 commit
-
-
sof authored
jtos: leave Integer-land ASAP
-
- 02 Feb, 1998 1 commit
-
-
simonm authored
Library re-organisation: All libraries now live under ghc/lib, which has the following structure: ghc/lib/std -- all prelude files (libHS.a) ghc/lib/std/cbits ghc/lib/exts -- standard Hugs/GHC extensions (libHSexts.a) -- available with '-fglasgow-exts' ghc/lib/posix -- POSIX library (libHSposix.a) ghc/lib/posix/cbits -- available with '-syslib posix' ghc/lib/misc -- used to be hslibs/ghc (libHSmisc.a) ghc/lib/misc/cbits -- available with '-syslib misc' ghc/lib/concurrent -- Concurrent libraries (libHSconc.a) -- available with '-concurrent' Also, several non-standard prelude modules had their names changed to begin with 'Prel' to reduce namespace pollution. Addr ==> PrelAddr (Addr interface available in 'exts') ArrBase ==> PrelArr CCall ==> PrelCCall (CCall interface available in 'exts') ConcBase ==> PrelConc GHCerr ==> PrelErr Foreign ==> PrelForeign (Foreign interface available in 'exts') GHC ==> PrelGHC IOHandle ==> PrelHandle IOBase ==> PrelIOBase GHCmain ==> PrelMain STBase ==> PrelST Unsafe ==> PrelUnsafe UnsafeST ==> PrelUnsafeST
-
- 22 Jan, 1998 1 commit
-
-
sof authored
* removed ghc/Error.{lhs,hi-boot} * moved contents of Error to GHCerr + adjusted import lists of files that use old Error functionality. * moved seqError from Prelude to GHCerr.
-