- 07 May, 2003 1 commit
-
-
simonpj authored
Print type of data constructors correctly in GHCi
-
- 08 Apr, 2003 1 commit
-
-
simonpj authored
ToDo comments
-
- 03 Mar, 2003 1 commit
-
-
simonmar authored
A round of space-leak fixing. - re-instate zapping of the PersistentCompilerState at various points during the compilation cycle in HscMain. This affects one-shot compilation only, since in this mode the information collected in the PCS is not required after creating the final interface file. - Unravel the recursive dependency between MkIface and CoreTidy/CoreToStg. Previously the CafInfo for each binding was calculated by CoreToStg, and fed back into the IdInfo of the Ids generated by CoreTidy (an earlier pass). MkIface then took this IdInfo and the bindings from CoreTidy to generate the interface; but it couldn't do this until *after* CoreToStg, because the CafInfo hadn't been calculated yet. The result was that the CoreTidy output lived until after CoreToStg, and at the same time as the CorePrep and STG syntax, which is wasted space, not to mention the complexity and general ugliness in HscMain. So now we calculate CafInfo directly in CoreTidy. The downside is that we have to predict what CorePrep is going to do to the bindings so we can tell what will turn into a CAF later, but it's no worse than before (it turned out that we were doing this prediction before in CoreToStg anyhow). - The typechecker lazilly typechecks unfoldings. It turns out that this is a good idea from a performance perspective, but it also means that it must hang on to all the information it needs to do the typechecking. Previously this meant holding on to the whole of the typechecker's environment, which includes all sorts of stuff which isn't necessary to typecheck unfoldings. By paring down the environment captured by the lazy unfoldings, we can save quite a bit of space in the phases after typechecking.
-
- 21 Feb, 2003 1 commit
-
-
simonpj authored
Import pruning, use mingw32_TARGET not HOST, use old-style foreign import (for 4.08 compat)
-
- 20 Feb, 2003 1 commit
-
-
simonpj authored
Another datacon-naming wibble
-
- 12 Feb, 2003 1 commit
-
-
simonpj authored
------------------------------------- Big upheaval to the way that constructors are named ------------------------------------- This commit enshrines the new story for constructor names. We could never really get External Core to work nicely before, but now it does. The story is laid out in detail in the Commentary ghc/docs/comm/the-beast/data-types.html so I will not repeat it here. [Manuel: the commentary isn't being updated, apparently.] However, the net effect is that in Core and in External Core, contructors look like constructors, and the way things are printed is all consistent. It is a fairly pervasive change (which is why it has been so long postponed), but I hope the question is now finally closed. All the libraries compile etc, and I've run many tests, but doubtless there will be some dark corners.
-
- 13 Jan, 2003 1 commit
-
-
simonpj authored
------------------------------------ (a) Improve reporting of staging errors (b) Tidy up the construction of dict funs and default methods ------------------------------------
-
- 06 Jan, 2003 1 commit
-
-
simonmar authored
Disable the version check on the .hi file for --show-iface. This means that it can be used on .hi files for other "ways" (eg. profiled) without having to resort to using the undocumented -buildtag option.
-
- 21 Nov, 2002 1 commit
-
-
simonpj authored
import trimming
-
- 18 Nov, 2002 1 commit
-
-
simonpj authored
---------------------------------------- Class ops that do not introduce for-alls ---------------------------------------- MERGE TO STABLE (if poss) The handling of class ops that do not add an extra for-all was utterly bogus. For example: class C a where fc :: (?p :: String) => a; class D a where fd :: (Ord a) => [a] -> [a] De-bogus-ing means a) Being careful when taking apart the class op type in MkIface.tcClassOpSig b) Ditto when making the method Id in an instance binding. Hence new function Inst.tcInstClassOp, and its calls in TcInstDcls, and TcClassDcls
-
- 25 Oct, 2002 1 commit
-
-
simonpj authored
------------------------ More dependency fiddling ------------------------ WARNING: Interface file format has changed (again) You need to 'make clean' in all library code * Orphan modules are now kept separately Home-package dependencies now contain only home-package dependencies! See HscTypes.Dependencies * Linker now uses the dependencies to do dynamic linking Result: Template Haskell should work even without --make (not yet tested)
-
- 24 Oct, 2002 2 commits
-
-
simonpj authored
Uh oh; got the versioning stuff a bit wrong in the last commit
-
simonpj authored
------------------------------------------ 1. New try and module and package dependencies 2. OrigNameCache always contains final info ------------------------------------------ These things nearly complete sorting out the incremental linking problem that started us off! 1. This commit separates two kinds of information: (a) HscTypes.Dependencies: What (i) home-package modules, and (ii) other packages this module depends on, transitively. That is, to link the module, it should be enough to link the dependent modules and packages (plus any C stubs etc). Along with this info we record whether the dependent module is (a) a boot interface or (b) an orphan module. So in fact (i) can contain non-home-package modules, namely the orphan ones in other packages (sigh). (b) HscTypes.Usage: What version of imported things were used to actually compile the module. This info is used for recompilation control only. 2. The Finder now returns a correct Module (incl package indicator) first time, so we can install the absolutely final Name in the OrigNameCache when we first come across an occurrence of that name, even if it's only an occurrence in an unfolding in some other interface file. This is much tidier. As a result Module.lhs is much cleaner No DunnoYet No mkVanillaModule ALl very joyful stuff.
-
- 27 Sep, 2002 1 commit
-
-
simonpj authored
-------------------------------- 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.
-
- 13 Sep, 2002 1 commit
-
-
simonpj authored
-------------------------------------- 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.
-
- 29 Apr, 2002 1 commit
-
-
simonmar authored
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.
-
- 01 Apr, 2002 1 commit
-
-
simonpj authored
------------------------------------ Change the treatment of the stupid context on data constructors ----------------------------------- Data types can have a context: data (Eq a, Ord b) => T a b = T1 a b | T2 a and that makes the constructors have a context too (notice that T2's context is "thinned"): T1 :: (Eq a, Ord b) => a -> b -> T a b T2 :: (Eq a) => a -> T a b Furthermore, this context pops up when pattern matching (though GHC hasn't implemented this, but it is in H98, and I've fixed GHC so that it now does): f (T2 x) = x gets inferred type f :: Eq a => T a b -> a I say the context is "stupid" because the dictionaries passed are immediately discarded -- they do nothing and have no benefit. It's a flaw in the language. Up to now I have put this stupid context into the type of the "wrapper" constructors functions, T1 and T2, but that turned out to be jolly inconvenient for generics, and record update, and other functions that build values of type T (because they don't have suitable dictionaries available). So now I've taken the stupid context out. I simply deal with it separately in the type checker on occurrences of a constructor, either in an expression or in a pattern. To this end * Lots of changes in DataCon, MkId * New function Inst.tcInstDataCon to instantiate a data constructor I also took the opportunity to * Rename dataConId --> dataConWorkId for consistency. * Tidied up MkId.rebuildConArgs quite a bit, and renamed it mkReboxingAlt * Add function DataCon.dataConExistentialTyVars, with the obvious meaning
-
- 25 Mar, 2002 1 commit
-
-
simonpj authored
imports
-
- 18 Mar, 2002 1 commit
-
-
simonpj authored
Tidier printing routines for Rules
-
- 14 Mar, 2002 2 commits
-
-
simonmar authored
Misc cleanup: remove the iface pretty-printing style, and clean up bits of StringBuffer that aren't required any more.
-
simonpj authored
------------------------ Change GlobalName --> ExternalName LocalName -> InternalName ------------------------ For a long time there's been terminological confusion between GlobalName vs LocalName (property of a Name) GlobalId vs LocalId (property of an Id) I've now changed the terminology for Name to be ExternalName vs InternalName I've also added quite a bit of documentation in the Commentary.
-
- 04 Mar, 2002 1 commit
-
-
simonmar authored
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).
-
- 27 Feb, 2002 1 commit
-
-
simonpj authored
comments
-
- 13 Feb, 2002 1 commit
-
-
simonpj authored
---------------------------------- Do the Right Thing for TyCons where we can't see all their constructors. ---------------------------------- Inside a TyCon, three things can happen 1. GHC knows all the constructors, and has them to hand. (Nowadays, there may be zero constructors.) 2. GHC knows all the constructors, but has declined to slurp them all in, to avoid sucking in more declarations than necessary. All we remember is the number of constructors, so we can get the return convention right. 3. GHC doesn't know anything. This happens *only* for decls coming from .hi-boot files, where the programmer declines to supply a representation. Until now, these three cases have been conflated together. Matters are worse now that a TyCon really can have zero constructors. In fact, by confusing (3) with (1) we can actually generate bogus code. With this commit, the dataCons field of a TyCon is of type: data DataConDetails datacon = DataCons [datacon] -- Its data constructors, with fully polymorphic types -- A type can have zero constructors | Unknown -- We're importing this data type from an hi-boot file -- and we don't know what its constructors are | HasCons Int -- In a quest for compilation speed we have imported -- only the number of constructors (to get return -- conventions right) but not the constructors themselves This says exactly what is going on. There are lots of consequential small changes.
-
- 05 Feb, 2002 1 commit
-
-
simonpj authored
--------- Main.main --------- A bunch of related fixes concerning 'main' * Arrange that 'main' doesn't need to be defined in module Main; it can be imported. * The typechecker now injects a binding Main.$main = PrelTopHandler.runMain main So the runtime system now calls Main.$main, not PrelMain.main. With z-encoding, this look like Main_zdmain_closure * The function PrelTopHandler.runMain :: IO a -> IO () wraps the programmer's 'main' in an exception-cacthing wrapper. * PrelMain.hs and Main.hi-boot are both removed from lib/std, along with multiple lines of special case handling in lib/std/Makefile. This is a worthwhile cleanup. * Since we now pick up whatever 'main' is in scope, the ranamer gets in on the act (RnRnv.checkMain). There is a little more info to get from the renamer to the typechecker, so I've defined a new type Rename.RnResult (c.f. TcModule.TcResult) * With GHCi, it's now a warning, not an error, to omit the binding of main (RnEnv.checkMain) * It would be easy to add a flag "-main-is foo"; the place to use that information is in RnEnv.checkMain. ------- On the way I made a new type, type HscTypes.FixityEnv = NameEnv Fixity and used it in various places I'd tripped over
-
- 30 Jan, 2002 1 commit
-
-
simonmar authored
Simplify the package story inside the compiler. The new story is this: The Finder no longer determines a module's package based on its filesystem location. The filesystem location indicates only whether a given module is in the current package or not (i.e. found along the -i path ==> current package, found along the package path ==> other package). Hence a Module no longer contains a package name. Instead it just contains PackageInfo, which is either ThisPackage or AnotherPackage. The compiler uses this information for generating cross-DLL calls and omitting certain version information from .hi files. The interface still contains the package name. This isn't used for anything right now, but in the future (when we have hierarchical libraries) we might use it to automatically determine which packages a binary should be linked against. When building a package, you should still use -package-name, but it won't be fatal if you don't. The warning/error about package name mismatches has gone away.
-
- 24 Jan, 2002 1 commit
-
-
simonmar authored
Add support for Hugs's :browse (or :b) command. There are two forms: - :b M (interpreted modules only) shows everything defined in M - the types of top-level functions, and definitions of classes and datatypes. - :b *M shows everything exported from module M. Available for both compiled and interpreted modules. The user interface is subject to change, but for now it is consistent with the new semantics of the :module command. The implementation is a little tricky, since for a package module we have to be sure to slurp in all the required declarations first.
-
- 05 Dec, 2001 1 commit
-
-
simonmar authored
Make some record selections strict to reduce space leaks.
-
- 25 Oct, 2001 1 commit
-
-
sof authored
follow-on from prev. commit; more tidyups
-
- 24 Oct, 2001 1 commit
-
-
simonpj authored
NB: (Just a) `mplus` (Just b) = a We want catMaybes, not mplus!
-
- 23 Oct, 2001 1 commit
-
-
sof authored
- ifaceTyThing: avoid using (++) when constructing the IdInfo for AnId - Maybe is preferable for this. - misc typesig tidy-ups to make easier to get into the workings of the functions herein.
-
- 18 Oct, 2001 1 commit
-
-
simonpj authored
---------------------------------------------- The CoreTidy/CorePrep/CoreToStg saga continues [actually, this commit mostly completes the job] ---------------------------------------------- DO NOT MERGE! * CorePrep injects implicit bindings, not the type checker, nor CgConTbls. (This way, all the code generators see them, so no need to fiddle with the byte code generator.) As a result, all bindings in the module are for LocalIds, at least until CoreTidy. This is a Big Win. Hence remove nasty isImplicitId test in update_bndr in SimplCore and DmdAnal * hasNoBinding is no longer true of a dataConId (worker). There's an implicit curried binding for it. * Remove yukky test in exprIsTrivial that did not regard a hasNoBinding Id as trivial; similarly in SimplUtils.tryEtaReduce * In CoreTidy, get the names to avoid from the type env. That way it includes implicit bindings too. * CoreTidy set the Arity of a top-level Id permanently; it's up to the rest of the compiler to respect it. Notably, CorePrep uses etaExpand to make the manifest arity match the claimed arity. * As a result, nuke CgArity, so that CgInfo now contains only CafInfo. The CafInfo is knot-tied as before. Other things * In Simplify.simplLazyBind, be a bit keener to float bindings out if it's a top-level binding.
-
- 15 Oct, 2001 1 commit
-
-
simonpj authored
Rename ifaceTyCls to ifaceTyThing (more consistent)
-
- 04 Oct, 2001 1 commit
-
-
simonpj authored
Heal the HEAD
-
- 26 Sep, 2001 1 commit
-
-
simonpj authored
------------------ 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!
-
- 14 Sep, 2001 1 commit
-
-
simonpj authored
-------------------------- Add a rule-check pass (special request by Manuel) -------------------------- DO NOT merge with stable The flag -frule-check foo will report all sites at which RULES whose name starts with "foo.." might apply, but in fact the arguments don't match so the rule doesn't apply. The pass is run right after all the core-to-core passes. (Next thing to do: make the core-to-core script external, so you can fiddle with it. Meanwhile, the core-to-core script is in DriverState.builCoreToDo so you can move the CoreDoRuleCheck line around if you want. The format of the report is experimental: Manuel, feel free to fiddle with it. Most of the code is in specialise/Rules.lhs Incidental changes ~~~~~~~~~~~~~~~~~~ Change BuiltinRule so that the rule name is accessible without actually successfully applying the rule. This change affects quite a few files in a trivial way.
-
- 20 Aug, 2001 1 commit
-
-
simonmar authored
Do something vaguely useful in ifaceTyCls when presented with a primitive type constructor. We pretend it's an abstract data type for now.
-
- 15 Aug, 2001 1 commit
-
-
simonmar authored
Implement the :info command for GHCi.
-
- 23 Jul, 2001 1 commit
-
-
simonpj authored
--------------------------------- Switch to the new demand analyser --------------------------------- This commit makes the new demand analyser the main beast, with the old strictness analyser as a backup. When DEBUG is on, the old strictness analyser is run too, and the results compared. WARNING: this isn't thorougly tested yet, so expect glitches. Delay updating for a few days if the HEAD is mission critical for you. But do try it out. I'm away for 2.5 weeks from Thursday, so it would be good to shake out any glaring bugs before then.
-
- 18 Jul, 2001 1 commit
-
-
rrt authored
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
-