- 18 Jun, 2011 4 commits
-
-
dterei authored
While we previously checked the safety of safe imported modules we didn't do this check transitively. This can be a problem when we depend on a trustworthy module in a package that is no longer trusted, so we should fail compilation. We already stored in an interface file the transitive list of packages a module depends on. Now we extend that list to include a flag saying if we depend on that package being trusted as well.
-
dterei authored
This patch disables the use of some GHC extensions in Safe mode and also the use of certain flags. Some are disabled completely while others are only allowed on the command line and not in source PRAGMAS. We also check that Safe imports are indeed importing a Safe or Trustworthy module.
-
dterei authored
-
dterei authored
-
- 16 Jun, 2011 1 commit
-
-
Simon Peyton Jones authored
See the long Note [Binders in Template Haskell] in Convert.lhs which explains it all. This patch fixes Trac #5037. The key change is that NameU binders (ones made up by newName in Template Haskell, and by TH quotations) now make Exact RdrNames again, rather than making RdrNames with heavily encoded OccNames like x[03cv]. (This encoding is what was making #5037 fail.)
-
- 13 Jun, 2011 1 commit
-
-
chak@cse.unsw.edu.au. authored
-
- 11 Jun, 2011 2 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
The issue here was: what import declaration brings into scope the 'op here import qualified Foo( op ) import Bar( C(op) ) instance C Int where op = ... Well, the import of Bar, obviously. But what if the import Bar had been import Bar( C ) Then the instance is still supposed to work, getting op from the Foo.op imported from Foo. (I'm assuming its the same op, of course.)
-
- 10 Jun, 2011 2 commits
-
-
waern authored
This is a merge of a patch contributed by Michal Terepeta and the recent generics changes.
-
Simon Peyton Jones authored
The general rule is now that we don't complain about a duplicate export from a "...". See RnNames.dupExport_ok
-
- 09 Jun, 2011 1 commit
-
-
Ian Lynagh authored
The "Unhelpful" cases are now in a separate type. This allows us to improve various things, e.g.: * Most of the panic's in SrcLoc are now gone * The Lexer now works with RealSrcSpans rather than SrcSpans, i.e. it knows that it has real locations and thus can assume that the line number etc really exists * Some of the more suspicious cases are no longer necessary, e.g. we no longer need this case in advanceSrcLoc: advanceSrcLoc loc _ = loc -- Better than nothing More improvements can probably be made, e.g. tick locations can probably use RealSrcSpans too.
-
- 09 May, 2011 1 commit
-
-
Simon Peyton Jones authored
This was making mc17 fail.
-
- 04 May, 2011 4 commits
-
-
Simon Peyton Jones authored
Fixes Trac #4851
-
dreixel authored
They belonged to the old generic deriving mechanism, so they can go. Adapted a lot of code as a consequence.
-
Simon Peyton Jones authored
* Do-notation in arrows is marked with HsStmtContext = ArrowExpr * tcMDoStmt (which was only used for arrows) is moved to TcArrows, and renamed tcArrDoStmt * Improved documentation in the user manual * Lots of other minor changes
-
dreixel authored
Add a new flag XDefaultSignatures to enable just the signatures on the default methods. Redefine the behavior of XGenerics to mean enable XDefaultSignatures and XDeriveRepresentable.
-
- 03 May, 2011 1 commit
-
-
Simon Peyton Jones authored
Lots of refactoring. In particular I have now combined TansformStmt and GroupStmt into a single constructor TransStmt. This gives lots of useful code sharing.
-
- 02 May, 2011 2 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
- 29 Apr, 2011 1 commit
-
-
Simon Peyton Jones authored
-
- 28 Apr, 2011 2 commits
-
-
Simon Peyton Jones authored
This is the work of Nils Schweinsberg <mail@n-sch.de> It adds the language extension -XMonadComprehensions, which generalises list comprehension syntax [ e | x <- xs] to work over arbitrary monads.
-
Simon Peyton Jones authored
Also get rid of the old {| |} brackets in the lexer. Fewer keywords!
-
- 26 Apr, 2011 1 commit
-
-
dterei authored
-
- 20 Apr, 2011 1 commit
-
-
Simon Peyton Jones authored
In RnBinds.rnValBindsRHS I had (sig_dus `plusDU` bind_dus) when it should be (bind_dus `plusDU` sig_dus) So the fix is easy.
-
- 19 Apr, 2011 3 commits
-
-
simonpj authored
-
simonpj authored
-
Simon Peyton Jones authored
See the paper "Practical aspects of evidence based compilation in System FC" * Coercion becomes a data type, distinct from Type * Coercions become value-level things, rather than type-level things, (although the value is zero bits wide, like the State token) A consequence is that a coerion abstraction increases the arity by 1 (just like a dictionary abstraction) * There is a new constructor in CoreExpr, namely Coercion, to inject coercions into terms
-
- 12 Apr, 2011 1 commit
-
-
simonpj authored
(See his Haskell Symposium 2010 paper "A generic deriving mechaism for Haskell")
-
- 02 Apr, 2011 1 commit
-
-
batterseapower authored
We collect variables introduced by the {...} part of a let-like record wildcard pattern and do not warn if the user then doesn't actually use them.
-
- 06 Mar, 2011 1 commit
-
-
simonpj@microsoft.com authored
Also change the behaviour slightly, to warn only for *unqualified* imports. See Trac #4977.
-
- 20 Feb, 2011 1 commit
-
-
chak@cse.unsw.edu.au. authored
- Added a pragma {-# VECTORISE var = exp #-} that prevents the vectoriser from vectorising the definition of 'var'. Instead it uses the binding '$v_var = exp' to vectorise 'var'. The vectoriser checks that the Core type of 'exp' matches the vectorised Core type of 'var'. (It would be quite complicated to perform that check in the type checker as the vectorisation of a type needs the state of the VM monad.) - Added parts of a related VECTORISE SCALAR pragma - Documented -ddump-vect - Added -ddump-vt-trace - Some clean up
-
- 12 Jan, 2011 1 commit
-
-
simonpj@microsoft.com authored
Fixes Trac #4877.
-
- 10 Jan, 2011 1 commit
-
-
simonpj@microsoft.com authored
This patch fixes Trac #4875. The main point is to do dependency analysis on type and class declarations, and kind-check them in dependency order, so as to improve error messages. This patch means that a few programs that would typecheck before won't typecheck any more; but before we were (naughtily) going beyond Haskell 98 without any language-extension flags, and Trac #4875 convinces me that doing so is a Bad Idea. Here's an example that won't typecheck any more data T a b = MkT (a b) type F k = T k Maybe If you look at T on its own you'd default 'a' to kind *->*; and then kind-checking would fail on F. But GHC currently accepts this program beause it looks at the *occurrences* of T.
-
- 27 Nov, 2010 1 commit
-
-
Michal Terepeta authored
-
- 22 Dec, 2010 2 commits
-
-
simonpj@microsoft.com authored
...so that you get helpful suggestions when you mis-spell a name Based on Max's patch in Trac #2442, but heavily refactored.
-
simonpj@microsoft.com authored
For a long time an 'mdo' expression has had a SyntaxTable attached to it. However, we're busy deprecating SyntaxTables in favour of rebindable syntax attached to individual Stmts, and MDoExpr was totally inconsistent with DoExpr in this regard. This patch tidies it all up. Now there's no SyntaxTable on MDoExpr, and 'modo' is generally handled much more like 'do'. There is resulting small change in behaviour: now MonadFix is required only if you actually *use* recursion in mdo. This seems consistent with the implicit dependency analysis that is done for mdo. Still to do: * Deal with #4148 (this patch is on the way) * Get rid of the last remaining SyntaxTable on HsCmdTop
-
- 19 Dec, 2010 1 commit
-
-
Ian Lynagh authored
-
- 10 Dec, 2010 1 commit
-
-
simonpj@microsoft.com authored
The renamer wasn't attaching the right used-variables to a TransformStmt constructor. The real modification is in RnExpr; the rest is just pretty-printing and white space.
-
- 27 Nov, 2010 1 commit
-
-
Michal Terepeta authored
But only when the module exports refer to different modules. See ticket #4478.
-
- 30 Oct, 2010 1 commit
-
-
Michal Terepeta authored
-