| Commit message (Collapse) | Author | Age | Files | Lines |
... | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We simply weren't giving anything like the right instantiating types
to patSynInstArgTys in matchOneConLike.
To get these instantiating types would have involved matching the
result type of the pattern synonym with the pattern type, which is
tiresome. So instead I changed ConPatOut so that instead of recording
the type of the *whole* pattern (in old field pat_ty), it not records
the *instantiating* types (in new field pat_arg_tys). Then we canuse
TcHsSyn.conLikeResTy to get the pattern type when needed.
There are lots of knock-on incidental effects, but they mostly made
the code simpler, so I'm happy.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been
reorganized, while following the convention, to
- place `{-# LANGUAGE #-}` pragmas at the top of the source file, before
any `{-# OPTIONS_GHC #-}`-lines.
- Moreover, if the list of language extensions fit into a single
`{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one
line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each
individual language extension. In both cases, try to keep the
enumeration alphabetically ordered.
(The latter layout is preferable as it's more diff-friendly)
While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma
occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
|
|
|
|
| |
Signed-off-by: Austin Seipp <austin@well-typed.com>
|
| |
|
|
|
|
|
|
|
|
|
|
| |
This is just making the parser behave more sensibly, and return
the list [x,y,z] from the signature
x,y,z :: Int
rathe than [x,z,y] as now.
Turns out that the other use of sig_vars *did* do the right
thing already.
|
|
|
|
|
|
|
|
|
| |
Patch submitted by an anonymous friend on the bug tracker.
This also fixes TH_RichKinds2 which had a slight message output wibble
(it uses the qualified name of the promoted datacon)
Signed-off-by: Austin Seipp <austin@well-typed.com>
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch implements Pattern Synonyms (enabled by -XPatternSynonyms),
allowing y ou to assign names to a pattern and abstract over it.
The rundown is this:
* Named patterns are introduced by the new 'pattern' keyword, and can
be either *unidirectional* or *bidirectional*. A unidirectional
pattern is, in the simplest sense, simply an 'alias' for a pattern,
where the LHS may mention variables to occur in the RHS. A
bidirectional pattern synonym occurs when a pattern may also be used
in expression context.
* Unidirectional patterns are declared like thus:
pattern P x <- x:_
The synonym 'P' may only occur in a pattern context:
foo :: [Int] -> Maybe Int
foo (P x) = Just x
foo _ = Nothing
* Bidirectional patterns are declared like thus:
pattern P x y = [x, y]
Here, P may not only occur as a pattern, but also as an expression
when given values for 'x' and 'y', i.e.
bar :: Int -> [Int]
bar x = P x 10
* Patterns can't yet have their own type signatures; signatures are inferred.
* Pattern synonyms may not be recursive, c.f. type synonyms.
* Pattern synonyms are also exported/imported using the 'pattern'
keyword in an import/export decl, i.e.
module Foo (pattern Bar) where ...
Note that pattern synonyms share the namespace of constructors, so
this disambiguation is required as a there may also be a 'Bar'
type in scope as well as the 'Bar' pattern.
* The semantics of a pattern synonym differ slightly from a typical
pattern: when using a synonym, the pattern itself is matched,
followed by all the arguments. This means that the strictness
differs slightly:
pattern P x y <- [x, y]
f (P True True) = True
f _ = False
g [True, True] = True
g _ = False
In the example, while `g (False:undefined)` evaluates to False,
`f (False:undefined)` results in undefined as both `x` and `y`
arguments are matched to `True`.
For more information, see the wiki:
https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms
https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms/Implementation
Reviewed-by: Simon Peyton Jones <simonpj@microsoft.com>
Signed-off-by: Austin Seipp <austin@well-typed.com>
|
|
|
|
|
|
|
|
|
|
|
| |
This reverts commit 174577912de7a21b8fe01881a28f5aafce02b92e.
This is part of the fix for #8607. Only reverting RdrHsSyn.lhs.
Conflicts:
compiler/parser/RdrHsSyn.lhs
compiler/typecheck/TcTyClsDecls.lhs
|
| |
|
|
|
|
|
| |
The lexer now uses unicode single quotation marks in its error messages
if possible. This is due to the use of the 'quotes' combinator.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The handling of typed and untyped brackets was extremely convoluted,
partly because of the evolutionary history. I've tidied it all up.
See Note [How brackets and nested splices are handled] in TcSplice
for the full story
Main changes:
* Untyped brackets: after the renamer, HsRnBracketOut carries
PendingRnSplices for splices in untyped brackets. In the
typechecker, these pending splices are typechecked quite
straigtforwardly, with no ps_var nonsense.
* Typed brackets: after the renamer typed brackest still look
like HsBracket. The type checker does the ps_var thing.
* In TcRnTypes.ThStage, the Brack constructor, we distinguish
the renaming from typehecking pending-stuff. Much more
perspicuous!
* The "typed" flag is in HsSpliceE, not in HsSplice, because
only expressions can be typed. Patterns, types, declarations
cannot.
There is further improvement to be done to make the handling of
declaration splices more uniform.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is to allow
class C a where
type family F a
type instance F a = Bool
instance C Int where
type instance F Int = Char
Plus minor improvements relating to Trac #8506
|
| |
|
| |
|
| |
|
|
|
|
| |
This commit moves the check from parser to renamer.
|
| |
|
|
|
|
| |
Patch by errge
|
| |
|
|
|
|
|
| |
Since declaration splices are now untyped, they can be used anywhere a
declaration is valid, including in declaration brackets.
|
| |
|
| |
|
| |
|
|
|
|
|
| |
Right now the syntax for typed expression brackets and splices maps to
conventional brackets and splices, i.e., they are not typed.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Instead of walking over the source decls, and looking up the Name
to find the TyCon or whatever, we just walk over the list of
TyThings that have been brought into scope. This is much tidier.
The only wrinkle is that, since we don't have the original declaration,
we don't have its SrcSpan to put in the error message. I fixed this
by making the SrcSpan for the TyCon itself be the span of the whole
declaration. This actually makes sense anyway.
There are bunch of error message wibbles in consequence.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This makes it possible to write
x = if | False -> if | False -> 1
| False -> 2
| True -> 3
Layout normally inserts semicolons between declarations at the same
indentation level, so I added optional semicolons to the syntax for
guards in MultiWayIf syntax. This is a bit of a hack, but the
alternative (a special kind of layout that doesn't insert semicolons)
seemed worse, or at least equally bad.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit adds a `{-# MINIMAL #-}` pragma, which defines the possible
minimal complete definitions for a class. The body of the pragma is a
boolean formula of names.
The old warning for missing methods is replaced with this new one.
Note: The interface file format is changed to store the minimal complete
definition.
Authored-by: Twan van Laarhoven <twanvl@gmail.com>
Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org>
|
|
|
|
|
|
|
|
|
| |
This fixes bugs #8185, #8234, and #8246. The new syntax is explained
in the comments to #8185, appears in the "Roles" subsection of the
manual, and on the [wiki:Roles] wiki page.
This change also removes the ability for a role annotation on type
synonyms, as noted in #8234.
|
|
|
|
|
|
|
|
|
|
|
| |
As Krzysztof pointed out in #8306, with NegativeLiterals and DataKinds,
definitions such as:
type T = -1
were accepted, although type literals must be greater than zero.
Signed-off-by: Austin Seipp <austin@well-typed.com>
|
|
|
|
| |
for easier copy'n'paste. This fixes: #3647
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In 9e133b, the build was modified to pass -fcmm-sink to Parser, but
unfortunately Parser specifies -O0 in its OPTIONS_GHC directive, meaning
the sinking pass was actually turned off.
HC_OPTS is the last thing passed to the compiler for that source file
however, so the correct fix is to also move -O0 out into the build
system as well.
This was uncovered thanks to a build report from Kazu Yamamoto. Thanks
to Jan Stolarek for eyeballing this bug and finding it.
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch encompasses most of the basic infrastructure for GHCJS. It
includes:
* A new extension, -XJavaScriptFFI
* A new architecture, ArchJavaScript
* Parser and lexer support for 'foreign import javascript', only
available under -XJavaScriptFFI, using ArchJavaScript.
* As a knock-on, there is also a new 'WayCustom' constructor in
DynFlags, so clients of the GHC API can add custom 'tags' to their
built files. This should be useful for other users as well.
The remaining changes are really just the resulting fallout, making sure
all the cases are handled appropriately for DynFlags and Platform.
Authored-by: Luite Stegeman <stegeman@gmail.com>
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Parser.hs needs to be compiled with -fcmm-sink on x86 platforms, so the
register allocator doesn't run out of stack slots. Previously, we had to
do some CPP hacks in order to emit an #ifdef into the file - this is
because we preprocess it once up front, and run the preprocessor again
when we compile it.
There's two cases: the boostrap compiler is > 7.8, and the stage1 parser
needs the flag, or the stage1 compiler is compiling the stage2
Parser.hs, and needs the flag..
The previous approach was super fragile with Clang. The more principled
fix is to instead do this through the build system.
This fixes #8182.
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
|
| |
happy reads .y files with the system encoding, so keep Parser.y.pp ASCII.
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fixes Trac #7901.
'∀' is neither upper nor lowercase, unlike the 'f' in 'forall', so when
explicit forall is not enabled, it creates a parse error before reaching
the '.', which is where we give a nice message for ascii 'forall'.
Therefore, we make '∀' into a token as long as UnicodeSyntax is enabled,
which is safe because its caselessness means it can never be mistaken
for a symbol, and check extensions in the parser when the 'forall' rule
is used.
Authored-by: Paul Cavallaro <ptc@fb.com>
Authored-by: Anders Papitto <anderspapitto@gmail.com>
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
| |
Authored-by: Paul Cavallaro <ptc@fb.com>
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
| |
Authored-by: Anders Papitto <anderspapitto@gmail.com>
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
| |
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
| |
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
|
|
|
| |
As documented in the users' guide, you can now write
type family Foo a where ..
in a hs-boot file to declare an abstract closed type family.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Roles are a solution to the GeneralizedNewtypeDeriving type-safety
problem.
Roles were first described in the "Generative type abstraction" paper,
by Stephanie Weirich, Dimitrios Vytiniotis, Simon PJ, and Steve Zdancewic.
The implementation is a little different than that paper. For a quick
primer, check out Note [Roles] in Coercion. Also see
http://ghc.haskell.org/trac/ghc/wiki/Roles
and
http://ghc.haskell.org/trac/ghc/wiki/RolesImplementation
For a more formal treatment, check out docs/core-spec/core-spec.pdf.
This fixes Trac #1496, #4846, #7148.
|
|
|
|
|
|
|
|
|
|
|
| |
I'd been meaning to do this for some time, but finally got around to it
due to the overflowing literals warning. With that enabled, we were
getting a warning for
-128 :: Int8
as that is parsed as
negate (fromInteger 128)
which just happens to do the right thing, as
negate (fromInteger 128) = negate (-128) = -128
|
|
|
|
| |
No functional changes
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This commit changes the syntax and story around overlapping type
family instances. Before, we had "unbranched" instances and
"branched" instances. Now, we have closed type families and
open ones.
The behavior of open families is completely unchanged. In particular,
coincident overlap of open type family instances still works, despite
emails to the contrary.
A closed type family is declared like this:
> type family F a where
> F Int = Bool
> F a = Char
The equations are tried in order, from top to bottom, subject to
certain constraints, as described in the user manual. It is not
allowed to declare an instance of a closed family.
|
|
|
|
|
|
|
|
|
|
| |
I really wish this were a joke, but alas...
This gets me a working stage1 compiler on Linux with Clang with no
modifications. Unfortunately it won't get much farther than that for
various other reasons.
Signed-off-by: Austin Seipp <aseipp@pobox.com>
|
|
|
|
|
|
| |
We were accepting
module ExportCommaComma (id, reverse,,) where
where only 1 trailing comma should be permitted.
|
| |
|