| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
| |
---------------------
PS: remove ParseUtils
---------------------
I've combined ParseUtils into RdrHsSyn. I could never
figure out which thing was defined in which module, and
they were both short.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------
Implement recursive do-notation
--------------------------------
This commit adds recursive do-notation, which Hugs has had for some time.
mdo { x <- foo y ;
y <- baz x ;
return (y,x) }
turns into
do { (x,y) <- mfix (\~(x,y) -> do { x <- foo y;
y <- baz x }) ;
return (y,x) }
This is all based on work by Levent Erkok and John Lanuchbury.
The really tricky bit is in the renamer (RnExpr.rnMDoStmts) where
we break things up into minimal segments. The rest is easy, including
the type checker.
Levent laid the groundwork, and Simon finished it off. Needless to say,
I couldn't resist tidying up other stuff, so there's no guaranteed I
have not broken something.
|
|
|
|
|
|
|
|
|
|
| |
Fix records with infix constructors (parser/should_compile/read010).
Also tidy up the parser a bit:
- clean up the tycon productions
- check the current s/r conflicts (29) against reality,
and update the comment.
|
|
|
|
| |
Type signatures may only be given for unqualified variables
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------
Make Template Haskell into the HEAD
--------------------------------------
This massive commit transfers to the HEAD all the stuff that
Simon and Tim have been doing on Template Haskell. The
meta-haskell-branch is no more!
WARNING: make sure that you
* Update your links if you are using link trees.
Some modules have been added, some have gone away.
* Do 'make clean' in all library trees.
The interface file format has changed, and you can
get strange panics (sadly) if GHC tries to read old interface files:
e.g. ghc-5.05: panic! (the `impossible' happened, GHC version 5.05):
Binary.get(TyClDecl): ForeignType
* You need to recompile the rts too; Linker.c has changed
However the libraries are almost unaltered; just a tiny change in
Base, and to the exports in Prelude.
NOTE: so far as TH itself is concerned, expression splices work
fine, but declaration splices are not complete.
---------------
The main change
---------------
The main structural change: renaming and typechecking have to be
interleaved, because we can't rename stuff after a declaration splice
until after we've typechecked the stuff before (and the splice
itself).
* Combine the renamer and typecheker monads into one
(TcRnMonad, TcRnTypes)
These two replace TcMonad and RnMonad
* Give them a single 'driver' (TcRnDriver). This driver
replaces TcModule.lhs and Rename.lhs
* The haskell-src library package has a module
Language/Haskell/THSyntax
which defines the Haskell data type seen by the TH programmer.
* New modules:
hsSyn/Convert.hs converts THSyntax -> HsSyn
deSugar/DsMeta.hs converts HsSyn -> THSyntax
* New module typecheck/TcSplice type-checks Template Haskell splices.
-------------
Linking stuff
-------------
* ByteCodeLink has been split into
ByteCodeLink (which links)
ByteCodeAsm (which assembles)
* New module ghci/ObjLink is the object-code linker.
* compMan/CmLink is removed entirely (was out of place)
Ditto CmTypes (which was tiny)
* Linker.c initialises the linker when it is first used (no need to call
initLinker any more). Template Haskell makes it harder to know when
and whether to initialise the linker.
-------------------------------------
Gathering the LIE in the type checker
-------------------------------------
* Instead of explicitly gathering constraints in the LIE
tcExpr :: RenamedExpr -> TcM (TypecheckedExpr, LIE)
we now dump the constraints into a mutable varabiable carried
by the monad, so we get
tcExpr :: RenamedExpr -> TcM TypecheckedExpr
Much less clutter in the code, and more efficient too.
(Originally suggested by Mark Shields.)
-----------------
Remove "SysNames"
-----------------
Because the renamer and the type checker were entirely separate,
we had to carry some rather tiresome implicit binders (or "SysNames")
along inside some of the HsDecl data structures. They were both
tiresome and fragile.
Now that the typechecker and renamer are more intimately coupled,
we can eliminate SysNames (well, mostly... default methods still
carry something similar).
-------------
Clean up HsPat
-------------
One big clean up is this: instead of having two HsPat types (InPat and
OutPat), they are now combined into one. This is more consistent with
the way that HsExpr etc is handled; there are some 'Out' constructors
for the type checker output.
So:
HsPat.InPat --> HsPat.Pat
HsPat.OutPat --> HsPat.Pat
No 'pat' type parameter in HsExpr, HsBinds, etc
Constructor patterns are nicer now: they use
HsPat.HsConDetails
for the three cases of constructor patterns:
prefix, infix, and record-bindings
The *same* data type HsConDetails is used in the type
declaration of the data type (HsDecls.TyData)
Lots of associated clean-up operations here and there. Less code.
Everything is wonderful.
|
|
|
|
|
|
|
|
|
|
|
| |
Fixed handling of infix operators in types:
- Pretty printing didn't take nested infix operators into account
- Explicit parenthesis were ignored in the fixity parser:
* I added a constructor `HsParTy' to `HsType' (in the spirit of `HsPar' in
`HsExpr'), which tracks the use of explicit parenthesis
* Occurences of `HsParTy' in type-ish things that are not quite types (like
context predicates) are removed in `ParseUtils'; all other occurences of
`HsParTy' are removed during type checking (just as it works with `HsPar')
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Make negative literals work in patterns
The issue here is that
f (-1) = True
f x = False
should generate
f x = x == negate (fromInteger 1)
rather than
f x = x == fromInteger (-1)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Allow infix type constructors
This commit adds infix type constructors (but not yet class constructors).
The documentation describes what should be the case. Lots of tiresome
changes, but nothing exciting.
Allows infix type constructors everwhere a type can occur, and in a data
or type synonym decl. E.g.
data a :*: b = ....
You can give fixity decls for type constructors, but the fixity decl
applies both to the tycon and the corresponding data con.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
FastString cleanup, stage 1.
The FastString type is no longer a mixture of hashed strings and
literal strings, it contains hashed strings only with O(1) comparison
(except for UnicodeStr, but that will also go away in due course). To
create a literal instance of FastString, use FSLIT("..").
By far the most common use of the old literal version of FastString
was in the pattern
ptext SLIT("...")
this combination still works, although it doesn't go via FastString
any more. The next stage will be to remove the need to use this
special combination at all, using a RULE.
To convert a FastString into an SDoc, now use 'ftext' instead of
'ptext'.
I've also removed all the FAST_STRING related macros from HsVersions.h
except for SLIT and FSLIT, just use the relevant functions from
FastString instead.
|
|
|
|
|
| |
Throw out OpApp patterns where the operator is not a constructor here,
rather than later in the typechecker(!).
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Remove the interface file parser, and move .hi-boot parsing into the
main parser. The syntax of .hi-boot files is now greatly improved in
terms of readability; here's an example:
module M where
data T
f :: T -> GHC.Base.Int
note that
(a) layout can be used
(b) there's no explcit export list; everything declared
is implicitly exported
(c) Z-encoding of names is no longer required
(d) Any identifier not declared in the current module must
still be quailified with the module which originally
defined it (eg. GHC.Base.Int above).
We'd like to relax (d), but that will come later.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Binary Interface Files - stage 1
--------------------------------
This commit changes the default interface file format from text to
binary, in order to improve compilation performace.
To view an interface file, use 'ghc --show-iface Foo.hi'.
utils/Binary.hs is the basic Binary I/O library, based on the nhc98
binary I/O library but much stripped-down and working in terms of
bytes rather than bits, and with some special features for GHC: it
remembers which Module is being emitted to avoid dumping too many
qualified names, and it keeps track of a "dictionary" of FastStrings
so that we don't dump the same FastString more than once into the
binary file. I'll make a generic version of this for the libraries at
some point.
main/BinIface.hs contains most of the Binary instances. Some
instances are in the same module as the data type (RdrName, Name,
OccName in particular). Most instances were generated using a
modified version of DrIFT, which I'll commit later. However, editing
them by hand isn't hard (certainly easier than modifying
ParseIface.y).
The first thing in a binary interface is the interface version, so
nice error messages will be generated if the binary format changes and
you still have old interfaces lying around. The version also now
includes the "way" as an extra sanity check.
Other changes
-------------
I don't like the way FastStrings contain both hashed strings (with
O(1) comparison) and literal C strings (with O(n) comparison). So as
a first step to separating these I made serveral "literal" type
strings into hashed strings. SLIT() still generates a literal, and
now FSLIT() generates a hashed string. With DEBUG on, you'll get a
warning if you try to compare any SLIT()s with anything, and the
compiler will fall over if you try to dump any literal C strings into
an interface file (usually indicating a use of SLIT() which should be
FSLIT()).
mkSysLocal no longer re-encodes its FastString argument each time it
is called.
I also fixed the -pgm options so that the argument can now optionally
be separted from the option.
Bugfix: PrelNames declared Names for several comparison primops, eg.
eqCharName, eqIntName etc. but these had different uniques from the
real primop names. I've moved these to PrimOps and defined them using
mkPrimOpIdName instead, and deleted some for which we don't have real
primops (Manuel: please check that things still work for you after
this change).
|
|
|
|
| |
Don't translate out negative (boxed) literals too early.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
----------------------------------
Implement kinded type declarations
----------------------------------
This commit allows the programmer to supply kinds in
* data decls
* type decls
* class decls
* 'forall's in types
e.g. data T (x :: *->*) = MkT
type Composer c = forall (x :: * -> *) (y :: * -> *) (z :: * -> *).
(c y z) -> (c x y) -> (c x z);
This is occasionally useful.
It turned out to be convenient to add the form
(type :: kind)
to the syntax of types too, so you can put kind signatures in types as well.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------
Towards kinded data type decls
------------------------------
Move towards being able to have 'kinded' data type decls.
The burden of this commit, though, is to tidy up the parsing
of data type decls. Previously we had
data ctype '=' constrs
where the 'ctype' is a completetely general polymorphic type.
forall a. (Eq a) => T a
Then a separate function checked that it was of a suitably restricted
form. The reason for this is the usual thing --- it's hard to tell
when looking at
data Eq a => T a = ...
whether you are reading the data type or the context when you have
only got as far as 'Eq a'.
However, the 'ctype' trick doesn't work if we want to allow
data T (a :: * -> *) = ...
So we have to parse the data type decl in a more serious way.
That's what this commit does, and it makes the grammar look much nicer.
The main new producion is tycl_hdr.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
*******************************
* Merging from ghc-ndp-branch *
*******************************
This commit merges the current state of the "parallel array extension" and
includes the following:
* (Almost) completed Milestone 1:
- The option `-fparr' activates the H98 extension for parallel arrays.
- These changes have a high likelihood of conflicting (in the CVS sense)
with other changes to GHC and are the reason for merging now.
- ToDo: There are still some (less often used) functions not implemented in
`PrelPArr' and a mechanism is needed to automatically import
`PrelPArr' iff `-fparr' is given. Documentation that should go into
the Commentary is currently in `ghc/compiler/ndpFlatten/TODO'.
* Partial Milestone 2:
- The option `-fflatten' activates the flattening transformation and `-ndp'
selects the "ndp" way (where all libraries have to be compiled with
flattening). The way option `-ndp' automagically turns on `-fparr' and
`-fflatten'.
- Almost all changes are in the new directory `ndpFlatten' and shouldn't
affect the rest of the compiler. The only exception are the options and
the points in `HscMain' where the flattening phase is called when
`-fflatten' is given.
- This isn't usable yet, but already implements function lifting,
vectorisation, and a new analysis that determines which parts of a module
have to undergo the flattening transformation. Missing are data structure
and function specialisation, the unboxed array library (including fusion
rules), and lots of testing.
I have just run the regression tests on the thing without any problems. So,
it seems, as if we haven't broken anything crucial.
|
|
|
|
|
|
|
|
| |
Tighten up syntax w.r.t. Haskell 98; this is disallowed:
(a `op` b) = ...
since a parenthesised lhs must be followed by at least one parameter.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Foreign import/export declarations now conform to FFI Addendum Version 1.0
* The old form of foreign declarations is still supported, but generates
deprecation warnings.
* There are some rather exotic old-style declarations which have become
invalid as they are interpreted differently under the new scheme and there
is no (easy) way to determine which style the programmer had in mind (eg,
importing a C function with the name `wrapper' where the external name is
explicitly given will not work in some situations - depends on whether an
`unsafe' was specified and similar things).
* Some "new" old-style forms have been introduced to make parsing a little bit
easier (ie, avoid shift/reduce conflicts between new-style and old-style
grammar rules), but they are few, arcane, and don't really hurt (and I won't
tell what they are, you need to find that out by yourself ;-)
* The FFI Addendum doesn't specify whether a header file that is requested for
inclusion by multiple foreign declarations should be included only once or
multiple times. GHC at the moment includes an header as often as it appears
in a foreign declaration. For properly written headers, it doesn't make a
difference anyway...
* Library object specifications are currently silently ignored. The feature
was mainly requested for external calls in .NET (ie, calls which invoke C
routines when Haskell is compiled to ILX), but those don't seem to be
supported yet.
* Foreign label declarations are currently broken, but they were already
broken before I started messing with the stuff.
The code is moderately tested. All modules in lib/std/ and hslibs/lang/
(using old-style declarations) still compile fine and I have run a couple of
tests on the different forms of new-style declarations.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
---------------------------------------------
More type system extensions (for John Hughes)
---------------------------------------------
1. Added a brand-new extension that lets you derive ARBITRARY CLASSES
for newtypes. Thus
newtype Age = Age Int deriving( Eq, Ord, Shape, Ix )
The idea is that the dictionary for the user-defined class Shape Age
is *identical* to that for Shape Int, so there is really no deriving
work to do. This saves you writing the very tiresome instance decl:
instance Shape Age where
shape_op1 (Age x) = shape_op1 x
shape_op2 (Age x1) (Age x2) = shape_op2 x1 x2
...etc...
It's more efficient, too, becuase the Shape Age dictionary really
will be identical to the Shape Int dictionary.
There's an exception for Read and Show, because the derived instance
*isn't* the same.
There is a complication where higher order stuff is involved. Here is
the example John gave:
class StateMonad s m | m -> s where ...
newtype Parser tok m a = Parser (State [tok] (Failure m) a)
deriving( Monad, StateMonad )
Then we want the derived instance decls to be
instance Monad (State [tok] (Failure m)) => Monad (Parser tok m)
instance StateMonad [tok] (State [tok] (Failure m))
=> StateMonad [tok] (Parser tok m)
John is writing up manual entry for all of this, but this commit
implements it. I think.
2. Added -fallow-incoherent-instances, and documented it. The idea
is that sometimes GHC is over-protective about not committing to a
particular instance, and the programmer may want to say "commit anyway".
Here's the example:
class Sat a where
dict :: a
data EqD a = EqD {eq :: a->a->Bool}
instance Sat (EqD a) => Eq a where
(==) = eq dict
instance Sat (EqD Integer) where
dict = EqD{eq=(==)}
instance Eq a => Sat (EqD a) where
dict = EqD{eq=(==)}
class Collection c cxt | c -> cxt where
empty :: Sat (cxt a) => c a
single :: Sat (cxt a) => a -> c a
union :: Sat (cxt a) => c a -> c a -> c a
member :: Sat (cxt a) => a -> c a -> Bool
instance Collection [] EqD where
empty = []
single x = [x]
union = (++)
member = elem
It's an updated attempt to model "Restricted Data Types", if you
remember my Haskell workshop paper. In the end, though, GHC rejects
the program (even with fallow-overlapping-instances and
fallow-undecideable-instances), because there's more than one way to
construct the Eq instance needed by elem.
Yet all the ways are equivalent! So GHC is being a bit over-protective
of me, really: I know what I'm doing and I would LIKE it to pick an
arbitrary one. Maybe a flag fallow-incoherent-instances would be a
useful thing to add?
|
|
|
|
| |
Improve error reporting
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------------
Improved handling of scoped type variables
------------------------------------------
The main effect of this commit is to allow scoped type variables
in pattern bindings, thus
(x::a, y::b) = e
This was illegal, but now it's ok. a and b have the same scope
as x and y.
On the way I beefed up the info inside a type variable
(TcType.TyVarDetails; c.f. IdInfo.GlobalIdDetails) which
helps to improve error messages. Hence the wide ranging changes.
Pity about the extra loop from Var to TcType, but can't be helped.
|
|
|
|
|
|
|
|
|
|
|
| |
Add support for Hugs's :info command. Doesn't work yet, but shouldn't
interfere with anything else. Some of the files touched are just to correct
out-of-date comments.
Highlights are:
hscThing: like hscStmt, but just gets info about a single identifier
cmInfoThing: exposes hscThing's functionality to the outside world
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------
Tidy up the "syntax rebinding" story
------------------------------------
I found a bug in the code that dealt with re-binding implicit
numerical syntax:
literals (fromInteger/fromRational)
negation (negate)
n+k patterns (minus)
This is triggered by the -fno-implicit-prelude flag, and it
used to be handled via the PrelNames.SyntaxMap.
But I found a nicer way to do it that involves much less code,
and doesn't have the bug. The explanation is with
RnEnv.lookupSyntaxName
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------------
Fix another bug in the squash-newtypes story.
--------------------------------------------
[This one was spotted by Marcin, and is now enshrined in test tc130.]
The desugarer straddles the boundary between the type checker and
Core, so it sometimes needs to look through newtypes/implicit parameters
and sometimes not. This is really a bit painful, but I can't think of
a better way to do it.
The only simple way to fix things was to pass a bit more type
information in the HsExpr type, from the type checker to the desugarer.
That led to the non-local changes you can see.
On the way I fixed one other thing. In various HsSyn constructors
there is a Type that is bogus (bottom) before the type checker, and
filled in with a real type by the type checker. In one place it was
a (Maybe Type) which was Nothing before, and (Just ty) afterwards.
I've defined a type synonym HsTypes.PostTcType for this, and a named
bottom value HsTypes.placeHolderType to use when you want the bottom
value.
|
|
|
|
| |
Correct spelling in error message
|
|
|
|
| |
Import wibbles
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------------------------
More stuff towards generalising 'foreign' declarations
------------------------------------------------------
This is the second step towards generalising 'foreign' declarations to
handle langauges other than C. Now I can handle
foreign import dotnet type T
foreign import dotnet "void Foo.Baz.f( T )" f :: T -> IO ()
** WARNING **
I believe that all the foreign stuff for C should
work exactly as before, but I have not tested it
thoroughly. Sven, Manuel, Marcin: please give it a
whirl and compare old with new output.
Lots of fiddling around with data types. The main changes are
* HsDecls.lhs
The ForeignDecl type and its friends
Note also the ForeignType constructor to TyClDecl
* ForeignCall.lhs
Here's where the stuff that survives right through
compilation lives
* TcForeign.lhs DsForeign.lhs
Substantial changes driven by the new data types
* Parser.y ParseIface.y RnSource
Just what you'd expect
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-------------------------------------------
Towards generalising 'foreign' declarations
-------------------------------------------
This is a first step towards generalising 'foreign' declarations to
handle langauges other than C. Quite a lot of files are touched,
but nothing has really changed. Everything should work exactly as
before.
But please be on your guard for ccall-related bugs.
Main things
Basic data types: ForeignCall.lhs
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Remove absCSyn/CallConv.lhs
* Add prelude/ForeignCall.lhs. This defines the ForeignCall
type and its variants
* Define ForeignCall.Safety to say whether a call is unsafe
or not (was just a boolean). Lots of consequential chuffing.
* Remove all CCall stuff from PrimOp, and put it in ForeignCall
Take CCallOp out of the PrimOp type (where it was always a glitch)
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Add IdInfo.FCallId variant to the type IdInfo.GlobalIdDetails,
along with predicates Id.isFCallId, Id.isFCallId_maybe
* Add StgSyn.StgOp, to sum PrimOp with FCallOp, because it
*is* useful to sum them together in Stg and AbsC land. If
nothing else, it minimises changes.
Also generally rename "CCall" stuff to "FCall" where it's generic
to all foreign calls.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
-----------------------------
Get unbox-strict-fields right
-----------------------------
The problem was that when a library was compiled *without* -funbox-strict-fields,
and the main program was compiled *with* that flag, we were wrongly treating
the fields of imported data types as unboxed.
To fix this I added an extra constructor to StrictnessMark to express whether
the "!" annotation came from an interface file (don't fiddle) or a source
file (decide whether to unbox).
On the way I tided things up:
* StrictnessMark moves to Demand.lhs, and doesn't have the extra DataCon
fields that kept it in DataCon before.
* HsDecls.BangType has one constructor, not three, with a StrictnessMark field.
* DataCon keeps track of its strictness signature (dcRepStrictness), but not
its "user strict marks" (which were never used)
* All the functions, like getUniquesDs, that used to take an Int saying how
many uniques to allocate, now return an infinite list. This saves arguments
and hassle. But it involved touching quite a few files.
* rebuildConArgs takes a list of Uniques to use as its unique supply. This
means I could combine DsUtils.rebuildConArgs with MkId.rebuildConArgs
(hooray; the main point of the previous change)
I also tidied up one or two error messages
|
|
|
|
| |
Fix yesterdays bogons in parsing do-expressions; MERGE IN BRANCH
|
|
|
|
| |
Give slightly more accurate line numbers for certain pattern parse errors.
|
|
|
|
| |
Eh hem... Wibble.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fix for infix decl w/ infix data constructor.
GHC was rejecting this:
infix 2 |-
ps |- q:qs = undefined
It parses the def as ((ps |- q) : qs), and doesn't have the fixity info
around at the point where it decides what is being defined. Lacking
anything else to go on, it decides that `:' is being defined.
Fortunately, we don't really need fixity info to parse this correctly,
as a data constructor is always the wrong choice ;-) The fix is to
dive into the left-hand-side until we find a non-data constructor.
This is naive - consider the case where `|-' has a high precedence.
Fortunately, someone clever put in a static check later on, presumably
at the point where we have all the fixity info, that rejects the definition
as bogus. Yeah!
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
----------------
Nuke ClassContext
----------------
This commit tidies up a long-standing inconsistency in GHC.
The context of a class or instance decl used to be restricted
to predicates of the form
C t1 .. tn
with
type ClassContext = [(Class,[Type])]
but everywhere else in the compiler we used
type ThetaType = [PredType]
where PredType can be any sort of constraint (= predicate).
The inconsistency actually led to a crash, when compiling
class (?x::Int) => C a where {}
I've tidied all this up by nuking ClassContext altogether, and using
PredType throughout. Lots of modified files, but all in
more-or-less trivial ways.
I've also added a check that the context of a class or instance
decl doesn't include a non-inheritable predicate like (?x::Int).
Other things
* rename constructor 'Class' from type TypeRep.Pred to 'ClassP'
(makes it easier to grep for)
* rename constructor HsPClass => HsClassP
HsPIParam => HsIParam
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Implement do-style bindings on the GHCi command line.
The syntax for a command-line is exactly that of a do statement, with
the following meanings:
- `pat <- expr'
performs expr, and binds each of the variables in pat.
- `let pat = expr; ...'
binds each of the variables in pat, doesn't do any evaluation
- `expr'
behaves as `it <- expr' if expr is IO-typed, or `let it = expr'
followed by `print it' otherwise.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Decoupling the Prelude [HsExpr, HsLit, HsPat, ParseUtil, Parser.y, PrelNames,
~~~~~~~~~~~~~~~~~~~~~~ Rename, RnEnv, RnExpr, RnHsSyn, Inst, TcEnv, TcMonad,
TcPat, TcExpr]
The -fno-implicit-prelude flag is meant to arrange that when you write
3
you get
fromInt 3
where 'fromInt' is whatever fromInt is in scope at the top level of
the module being compiled. Similarly for
* numeric patterns
* n+k patterns
* negation
This used to work, but broke when we made the static/dynamic flag distinction.
It's now tidied up a lot. Here's the plan:
- PrelNames contains sugarList :: SugarList, which maps built-in names
to the RdrName that should replace them.
- The renamer makes a finite map :: SugarMap, which maps the built-in names
to the Name of the re-mapped thing
- The typechecker consults this map via tcLookupSyntaxId when it is doing
numeric things
At present I've only decoupled numeric syntax, since that is the main demand,
but the scheme is much more robustly extensible than the previous method.
As a result some HsSyn constructors don't need to carry names in them
(notably HsOverLit, NegApp, NPlusKPatIn)
|
|
|
|
| |
Improve a parser error message.
|
|
|
|
| |
PrelBase compiles!
|
|
|
|
| |
Rename a bunch of mkSrc* things into mk*'s.
|
|
|
|
| |
Parser changes to support type constructor operators; part of the generics stuff
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------
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
|
|
|
|
| |
Wibbles
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
------------------------------------
Mainly PredTypes (28 Sept 00)
------------------------------------
Three things in this commit:
1. Main thing: tidy up PredTypes
2. Move all Keys into PrelNames
3. Check for unboxed tuples in function args
1. Tidy up PredTypes
~~~~~~~~~~~~~~~~~~~~
The main thing in this commit is to modify the representation of Types
so that they are a (much) better for the qualified-type world. This
should simplify Jeff's life as he proceeds with implicit parameters
and functional dependencies. In particular, PredType, introduced by
Jeff, is now blessed and dignified with a place in TypeRep.lhs:
data PredType = Class Class [Type]
| IParam Name Type
Consider these examples:
f :: (Eq a) => a -> Int
g :: (?x :: Int -> Int) => a -> Int
h :: (r\l) => {r} => {l::Int | r}
Here the "Eq a" and "?x :: Int -> Int" and "r\l" are all called
*predicates*, and are represented by a PredType. (We don't support
TREX records yet, but the setup is designed to expand to allow them.)
In addition, Type gains an extra constructor:
data Type = .... | PredTy PredType
so that PredType is injected directly into Type. So the type
p => t
is represented by
PredType p `FunTy` t
I have deleted the hackish IPNote stuff; predicates are dealt with entirely
through PredTys, not through NoteTy at all.
2. Move Keys into PrelNames
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
This is just a housekeeping operation. I've moved all the pre-assigned Uniques
(aka Keys) from Unique.lhs into PrelNames.lhs. I've also moved knowKeyRdrNames
from PrelInfo down into PrelNames. This localises in PrelNames lots of stuff
about predefined names. Previously one had to alter three files to add one,
now only one.
3. Unboxed tuples
~~~~~~~~~~~~~~~~~~
Add a static check for unboxed tuple arguments. E.g.
data T = T (# Int, Int #)
is illegal
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
--------------------------------------------------
Tidying up HsLit, and making it possible to define
your own numeric library
Simon PJ 22 Sept 00
--------------------------------------------------
** NOTE: I did these changes on the aeroplane. They should compile,
and the Prelude still compiles OK, but it's entirely
possible that I've broken something
The original reason for this many-file but rather shallow
commit is that it's impossible in Haskell to write your own
numeric library. Why? Because when you say '1' you get
(Prelude.fromInteger 1), regardless of what you hide from the
Prelude, or import from other libraries you have written. So the
idea is to extend the -fno-implicit-prelude flag so that
in addition to no importing the Prelude, you can rebind
fromInteger -- Applied to literal constants
fromRational -- Ditto
negate -- Invoked by the syntax (-x)
the (-) used when desugaring n+k patterns
After toying with other designs, I eventually settled on a simple,
crude one: rather than adding a new flag, I just extended the
semantics of -fno-implicit-prelude so that uses of fromInteger,
fromRational and negate are all bound to "whatever is in scope"
rather than "the fixed Prelude functions". So if you say
{-# OPTIONS -fno-implicit-prelude #-}
module M where
import MyPrelude( fromInteger )
x = 3
the literal 3 will use whatever (unqualified) "fromInteger" is in scope,
in this case the one gotten from MyPrelude.
On the way, though, I studied how HsLit worked, and did a substantial tidy
up, deleting quite a lot of code along the way. In particular.
* HsBasic.lhs is renamed HsLit.lhs. It defines the HsLit type.
* There are now two HsLit types, both defined in HsLit.
HsLit for non-overloaded literals (like 'x')
HsOverLit for overloaded literals (like 1 and 2.3)
* HsOverLit completely replaces Inst.OverloadedLit, which disappears.
An HsExpr can now be an HsOverLit as well as an HsLit.
* HsOverLit carries the Name of the fromInteger/fromRational operation,
so that the renamer can help with looking up the unqualified name
when -fno-implicit-prelude is on. Ditto the HsExpr for negation.
It's all very tidy now.
* RdrHsSyn contains the stuff that handles -fno-implicit-prelude
(see esp RdrHsSyn.prelQual). RdrHsSyn also contains all the "smart constructors"
used by the parser when building HsSyn. See for example RdrHsSyn.mkNegApp
(previously the renamer (!) did the business of turning (- 3#) into -3#).
* I tidied up the handling of "special ids" in the parser. There's much
less duplication now.
* Move Sven's Horner stuff to the desugarer, where it belongs.
There's now a nice function DsUtils.mkIntegerLit which brings together
related code from no fewer than three separate places into one single
place. Nice!
* A nice tidy-up in MatchLit.partitionEqnsByLit became possible.
* Desugaring of HsLits is now much tidier (DsExpr.dsLit)
* Some stuff to do with RdrNames is moved from ParseUtil.lhs to RdrHsSyn.lhs,
which is where it really belongs.
* I also removed
many unnecessary imports from modules
quite a bit of dead code
in divers places
|
|
|
|
|
|
|
|
| |
The parser didn't properly check that the constructor in a data
declaration really are constructors (ie. begin with an upper case
character). This patch fixes the problem.
bug reported by: Tim Giesler, a couple of weeks ago.
|
|
|
|
| |
remove unused imports
|
|
|
|
|
| |
Don't group variable bindings with the same name together. They
should be flagged as duplicate definitions.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
~~~~~~~~~~~~
Apr/May 2000
~~~~~~~~~~~~
This is a pretty big commit! It adds stuff I've been working on
over the last month or so. DO NOT MERGE IT WITH 4.07!
Interface file formats have changed a little; you'll need
to make clean before remaking.
Simon PJ
Recompilation checking
~~~~~~~~~~~~~~~~~~~~~~
Substantial improvement in recompilation checking. The version management
is now entirely internal to GHC. ghc-iface.lprl is dead!
The trick is to generate the new interface file in two steps:
- first convert Types etc to HsTypes etc, and thereby
build a new ParsedIface
- then compare against the parsed (but not renamed) version of the old
interface file
Doing this meant adding code to convert *to* HsSyn things, and to
compare HsSyn things for equality. That is the main tedious bit.
Another improvement is that we now track version info for
fixities and rules, which was missing before.
Interface file reading
~~~~~~~~~~~~~~~~~~~~~~
Make interface files reading more robust.
* If the old interface file is unreadable, don't fail. [bug fix]
* If the old interface file mentions interfaces
that are unreadable, don't fail. [bug fix]
* When we can't find the interface file,
print the directories we are looking in. [feature]
Type signatures
~~~~~~~~~~~~~~~
* New flag -ddump-types to print type signatures
Type pruning
~~~~~~~~~~~~
When importing
data T = T1 A | T2 B | T3 C
it seems excessive to import the types A, B, C as well, unless
the constructors T1, T2 etc are used. A,B,C might be more types,
and importing them may mean reading more interfaces, and so on.
So the idea is that the renamer will just import the decl
data T
unless one of the constructors is used. This turns out to be quite
easy to implement. The downside is that we must make sure the
constructors are always available if they are really needed, so
I regard this as an experimental feature.
Elimininate ThinAir names
~~~~~~~~~~~~~~~~~~~~~~~~~
Eliminate ThinAir.lhs and all its works. It was always a hack, and now
the desugarer carries around an environment I think we can nuke ThinAir
altogether.
As part of this, I had to move all the Prelude RdrName defns from PrelInfo
to PrelMods --- so I renamed PrelMods as PrelNames.
I also had to move the builtinRules so that they are injected by the renamer
(rather than appearing out of the blue in SimplCore). This is if anything simpler.
Miscellaneous
~~~~~~~~~~~~~
* Tidy up the data types involved in Rules
* Eliminate RnEnv.better_provenance; use Name.hasBetterProv instead
* Add Unique.hasKey :: Uniquable a => a -> Unique -> Bool
It's useful in a lot of places
* Fix a bug in interface file parsing for __U[!]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
*** MERGE WITH 4.07 (once I've checked it works) ***
* Fix result type signatures. Note that a consequential change is that
an ordinary binding with a variable on the left
f = e
is now treated as a FunMonoBind, not a PatMonoBind. This makes
a few things a bit simpler (eg rnMethodBinds)
* Fix warnings for unused imports. This meant moving where provenances
are improved in RnNames. Move mkExportAvails from RnEnv to RnNames.
* Print module names right (small change in Module.lhs and Rename.lhs)
* Remove a few unused bindings
* Add a little hack to let us print info about join points that turn
out not to be let-no-escaped. The idea is to call them "$j" and report
any such variables that are not let-no-escaped.
* Some small things aiming towards -ddump-types (harmless but incomplete)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|