summaryrefslogtreecommitdiff
path: root/ghc/compiler
Commit message (Collapse)AuthorAgeFilesLines
...
* [project @ 2005-11-19 14:59:53 by simonmar]simonmar2005-11-191-7/+4
| | | | | | fix repType after changes to the representation of type synonyms. This caused the stage2 compiler to crash, because various info tables misrepresented the pointerhood of constructor arguments.
* [project @ 2005-11-16 17:45:38 by simonpj]simonpj2005-11-163-18/+27
| | | | | | | | | Better error reporting for newtypes with too many constructors, or too many fields. Instead of yielding a parse error, we parse it like a data type declaration, and give a comprehensible error message later. A suggestion from Jan-Willem.
* [project @ 2005-11-16 12:55:58 by simonpj]simonpj2005-11-1618-360/+450
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Two significant changes to the representation of types 1. Change the representation of type synonyms Up to now, type synonym applications have been held in *both* expanded *and* un-expanded form. Unfortunately, this has exponential (!) behaviour when type synonyms are deeply nested. E.g. type P a b = (a,b) f :: P a (P b (P c (P d e))) This showed up in a program of Joel Reymont, now immortalised as typecheck/should_compile/syn-perf.hs So now synonyms are held as ordinary TyConApps, and expanded only on demand. SynNote has disappeared altogether, so the only remaining TyNote is a FTVNote. I'm not sure if it's even useful. 2. Eta-reduce newtypes See the Note [Newtype eta] in TyCon.lhs If we have newtype T a b = MkT (S a b) then, in Core land, we would like S = T, even though the application of T is then not saturated. This commit eta-reduces T's RHS, and keeps that inside the TyCon (in nt_etad_rhs). Result is that coreEqType can be simpler, and has less need of expanding newtypes.
* [project @ 2005-11-15 17:37:54 by simonpj]simonpj2005-11-151-1/+2
| | | | Yet more detail in types with -dppr-debug
* [project @ 2005-11-12 21:41:12 by simonpj]simonpj2005-11-127-328/+465
| | | | | | | | | | | | | | Better TH -> HsSyn conversion Merge to stable (attempt) This commit monad-ises the TH syntax -> HS syntax conversion. This means that error messages can be reported in a more civilised way. It also ensures that the entire structure is converted eagerly. That means that any exceptions buried inside it are triggered during conversion, and caught by the exception handler in TcSplice. Before, they could be triggered later, and looked like comiler crashes.
* [project @ 2005-11-09 11:36:43 by simonmar]simonmar2005-11-091-1/+1
| | | | oops, it's i386_TARGET_ARCH, not x86_TARGET_ARCH
* [project @ 2005-11-08 12:56:04 by simonmar]simonmar2005-11-081-3/+20
| | | | | | | | | | | | | | | | | | gcc's -fstrict-aliasing is biting us when we use the stack to store different types of objects. For example: *((StgDouble*)((W_)Sp-8)) = *((StgDouble*)((W_)Sp+8)); Sp[1] = (W_)&s1Cx_info; gcc feels free to reorder these two lines, because they refer to differently typed objects, even though the assignment to Sp[1] clearly aliases the read from the same location. Trying to fix this by accessing locations using union types might be possible, but I took the sledgehammer approach of -fno-strict-aliasing. This is justified to a certain extent because our generated C code is derived from a very weakly-typed internal language (C--).
* [project @ 2005-11-08 12:31:36 by simonmar]simonmar2005-11-081-0/+2
| | | | | | | unless I'm mistaken, only x86 needs -ffloat-store. x86_64 certainly doesn't need it, because it uses SSE2 with the correct-sized floating point registers and doesn't store temporary results with more precision than results in memory.
* [project @ 2005-11-04 15:48:25 by simonmar]simonmar2005-11-042-13/+62
| | | | | | | | | | | | | | | | | | | | | | | | | | - Add support for the GHC_PACKAGE_PATH environment variable, which specifies a :-separated (;-separated on Windows) list of package database files. If the list ends in : (; on Windows), then the normal user and global databases are added. GHC_PACKAGE_PATH is searched left-to-right for packages, like $PATH, but unlike -package-conf flags, which are searched right-to-left. This isn't ideal, but it seemed the least worst to me (command line flags always override right-to-left (except -i), whereas the PATH environment variable overrides left-to-right, I chose to follow the environment variable convention). I can always change it if there's an outcry. - Rationalise the interpretation of --user, --global, and -f on the ghc-pkg command line. The story is now this: --user and --global say which package database to *act upon*, they do not change the shape of the database stack. -f pushes a database on the stack, and also requests that the specified database be the one to act upon, for commands that modify the database. If a database is already on the stack, then -f just selects it as the one to act upon. This means you can have a bunch of databases in GHC_PACKAGE_PATH, and use -f to select the one to modify.
* [project @ 2005-11-03 15:00:23 by simonpj]simonpj2005-11-031-2/+2
| | | | Missing import for new assert
* [project @ 2005-11-02 17:41:00 by simonpj]simonpj2005-11-022-18/+24
| | | | | | | | | | | | | Second correction to the TH fix of Oct 26, involving thFAKE Original message 1) A bug in the renaming of [d| brackets |]. The problem was that when we renamed the bracket we messed up the name cache, because the module was still that of the parent module. Now we set a fake module before renaming it. This commit fixes the typecheker problem in a different way, in tcLookupGlobal.
* [project @ 2005-11-02 17:39:57 by simonpj]simonpj2005-11-021-1/+1
| | | | Trace output only
* [project @ 2005-11-02 11:56:56 by simonmar]simonmar2005-11-021-0/+4
| | | | | Fix warnings when assigning the result of a foreign call to BaseReg (as now happens in SMP mode with resumeThread()).
* [project @ 2005-11-02 09:57:45 by simonpj]simonpj2005-11-022-1/+9
| | | | | | | | | | | | | | | | Correct the TH fix of Oct 26, involving thFAKE MERGE TO STABLE Original message 1) A bug in the renaming of [d| brackets |]. The problem was that when we renamed the bracket we messed up the name cache, because the module was still that of the parent module. Now we set a fake module before renaming it. But we have to tell the *typechecker* too, not just the renamer. See comments with TcSplice.tc_bracket (DecBr case). Should fix TH failures in the STABLE branch
* [project @ 2005-11-02 09:53:18 by simonpj]simonpj2005-11-022-7/+6
| | | | Export lists
* [project @ 2005-10-31 11:53:42 by simonmar]simonmar2005-10-311-1/+6
| | | | x86_64: pass -fno-unit-at-a-time to gcc. See comment for details.
* [project @ 2005-10-31 11:49:29 by simonpj]simonpj2005-10-313-10/+20
| | | | | | Wibble to: "Add a new pragma: SPECIALISE INLINE" I messed up the way that NOINLINE is parsed; this commit fixes it.
* [project @ 2005-10-30 19:12:31 by krasimir]krasimir2005-10-302-5/+8
| | | | | | Change the way in which the .exe suffix to the output file is added. The reason is that "-o main" will generate main.exe on Windows while the doesFileExists "main" in DriverPipeline.link will return False.
* [project @ 2005-10-29 18:13:52 by krasimir]krasimir2005-10-291-0/+4
| | | | | | | The guessed output file should have ".exe" extension on Windows. ld tends to add .exe automatically if the output file doesn't have extension but if we don't add the extension explicitly then the doesFileExists check in DriverPipeline.link will fail.
* [project @ 2005-10-29 14:19:59 by panne]panne2005-10-291-2/+4
| | | | | Fixed the last commit, which broke the nightly builds. I'm not sure if this is really a fix or a workaround only, though...
* [project @ 2005-10-28 15:22:39 by simonmar]simonmar2005-10-286-69/+117
| | | | | | | | | | | | | | Add -stubdir option to control location of generated stub files. Also do some clean up while I'm here - remove hscStubCOut/hscStubHOut from DynFlags, and add mkStubPaths :: DynFlags -> Module -> ModLocation -> (FilePath,FilePath) to Finder. (this seemed better than caching the stub paths in every ModLocation, because they are rarely needed and only present in home modules, and are easily calculated from other available information). -stubdir behaves in exactly the same way as -odir and -hidir.
* [project @ 2005-10-28 11:35:35 by simonmar]simonmar2005-10-284-21/+33
| | | | | | | | | | | | Change the default executable name to match the basename of the source file containing the Main module (or the module specified by -main-is), if there is one. On Windows, the .exe extension is added. As requested on the ghc-users list, and as implemented by Tomasz Zielonka <tomasz.zielonka at gmail.com>, with modifications by me. I changed the type of the mainModIs field of DynFlags from Maybe String to Module, which removed some duplicate code.
* [project @ 2005-10-28 11:29:19 by simonmar]simonmar2005-10-281-3/+2
| | | | | Fix double "Linking ..." message, and mention the name of the executable in the message.
* [project @ 2005-10-27 15:21:05 by simonpj]simonpj2005-10-271-4/+7
| | | | Improve warning a little (suggested by Benjamin Pierce)
* [project @ 2005-10-27 14:35:20 by simonpj]simonpj2005-10-2722-134/+160
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Add a new pragma: SPECIALISE INLINE This amounts to adding an INLINE pragma to the specialised version of the function. You can add phase stuff too (SPECIALISE INLINE [2]), and NOINLINE instead of INLINE. The reason for doing this is to support inlining of type-directed recursive functions. The main example is this: -- non-uniform array type data Arr e where ArrInt :: !Int -> ByteArray# -> Arr Int ArrPair :: !Int -> Arr e1 -> Arr e2 -> Arr (e1, e2) (!:) :: Arr e -> Int -> e {-# SPECIALISE INLINE (!:) :: Arr Int -> Int -> Int #-} {-# SPECIALISE INLINE (!:) :: Arr (a, b) -> Int -> (a, b) #-} ArrInt _ ba !: (I# i) = I# (indexIntArray# ba i) ArrPair _ a1 a2 !: i = (a1 !: i, a2 !: i) If we use (!:) at a particular array type, we want to inline (:!), which is recursive, until all the type specialisation is done. On the way I did a bit of renaming and tidying of the way that pragmas are carried, so quite a lot of files are touched in a fairly trivial way.
* [project @ 2005-10-27 14:34:32 by simonpj]simonpj2005-10-271-24/+35
| | | | Filter out inaccessible GADT alternatives
* [project @ 2005-10-27 13:51:27 by simonpj]simonpj2005-10-271-15/+19
| | | | | | | | Allow GADTs in record update, provided all the relevant datacons are vanilla. Turns out that ObjectIO.StdMenuElement uses this facility! This a slight enhancement to the new stuff allowing record fields in GADTs.
* [project @ 2005-10-27 01:39:40 by sof]sof2005-10-271-37/+3
| | | | | | | | | | | | | | | [mingw/msys only] Undo long-standing workaround for buggy GNU ld's on mingw/msys; i.e., the linker wasn't correctly generating relocatable object files when the number of relocs exceeded 2^16. Worked around the issue by hackily splitting up the GHCi object file for the larger packages ('base', 'ObjectIO' and 'win32') into a handful of object files, each with a manageable number of relocs. Tiresome and error-prone (but the hack has served us well!) This commit imposes a restriction on the 'ld' you use to compile up GHC with; it now has to be ld-2.15.x or later (something GHC binary dists have shipped with since 6.2.2)
* [project @ 2005-10-27 00:21:24 by sof]sof2005-10-271-2/+2
| | | | emitForeignCall: avoid CC warnings by hinting that resume/suspendThread id arg is a ptr
* [project @ 2005-10-26 12:35:12 by simonpj]simonpj2005-10-263-23/+19
| | | | Simplify Provenance (the LocalDef constructor) a little
* [project @ 2005-10-26 12:05:03 by simonpj]simonpj2005-10-263-16/+61
| | | | | | | | | | | | | | | | | | | | | | | MERGE TO STABLE Fix two small Template Haskell bugs. (1) A bug in the renaming of [d| brackets |]. The problem was that when we renamed the bracket we messed up the name cache, because the module was still that of the parent module. Now we set a fake module before renaming it. TH_spliceDecl4 is the test. (2) An expression splice can in principle mention *any* variable, so the renamer really has to assume that it does when doing depdendency analysis. For example f = ... h = ...$(thing "f")... The renamer had better not put 'h' before 'f', else the type checker won't find a defn for 'f' in the type envt. TH_spliceE5 is the test
* [project @ 2005-10-26 10:23:47 by simonpj]simonpj2005-10-262-5/+6
| | | | Cosmetics
* [project @ 2005-10-25 15:04:58 by simonmar]simonmar2005-10-252-0/+27
| | | | add missing boot files
* [project @ 2005-10-25 12:48:35 by simonmar]simonmar2005-10-2516-222/+363
| | | | | | | | | | | | | | | | | | | | | | | | | | | Two changes from Krasimir Angelov, which were required for Visual Haskell: - messaging cleanup throughout the compiler. DynFlags has a new field: log_action :: Severity -> SrcSpan -> PprStyle -> Message -> IO () this action is invoked for every message generated by the compiler. This means a client of the GHC API can direct messages to any destination, or collect them up in an IORef for later perusal. This replaces previous hacks to redirect messages in the GHC API (hence some changes to function types in GHC.hs). - The JustTypecheck mode of GHC now does what it says. It doesn't run any of the compiler passes beyond the typechecker for each module, but does generate the ModIface in order that further modules can be typechecked. And one change from me: - implement the LANGUAGE pragma, finally
* [project @ 2005-10-25 10:48:44 by simonmar]simonmar2005-10-251-5/+0
| | | | companion to Lexer.x rev. 1.29; columns now always count tabs as 1 in SrcLoc.
* [project @ 2005-10-21 14:02:17 by simonmar]simonmar2005-10-211-6/+10
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Big re-hash of the threaded/SMP runtime This is a significant reworking of the threaded and SMP parts of the runtime. There are two overall goals here: - To push down the scheduler lock, reducing contention and allowing more parts of the system to run without locks. In particular, the scheduler does not require a lock any more in the common case. - To improve affinity, so that running Haskell threads stick to the same OS threads as much as possible. At this point we have the basic structure working, but there are some pieces missing. I believe it's reasonably stable - the important parts of the testsuite pass in all the (normal,threaded,SMP) ways. In more detail: - Each capability now has a run queue, instead of one global run queue. The Capability and Task APIs have been completely rewritten; see Capability.h and Task.h for the details. - Each capability has its own pool of worker Tasks. Hence, Haskell threads on a Capability's run queue will run on the same worker Task(s). As long as the OS is doing something reasonable, this should mean they usually stick to the same CPU. Another way to look at this is that we're assuming each Capability is associated with a fixed CPU. - What used to be StgMainThread is now part of the Task structure. Every OS thread in the runtime has an associated Task, and it can ask for its current Task at any time with myTask(). - removed RTS_SUPPORTS_THREADS symbol, use THREADED_RTS instead (it is now defined for SMP too). - The RtsAPI has had to change; we must explicitly pass a Capability around now. The previous interface assumed some global state. SchedAPI has also changed a lot. - The OSThreads API now supports thread-local storage, used to implement myTask(), although it could be done more efficiently using gcc's __thread extension when available. - I've moved some POSIX-specific stuff into the posix subdirectory, moving in the direction of separating out platform-specific implementations. - lots of lock-debugging and assertions in the runtime. In particular, when DEBUG is on, we catch multiple ACQUIRE_LOCK()s, and there is also an ASSERT_LOCK_HELD() call. What's missing so far: - I have almost certainly broken the Win32 build, will fix soon. - any kind of thread migration or load balancing. This is high up the agenda, though. - various performance tweaks to do - throwTo and forkProcess still do not work in SMP mode
* [project @ 2005-10-20 14:00:36 by simonmar]simonmar2005-10-201-31/+42
| | | | | | | | | | Column numbers in SrcLocs are now counted as the number of characters, rather than columns. i.e. a tab always counts as 1. This was necessary for communication with Visual Studio interfaces which expect character indices, but also it seems the majority of other compilers also do things this way. From: Krasimir Angelov <kr.angelov@gmail.com>
* [project @ 2005-10-20 00:52:38 by sof]sof2005-10-201-11/+12
| | | | [mingw]delay flushing console buffer until last possible moment. Merge to STABLE
* [project @ 2005-10-17 11:11:15 by simonpj]simonpj2005-10-173-14/+16
| | | | Buglets in GADT record-syntax stuff, which killed the weekend builds
* [project @ 2005-10-17 11:10:36 by simonpj]simonpj2005-10-171-10/+18
| | | | | | | | | | | | | | | | | | | | | | | | | Small simplifier bug in case optimisation ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The simplifier eliminates redundant case branches, and panics if there are no case alternatives. But due to a slightly delayed instantiation of a type constructor variable 'p' by a type constructor 'P', it turned out that an inner case had no alternatives at all, becuase an outer case had not pruned a branch as quickly as it should have. This commit fixes both problems: a) SimplUtils.mkCase1 now returns a call to 'error' (instead of panicing) when it gets an empty list of alternatives. Somewhat analogous to the inaccessible GADT case in Simplify.simplifyAlt b) In SimplUtils.prepareDefault, use the up-to-date scrutinee, rather than the less up-to-date case_bndr, to get the case type constructor. That leads to slightly earlier pruning of inaccessible branches. Fixes a bug reported by Ian Lynagh. Test is simplCore/should_compile/simpl013
* [project @ 2005-10-17 11:09:51 by simonpj]simonpj2005-10-171-3/+4
| | | | Comments only
* [project @ 2005-10-14 12:29:53 by simonmar]simonmar2005-10-141-21/+39
| | | | | | | | | | | | | | | | | | | | | Some more informative diagnostics for ghc -v about what the package system is doing. This should help when diagnosing strange-looking errors from GHC: Using package config file: /home/simonmar/fp/lib/i386-unknown-linux/ghc-6.4.1/package.conf package posix-1.0 will be ignored due to missing dependencies: lang-1.0 package util-1.0 will be ignored due to missing dependencies: lang-1.0 package data-1.0 will be ignored due to missing dependencies: lang-1.0 package text-1.0 will be ignored due to missing dependencies: lang-1.0 package Cabal-1.1.4 will be ignored due to missing dependencies: util-1.0 *** Deleting temp files Deleting: ghc-6.4.1: unknown package: Cabal-1.1.4
* [project @ 2005-10-14 11:48:56 by simonmar]simonmar2005-10-141-2/+2
| | | | Fix a couple of problems with the "unknown package" error message
* [project @ 2005-10-14 11:22:41 by simonpj]simonpj2005-10-1430-438/+630
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Add record syntax for GADTs ~~~~~~~~~~~~~~~~~~~~~~~~~~~ Atrijus Tang wanted to add record syntax for GADTs and existential types, so he and I worked on it a bit at ICFP. This commit is the result. Now you can say data T a where T1 { x :: a } :: T [a] T2 { x :: a, y :: Int } :: T [a] forall b. Show b => T3 { naughty :: b, ok :: Int } :: T Int T4 :: Eq a => a -> b -> T (a,b) Here the constructors are declared using record syntax. Still to come after this commit: - User manual documentation - More regression tests - Some missing cases in the parser (e.g. T3 won't parse) Autrijus is going to do these. Here's a quick summary of the rules. (Atrijus is going to write proper documentation shortly.) Defnition: a 'vanilla' constructor has a type of the form forall a1..an. t1 -> ... -> tm -> T a1 ... an No existentials, no context, nothing. A constructor declared with Haskell-98 syntax is vanilla by construction. A constructor declared with GADT-style syntax is vanilla iff its type looks like the above. (In the latter case, the order of the type variables does not matter.) * You can mix record syntax and non-record syntax in a single decl * All constructors that share a common field 'x' must have the same result type (T [a] in the example). * You can use field names without restriction in record construction and record pattern matching. * Record *update* only works for data types that only have 'vanilla' constructors. * Consider the field 'naughty', which uses a type variable that does not appear in the result type ('b' in the example). You can use the field 'naughty' in pattern matching and construction, but NO SELECTOR function is generated for 'naughty'. [An attempt to use 'naughty' as a selector function will elicit a helpful error message.] * Data types declared in GADT syntax cannot have a context. So this is illegal: data (Monad m) => T a where .... * Constructors in GADT syntax can have a context (t.g. T3, T4 above) and that context is stored in the constructor and made available when the constructor is pattern-matched on. WARNING: not competely implemented yet, but that's the plan. Implementation notes ~~~~~~~~~~~~~~~~~~~~ - Data constructors (even vanilla ones) no longer share the type variables of their parent type constructor. - HsDecls.ConDecl has changed quite a bit - TyCons don't record the field labels and type any more (doesn't make sense for existential fields) - GlobalIdDetails records which selectors are 'naughty', and hence don't have real code.
* [project @ 2005-10-12 13:31:12 by simonpj]simonpj2005-10-121-30/+40
| | | | | | | | | MERGE TO STABLE Fix a bug in TcUnify.unifyTyConApp that made a GADT program fail. The trouble happens if the type that we are expecting to be a TyConApp is of form (m a b), where 'm' is refined to a type constructor. Then we want to get nice rigid results, and we weren't.
* [project @ 2005-10-12 13:29:12 by simonpj]simonpj2005-10-121-23/+24
| | | | Small refactoring
* [project @ 2005-10-07 11:01:47 by simonmar]simonmar2005-10-071-1/+2
| | | | | Fix a bug I just found: hiding a package if later versions are exposed wasn't actually checking the exposed flag.
* [project @ 2005-10-06 10:41:15 by simonmar]simonmar2005-10-061-1/+1
| | | | | | comment typo From: Autrijus Tang <autrijus@autrijus.org>
* [project @ 2005-10-06 10:40:40 by simonmar]simonmar2005-10-061-1/+1
| | | | | | remove old comment From: Autrijus Tang <autrijus@autrijus.org>
* [project @ 2005-10-06 10:40:10 by simonmar]simonmar2005-10-061-1/+7
| | | | | | add dataConFieldType From: Autrijus Tang <autrijus@autrijus.org>