- 22 Jan, 2008 2 commits
-
-
Simon Marlow authored
-
Simon Marlow authored
-
- 21 Jan, 2008 9 commits
-
-
claus.reinke@talk21.com authored
- #1839 asks for a ghc-pkg dump feature, #1463 for the ability to query the same fields in several packages at once. - this patch enables substring matching for packages in 'list', 'describe', and 'field', and for modules in find-module. it also allows for comma-separated multiple fields in 'field'. substring matching can optionally ignore cases to avoid the rather unpredictable capitalisation of packages. - the patch is not quite as full-featured as the one attached to #1839, but avoids the additional dependency on regexps. open ended substrings are indicated by '*' (only the three forms prefix*, *suffix, *infix* are supported) - on windows, the use of '*' for package/module name globbing leads to conflicts with filename globbing: by default, windows programs are self-globbing, and bash adds another level of globbing on top of that. it seems impossible to escape '*' from both levels of globbing, so we disable default globbing for ghc-pkg and ghc-pkg-inplace. users of bash will still have filename globbing available, users of cmd won't. - if it is considered necessary to reenable filename globbing for cmd users, it should be done selectively, only for filename parameters. to this end, the patch includes a glob.hs program which simply echoes its parameters after filename globbing. see the commented out glob command in Main.hs for usage or testing. - this covers both tickets, and permits for the most common query patterns (finding all packages contributing to the System. hierarchy, finding all regex or string packages, listing all package maintainers or haddock directories, ..), which not only i have wanted to have for a long time. examples (the quotes are needed to escape shell-based filename globbing and should be omitted in cmd.exe): ghc-pkg list '*regex*' --ignore-case ghc-pkg list '*string*' --ignore-case ghc-pkg list '*gl*' --ignore-case ghc-pkg find-module 'Data.*' ghc-pkg find-module '*Monad*' ghc-pkg field '*' name,maintainer ghc-pkg field '*' haddock-html ghc-pkg describe '*'
-
simonpj@microsoft.com authored
-
Simon Marlow authored
The previous attempt to fix this (#1873, #1360) left a problem that occurred when the first :load of the program failed (#2049). Now I've implemented a different strategy: between :loads, we remember all the :module commands, and just replay them after a :reload. This is in addition to remembering all the package modules added with :module, which is orthogonal. This approach is simpler than the previous one, and seems to do the right thing in all the cases I could think of. Let's hope this is the last bug in this series...
-
Simon Marlow authored
- remove $(ghc_ge_601), $(ghc_ge_602), $(ghc_ge_603) - configure now checks the GHC version number - there are probably various cleanups that we can now do in compat/ and compiler/, but I haven't done those yet.
-
simonpj@microsoft.com authored
This patch stops the worker/wrapper transform working on an INLINE thing, even if it's in a recursive group. It might not be the loop breaker. Indeed a recursive group might have no loop breaker, if the only recursion is through rules. Again, this change was provoked by one of Roman's NDP libraries. Specifically the Rec { splitD, splitJoinD } group in Data.Array.Parallel.Unlifted.Distributed.Arrays Simon
-
simonpj@microsoft.com authored
This is another gloss on the now-quite-subtle and heavily-documented algorithm for choosing loop breakers. This fix, provoked by Roman's NDP library, makes sure that when we are choosing a loop breaker we only take into account variables free on the *rhs* of a rule not the *lhs*. Most of the new lines are comments!
-
simonpj@microsoft.com authored
Sorry, this was my fault, a consequence of the quasi-quoting patch. I've added rn062 as a test.
-
Ian Lynagh authored
When running with ghc -e, exceptions should claim to be from the program that we are running, not ghc.
-
Ian Lynagh authored
-
- 20 Jan, 2008 3 commits
-
-
Ian Lynagh authored
-
Ian Lynagh authored
-
Ian Lynagh authored
-
- 21 Jan, 2008 1 commit
-
-
simonpj@microsoft.com authored
-
- 19 Jan, 2008 6 commits
-
-
Ian Lynagh authored
-
Ian Lynagh authored
-
Ian Lynagh authored
-
Ian Lynagh authored
-
Ian Lynagh authored
-
Ian Lynagh authored
You can now give :main a Haskell [String] as an argument, e.g. :main ["foo", "bar"] and :run is a variant that takes the name of the function to run. Also, :main now obeys the -main-is flag.
-
- 17 Dec, 2007 1 commit
-
-
judah.jacobson@gmail.com authored
-
- 27 Nov, 2007 1 commit
-
-
judah.jacobson@gmail.com authored
-
- 12 Dec, 2007 1 commit
-
-
judah.jacobson@gmail.com authored
-
- 10 Dec, 2007 1 commit
-
-
df@dfranke.us authored
-
- 18 Jan, 2008 2 commits
-
-
Ian Lynagh authored
-
Ian Lynagh authored
-
- 16 Jan, 2008 1 commit
-
-
Ian Lynagh authored
We were generating a label ".LnLC7", which the splitter was confusing with a literal constant (LC). The end result was the assembler tripping up on ".Ln.text".
-
- 18 Jan, 2008 2 commits
-
-
simonpj@microsoft.com authored
I've gotten this wrong more than once. Hopefully this has it nailed. The issue is that in float-out we must abstract over the correct variables.
-
simonpj@microsoft.com authored
This patch adds quasi-quotation, as described in "Nice to be Quoted: Quasiquoting for Haskell" (Geoffrey Mainland, Haskell Workshop 2007) Implemented by Geoffrey and polished by Simon. Overview ~~~~~~~~ The syntax for quasiquotation is very similar to the existing Template haskell syntax: [$q| stuff |] where 'q' is the "quoter". This syntax differs from the paper, by using a '$' rather than ':', to avoid clashing with parallel array comprehensions. The "quoter" is a value of type Language.Haskell.TH.Quote.QuasiQuoter, which contains two functions for quoting expressions and patterns, respectively. quote = Language.Haskell.TH.Quote.QuasiQuoter quoteExp quotePat quoteExp :: String -> Language.Haskell.TH.ExpQ quotePat :: String -> Language.Haskell.TH.PatQ TEXT is passed unmodified to the quoter. The context of the quasiquotation statement determines which of the two quoters is called: if the quasiquotation occurs in an expression context, quoteExp is called, and if it occurs in a pattern context, quotePat is called. The result of running the quoter on its arguments is spliced into the program using Template Haskell's existing mechanisms for splicing in code. Note that although Template Haskell does not support pattern brackets, with this patch binding occurrences of variables in patterns are supported. Quoters must also obey the same stage restrictions as Template Haskell; in particular, in this example quote may not be defined in the module where it is used as a quasiquoter, but must be imported from another module. Points to notice ~~~~~~~~~~~~~~~~ * The whole thing is enabled with the flag -XQuasiQuotes * There is an accompanying patch to the template-haskell library. This involves one interface change: currentModule :: Q String is replaced by location :: Q Loc where Loc is a data type defined in TH.Syntax thus: data Loc = Loc { loc_filename :: String , loc_package :: String , loc_module :: String , loc_start :: CharPos , loc_end :: CharPos } type CharPos = (Int, Int) -- Line and character position So you get a lot more info from 'location' than from 'currentModule'. The location you get is the location of the splice. This works in Template Haskell too of course, and lets a TH program generate much better error messages. * There's also a new module in the template-haskell package called Language.Haskell.TH.Quote, which contains support code for the quasi-quoting feature. * Quasi-quote splices are run *in the renamer* because they can build *patterns* and hence the renamer needs to see the output of running the splice. This involved a bit of rejigging in the renamer, especially concerning the reporting of duplicate or shadowed names. (In fact I found and removed a few calls to checkDupNames in RnSource that are redundant, becuase top-level duplicate decls are handled in RnNames.)
-
- 17 Jan, 2008 7 commits
-
-
Isaac Dupree authored
re-recording to avoid new conflicts was too hard, so I just put it all in one big patch :-( (besides, some of the changes depended on each other.) Here are what the component patches were: Fri Dec 28 11:02:55 EST 2007 Isaac Dupree <id@isaac.cedarswampstudios.org> * document BreakArray better Fri Dec 28 11:39:22 EST 2007 Isaac Dupree <id@isaac.cedarswampstudios.org> * properly ifdef BreakArray for GHCI Fri Jan 4 13:50:41 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * change ifs on __GLASGOW_HASKELL__ to account for... (#1405) for it not being defined. I assume it being undefined implies a compiler with relatively modern libraries but without most unportable glasgow extensions. Fri Jan 4 14:21:21 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * MyEither-->EitherString to allow Haskell98 instance Fri Jan 4 16:13:29 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * re-portabilize Pretty, and corresponding changes Fri Jan 4 17:19:55 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * Augment FastTypes to be much more complete Fri Jan 4 20:14:19 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * use FastFunctions, cleanup FastString slightly Fri Jan 4 21:00:22 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * Massive de-"#", mostly Int# --> FastInt (#1405) Fri Jan 4 21:02:49 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * miscellaneous unnecessary-extension-removal Sat Jan 5 19:30:13 EST 2008 Isaac Dupree <id@isaac.cedarswampstudios.org> * add FastFunctions
-
simonpj@microsoft.com authored
Oops -- missed this from previous commit; sorry
-
simonpj@microsoft.com authored
This patch addresses a problem that Roman found in SpecConstr. Consider: foo :: Maybe Int -> Maybe Int -> Int foo a b = let j b = foo a b in case b of Nothing -> ... Just n -> case a of Just m -> ... j (Just (n+1)) ... Nothing -> ... j (Just (n-1)) ... We want to make specialised versions for 'foo' for the patterns Nothing (Just v) (Just a) (Just b) Two problems, caused by the join point j. First, j does not scrutinise b, so j won't be specialised f for the (Just v) pattern. Second, j is defined where the free var 'a' is not evaluated. Both are solved by brutally inlining j at its call sites. This risks major code bloat, but it's relatively quick to implement. The flag -fspec-inline-join-points causes brutal inlining for a non-recursive binding of a function whose RHS contains calls of a recursive function The (experimental) flag is static for now, and I have not even documented it properly.
-
Clemens Fruhwirth authored
-
simonpj@microsoft.com authored
-
simonpj@microsoft.com authored
-
simonpj@microsoft.com authored
The add_evals code in Simplify.simplAlt had bit-rotted. Example: data T a = T !a data U a = U !a foo :: T a -> U a foo (T x) = U x Here we should not evaluate x before building the U result, because the x argument of T is already evaluated. Thanks to Roman for finding this.
-
- 16 Jan, 2008 3 commits
-
-
simonpj@microsoft.com authored
I can't remember where this bug showed up, but we were abstracting over a coercion variable (co :: a ~ T), without also abstracting over 'a'. The fix is simple.
-
simonpj@microsoft.com authored
-
simonpj@microsoft.com authored
This fixes Trac #2024; worth merging onto 6.8 branch.
-