- 21 Feb, 2001 3 commits
- 20 Feb, 2001 20 commits
-
-
qrczak authored
Apply tweaks needed to let this compile: remove syn_map argument from typecheckExpr in HscMain, import PrelNum.fromInt to modules which use integer literals with -fno-implicit-prelude flag. It crashes later, on Directory.hs: ghc: panic! (the `impossible' happened): srtExpr I'm not sure if resolving numeric literals to top-level definitions of fromInt/fromInteger with -fno-implicit-prelude is a good idea. Using names from whatever module is called Prelude would be IMHO better, probably when -fglasgow-exts is given. Prel* modules themselves would import PrelNum as Prelude. Both schemes break for fromInt, which is non-standard and by default it's visible neither at the top level nor in the Prelude module. My proposal for dealing with it is as follows (assuming that fromInteger is taken from the module locally called Prelude instead of the top level): when the standard Prelude is used, take fromInt from PrelNum; when a Prelude replacement is used, use fromInt from it if available, otherwise use its fromInteger instead. That way Prelude replacements can ignore this non-standard extension and get the expected behavior, or they can also choose to use this extension (in a way compatible with Haskell implementations which allow to replace Prelude but don't have fromInt).
-
simonmar authored
More doc hacking. Call for Release Notes (CFRN): the 5-00-notes.sgml file is currently a skeleton only; PLEASE add or expand entries for things you've done.
-
simonpj authored
Eta expansion wibbles ~~~~~~~~~~~~~~~~~~~~~ * Don't eta reduce, and do eta expand, data con workers and primops Reason: they don't have bindings, so they aren't really ordinary variables. This is a bit of a swamp, provoked by moving CoreSat later, something I'm beginning to wonder about... Not are things settled yet -- I think some rules may not fire that should because of constructor worker/wrapper issues. E.g when you have foldr (:) [] xs = xs
-
simonpj authored
Import wibble
-
simonpj authored
Layout wibble
-
simonpj authored
Add another assert
-
simonpj authored
Remove IPName altogether
-
simonpj authored
Use tcIfaceType
-
simonpj authored
Fix top level float
-
simonmar authored
Make the warning package options (-W, -w, -Wall) dynamic.
-
simonpj authored
Wibble
-
simonpj authored
Import wibbles
-
simonpj authored
A bit more on deprecations
-
simonpj authored
A bit more on decoupling the prelude
-
simonpj authored
Typechecking [TcModule, TcBinds, TcHsSyn, TcInstDcls, TcSimplify] ~~~~~~~~~~~~ * Fix a bug in TcSimplify that broke functional dependencies. Interleaving unification and context reduction is trickier than I thought. Comments in the code amplify. * Fix a functional-dependency bug, that meant that this pgm: class C a b | a -> b where f :: a -> b g :: (C a b, Eq b) => a -> Bool g x = f x == f x gave an ambiguity error report. I'm afraid I've forgotten what the problem was. * Correct the implementation of the monomorphism restriction, in TcBinds.generalise. This fixes Marcin's bug report: test1 :: Eq a => a -> b -> b test1 x y = y test2 = test1 (3::Int) Previously we were erroneously inferring test2 :: () -> () * Make the "unf_env" that is looped round in TcModule go round in a big loop, not just round tcImports. This matters when we have mutually recursive modules, so that the Ids bound in the source code may appear in the imports. Sigh. But no big deal. It does mean that you have to be careful not to call isLocalId, isDataConId etc, because they consult the IdInfo of an Id, which in turn may be determined by the loop-tied unf_env.
-
simonpj authored
Deprecations [HscTypes, MkIface, Rename, RnEnv, RnIfaces] ~~~~~~~~~~~~ * Arrange that a change in deprecations is treated as a hi-file difference. * Warn about deprecations at the usage site. This entailed changing HscTypes.GlobalRdrEnv to include deprecations. While I was at it, I changed the range of GlobalRdrEnv to a data type, GlobalRdrElt, instead a of a pair.
-
simonpj authored
Decoupling the Prelude [HsExpr, HsLit, HsPat, ParseUtil, Parser.y, PrelNames, ~~~~~~~~~~~~~~~~~~~~~~ Rename, RnEnv, RnExpr, RnHsSyn, Inst, TcEnv, TcMonad, TcPat, TcExpr] The -fno-implicit-prelude flag is meant to arrange that when you write 3 you get fromInt 3 where 'fromInt' is whatever fromInt is in scope at the top level of the module being compiled. Similarly for * numeric patterns * n+k patterns * negation This used to work, but broke when we made the static/dynamic flag distinction. It's now tidied up a lot. Here's the plan: - PrelNames contains sugarList :: SugarList, which maps built-in names to the RdrName that should replace them. - The renamer makes a finite map :: SugarMap, which maps the built-in names to the Name of the re-mapped thing - The typechecker consults this map via tcLookupSyntaxId when it is doing numeric things At present I've only decoupled numeric syntax, since that is the main demand, but the scheme is much more robustly extensible than the previous method. As a result some HsSyn constructors don't need to carry names in them (notably HsOverLit, NegApp, NPlusKPatIn)
-
simonpj authored
Back end changes [CgExpr, ClosureInfo, CoreSat, CoreUtils, ~~~~~~~~~~~~~~~~ CmdLineOpts, HscMain, CoreToStg, StgSyn] * Move CoreTidy and interface-file dumping *before* CoreSat. In this way interface files are not in A-normal form, so they are less bulky, and a bit easier to use as input to the optimiser. So now CoreSat is regarded as a pre-pass to CoreToStg. Since CoreTidy pins on utterly-final IdInfo, CoreSat has to be very careful not to change the arity of any function. * CoreSat uses OrdList instead of lists to collect floating binds This in turn meant I could simplify the FloatingBind type a bit * Greatly simplfy the StgBinderInfo data type. It was gathering far more information than we needed. * Add a flag -fkeep-stg-types, which keeps type abstractions and applications in STG code, for the benefit of code generators that are typed; notably the .NET ILX code generator.
-
simonpj authored
Add fundeps tests
-
qrczak authored
Remove unbalanced #endif.
-
- 19 Feb, 2001 9 commits
-
-
rrt authored
Use Sleep under mingw rather than sleep (which is obsolete), and try using fork under cygwin (it should work by now, shurely...).
-
rrt authored
Don't declare unused struct termios on mingwin.
-
rrt authored
Move if #ifndefs so that no code is compiled on win32; the code that was compiled was doing nothing useful, and probably shouldn't have been.
-
rrt authored
Add -mno-cygwin to CPPFLAGS on i386-unknown-mingw32 to stop configure.h getting lots of bogus headers that aren't there. I'm not at all sure why this hasn't caused problems before...
-
simonmar authored
fix the GHC_HAPPY_OPTS hack to correctly detect happy 1.10
-
simonmar authored
Rather than implement -K (which would probably need another primop), simply bump the maximum stack size to 8M. It dynamically grows anyhow.
-
sewardj authored
Expand on comments re StString lifting activity
-
sewardj authored
Fix two bugs exposed when trying to boot HEAD on sparc with NCG and -O: 1. StScratchWords on sparc were in the wrong place; they were immediately above %fp and should have been immediately below. Fixed. Also removed a suspicious-looking "+1" in the x86 version of same. 2. (Potentially affects all platforms): Lift strings out from top-level literal data, and place them at the end of the block. The motivating example (bug) was: Stix: (DataSegment) Bogon.ping_closure : (Data P_ Addr.A#_static_info) (Data StgAddr (Str `alalal')) (Data P_ (0)) results in: .data .align 8 .global Bogon_ping_closure Bogon_ping_closure: .long Addr_Azh_static_info .long .Ln1a8 .Ln1a8: .byte 0x61 .byte 0x6C .byte 0x61 .byte 0x6C .byte 0x61 .byte 0x6C .byte 0x00 .long 0 ie, the Str is planted in-line, when what we really meant was to place a _reference_ to the string there. This is Way Wrong (tm). Fixed.
-
qrczak authored
Oops, I broke it yesterday; don't use autoheader. (I don't see my yesterday's commit log. I changed #define to #undef in autoconf templates.)
-
- 18 Feb, 2001 2 commits
- 17 Feb, 2001 2 commits
- 16 Feb, 2001 4 commits
-
-
simonmar authored
Today's doc hacking.
-
sewardj authored
Remove ghc-$(ProjectVersion) from GhcBinDistPrlScripts, since it's not a perl script any more.
-
sewardj authored
Remove ghc-stats from GhcBinDistLibPrlScripts.
-
simonmar authored
deLam the contents of an _scc_: they don't disappear at code generation time.
-