- 13 Sep, 2002 3 commits
-
-
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.
-
simonpj authored
Make ghc-pkg independent of hslibs
-
simonpj authored
Correct comments
-
- 11 Sep, 2002 2 commits
- 10 Sep, 2002 5 commits
-
-
simonmar authored
Tidy up error message for "funny global things"
-
simonmar authored
Put debugging output in #ifdef DEBUG MERGE TO STABLE
-
simonpj authored
Remove redundant debug printing
-
simonmar authored
Fix a(nother) bug in the new THUNK_SELECTOR code. Hopefully should fix the crashes seen in the last few nightly builds.
-
simonmar authored
Add notes on how to build a .a file to the docs, as requested by Koen Claessen.
-
- 09 Sep, 2002 13 commits
-
-
simonpj authored
Sigh! forgot one case! MERGE TO STABLE
-
simonpj authored
Cosmetics only
-
simonpj authored
Correction to earlier commit.. *now* those rank-2 pattern matches should work MERGE TO STABLE
-
simonpj authored
The body of a for-all should be of kind * MERGE TO STABLE
-
simonpj authored
-------------------------------- Fix rank-2 pattern-match failure -------------------------------- This fixes the failure when you have a rank-2 type sig matching a data type pattern. Thus data T a = T1 | T2 a f :: (forall x. T x) -> Int f T1 = ... This crashes GHC 5.04
-
simonpj authored
-------------------------------------- Attach inline pragmas to class methods -------------------------------------- This fix makes INLINE pragmas on method bindings (in class or instance decls) work properly. It seems to have been hanging around in my tree for some time. To be on the safe side, let's not merge this into 5.04.1, although it should be fine (an an improvement).
-
simonpj authored
Formatting only
-
simonpj authored
Formatting only
-
simonmar authored
Make sure we get the compiler's own Pretty library when we #include ../utils/ghc-pkg/Package.hs.
-
simonmar authored
Urk, the 'import Pretty' in this module was a bit of a hack; when compiled as part of the standalone ghc-pkg tool it referred to the Pretty library from the util package, but when compiled as part of the compiler it referred to the compiler's own Pretty module. Hack around this.
-
simonmar authored
Build without hslibs on GHC >= 5.04
-
simonmar authored
Build without hslibs on GHC >= 5.04
-
simonmar authored
Build without hslibs on GHC >= 5.04
-
- 07 Sep, 2002 1 commit
-
-
panne authored
Tentative fix for the recent blkcnt_t trouble
-
- 06 Sep, 2002 10 commits
-
-
panne authored
Nuke the unsupported hslibs version of HOpenGL on the HEAD, too. Now we are only left with two versions, which I think is OK: A stable one (not in the fptools repository, but on my web site) and a cool, but *very* incomplete one (currently only GLUT) for bleeding edge people in the hierarchical libraries parts of the repository.
-
simonmar authored
Disallow ForeignObj as well as ForeignPtr FFI arguments
-
simonmar authored
Finally separate the compiler from hslibs. Mainly import wibbles, and use the new POSIX library when bootstrapping.
-
simonmar authored
Partial rewrite of the POSIX library. The main purpose of this sweep is to remove the last dependencies of the compiler on hslibs. When I've committed the associated compiler changes, only the 'base' package will be required to bootstrap the compiler. Additionally to build GHCi, the 'readline' and 'unix' packages will be required. The new POSIX library lives mostly in libraries/unix, with a few bits required for compiler bootstrapping in libraries/base. The 'base' package is mostly free of hsc2hs code to make bootstrapping from HC files easier, but the 'unix' package will use hsc2hs liberally. The old POSIX library continues to provide more-or-less the same interface as before, although some of the types are more correct now (previously lots of POSIX types were just mapped to Int). The new interface is largely the same as the old, except that some new functionality from the latest POSIX spec has been added (eg. symbolic links). So far, the new POSIX library has signal support, directory/file operations and lots of stuff from unistd.h. The module names are: System.Posix The main dude, exports everything System.Posix.Types All the POSIX types, using the same naming scheme as Foreign.C.Types, Eg. CUid, COff, etc. Many of these types were previously exported by GHC.Posix. Additionally exports the "nicer" names used by the old POSIX library for compatibility (eg. ProcessID == CPid, FileMode == CMode, etc.) All reasonable instances are derived for these types. System.Posix.Signals Signal support, contains most of which was in PosixProcPrim before. The RTS interface to the signal handling support has been rationalised slightly. System.Posix.Directory Directory support, most were in PosixFiles before. System.Posix.Files File operations, most were in PosixFiles before. System.Posix.Unistd (for want of a better name) Miscellaneous bits that mostly come from the unistd.h header file. PosixProcEnv before. The rest of the library should pan out like so: System.Posix.IO System.Posix.Error (maybe) System.Posix.Process System.Posix.Terminal (I've no doubt broken Win32 support, but I'm checking the build at the moment).
-
simonmar authored
Remove ForeignObj and ForeignPtr keys
-
simonmar authored
Remove foreignPtrTyCon and foreignObjTyCon
-
simonmar authored
Disallow ForeignPtr as an FFI argument type.
-
simonmar authored
Disallow 'ForeignPtr' as an FFI argument type. It has been deprecated for some time (withForeignPtr is the approved way to pass a ForeignPtr). The changes I'm about to make to ForeignPtr will stop it working anyhow.
-
simonmar authored
Selector Thunk Fix, take II. The previous version didn't deal well with selector thunks which point to more selector thunks, and on closer inspection the method was flawed. Now I've introduced a function StgClosure *eval_selector_thunk( int field, StgClosure * ) which evaluates a selector thunk returning its value, in from-space, if possible. It blackholes the thunk during evaluation. It might recursively evaluate more selector thunks, but it does this in a bounded way and updates the thunks with indirections (NOT forwarding pointers) after evaluation. This cleans things up somewhat, and I believe it deals properly with both types of selector-thunk loops that arise. MERGE TO STABLE
-
ken authored
perl made uglier to work around the perl 5.7/5.8 bug documented at http://bugs6.perl.org/rt2/Ticket/Display.html?id=1760 and illustrated by the seg fault of perl -e '("x\n" x 5000) =~ /(.*\n)+/' MERGE TO STABLE
-
- 05 Sep, 2002 3 commits
-
-
simonmar authored
Fix for infinite loop when there is a THUNK_SELECTOR which eventually refers to itself, such as might be generated by code like let x = (fst x, snd x) in ... At the same time, I re-enabled the code to traverse multiple selector thunks with bounded depth, because I believe it now works. MERGE TO STABLE (but test thoroughly in the HEAD first, this is fragile stuff)
-
simonmar authored
In code style, print negative floating point literals in parentheses to avoid interacting with surrounding syntax. Fixes SourceForge bug #604849 MERGE TO STABLE
-
simonmar authored
Remove RtsAPIDeprec.c, since this is causing grief. The upshot (I think) is that you won't be able to do foreign import "wrapper" with an Addr in the type.
-
- 04 Sep, 2002 3 commits