- 25 Jun, 2001 11 commits
-
-
simonpj authored
Import wibbles
-
simonpj authored
In nubBy, put argument to eq in the standard order
-
rrt authored
Fix so that it compiles on both pre and post 5.00 series compilers.
-
rrt authored
Comment out an uncomfortable ASSERT for now.
-
rrt authored
Add more symbols for mingwin version to get it to work. This still needs tidying up.
-
rrt authored
Remove hacked-in definition of system for mingwin; instead we now just link against the new version of systemCmd from lib/std/cbits/system.c.
-
simonpj authored
---------------- Squash newtypes ---------------- This commit squashes newtypes and their coerces, from the typechecker onwards. The original idea was that the coerces would not get in the way of optimising transformations, but despite much effort they continue to do so. There's no very good reason to retain newtype information beyond the typechecker, so now we don't. Main points: * The post-typechecker suite of Type-manipulating functions is in types/Type.lhs, as before. But now there's a new suite in types/TcType.lhs. The difference is that in the former, newtype are transparent, while in the latter they are opaque. The typechecker should only import TcType, not Type. * The operations in TcType are all non-monadic, and most of them start with "tc" (e.g. tcSplitTyConApp). All the monadic operations (used exclusively by the typechecker) are in a new module, typecheck/TcMType.lhs * I've grouped newtypes with predicate types, thus: data Type = TyVarTy Tyvar | .... | SourceTy SourceType data SourceType = NType TyCon [Type] | ClassP Class [Type] | IParam Type [SourceType was called PredType.] This is a little wierd in some ways, because NTypes can't occur in qualified types. However, the idea is that a SourceType is a type that is opaque to the type checker, but transparent to the rest of the compiler, and newtypes fit that as do implicit parameters and dictionaries. * Recursive newtypes still retain their coreces, exactly as before. If they were transparent we'd get a recursive type, and that would make various bits of the compiler diverge (e.g. things which do type comparison). * I've removed types/Unify.lhs (non-monadic type unifier and matcher), merging it into TcType. Ditto typecheck/TcUnify.lhs (monadic unifier), merging it into TcMType.
-
simonpj authored
--------------------------- Add a new case optimisation --------------------------- I found that lib/std/PrelCError had a case-expression that was generating terrible code. Something like this x | p `is` 1 -> e1 | p `is` 2 -> e2 ...etc... where @is@ was something like p `is` n = p /= (-1) && p == n This gave rise to a horrible sequence of cases case p of (-1) -> $j p 1 -> e1 DEFAULT -> $j p and similarly in cascade for all the join points! Solution: add the following transformation: case e of =====> case e of C _ -> <expr> D v -> ....v.... D v -> ....v.... DEFAULT -> <expr> DEFAULT -> <expr> The point is that we merge common RHSs, at least for the DEFAULT case. [One could do something more elaborate but I've never seen it needed.] This transformation is implemented in SimplUtils.mkCase *** WARNING *** To make this transformation easy, I have switched the convention for DEFAULT clauses. They must now occur FIRST in the list of alternatives for a Core case expression. (The semantics is unchanged: they still are a catch-all case.) The reason is that DEFAULT clauses sometimes need special treatment, and it's a lot easier to find them at the front. The easiest way to be insensitive to this change is to use CoreUtils.findDefault to pull the default clause out. I've made the (surprisingly few) changes consequent on this changed of convention, but they aren't in this commit. Instead they are part of the big commit on newtypes I'm doing at the same time.
-
simonpj authored
---------------------------------- Fix a predicate-simplification bug ---------------------------------- Fixes a bug pointed out by Marcin data R = R {f :: Int} foo:: (?x :: Int) => R -> R foo r = r {f = ?x} Test.hs:4: Could not deduce `?x :: Int' from the context () arising from use of implicit parameter `?x' at Test.hs:4 In the record update: r {f = ?x} In the definition of `foo': r {f = ?x} The predicate simplifier was declining to 'inherit' an implicit parameter. This is right for a let-binding, but wrong for an expression binding. For example, a simple expression type signature: (?x + 1) :: Int This was rejected because the ?x constraint could not be floated out -- but that's wrong for expressions.
-
sof authored
One RCS will do
-
sof authored
With -no-hs-main, don't force PrelMain.o to be linked (=> Main.o)
-
- 23 Jun, 2001 2 commits
- 22 Jun, 2001 8 commits
-
-
rrt authored
Add some extra tests and correct some error messages. This file is no longer used for its original purpose, but is a useful example of how to start and manage processes under Windows.
-
rrt authored
Add machinery to copy system.c to main/ from lib/std/cbits/ when building GHC on Windows with GHC<5.01, so that the new implementation of system can be used rather than the old.
-
rrt authored
Instead of using the old kludgedSystem on Windows, use the new system. This makes the use of DOS built-ins such as copy work, which they didn't when the command was run under sh (as the old kludgedSystem did).
-
rrt authored
Move include of config.h to top so it works for mkdependC.
-
rrt authored
Correct path to NCG.h
-
rrt authored
Add wsock32 to list of libraries needed for rts under Windows.
-
rrt authored
Fix paths to HsStd.h.
-
rrt authored
Fix typo.
-
- 18 Jun, 2001 4 commits
-
-
sof authored
For GHCen < 5.00, assume that Exception.throwTo is Exception.raiseInThread
-
simonmar authored
Forced commit to note that the previous commit also adds flushing of stdout/stderr before printing an exception. This fixes the problem reported by Leon Smith last week.
-
simonpj authored
Fix Unix imports
-
chak authored
Adapted to changes in build system
-
- 15 Jun, 2001 8 commits
-
-
sof authored
Make it compile
-
simonpj authored
More windows wibbles
-
simonpj authored
* Restore SysTools.system, which implements a kludged version of system for reasons that are explained at length in the comments [overlong command-lines fail if compiling GHC with pre-5.02 GHCs] * Wibble in Makefile
-
simonmar authored
Restore an #ifdef mingw32_TARGET_OS that shouldn't have been removed (but do it better this time and don't use an arch-specific #ifdef).
-
simonmar authored
- separate location installed binaries from non-binaries (previously installed package.conf was in $(libdir)/extra-bin). - remove v_Path_Perl so that we don't accidentally wire-in the location of perl on Unix systems. It wasn't actually used anywhere. - minor non-functional cleanups and comment fixups. - We still look for package.conf twice; I haven't done anything about this yet.
-
simonmar authored
import Packages
-
simonmar authored
override $(libexecdir) to be $(libdir)/bin (the installation machinery will have to catch up with this too).
-
simonpj authored
Some tidying up * Remove CmStaticInfo - GhciMode moves to HscTypes - The package stuff moves to new module main/Packages.lhs [put any package-related stuff in the new module] * Add Outputable.docToSDoc
-
- 14 Jun, 2001 7 commits
-
-
rrt authored
Add getExecDir to return current directory of executable on Windows (to find config information).
-
simonpj authored
Windows wibbles
-
simonmar authored
- CURRENT_DIR isn't used any more - TmpFiles doesn't exist
-
simonmar authored
fix typo in Simon's commit (cGHC_RAWCPP ==> GHC_RAWCPP)
-
simonpj authored
---------------------- Installation packaging ---------------------- GHC runs various system programs like cp, touch gcc, as, ld etc On Windows we plan to deliver these programs along with GHC, so we have to be careful about where to find them. This commit isolates all these dependencies in a single module main/SysTools.lhs Most of the #ifdefery for mingw has moved into this module. There's some documentation in SysTools.lhs Along the way I did lots of other cleanups. In particular * There is no more 'globbing' needed when calling runSomething * All file removal goes via the standard Directory.removeFile * TmpFiles.hs has gone; absorbed into SysTools * Some DynFlag stuff has moved from DriverFlags to CmdLineOpts Still to do: ** I'm a bit concerned that calling removeFile one at a time when deleting masses of split-object files is going to be rather slow ** GHC now expects to find split,mangle,unlit in libdir/extra-bin instead of just libdir So something needs to change in the Unix installation scripts ** The "ineffective C preprocessor" is a perversion and should die
-
simonmar authored
just move some code around.
-
simonmar authored
comment fixes
-