| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Switch over to the new hierarchical libraries
---------------------------------------------
This commit reorganises our libraries to use the new hierarchical
module namespace extension.
The basic story is this:
- fptools/libraries contains the new hierarchical libraries.
Everything in here is "clean", i.e. most deprecated stuff has
been removed.
- fptools/libraries/base is the new base package
(replacing "std") and contains roughly what was previously
in std, lang, and concurrent, minus deprecated stuff.
Things that are *not allowed* in libraries/base include:
Addr, ForeignObj, ByteArray, MutableByteArray,
_casm_, _ccall_, ``'', PrimIO
For ByteArrays and MutableByteArrays we use UArray and
STUArray/IOUArray respectively now.
Modules previously called PrelFoo are now under
fptools/libraries/GHC. eg. PrelBase is now GHC.Base.
- fptools/libraries/haskell98 provides the Haskell 98 std.
libraries (Char, IO, Numeric etc.) as a package. This
package is enabled by default.
- fptools/libraries/network is a rearranged version of
the existing net package (the old package net is still
available; see below).
- Other packages will migrate to fptools/libraries in
due course.
NB. you need to checkout fptools/libraries as well as
fptools/hslibs now. The nightly build scripts will need to be
tweaked.
- fptools/hslibs still contains (almost) the same stuff as before.
Where libraries have moved into the new hierarchy, the hslibs
version contains a "stub" that just re-exports the new version.
The idea is that code will gradually migrate from fptools/hslibs
into fptools/libraries as it gets cleaned up, and in a version or
two we can remove the old packages altogether.
- I've taken the opportunity to make some changes to the build
system, ripping out the old hslibs Makefile stuff from
mk/target.mk; the new package building Makefile code is in
mk/package.mk (auto-included from mk/target.mk).
The main improvement is that packages now register themselves at
make boot time using ghc-pkg, and the monolithic package.conf
in ghc/driver is gone.
I've updated the standard packages but haven't tested win32,
graphics, xlib, object-io, or OpenGL yet. The Makefiles in
these packages may need some further tweaks, and they'll need
pkg.conf.in files added.
- Unfortunately all this rearrangement meant I had to bump the
interface-file version and create a bunch of .hi-boot-6 files :-(
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This fixes a problem with the recent clean up in the parsing of type
declarations. The cleaned up version was correct by H98 (I think), but
unfortunately won't compile the Prelude anymore.
I made the definition a little bit more liberal as follows:
- In `tycl_hdr' allow `gtycon' instead of just `tycon' for the defined type
constructor. This allows beyond H98 special syntax like "[]" etc as well as
tycon ops in parenthesis. Moreover, it allows qualified names, but the
renamer flags the latter as errors.
- Allow `gtycon' instead of only `qtycon' for the class name in definitions of
the form `Eq a => T a' to avoid a whole list of s/r conflicts. (I have *not*
checked that the renamer flags misuse, but I would expect that it does.)
ToDo: I think, the renamer should raise an error for all these additional
forms *unless* -fglasgow-exts is given.
In PrelBase, I needed to replace the infix notation by prefix notation in the
definition of `:+:' and `:*:'.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------
Rule phasing
------------
This commit adds a little more control to when rules are enabled.
{-# RULES
"foo" [2] forall ...
"baz" [~2] forall ...
#-}
Rule "foo" is active in phase 2 and later. The new thing is that the
"~2" means that Rule "baz" is active in phase 3 and earlier.
(Remember tha phases decrease towards zero.)
All the machinery was there to implement this, it just needed the syntax.
Why do this? Peter Gammie (at UNSW) found that rules weren't firing
because of bindings of the form
M.f = f
f = ....
where the rules where on the M.f binding. It turned out that an old
hack (which have for some time elicited the harmless "shortMeOut" debug
warnings) prevented this trivial construction from being correctly
simplified. The hack in turn derived from a trick in the way the
foldr/build rule was implemented....and that hack is no longer necessary
now we can switch rules *off* as well as *on*.
There are consequential changes in the Prelude foldr/build RULE stuff.
It's a clean-up.... Instead of strange definitions like
map = mapList
which we had before, we have an ordinary recursive defn of map, together
with rules to convert first to foldr/build form, and then (if nothing
happens) back again.
There's a fairly long comment about the general plan of attack in
PrelBase, near the defn of map.
|
|
|
|
| |
Add a rule for foldr k z [x]
|
|
|
|
| |
shiftR# --> shiftRL#
|
|
|
|
|
|
|
| |
Add shifty wrappers:
shiftL#, shiftR# :: Word# -> Int# -> Word#
iShiftL#, iShiftRA#, iShiftRL# :: Int# -> Int# -> Int#
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Change the story on shifting primops: SllOp, SrlOp, ISllOp, ISraOp, ISrlOp.
In the old primop story, these were implemented by C macros which
checked that the shift amount did not exceed the word size, and if so
returns a suitable value (0 or -1). This gives consistent, defined
behaviour for any shift amount. However, these checks were not
implemented on the NCG route, an inconsistency.
New story: these primops do NOT check their args; they just do the shift.
Shift values >= word size give undefined results. To reflect this, their
Haskell names have been prefixed with 'unchecked'.
The checks are now done on the Bits instances in the Prelude. This means
all code generation routes are consistently checked, and hopefully the
simplifier will remove the checks for literal shift amounts.
I have tried to fix up the implementation for 64-bit platforms too, but
not having one to hand, I don't know if it will work as-is.
|
|
|
|
| |
Remove foldr/cons RULE; see comments with the RULE
|
|
|
|
| |
Wibble in eqString
|
|
|
|
| |
Add a rule for equality on strings
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------
Simon's big commit
------------------
This commit, which I don't think I can sensibly do piecemeal, consists
of the things I've been doing recently, mainly directed at making
Manuel, George, and Marcin happier with RULES.
Reogranise the simplifier
~~~~~~~~~~~~~~~~~~~~~~~~~
1. The simplifier's environment is now an explicit parameter. This
makes it a bit easier to figure out where it is going.
2. Constructor arguments can now be arbitrary expressions, except
when the application is the RHS of a let(rec). This makes it much
easier to match rules like
RULES
"foo" f (h x, g y) = f' x y
In the simplifier, it's Simplify.mkAtomicArgs that ANF-ises a
constructor application where necessary. In the occurrence analyser,
there's a new piece of context info (OccEncl) to say whether a
constructor app is in a place where it should be in ANF. (Unless
it knows this it'll give occurrence info which will inline the
argument back into the constructor app.)
3. I'm experimenting with doing the "float-past big lambda" transformation
in the full laziness pass, rather than mixed in with the simplifier (was
tryRhsTyLam).
4. Arrange that
case (coerce (S,T) (x,y)) of ...
will simplify. Previous it didn't.
A local change to CoreUtils.exprIsConApp_maybe.
5. Do a better job in CoreUtils.exprEtaExpandArity when there's an
error function in one branch.
Phase numbers, RULES, and INLINE pragmas
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1. Phase numbers decrease from N towards zero (instead of increasing).
This makes it easier to add new earlier phases, which is what users want
to do.
2. RULES get their own phase number, N, and are disabled in phases before N.
e.g. {-# RULES "foo" [2] forall x y. f (x,y) = f' x y #-}
Note the [2], which says "only active in phase 2 and later".
3. INLINE and NOINLINE pragmas have a phase number to. This is now treated
in just the same way as the phase number on RULE; that is, the Id is not inlined
in phases earlier than N. In phase N and later the Id *may* be inlined, and
here is where INLINE and NOINLINE differ: INLNE makes the RHS look small, so
as soon as it *may* be inlined it probably *will* be inlined.
The syntax of the phase number on an INLINE/NOINLINE pragma has changed to be
like the RULES case (i.e. in square brackets). This should also make sure
you examine all such phase numbers; many will need to change now the numbering
is reversed.
Inlining Ids is no longer affected at all by whether the Id appears on the
LHS of a rule. Now it's up to the programmer to put a suitable INLINE/NOINLINE
pragma to stop it being inlined too early.
Implementation notes:
* A new data type, BasicTypes.Activation says when a rule or inline pragma
is active. Functions isAlwaysActive, isNeverActive, isActive, do the
obvious thing (all in BasicTypes).
* Slight change in the SimplifierSwitch data type, which led to a lot of
simplifier-specific code moving from CmdLineOpts to SimplMonad; a Good Thing.
* The InlinePragma in the IdInfo of an Id is now simply an Activation saying
when the Id can be inlined. (It used to be a rather bizarre pair of a
Bool and a (Maybe Phase), so this is much much easier to understand.)
* The simplifier has a "mode" environment switch, replacing the old
black list. Unfortunately the data type decl has to be in
CmdLineOpts, because it's an argument to the CoreDoSimplify switch
data SimplifierMode = SimplGently | SimplPhase Int
Here "gently" means "no rules, no inlining". All the crucial
inlining decisions are now collected together in SimplMonad
(preInlineUnconditionally, postInlineUnconditionally, activeInline,
activeRule).
Specialisation
~~~~~~~~~~~~~~
1. Only dictionary *functions* are made INLINE, not dictionaries that
have no parameters. (This inline-dictionary-function thing is Marcin's
idea and I'm still not sure whether it's a good idea. But it's definitely
a Bad Idea when there are no arguments.)
2. Be prepared to specialise an INLINE function: an easy fix in
Specialise.lhs
But there is still a problem, which is that the INLINE wins
at the call site, so we don't use the specialised version anyway.
I'm still unsure whether it makes sense to SPECIALISE something
you want to INLINE.
Random smaller things
~~~~~~~~~~~~~~~~~~~~~~
* builtinRules (there was only one, but may be more) in PrelRules are now
incorporated. They were being ignored before...
* OrdList.foldOL --> OrdList.foldrOL, OrdList.foldlOL
* Some tidying up of the tidyOpenTyVar, tidyTyVar functions. I've
forgotten exactly what!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
How I spent my summer vacation.
Primops
-------
The format of the primops.txt.pp file has been enhanced to allow
(latex-style) primop descriptions to be included. There is a new flag
to genprimopcode that generates documentation including these
descriptions. A first cut at descriptions of the more interesting
primops has been made, and the file has been reordered a bit.
31-bit words
------------
The front end now can cope with the possibility of 31-bit (or even 30-bit)
Int# and Word# types. The only current use of this is to generate
external .core files that can be translated into OCAML source files
(OCAML uses a one-bit tag to distinguish integers from pointers).
The only way to get this right now is by hand-defining the preprocessor
symbol WORD_SIZE_IN_BITS, which is normally set automatically from
the familiar WORD_SIZE_IN_BYTES.
Just in case 31-bit words are used, we now have Int32# and Word32# primitive types
and an associated family of operators, paralleling the existing 64-bit
stuff. Of course, none of the operators actually need to be implemented
in the absence of a 31-bit backend.
There has also been some minor re-jigging of the 32 vs. 64 bit stuff.
See the description at the top of primops.txt.pp file for more details.
Note that, for the first time, the *type* of a primop can now depend
on the target word size.
Also, the family of primops intToInt8#, intToInt16#, etc.
have been renamed narrow8Int#, narrow16Int#, etc., to emphasize
that they work on Int#'s and don't actually convert between types.
Addresses
---------
As another part of coping with the possibility of 31-bit ints,
the addr2Int# and int2Addr# primops are now thoroughly deprecated
(and not even defined in the 31-bit case) and all uses
of them have been removed except from the (deprecated) module
hslibs/lang/Addr
Addr# should now be treated as a proper abstract type, and has these suitable operators:
nullAddr# : Int# -> Addr# (ignores its argument; nullary primops cause problems at various places)
plusAddr# : Addr# -> Int# -> Addr#
minusAddr : Addr# -> Addr# -> Int#
remAddr# : Addr# -> Int# -> Int#
Obviously, these don't allow completely arbitrary offsets if 31-bit ints are
in use, but they should do for all practical purposes.
It is also still possible to generate an address constant, and there is a built-in rule
that makes use of this to remove the nullAddr# calls.
Misc
----
There is a new compile flag -fno-code that causes GHC to quit after generating .hi files
and .core files (if requested) but before generating STG.
Z-encoded names for tuples have been rationalized; e.g.,
Z3H now means an unboxed 3-tuple, rather than an unboxed
tuple with 3 commas (i.e., a 4-tuple)!
Removed misc. litlits in hslibs/lang
Misc. small changes to external core format. The external core description
has also been substantially updated, and incorporates the automatically-generated
primop documentation; its in the repository at /papers/ext-core/core.tex.
A little make-system addition to allow passing CPP options to compiler and
library builds.
|
|
|
|
| |
Use infix syntax on lhs of some rules.
|
|
|
|
| |
Cosmetics.
|
|
|
|
| |
Enable primop rules - they work now.
|
|
|
|
| |
Checking 0..0x10FFFF range can be done by a single unsigned comparison.
|
|
|
|
|
|
|
|
| |
Add various rules for primops (x# <=# x#, x# *# 1# etc.).
But they are commented out for now. Please uncomment parts marked
with XXX when the bug with source primop rules shadowing builtin
primop rules is fixed.
|
|
|
|
| |
Cosmetics.
|
|
|
|
|
| |
Move the RULES for intToInt32# and wordToWord32# to PrelBase, so that
PrelInt and PrelWord are no longer orphan modules.
|
|
|
|
|
|
|
|
|
| |
Uncomment {-# SPECIALISE instance Eq [Char] #-}
{-# SPECIALISE instance Ord [Char] #-}
Remove explicit (<), (<=), (>), (>=) in instance Ord [a].
eqString is defined as (==) instead of vice versa.
ghc generates good specialized code for these automatically.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* 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.
|
|
|
|
|
| |
- Move compareInt# to PrelBase (where it was duplicated)
- remove some unnecessary truncations in the Int8/Int16 code
|
|
|
|
|
|
| |
Recent Unicode and future ISO-10646 finally decided that the character
code space ends at U+10FFFF. Let ghc follow the rules: maxBound::Char
is now '\x10FFFF', etc.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------
Adding generics SLPJ Oct 2000
--------------------------------------
This big commit adds Hinze/PJ-style generic class definitions, based
on work by Andrei Serjantov. For example:
class Bin a where
toBin :: a -> [Int]
fromBin :: [Int] -> (a, [Int])
toBin {| Unit |} Unit = []
toBin {| a :+: b |} (Inl x) = 0 : toBin x
toBin {| a :+: b |} (Inr y) = 1 : toBin y
toBin {| a :*: b |} (x :*: y) = toBin x ++ toBin y
fromBin {| Unit |} bs = (Unit, bs)
fromBin {| a :+: b |} (0:bs) = (Inl x, bs') where (x,bs') = fromBin bs
fromBin {| a :+: b |} (1:bs) = (Inr y, bs') where (y,bs') = fromBin bs
fromBin {| a :*: b |} bs = (x :*: y, bs'') where (x,bs' ) = fromBin bs
(y,bs'') = fromBin bs'
Now we can say simply
instance Bin a => Bin [a]
and the compiler will derive the appropriate code automatically.
(About 9k lines of diffs. Ha!)
Generic related things
~~~~~~~~~~~~~~~~~~~~~~
* basicTypes/BasicTypes: The EP type (embedding-projection pairs)
* types/TyCon:
An extra field in an algebraic tycon (genInfo)
* types/Class, and hsSyn/HsBinds:
Each class op (or ClassOpSig) carries information about whether
it a) has no default method
b) has a polymorphic default method
c) has a generic default method
There's a new data type for this: Class.DefMeth
* types/Generics:
A new module containing good chunk of the generic-related code
It has a .hi-boot file (alas).
* typecheck/TcInstDcls, typecheck/TcClassDcl:
Most of the rest of the generics-related code
* hsSyn/HsTypes:
New infix type form to allow types of the form
data a :+: b = Inl a | Inr b
* parser/Parser.y, Lex.lhs, rename/ParseIface.y:
Deal with the new syntax
* prelude/TysPrim, TysWiredIn:
Need to generate generic stuff for the wired-in TyCons
* rename/RnSource RnBinds:
A rather gruesome hack to deal with scoping of type variables
from a generic patterns. Details commented in the ClassDecl
case of RnSource.rnDecl.
Of course, there are many minor renamer consequences of the
other changes above.
* lib/std/PrelBase.lhs
Data type declarations for Unit, :+:, :*:
Slightly unrelated housekeeping
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* hsSyn/HsDecls:
ClassDecls now carry the Names for their implied declarations
(superclass selectors, tycon, etc) in a list, rather than
laid out one by one. This simplifies code between the parser
and the type checker.
* prelude/PrelNames, TysWiredIn:
All the RdrNames are now together in PrelNames.
* utils/ListSetOps:
Add finite mappings based on equality and association lists (Assoc a b)
Move stuff from List.lhs that is related
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Remove all traces of addr2Integer. Big integer literals are now
done by multiplying up small integers.
* As a result, we can remove PrelNum.hi-boot altogether.
* Correct the default method for (==) in PrelBase. (It simply
returned True, which seems bogus to me!)
* Add a type signature for PrelBase.mapFB
|
|
|
|
|
|
|
|
| |
* Make the desugarer use string equality for string literal
patterns longer than 1 character. And put a specialised
eqString into PrelBase, with a suitable specialisation rule.
This makes a huge difference to the size of the code generated
by deriving(Read) notably in Time.lhs
|
|
|
|
| |
Don't use Int# values larger than 2^31.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Now Char, Char#, StgChar have 31 bits (physically 32).
"foo"# is still an array of bytes.
CharRep represents 32 bits (on a 64-bit arch too). There is also
Int8Rep, used in those places where bytes were originally meant.
readCharArray, indexCharOffAddr etc. still use bytes. Storable and
{I,M}Array use wide Chars.
In future perhaps all sized integers should be primitive types. Then
some usages of indexing primops scattered through the code could
be changed to then-available Int8 ones, and then Char variants of
primops could be made wide (other usages that handle text should use
conversion that will be provided later).
I/O and _ccall_ arguments assume ISO-8859-1. UTF-8 is internally used
for string literals (only).
Z-encoding is ready for Unicode identifiers.
Ranges of intlike and charlike closures are more easily configurable.
I've probably broken nativeGen/MachCode.lhs:chrCode for Alpha but I
don't know the Alpha assembler to fix it (what is zapnot?). Generally
I'm not sure if I've done the NCG changes right.
This commit breaks the binary compatibility (of course).
TODO:
* is* and to{Lower,Upper} in Char (in progress).
* Libraries for text conversion (in design / experiments),
to be plugged to I/O and a higher level foreign library.
* PackedString.
* StringBuffer and accepting source in encodings other than ISO-8859-1.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Many fixes to DLLisation. These were previously covered up because code was
leaking into the import libraries for DLLs, so the fact that some symbols
were thought of as local rather than in another DLL wasn't a problem.
The main problems addressed by this commit are:
1. Fixes RTS symbols working properly when DLLised. They didn't before.
2. Uses NULL instead of stg_error_entry, because DLL entry points can't be
used as static initialisers.
3. PrelGHC.hi-boot changed to be in package RTS, and export of PrelNum and
PrelErr moved to PrelBase, so that references to primops & the like
are cross-DLL as they should be.
4. Pass imports around as Modules rather than ModuleNames, so that
ModuleInitLabels can be checked to see if they're in a DLL or not.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Rearrange exception stuff, as per my message on glasgow-haskell-users
recently.
The main change is the IOError type is now a synonym for Exception.
IO.ioError can therefore be used for throwing exceptions. IO.catch
still catches only IO exceptions, for backwards compatibility.
The interface exported by Exception has changed somewhat:
try :: IO a -> IO (Either Exception a)
tryJust :: (Exception -> Maybe b) -> a -> IO (Either b a)
catch :: IO a -> (Exception -> IO a) -> IO a
catchJust :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a
ioErrors :: Exception -> Maybe IOError
arithExceptions :: Exception -> Maybe ArithException
errorCalls :: Exception -> Maybe String
dynExceptions :: Exception -> Maybe Dynamic
assertions :: Exception -> Maybe String
asyncExceptions :: Exception -> Maybe AsyncException
raiseInThread is now called throwTo.
Where possible, the old functions have been left around, but marked
deprecated.
|
|
|
|
|
|
| |
- fix copyrights
- remove some unused imports
- comment formatting fixes
|
|
|
|
|
|
| |
The n-th attempt to get GCD right, this time negative Int arguments in
combination with zero. Another bug in this area and I'll leap out of
the window immediately... :-P
|
|
|
|
|
|
|
| |
The GCD saga continues: Fixed gcdInt/gcdInteger to work correctly for
non-positive values, i.e. call mpn_gcd_1 only with positive inputs,
and issue an error if both operands are zero. This should fix the bug
reported by Marc.
|
|
|
|
| |
Removed -fcompiling-prelude flag (now removed from compiler)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add support for 'packages'.
* A package is a group of modules.
* A package has a name (e.g. std)
* A package is built into a single library (Unix; e.g. libHSstd.a)
or a single DLL (Windows; e.g. HSstd.dll)
* The '-package-name foo' flag tells GHC that the module being compiled
is destined for package foo.
* The '-package foo' flag tells GHC to make available modules
from package 'foo'. It replaces '-syslib foo' which is now deprecated.
* Cross-package references cost an extra indirection in Windows,
but not Unix
* GHC does not maintain detailed cross-package dependency information.
It does remember which modules in other packages the current module
depends on, but not which things within those imported things.
All of this tidies up the Prelude enormously. The Prelude and
Standard Libraries are built into a singl package called 'std'. (This
is a change; the library is now called libHSstd.a instead of libHS.a)
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
| |
remove instance for CCallable [Char]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit arranges that literal strings will fuse
nicely, by expressing them as an application of build.
* NoRepStr is now completely redundant, though I havn't removed it yet.
* The unpackStr stuff moves from PrelPack to PrelBase.
* There's a new form of Rule, a BuiltinRule, for rules that
can't be expressed in Haskell. The string-fusion rule is one
such. It's defined in prelude/PrelRules.lhs.
* PrelRules.lhs also contains a great deal of code that
implements constant folding. In due course this will replace
ConFold.lhs, but for the moment it simply duplicates it.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
| |
Reduce the number of orphan-instance modules. There are a few left,
but these can't be removed without significant reorganisation due to
recursive dependencies.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
All Simon's recent tuning changes. Rough summary follows:
* Fix Kevin Atkinson's cant-find-instance bug. Turns out that Rename.slurpSourceRefs
needs to repeatedly call getImportedInstDecls, and then go back to slurping
source-refs. Comments with Rename.slurpSourceRefs.
* Add a case to Simplify.mkDupableAlt for the quite-common case where there's
a very simple alternative, in which case there's no point in creating a
join-point binding.
* Fix CoreUtils.exprOkForSpeculation so that it returns True of (==# a# b#).
This lack meant that
case ==# a# b# of { True -> x; False -> x }
was not simplifying
* Make float-out dump bindings at the top of a function argument, as
at the top of a let(rec) rhs. See notes with FloatOut.floatRhs
* Make the ArgOf case of mkDupableAlt generate a OneShot lambda.
This gave a noticeable boost to spectral/boyer2
* Reduce the number of coerces, using worker/wrapper stuff.
The main idea is in WwLib.mkWWcoerce. The gloss is that we must do
the w/w split even for small non-recursive things. See notes with
WorkWrap.tryWw.
* This further complicated getWorkerId, so I finally bit the bullet and
make the workerInfo field of the IdInfo work properly, including
under substitutions. Death to getWorkerId. Kevin Glynn will be happy.
* Make all lambdas over realWorldStatePrimTy
into one-shot lambdas. This is a GROSS HACK.
* Also make the occurrence analyser aware of one-shot lambdas.
* Make various Prelude things into INLINE, so that foldr doesn't
get inlined in their body, so that the caller gets the benefit
of fusion. Notably in PrelArr.lhs.
|
|
|
|
| |
Many small tuning changes
|
|
|
|
| |
Make the default instance for Ord such that it suffices to define <=, as claimed
|
|
|
|
| |
Misc patches from SLPJ.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Simon's Prelude changes
~~~~~~~~~~~~~~~~~~~~~~~
[The real commit preceded this, but had the stupid message "msg_prel"
because I used "cvs commit -m" instead of "cvs commit -F"]
Prelude is split into more modules
new are: PrelEnum, PrelShow, PrelNum
removed: PrelBounded (all in PrelEnum now)
PrelEither (all in PrelMaybe now)
There are also a lot of RULES, of course.
|
|
|
|
| |
../compiler/msg_prel
|
|
|
|
| |
Remove the Show instance for (a->b). It will not be missed..
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|