- Oct 03, 2000
-
-
Reuben Thomas authored
Backed out bogon (last commit was completely nonsensical).
-
Reuben Thomas authored
Add $(FPTOOLS_TOP)/dll to PATH when running GHC_INPLACE. This is to make the inplace compiler pick up the right set of DLLs under Windows, and won't have any effect on other platforms (where the dll directory is empty).
-
Simon Peyton Jones authored
First cut at documenting generic classes
-
Simon Peyton Jones authored
-------------------------------------- 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
-
Simon Peyton Jones authored
Remove dead code mkLookupFun
-
- Oct 02, 2000
-
-
Simon Peyton Jones authored
Add check for unboxed function arguments
-
Julian Seward authored
First shot at the summariser. Doesn't know how to unlit or cppify source yet.
-
Julian Seward authored
@ModSummary@ wibble.
-
Julian Seward authored
Partially back out changes mistakenly included in last commit :-(
-
Julian Seward authored
Implement initial-state (emptyTy :: Ty) functions.
-
Simon Marlow authored
Names of mpz routines in GMP 3 now have a "__g" prefix (untested, but should fix the NCG).
-
Simon Marlow authored
- move readMVar and swapMVar from PrelConc to concurrent - add the following exception-safe MVar operations: withMVar :: MVar a -> (a -> IO b) -> IO b modifyMVar :: MVar a -> (a -> IO (a,b)) -> IO b modifyMVar_ :: MVar a -> (a -> IO a) -> IO () - re-implement readMVar and swapMVar in an exception-safe way. - re-implement the Chan operations using withMVar et al.
-
Simon Peyton Jones authored
Add tc107
-
- Sep 29, 2000
-
-
Julian Seward authored
New modules for GHCI.
-
Julian Seward authored
A few more internal consistency fixes seen when making new modules in ghc/compiler/ghci.
-
Reuben Thomas authored
Changed *do* to <Emphasis>do</Emphasis>
-
Julian Seward authored
Internal consistency wibble: @LinkState@ --> @PLS@.
-
- Sep 28, 2000
-
-
Simon Peyton Jones authored
Another wibble
-
Julian Seward authored
wibbles
-
Julian Seward authored
Fill in details about how CM works.
-
Simon Peyton Jones authored
Simon's log file; I don't want to lose this!
-
Simon Peyton Jones authored
Wibbles
-
Simon Peyton Jones authored
------------------------------------ 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
-
Julian Seward authored
Define relationship between what CM implements and the HEP interface. Start on saying how CM behaves.
-
- Sep 27, 2000
-
-
Julian Seward authored
Further cleanups, and add defs for ModDetails, ModIFace and Ifaces.
-
Julian Seward authored
Big reorganisation, to put CM, compile, link into seperate sections. Ongoing.
-
Simon Peyton Jones authored
Remove Addr2IntegerOp reference
-
- Sep 26, 2000
-
-
Simon Peyton Jones authored
* 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
-
Julian Seward authored
Rearrange the Linker section a bit, in line with upcoming rearrangement of Compiler and CM sections.
-
Simon Peyton Jones authored
Document the new behaviour of -fno-implicit-prelude. (I havn't checked that the new document builds right because my build tree doesn't seem to build documentation. Reuben, could you check, please.)
-
Simon Marlow authored
linker spec updates
-
Julian Seward authored
Add the GHCi design document to CVS.
-
chak@cse.unsw.edu.au. authored
Added missing !
-
- Sep 25, 2000
-
-
Simon Peyton Jones authored
Suck in plus/timesInteger for integer literals
-
Simon Peyton Jones authored
Fix slightly bogus error message
-
Simon Peyton Jones authored
-------------------------------------------------- Tidying up HsLit, and making it possible to define your own numeric library Simon PJ 22 Sept 00 -------------------------------------------------- I forgot to commit changes to the libraries! The main thing is to define monomorphic plusInteger, timesInteger etc, in PrelNum.
-
Simon Marlow authored
Fix a couple of problems with the recompilation avoidance stuff.
-
Simon Marlow authored
arguments of StgLam should be bndrs, not Id.
-
Simon Marlow authored
INLINE is_ctype, otherwise charType gets inlined in the RHS by virtue of only being used once, and we lose the opportunity to inline is_ctype.
-
Simon Marlow authored
remove unused imports
-