| Commit message (Collapse) | Author | Age | Files | Lines |
... | |
|\ |
|
| | |
|
|/
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is the last major addition to the kind-polymorphism story,
by allowing (Trac #5938)
type family F a -- F :: forall k. k -> *
data T a -- T :: forall k. k -> *
type instance F (T (a :: Maybe k)) = Char
The new thing is the explicit 'k' in the type signature on 'a',
which itself is inside a type pattern for F.
Main changes are:
* HsTypes.HsBSig now has a *pair* (kvs, tvs) of binders,
the kind variables and the type variables
* extractHsTyRdrTyVars returns a pair (kvs, tvs)
and the function itself has moved from RdrHsSyn to RnTypes
* Quite a bit of fiddling with
TcHsType.tcHsPatSigType and tcPatSig
which have become a bit simpler. I'm still not satisfied
though. There's some consequential fiddling in TcRules too.
* Removed the unused HsUtils.collectSigTysFromPats
There's a consequential wibble to Haddock too
|
| |
|
|\ |
|
| |
| |
| |
| |
| | |
RdrHsSyn.extractGenericPatTyVars was a leftover from the
old generic classes.
|
|\ \
| |/
| |
| |
| |
| | |
Conflicts:
compiler/hsSyn/Convert.lhs
compiler/hsSyn/HsDecls.lhs
|
| |
| |
| |
| |
| |
| |
| |
| | |
This extension is implied by:
* TypeOperators: so that we can import/export things like (+)
* TypeFamilies: because associated type synonyms use "type T"
to name the associated type in a subordinate list.
|
| |\ |
|
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | | |
This fixes Trac #5937, where a kind variable is mentioned only
in the kind signature of a GADT
data SMaybe :: (k -> *) -> Maybe k -> * where ...
The main change is that the tcdKindSig field of TyData and TyFamily
now has type Maybe (HsBndrSig (LHsKind name)), where the HsBndrSig
part deals with the kind variables that the signature may bind.
I also removed the now-unused PostTcKind field of UserTyVar and
KindedTyVar.
|
| | | |
|
| |\ \
| | |/
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | |
| | | |
Conflicts:
compiler/coreSyn/CoreLint.lhs
compiler/deSugar/DsBinds.lhs
compiler/hsSyn/HsTypes.lhs
compiler/iface/IfaceType.lhs
compiler/rename/RnHsSyn.lhs
compiler/rename/RnTypes.lhs
compiler/stgSyn/StgLint.lhs
compiler/typecheck/TcHsType.lhs
compiler/utils/ListSetOps.lhs
|
| |\ \
| | | |
| | | |
| | | |
| | | | |
Conflicts:
compiler/coreSyn/CoreLint.lhs
|
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | | |
These are types that look like "this" and "that".
They are of kind `Symbol`, defined in module `GHC.TypeLits`.
For each type-level symbol `X`, we have a singleton type, `TSymbol X`.
The value of the singleton type can be named with the overloaded
constant `tSymbol`. Here is an example:
tSymbol :: TSymbol "Hello"
|
| |\ \ \
| | | | |
| | | | |
| | | | |
| | | | | |
Conflicts:
compiler/typecheck/TcEvidence.lhs
|
| |\ \ \ \ |
|
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | | |
Previously, only type operators starting with ":" were type constructors,
and writing "+" in a type resulted in a type variable. Now, type
variables are always ordinary identifiers, and all operators are treated
as constructors. One can still write type variables in infix form though,
for example, "a `fun` b" is a type expression with 3 type variables: "a",
"fun", and "b".
Writing (+) in an import/export list always refers to the value (+)
and not the type. To refer to the type one can write either "type (+)",
or provide an explicit suobrdinate list (e.g., "(+)()"). For clarity,
one can also combine the two, for example "type (+)(A,B,C)" is also
accepted and means the same thing as "(+)(A,B,C)" (i.e., export the type
(+), with the constructors A,B,and C).
|
| |\ \ \ \ \
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | | |
Conflicts:
compiler/typecheck/TcCanonical.lhs
compiler/typecheck/TcSMonad.lhs
|
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | | |
For the moment, the kind of the numerical literals is the type "Word"
lifted to the kind level. This should probably be changed in the future.
|
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | | |
of an HsType return RdrNames rather than (Located RdrNames).
This means less clutter, and the individual locations are
a bit arbitrary if a name occurs more than once.
|
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | |
| | | | | | | |
RHS of a data type or type synonym declaration. This can be shared
between type declarations and type *instance* declarations.
|
| |_|_|_|_|/
|/| | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | | |
This fixes Trac #5937, where a kind variable is mentioned only
in the kind signature of a GADT
data SMaybe :: (k -> *) -> Maybe k -> * where ...
The main change is that the tcdKindSig field of TyData and TyFamily
now has type Maybe (HsBndrSig (LHsKind name)), where the HsBndrSig
part deals with the kind variables that the signature may bind.
I also removed the now-unused PostTcKind field of UserTyVar and
KindedTyVar.
|
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | | |
which (finally) fills out the functionality of polymorphic kinds.
It also fixes numerous bugs.
Main changes are:
Renaming stuff
~~~~~~~~~~~~~~
* New type in HsTypes:
data HsBndrSig sig = HsBSig sig [Name]
which is used for type signatures in patterns, and kind signatures
in types. So when you say
f (x :: [a]) = x ++ x
or
data T (f :: k -> *) (x :: *) = MkT (f x)
the signatures in both cases are a HsBndrSig.
* The [Name] in HsBndrSig records the variables bound by the
pattern, that is 'a' in the first example, 'k' in the second,
and nothing in the third. The renamer initialises the field.
* As a result I was able to get rid of
RnHsSyn.extractHsTyNames :: LHsType Name -> NameSet
and its friends altogether. Deleted the entire module!
This led to some knock-on refactoring; in particular the
type renamer now returns the free variables just like the
term renamer.
Kind-checking types: mainly TcHsType
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A major change is that instead of kind-checking types in two
passes, we now do one. Under the old scheme, the first pass did
kind-checking and (hackily) annotated the HsType with the
inferred kinds; and the second pass desugared the HsType to a
Type. But now that we have kind variables inside types, the
first pass (TcHsType.tc_hs_type) can go straight to Type, and
zonking will squeeze out any kind unification variables later.
This is much nicer, but it was much more fiddly than I had expected.
The nastiest corner is this: it's very important that tc_hs_type
uses lazy constructors to build the returned type. See
Note [Zonking inside the knot] in TcHsType.
Type-checking type and class declarations: mainly TcTyClsDecls
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
I did tons of refactoring in TcTyClsDecls. Simpler and nicer now.
Typechecking bindings: mainly TcBinds
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
I rejigged (yet again) the handling of type signatures in TcBinds.
It's a bit simpler now. The main change is that tcTySigs goes
right through to a TcSigInfo in one step; previously it was split
into two, part here and part later.
Unsafe coercions
~~~~~~~~~~~~~~~~
Usually equality coercions have exactly the same kind on both
sides. But we do allow an *unsafe* coercion between Int# and Bool,
say, used in
case error Bool "flah" of { True -> 3#; False -> 0# }
-->
(error Bool "flah") |> unsafeCoerce Bool Int#
So what is the instantiation of (~#) here?
unsafeCoerce Bool Int# :: (~#) ??? Bool Int#
I'm using OpenKind here for now, but it's un-satisfying that
the lhs and rhs of the ~ don't have precisely the same kind.
More minor
~~~~~~~~~~
* HsDecl.TySynonym has its free variables attached, which makes
the cycle computation in TcTyDecls.mkSynEdges easier.
* Fixed a nasty reversed-comparison bug in FamInstEnv:
@@ -490,7 +490,7 @@ lookup_fam_inst_env' match_fun one_sided ie fam tys
n_tys = length tys
extra_tys = drop arity tys
(match_tys, add_extra_tys)
- | arity > n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys)
+ | arity < n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys)
| otherwise = (tys, \res_tys -> res_tys)
|
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | | |
This allows us to import values (i.e. non-functions) with the CAPI.
This means we can access values even if (on some or all platforms)
they are simple #defines.
|
| | | | | |
| | | | | |
| | | | | |
| | | | | | |
We no longer parse "staticfoo" as "static foo".
|
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | | |
It's not clear whether it's desirable or not, and it turns out that
the way we use coercions in GHC means we tend to lose information
about type synonyms.
|
| | | | | | |
|
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | |
| | | | | | |
You can now say
data {-# CTYPE "some_header.h" "the C type" #-} Foo = ...
I think it's rare that this will actually be needed. If the
header for a CAPI FFI import includes a
void f(ctype x);
prototype then ctype must already be defined.
However, if the header only has
#define f(p) p->j
then the type need not be defined.
But either way, it seems good practice for us to specify the header that
we need.
|
| | | | | | |
|
| |_|_|_|/
|/| | | |
| | | | |
| | | | |
| | | | |
| | | | |
| | | | | |
For now, the syntax is
type {-# CTYPE "some C type" #-} Foo = ...
newtype {-# CTYPE "some C type" #-} Foo = ...
data {-# CTYPE "some C type" #-} Foo = ...
|
| |_|_|/
|/| | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | |
| | | | |
This continues the clean up of the front end. Since they
were first invented, type and data family *instance* decls
have been in the TyClDecl data type, even though they always
treated separately.
This patch takes a step in the right direction
* The InstDecl type now includes both class instances and
type/data family instances
* The hs_tyclds field of HsGroup now never has any family
instance declarations in it
However a family instance is still a TyClDecl. It should really
be a separate type, but that's the next step.
All this was provoked by fixing Trac #5792 in the HEAD.
(I did a less invasive fix on the branch.)
|
| | | |
| | | |
| | | |
| | | | |
They weren't being lexed any more, but we still had productions!
|
| | | | |
|
| |_|/
|/| | |
|
| |/
|/|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
This patch implements the idea of deferring (most) type errors to
runtime, instead emitting only a warning at compile time. The
basic idea is very simple:
* The on-the-fly unifier in TcUnify never fails; instead if it
gets stuck it emits a constraint.
* The constraint solver tries to solve the constraints (and is
entirely unchanged, hooray).
* The remaining, unsolved constraints (if any) are passed to
TcErrors.reportUnsolved. With -fdefer-type-errors, instead of
emitting an error message, TcErrors emits a warning, AND emits
a binding for the constraint witness, binding it
to (error "the error message"), via the new form of evidence
TcEvidence.EvDelayedError. So, when the program is run,
when (and only when) that witness is needed, the program will
crash with the exact same error message that would have been
given at compile time.
Simple really. But, needless to say, the exercise forced me
into some major refactoring.
* TcErrors is almost entirely rewritten
* EvVarX and WantedEvVar have gone away entirely
* ErrUtils is changed a bit:
* New Severity field in ErrMsg
* Renamed the type Message to MsgDoc (this change
touches a lot of files trivially)
* One minor change is that in the constraint solver we try
NOT to combine insoluble constraints, like Int~Bool, else
all such type errors get combined together and result in
only one error message!
* I moved some definitions from TcSMonad to TcRnTypes,
where they seem to belong more
|
| |
| |
| |
| |
| |
| | |
This is just a tidy-up triggered by #5719. We were parsing () as a
type constructor, rather than as a HsTupleTy, but it's better dealt
with uniformly as the former, I think. Somewhat a matter of taste.
|
| |
| |
| |
| |
| |
| |
| |
| |
| | |
See Trac #5720: make the unit unboxed tuple (# #) behave uniformly
with the unit boxed tuple ()
This is actually a change in behaviour, but in a very dark corner,
so I don't think this is going to hurt anyone, and the current
behaviour is deeply strange.
|
|/
|
|
|
|
|
|
| |
We no longer have many separate, clashing getDynFlags functions
I've given each GhcMonad its own HasDynFlags instance, rather than
using UndecidableInstances to make a GhcMonad m => HasDynFlags m
instance.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The main idea is that when we unify
forall a. t1 ~ forall a. t2
we get constraints from unifying t1~t2 that mention a.
We are producing a coercion witnessing the equivalence of
the for-alls, and inside *that* coercion we need bindings
for the solved constraints arising from t1~t2.
We didn't have way to do this before. The big change is
that here's a new type TcEvidence.TcCoercion, which is
much like Coercion.Coercion except that there's a slot
for TcEvBinds in it.
This has a wave of follow-on changes. Not deep but broad.
* New module TcEvidence, which now contains the HsWrapper
TcEvBinds, EvTerm etc types that used to be in HsBinds
* The typechecker works exclusively in terms of TcCoercion.
* The desugarer converts TcCoercion to Coercion
* The main payload is in TcUnify.unifySigmaTy. This is the
function that had a gross hack before, but is now beautiful.
* LCoercion is gone! Hooray.
Many many fiddly changes in conssequence. But it's nice.
|
|\ |
|
| |
| |
| |
| |
| |
| |
| |
| |
| | |
In GHC, this provides an easy way to call a C function via a C wrapper.
This is important when the function is really defined by CPP.
Requires the new CApiFFI extension.
Not documented yet, as it's still an experimental feature at this stage.
|
| | |
|
|\ \
| |/ |
|
| |
| |
| |
| |
| |
| |
| |
| | |
instance pragmas
* Correct usage of new type wrappers from MkId
* 'VECTORISE [SCALAR] type T = S' didn't work correctly across module boundaries
* Clean up 'VECTORISE SCALAR instance'
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
This featurelet allows Trac #5237 to be fixed.
The idea is to allow SPECIALISE pragmas to specify
the phases in which the RULE is active, just as you can
do with RULES themselves.
{-# SPECIALISE [1] foo :: Int -> Int #-}
This feature is so obvious that not having it is really a bug.
There are, needless to say, a few wrinkles. See
Note [Activation pragmas for SPECIALISE]
in DsBinds
|
| | |
|
|/ |
|
|
|
|
|
|
|
|
|
|
| |
This was pretty straightforward: collect the filenames in the lexer,
and add them in to the tcg_dependent_files list that the typechecker
collects.
Note that we still don't get #included files in the ghc -M output.
Since we don't normally lex the whole file in ghc -M, this same
mechanism can't be used directly.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We now always check against an expected kind. When we really don't know what
kind to expect, we match against a new meta kind variable.
Also, we are more explicit about tuple sorts:
HsUnboxedTuple -> Produced by the parser
HsBoxedTuple -> Certainly a boxed tuple
HsConstraintTuple -> Certainly a constraint tuple
HsBoxedOrConstraintTuple -> Could be a boxed or a constraint
tuple. Produced by the parser only,
disappears after type checking
|