| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This work was all done by
Achim Krause <achim.t.krause@gmail.com>
George Giorgidze <giorgidze@gmail.com>
Weijers Jeroen <jeroen.weijers@uni-tuebingen.de>
It allows list syntax, such as [a,b], [a..b] and so on, to be
overloaded so that it works for a variety of types.
The design is described here:
http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists
Eg. you can use it for maps, so that
[(1,"foo"), (4,"bar")] :: Map Int String
The main changes
* The ExplicitList constructor of HsExpr gets witness field
* Ditto ArithSeq constructor
* Ditto the ListPat constructor of HsPat
Everything else flows from this.
|
| |
|
|\
| |
| |
| |
| |
| |
| |
| |
| | |
Conflicts:
compiler/rename/RnSource.lhs
compiler/simplCore/OccurAnal.lhs
compiler/vectorise/Vectorise/Exp.hs
NB: Merging instead of rebasing for a change. During rebase Git got confused due to the lack of the submodules in my quite old fork.
|
| |
| |
| |
| |
| |
| |
| | |
* Vectorisation avoidance is now the default
* Types and values from unvectorised modules are permitted in scalar code
* Simplified the VECTORISE pragmas (see http://hackage.haskell.org/trac/ghc/wiki/DataParallel/VectPragma for the spec)
* Vectorisation information is now included in the annotated Core AST
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
This code:
f _ = do
x <- computation
case () of
_ ->
result <- computation
case () of () -> undefined
Now gives this error:
Parse error in pattern: case () of { _ -> result }
Possibly caused by a missing 'do'?
|
| | |
|
| | |
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
This change gives a more helpful error message when the
user says data T = MkT {-# UNPACK #-} Int
which should have a strictness '!' as well. Rather than
just a parse error, we get
T7562.hs:3:14: Warning:
UNPACK pragma lacks '!' on the first argument of `MkT'
Fixes Trac #7562
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
* Make MatchGroup into a record, and use the record fields
* Split the type field into two: mg_arg_tys and mg_res_ty
This makes life much easier for the desugarer when the
case alterantives are empty
A little bit of this change unavoidably ended up in the preceding
commit about empty case alternatives
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
The main changes are:
* Parser accepts empty case alternatives
* Renamer checks that -XEmptyCase is on in that case
* (Typechecker is pretty much unchanged.)
* Desugarer desugars empty case alternatives, esp:
- Match.matchWrapper and Match.match now accept empty eqns
- New function matchEmpty deals with the empty case
- See Note [Empty case alternatives] in Match
This patch contains most of the work, but it's a bit mixed up
with a refactoring of MatchGroup that I did at the same time
(next commit).
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
An ordered, overlapping type family instance is introduced by 'type
instance
where', followed by equations. See the new section in the user manual
(7.7.2.2) for details. The canonical example is Boolean equality at the
type
level:
type family Equals (a :: k) (b :: k) :: Bool
type instance where
Equals a a = True
Equals a b = False
A branched family instance, such as this one, checks its equations in
order
and applies only the first the matches. As explained in the note
[Instance
checking within groups] in FamInstEnv.lhs, we must be careful not to
simplify,
say, (Equals Int b) to False, because b might later unify with Int.
This commit includes all of the commits on the overlapping-tyfams
branch. SPJ
requested that I combine all my commits over the past several months
into one
monolithic commit. The following GHC repos are affected: ghc, testsuite,
utils/haddock, libraries/template-haskell, and libraries/dph.
Here are some details for the interested:
- The definition of CoAxiom has been moved from TyCon.lhs to a
new file CoAxiom.lhs. I made this decision because of the
number of definitions necessary to support BranchList.
- BranchList is a GADT whose type tracks whether it is a
singleton list or not-necessarily-a-singleton-list. The reason
I introduced this type is to increase static checking of places
where GHC code assumes that a FamInst or CoAxiom is indeed a
singleton. This assumption takes place roughly 10 times
throughout the code. I was worried that a future change to GHC
would invalidate the assumption, and GHC might subtly fail to
do the right thing. By explicitly labeling CoAxioms and
FamInsts as being Unbranched (singleton) or
Branched (not-necessarily-singleton), we make this assumption
explicit and checkable. Furthermore, to enforce the accuracy of
this label, the list of branches of a CoAxiom or FamInst is
stored using a BranchList, whose constructors constrain its
type index appropriately.
I think that the decision to use BranchList is probably the most
controversial decision I made from a code design point of view.
Although I provide conversions to/from ordinary lists, it is more
efficient to use the brList... functions provided in CoAxiom than
always to convert. The use of these functions does not wander far
from the core CoAxiom/FamInst logic.
BranchLists are motivated and explained in the note [Branched axioms] in
CoAxiom.lhs.
- The CoAxiom type has changed significantly. You can see the new
type in CoAxiom.lhs. It uses a CoAxBranch type to track
branches of the CoAxiom. Correspondingly various functions
producing and consuming CoAxioms had to change, including the
binary layout of interface files.
- To get branched axioms to work correctly, it is important to have a
notion
of type "apartness": two types are apart if they cannot unify, and no
substitution of variables can ever get them to unify, even after type
family
simplification. (This is different than the normal failure to unify
because
of the type family bit.) This notion in encoded in tcApartTys, in
Unify.lhs.
Because apartness is finer-grained than unification, the tcUnifyTys
now
calls tcApartTys.
- CoreLinting axioms has been updated, both to reflect the new
form of CoAxiom and to enforce the apartness rules of branch
application. The formalization of the new rules is in
docs/core-spec/core-spec.pdf.
- The FamInst type (in types/FamInstEnv.lhs) has changed
significantly, paralleling the changes to CoAxiom. Of course,
this forced minor changes in many files.
- There are several new Notes in FamInstEnv.lhs, including one
discussing confluent overlap and why we're not doing it.
- lookupFamInstEnv, lookupFamInstEnvConflicts, and
lookup_fam_inst_env' (the function that actually does the work)
have all been more-or-less completely rewritten. There is a
Note [lookup_fam_inst_env' implementation] describing the
implementation. One of the changes that affects other files is
to change the type of matches from a pair of (FamInst, [Type])
to a new datatype (which now includes the index of the matching
branch). This seemed a better design.
- The TySynInstD constructor in Template Haskell was updated to
use the new datatype TySynEqn. I also bumped the TH version
number, requiring changes to DPH cabal files. (That's why the
DPH repo has an overlapping-tyfams branch.)
- As SPJ requested, I refactored some of the code in HsDecls:
* splitting up TyDecl into SynDecl and DataDecl, correspondingly
changing HsTyDefn to HsDataDefn (with only one constructor)
* splitting FamInstD into TyFamInstD and DataFamInstD and
splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl
* making the ClsInstD take a ClsInstDecl, for parallelism with
InstDecl's other constructors
* changing constructor TyFamily into FamDecl
* creating a FamilyDecl type that stores the details for a family
declaration; this is useful because FamilyDecls can appear in classes
but
other decls cannot
* restricting the associated types and associated type defaults for a
* class
to be the new, more restrictive types
* splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts,
according to the new types
* perhaps one or two more that I'm overlooking
None of these changes has far-reaching implications.
- The user manual, section 7.7.2.2, is updated to describe the new type
family
instances.
|
| | |
|
|\ \ |
|
| | | |
|
| | |
| | |
| | |
| | | |
Nothing big here, just tidying up deetails
|
|/ /
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
The situation was pretty dire. The way in which data constructors
were handled, notably the mapping between their *source* argument types
and their *representation* argument types (after seq'ing and unpacking)
was scattered in three different places, and hard to keep in sync.
Now it is all in one place:
* The dcRep field of a DataCon gives its representation,
specified by a DataConRep
* As well as having the wrapper, the DataConRep has a "boxer"
of type DataConBoxer (defined in MkId for loopy reasons).
The boxer used at a pattern match to reconstruct the source-level
arguments from the rep-level bindings in the pattern match.
* The unboxing in the wrapper and the boxing in the boxer are dual,
and are now constructed together, by MkId.mkDataConRep. This is
the key function of this change.
* All the computeBoxingStrategy code in TcTyClsDcls disappears.
Much nicer.
There is a little bit of refactoring left to do; the strange
deepSplitProductType functions are now called only in WwLib, so
I moved them there, and I think they could be tidied up further.
|
| | |
|
| | |
|
| | |
|
| | |
|
| |
| |
| |
| |
| | |
Mostly d -> g (matching DynFlag -> GeneralFlag).
Also renamed if* to when*, matching the Haskell if/when names
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
All the work was done by Dan Winograd-Cort.
The main thing is that arrow comamnds now have their own
data type HsCmd (defined in HsExpr). Previously it was
punned with the HsExpr type, which was jolly confusing,
and made it hard to do anything arrow-specific.
To make this work, we now parameterise
* MatchGroup
* Match
* GRHSs, GRHS
* StmtLR and friends
over the "body", that is the kind of thing they
enclose. This "body" parameter can be instantiated to
either LHsExpr or LHsCmd respectively.
Everything else is really a knock-on effect; there should
be no change (yet!) in behaviour. But it should be a sounder
basis for fixing bugs.
|
| | |
|
| | |
|
| | |
|
|/
|
|
|
|
|
| |
e.g.
data T = MkT { x,y :: Int }
f (MkT { x = !v, y = negate -> w }) = v + w
|
|
|
|
| |
All the flags that 'ways' imply are now dynamic
|
|\ |
|
| | |
|
| | |
|
| | |
|
| | |
|
| | |
|
|/
|
|
|
|
|
|
|
|
|
|
|
| |
This is a first step on the way to refactoring the FastString type.
FastBytes currently has no unique, mainly because there isn't currently
a nice way to produce them in Binary.
Also, we don't currently do the "Dictionary" thing with FastBytes in
Binary. I'm not sure whether this is important.
We can change both decisions later, but in the meantime this gets the
refactoring underway.
|
|
|
|
|
|
| |
I have observed that whenever GHC tells me that I have possibly
incorrect indentation, the real problem is often that I forgot
to close some sort of bracket.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch re-implements implicit parameters via a class
with a functional dependency:
class IP (n::Symbol) a | n -> a where
ip :: a
This definition is in the library module GHC.IP. Notice
how it use a type-literal, so we can have constraints like
IP "x" Int
Now all the functional dependency machinery works right to make
implicit parameters behave as they should.
Much special-case processing for implicit parameters can be removed
entirely. One particularly nice thing is not having a dedicated
"original-name cache" for implicit parameters (the nsNames field of
NameCache). But many other cases disappear:
* BasicTypes.IPName
* IPTyCon constructor in Tycon.TyCon
* CIPCan constructor in TcRnTypes.Ct
* IPPred constructor in Types.PredTree
Implicit parameters remain special in a few ways:
* Special syntax. Eg the constraint (IP "x" Int) is parsed
and printed as (?x::Int). And we still have local bindings
for implicit parameters, and occurrences thereof.
* A implicit-parameter binding (let ?x = True in e) amounts
to a local instance declaration, which we have not had before.
It just generates an implication contraint (easy), but when
going under it we must purge any existing bindings for
?x in the inert set. See Note [Shadowing of Implicit Parameters]
in TcSimplify
* TcMType.sizePred classifies implicit parameter constraints as size-0,
as before the change
There are accompanying patches to libraries 'base' and 'haddock'
All the work was done by Iavor Diatchki
|
|\
| |
| |
| |
| | |
Fix conflicts in:
compiler/main/DynFlags.hs
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
Summary:
- mdo expressions are enabled by RecursiveDo pragma
- mdo expressions perform full segmentation
- 'rec' groups inside 'do' are changed so they do *not*
perform any segmentation.
- Both 'mdo' and 'rec' are enabled by 'RecursiveDo'
'DoRec' is deprecated in favour of 'RecursiveDo'
(The 'rec' keyword is also enabled by 'Arrows', as now.)
Thanks to Levent for doing all the work
|
|/ |
|
|\ |
|
| |
| |
| |
| |
| |
| |
| |
| |
| |
| |
| | |
This is done by a 'unarisation' pre-pass at the STG level which
translates away all (live) binders binding something of unboxed
tuple type.
This has the following knock-on effects:
* The subkind hierarchy is vastly simplified (no UbxTupleKind or ArgKind)
* Various relaxed type checks in typechecker, 'foreign import prim' etc
* All case binders may be live at the Core level
|
|/
|
|
|
| |
By using Haskell's debugIsOn rather than CPP's "#ifdef DEBUG", we
don't need to kludge things to keep the warning checker happy etc.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We were hitting a problem when reading the LANGUAGE/OPTIONS pragmas
from GHC.TypeLits, where the buffer ended "{-". The rules for the
start-comment lexeme check that "{-" is not followed by "#", but the
test returned False when there was no next character. Therefore we
were lexing this as as an open-curly lexeme (only consuming the "{",
and not reaching the end of the buffer),
which meant the options parser think that it had reached the end of
the options.
Now we correctly lex as "{-".
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is really a small change, but it touches a lot of files quite
significantly. The real goal is to put the implicitly-bound kind
variables of a data/class decl in the right place, namely on the
LHsTyVarBndrs type, which now looks like
data LHsTyVarBndrs name
= HsQTvs { hsq_kvs :: [Name]
, hsq_tvs :: [LHsTyVarBndr name]
}
This little change made the type checker neater in a number of
ways, but it was fiddly to push through the changes.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
There was one place, in type checking parallel list comprehensions
where we were unifying types, but had no convenient way to use the
resulting coercion; instead we just checked that it was Refl. This
was Wrong Wrong; it might fail unpredicably in a GADT-like situation,
and it led to extra error-generation code used only in this one place.
This patch tidies it all up, by moving the 'return' method from the
*comprehension* to the ParStmtBlock. The latter is a new data type,
now used for each sub-chunk of a parallel list comprehension.
Because of the data type change, quite a few modules are touched,
but only in a fairly trivial way. The real changes are in TcMatches
(and corresponding desugaring); plus deleting code from TcUnify.
This patch also fixes the pretty-printing bug in Trac #6060
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The trouble here is that given
{-# LANGUAGE DataKinds, TypeFamilies #-}
data instance Foo a = Bar (Bar a)
we want to get a sensible message that we can't use the promoted 'Bar'
constructor until after its definition; it's a staging error. Bud the
staging mechanism that we use for vanilla data declarations don't work
here.
Solution is to perform strongly-connected component analysis on the
instance declarations. But that in turn means that we need to track
free-variable information on more HsSyn declarations, which is why
so many files are touched. All the changes are boiler-platey except
the ones in TcInstDcls.
|
|\ |
|
| | |
|
|/
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
|