- 12 Mar, 2001 2 commits
-
-
simonpj authored
---------------- First cut at ILX ---------------- This commit puts the ILX .NET code generator into the head. It's entirely untested, mind you. Some changes to the Module/Package strutures, mainly of a naming variety. In particular: Package ===> PackageConfig
-
simonpj authored
Remove -funfolding-interface-threshold
-
- 09 Mar, 2001 1 commit
-
-
simonmar authored
infix declarations for unknown identifiers aren't allowed (contrary to what GHC thinks).
-
- 08 Mar, 2001 9 commits
-
-
qrczak authored
s/setIdGlobalDetails/sedGlobalIdDetails/, and import it.
-
qrczak authored
Fix names imported from Id.
-
simonmar authored
add expected output
-
simonmar authored
update for blocking putMVar
-
simonpj authored
Add NameEnv!
-
simonpj authored
-------------------- A major hygiene pass -------------------- 1. The main change here is to Move what was the "IdFlavour" out of IdInfo, and into the varDetails field of a Var It was a mess before, because the flavour was a permanent attribute of an Id, whereas the rest of the IdInfo was ephemeral. It's all much tidier now. Main places to look: Var.lhs Defn of VarDetails IdInfo.lhs Defn of GlobalIdDetails The main remaining infelicity is that SpecPragmaIds are right down in Var.lhs, which seems unduly built-in for such an ephemeral thing. But that is no worse than before. 2. Tidy up the HscMain story a little. Move mkModDetails from MkIface into CoreTidy (where it belongs more nicely) This was partly forced by (1) above, because I didn't want to make DictFun Ids into a separate kind of Id (which is how it was before). Not having them separate means we have to keep a list of them right through, rather than pull them out of the bindings at the end. 3. Add NameEnv as a separate module (to join NameSet). 4. Remove unnecessary {-# SOURCE #-} imports from FieldLabel.
-
simonpj authored
------------------------- Remove function coercions ------------------------- (coerce (T1->T2) (S1->S2) F) E ===> coerce T2 S2 (F (coerce S1 T1 E)) This is a generally good transformation, but it still doesn't solve the problem I was after. Consider newtype T = MkT (Int -> Int) p :: T->T; p = ... q :: T; q = ... foo :: T {-# INLINE foo #-} foo = p $ q f = \y -> ...((coerce (Int->Int) foo) 3)... Trouble is, foo doesn't see the argument because of the coerce, so it thinks it's a lone variable and doesn't inline. Another problem is that since $ ins't inlined into foo's RHS, foo looks like a redex, which we are reluctant to inline inside a lambda, even with an INLINE pragma. Maybe we should be bolder? Anyway, this commit is an improvement to Simplify, but the story is not over!
-
simonmar authored
remove cyclic dependency
-
simonmar authored
rearrange slightly to make this compile again.
-
- 07 Mar, 2001 5 commits
-
-
sewardj authored
Driver and infrastructure files (.T's) for the new test framework.
-
simonpj authored
Remove DOS Ctrl-Ms
-
rrt authored
Import v_TmpDir.
-
rrt authored
On mingwin, remove CRs from input file, to prevent problems when reading from unmounted partitions. (This shouldn't be a problem, but it is; this fix makes the mangler a bit more robust anyway.)
-
rrt authored
Make Windows path mangling of FPTOOLS_TOP_ABS work.
-
- 06 Mar, 2001 6 commits
-
-
simonmar authored
undo accidental change
-
simonmar authored
changes to build new ParsePkgConf module
-
rrt authored
Use TMPDIR, not /tmp.
-
simonmar authored
- Add a Happy parser for the package config file. This is faster and compiles to less code than the derived Read instance we had before. - Add a source_dirs field to the package spec. This isn't used by GHC, because we currently assume all packages are compiled. It could be used by Hugs, though. - Make unspecified fields of type [String] default to the empty list in a package spec.
-
simonmar authored
import wibbles
-
simonpj authored
Fix minor bug in SpecConstr; failed to deal with DEFAULT case
-
- 05 Mar, 2001 12 commits
-
-
simonpj authored
Exploit the 1-shot lambda HACK in etaExpandArity We often find code like f :: Int -> IO () f = \ x -> case ... of p1 -> \s -> ...rhs1... p2 -> \s -> ...rhs2... where the \s is a state transformer lambda. Almost invariably these \s things are one-shot; that is, we virtually never say let h = f 3 in h >> h >> h In this case we'd be much better off eta-expanding f, to f :: Int -> IO () f = \ x \ s -> case ... of p1 -> ...rhs1... p2 -> ...rhs2... GHC already has a MAJOR HACK in Id.isOneShotLambda which declares that any \s::State# T is a one-shot lambda. It's almost always true, and it makes a big difference. This commit simply makes use of isOneShotLambda to improve the results of CoreUtils.etaExpandArity. Which has the desired effect. There isn't a flag to control the MAJOR HACK yet. Maybe there should be. Anyway, some of Manuel's array code should improve a lot.
-
simonpj authored
Print debug uniques consistently in base64
-
simonpj authored
Improve SpecConstr This commit fixes SpecConstr so that it can see the effect of enclosing case expressions properly. That's what the "cons" field in ScEnv is for. As a result, consider this function: data AccessPath = Cont AccessPath | Value Int demandAll n ap@(Cont (Value (I# i1))) = case n of 0 -> i1 other -> i1 +# demandAll (n-1) ap SpecConstr now successfully compiles it to this: $s$wdemandAll = \ i1 :: PrelGHC.Int# sc :: PrelGHC.Int# -> case sc of ds { 0 -> i1; __DEFAULT -> PrelGHC.+# i1 (Foo.$s$wdemandAll i1 (PrelGHC.-# ds 1)) } with the rule "SC:$wdemandAll1" __forall i1 :: PrelGHC.Int# , sc :: PrelGHC.Int# . Foo.$wdemandAll sc (Foo.$wCont (Foo.$wValue (PrelBase.$wI# i1))) = Foo.$s$wdemandAll i1 sc ;
-
simonpj authored
Better dump of transformation rules
-
simonpj authored
Remove debug trace
-
simonpj authored
Make error message more helpful
-
simonpj authored
Remove dead isSysOcc
-
simonpj authored
Add a test that Hugs-Feb-2001 fails
-
simonmar authored
remove cruft
-
simonmar authored
small rearrangement
-
simonmar authored
fix -fgenerics
-
qrczak authored
Use custom parser monad instead of Parsec. It remembers the text which has been parsed, so it needs not to be reconstructed after parsing. Operators containing '--' are now handled correctly. '#' triggers special processing only if it's not a part of an operator, i.e. if a varsym token is exactly a single '#'. Backslash-newline pairs in C lexical world are now handled correctly (removed at an early stage). Option --keep replaced with --no-compile (stop after writing *.hs_make.c).
-
- 04 Mar, 2001 2 commits
- 03 Mar, 2001 1 commit
-
-
chak authored
Slightly more compact ppr for Core (makes it easier to read large functions).
-
- 02 Mar, 2001 2 commits
-
-
simonmar authored
Fix :type again, by resurrecting typecheckExpr. Now the expression doesn't get the monomorphism restriction applied to it.
-
simonmar authored
ASSERT in updateWithIndirection() that we haven't already updated this object with an indirection, and fix two places in the RTS where this could happen. The problem only occurs when we're in a black-hole-style loop, and there are multiple update frames on the stack pointing to the same object (this is possible because of lazy black-holing). Both stack squeezing and asynchronous exception raising walk down the stack and remove update frames, updating their contents with indirections. If we don't protect against multiple updates, the mutable list in the old generation may get into a bogus state.
-