- 11 Dec, 2015 9 commits
-
-
eir@cis.upenn.edu authored
This implements the ideas originally put forward in "System FC with Explicit Kind Equality" (ICFP'13). There are several noteworthy changes with this patch: * We now have casts in types. These change the kind of a type. See new constructor `CastTy`. * All types and all constructors can be promoted. This includes GADT constructors. GADT pattern matches take place in type family equations. In Core, types can now be applied to coercions via the `CoercionTy` constructor. * Coercions can now be heterogeneous, relating types of different kinds. A coercion proving `t1 :: k1 ~ t2 :: k2` proves both that `t1` and `t2` are the same and also that `k1` and `k2` are the same. * The `Coercion` type has been significantly enhanced. The documentation in `docs/core-spec/core-spec.pdf` reflects the new reality. * The type of `*` is now `*`. No more `BOX`. * Users can write explicit kind variables in their code, anywhere they can write type variables. For backward compatibility, automatic inference of kind-variable binding is still permitted. * The new extension `TypeInType` turns on the new user-facing features. * Type families and synonyms are now promoted to kinds. This causes trouble with parsing `*`, leading to the somewhat awkward new `HsAppsTy` constructor for `HsType`. This is dispatched with in the renamer, where the kind `*` can be told apart from a type-level multiplication operator. Without `-XTypeInType` the old behavior persists. With `-XTypeInType`, you need to import `Data.Kind` to get `*`, also known as `Type`. * The kind-checking algorithms in TcHsType have been significantly rewritten to allow for enhanced kinds. * The new features are still quite experimental and may be in flux. * TODO: Several open tickets: #11195, #11196, #11197, #11198, #11203. * TODO: Update user manual. Tickets addressed: #9017, #9173, #7961, #10524, #8566, #11142. Updates Haddock submodule.
-
Adam Gundry authored
This extends D1585 with proper support for infix duplicate record fields. In particular, it is now possible to declare record fields as infix in a module for which `DuplicateRecordFields` is enabled, fixity is looked up correctly and a readable (although unpleasant) error message is generated if multiple fields with different fixities are in scope. As a bonus, `DEPRECATED` and `WARNING` pragmas now work for duplicate record fields. The pragma applies to all fields with the given label. In addition, a couple of minor `DuplicateRecordFields` bugs, which were pinpointed by the `T11167_ambig` test case, are fixed by this patch: - Ambiguous infix fields can now be disambiguated by putting a type signature on the first argument - Polymorphic type constructor signatures (such as `ContT () IO a` in `T11167_ambig`) now work for disambiguation Parts of this patch are from D1585 authored by @KaneTW. Test Plan: New tests added. Reviewers: KaneTW, bgamari, austin Reviewed By: bgamari Subscribers: thomie, hvr Differential Revision: https://phabricator.haskell.org/D1600 GHC Trac Issues: #11167, #11173
-
Ben Gamari authored
It fails on OS X with hundreds of messages of the form, ``` ManySections.s:196576:10: error: error: mach-o section specifier uses an unknown section type .section s65525,"",@progbits ^ ManySections.s:196579:10: error: error: mach-o section specifier uses an unknown section type .section s65526,"",@progbits ``` It fails on Windows with messages of the form, ``` ManySections.s:196579:10: error: Error: junk at the end of line, first unrecognized character is ',' ``` Test Plan: Validate Reviewers: hsyl20, thomie, austin Reviewed By: thomie, austin Differential Revision: https://phabricator.haskell.org/D1601 GHC Trac Issues: #11022
-
kanetw authored
Reviewers: simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1587 GHC Trac Issues: #11164
-
Ben Gamari authored
Reviewers: jgertm, austin, thomie Reviewed By: thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1164 GHC Trac Issues: #10785
-
Ben Gamari authored
-
Ben Gamari authored
Due to #11204. A relatively easy fix would be to add a one second delay as described in the ticket, but this seems terrible.
-
Ben Gamari authored
This appears to be fixed as noted by goldfire on #7478 and my own experience.
-
Matthew Pickering authored
Summary: Before, `PatSyn`s were getting added twice to `tcg_patsyns` so when inspecting afterwards there were duplicates in the list. This makes sure that only they only get added once. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1597
-
- 10 Dec, 2015 2 commits
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
- 09 Dec, 2015 4 commits
-
-
Gabor Greif authored
-
Simon Peyton Jones authored
c.f. Trac #9968
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
The main issue concerned things like data T a = MkT a deriving( C Int ) which is supposed to generate instance C Int (T a) where {} But the 'Int' argument (called cls_tys in the code) wasn't even being passed to inferConstraints and mk_data_eqn, so it really had no chance. DeriveAnyClass came along after this code was written! Anyway I did quite a bit of tidying up in inferConstraints. Also I discovered that this case was not covered at all data T a b = MkT a b deriving( Bifunctor ) What constraints should we generate for the instance context? We can deal with classes whose last arg has kind *, like Eq, Ord; or (* -> *), like Functor, Traversable. But we really don't have a story for classes whose last arg has kind (* -> * -> *). So I augmented checkSideConditions to check for that and give a sensible error message. ToDo: update the user manual.
-
- 08 Dec, 2015 14 commits
-
-
Herbert Valerio Riedel authored
Differential Revision: https://phabricator.haskell.org/D1591
-
Herbert Valerio Riedel authored
This transforms the 'Command' tuple into a record which is easier to extend. While at it, this refactoring turns the IDE `:complete` into a hidden command excluded from completion. The next obvious step is to add a summary text field for constructing the `:help` output (as well as allowing to get `:help <CMD>` for single commands. This is a preparatory refactoring for D1240 / #10874 Reviewed By: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1590
-
Gabor Greif authored
-
Simon Peyton Jones authored
See Trac #11176
-
Simon Peyton Jones authored
-
Ben Gamari authored
-
Ben Gamari authored
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
This is a fixup to fd3b845c which didn't take into account 09333313 having pushed as well.
-
Herbert Valerio Riedel authored
[skip ci]
-
Herbert Valerio Riedel authored
Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1589 GHC Trac Issues: #10238
-
Herbert Valerio Riedel authored
Ideally, we'd have the more general instance (MonadTrans t, Monad m, HasDynFlags m) => HasDynFlags (t m) where getDynFlags = lift getDynFlags definition. However, that one would overlap with the `HasDynFlags (GhcT m)` instance. Instead we define instances for a couple of common Monad transformers explicitly in order to avoid nasty overlapping instances. This is a preparatory refactoring for #10874 Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D1581
-
Herbert Valerio Riedel authored
This way, import Control.Exception (ErrorCall(ErrorCall)) or import Control.Exception (ErrorCall(..)) work as expected, and import the `ErrorCall` compatibility pattern as well. When #5273 was implemented, it wasn't possible yet to associated patterns with their types (see #10653). Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D1588
-
Herbert Valerio Riedel authored
This allows to reach the GhciState without having to keep track how many Monad transformer layers sit on top of the GHCi monad. While at it, this also refactors code to make more use of the existing `modifyGHCiState` operation. This is a preparatory refactoring for #10874 Differential Revision: https://phabricator.haskell.org/D1582
-
- 07 Dec, 2015 11 commits
-
-
Ömer Sinan Ağacan authored
This is just a trivial renaming that implements a ToDo mentioned in a comment in Type.hs. Adding Simon as reviewer since he added the ToDo comment. Reviewers: simonpj, austin, goldfire, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1584
-
Herbert Valerio Riedel authored
It makes little sense to have __GLASGOW_HASKELL__ conditional code inside GHCi's source-code, as GHCi is only ever build by the current stage1 GHC, whose version is assumed to be the same as the GHCi version being built.
-
Herbert Valerio Riedel authored
The now removed `MaybeT` type was originally added back in 2008 via bc845b71 Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D1583
-
Ben Gamari authored
-
thomie authored
The packages in the package database are already sorted alphabetically by this point (see db_stack_sorted). This is a better fix for #8245, commit 021b1f89. Test Plan: look at output of './inplace/bin/ghc-pkg list [--simple-output]' Reviewers: austin, bgamari, psibi Reviewed By: psibi Differential Revision: https://phabricator.haskell.org/D1579 GHC Trac Issues: #8245
-
Eric Seidel authored
Checking for missing signatures before renaming the export list is prone to errors, so we now perform the check in `reportUnusedNames` at which point everything has been renamed. Test Plan: validate, new test case is T10908 Reviewers: goldfire, simonpj, austin, bgamari Subscribers: thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D1561 GHC Trac Issues: #10908
-
Alan Zimmerman authored
The ConDecl type in HsDecls is an uneasy compromise. For the most part, HsSyn directly reflects the syntax written by the programmer; and that gives just the right "pegs" on which to hang Alan's API annotations. But ConDecl doesn't properly reflect the syntax of Haskell-98 and GADT-style data type declarations. To be concrete, here's a draft new data type ```lang=hs data ConDecl name | ConDeclGADT { con_names :: [Located name] , con_type :: LHsSigType name -- The type after the ‘::’ , con_doc :: Maybe LHsDocString } | ConDeclH98 { con_name :: Located name , con_qvars :: Maybe (LHsQTyVars name) -- User-written forall (if any), and its implicit -- kind variables -- Non-Nothing needs -XExistentialQuantification , con_cxt :: Maybe (LHsContext name) -- ^ User-written context (if any) , con_details :: HsConDeclDetails name -- ^ Arguments , con_doc :: Maybe LHsDocString -- ^ A possible Haddock comment. } deriving (Typeable) ``` Note that For GADTs, just keep a type. That's what the user writes. NB:HsType can represent records on the LHS of an arrow: { x:Int,y:Bool} -> T con_qvars and con_cxt are both Maybe because they are both optional (the forall and the context of an existential data type For ConDeclGADT the type variables of the data type do not scope over the con_type; whereas for ConDeclH98 they do scope over con_cxt and con_details. Updates haddock submodule. Test Plan: ./validate Reviewers: simonpj, erikd, hvr, goldfire, austin, bgamari Subscribers: erikd, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1558 GHC Trac Issues: #11028
-
Ryan Scott authored
Test Plan: Validate. Reviewers: simonpj, goldfire, hvr, dreixel, kosmikus, austin, bgamari Reviewed By: kosmikus, austin, bgamari Subscribers: RyanGlScott, Fuuzetsu, bgamari, thomie, carter, dreixel Differential Revision: https://phabricator.haskell.org/D493 GHC Trac Issues: #9766
-
Ben Gamari authored
Test Plan: Validate Reviewers: austin, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1569
-
roshats authored
Reviewers: austin, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D1518 GHC Trac Issues: #9015
-
Ben Gamari authored
-