| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
While the deriving machinery always unifies the kind of the typeclass
argument with the kind of the datatype, this proves not to be sufficient
to produce well kinded instances for some poly-kinded datatypes. For
example:
```
newtype Compose (f :: k2 -> *) (g :: k1 -> k2) (a :: k1)
= Compose (f (g a)) deriving Functor
```
would fail because only `k1` would get unified with `*`, causing the
following
ill kinded instance to be generated:
```
instance (Functor (f :: k2 -> *), Functor (g :: * -> k2)) =>
Functor (Compose f g) where ...
```
To prevent this, we need to take the subtypes and unify their kinds with
`* -> *`.
Fixes #10524 for good.
Test Plan: ./validate
Reviewers: simonpj, hvr, austin, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2097
GHC Trac Issues: #10524, #10561
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* `Identity` and `Const` now have `Num`, `Real`, `Integral`,
`Fractional`, `Floating`, `RealFrac` and `RealFloat` instances
* `Identity` and `Const` now have `Bits` and `FiniteBits` instances
* `Identity` and `Const` now have `IsString` instances
Reviewers: RyanGlScott, austin, hvr, bgamari, ekmett
Reviewed By: ekmett
Subscribers: nomeata, ekmett, RyanGlScott, thomie
Differential Revision: https://phabricator.haskell.org/D2079
GHC Trac Issues: #11790
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: currently no test plan
Reviewers: hvr, RyanGlScott, bgamari, austin
Reviewed By: RyanGlScott, bgamari, austin
Subscribers: thomie, RyanGlScott, andrewthad
Differential Revision: https://phabricator.haskell.org/D2051
GHC Trac Issues: #11756
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: bgamari, hvr, austin
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1989
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: Validate
Reviewers: austin, ekmett, hvr
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1957
GHC Trac Issues: #11625
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This accomplishes three things:
* Adds missing `Alternative`, `MonadPlus`, and `MonadZip` instances for
`Proxy`
* Adds a missing `MonadPlus` instance for `U1`
* Changes several existing `U1` instances to use lazy pattern-matching,
exactly how `Proxy` does it (in case we ever replace `U1` with
`Proxy`). This is technically a breaking change (albeit an extremely
minor one).
Test Plan: ./validate
Reviewers: austin, ekmett, hvr, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1962
GHC Trac Issues: #11650
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
GHC.Generics provides several representation data types that have
obvious instances of various type classes in base, along with various
other types of meta-data (such as associativity and fixity).
Specifically, instances have been added for the following type classes
(where possible):
- Applicative
- Data
- Functor
- Monad
- MonadFix
- MonadPlus
- MonadZip
- Foldable
- Traversable
- Enum
- Bounded
- Ix
- Generic1
Thanks to ocharles for starting this!
Test Plan: Validate
Reviewers: ekmett, austin, hvr, bgamari
Reviewed By: bgamari
Subscribers: RyanGlScott, thomie
Differential Revision: https://phabricator.haskell.org/D1937
GHC Trac Issues: #9043
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
See Note [TYPE] in TysPrim. There are still some outstanding
pieces in #11471 though, so this doesn't actually nail the bug.
This commit also contains a few performance improvements:
* Short-cut equality checking of nullary type syns
* Compare types before kinds in eqType
* INLINE coreViewOneStarKind
* Store tycon binders separately from kinds.
This resulted in a ~10% performance improvement in compiling
the Cabal package. No change in functionality other than
performance. (This affects the interface file format, though.)
This commit updates the haddock submodule.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Previously, `-Wunused-matches` would fire whenever it detected unused type
variables in a type family or data family instance. This can be annoying for
users who wish to use type variable names as documentation, as being
`-Wall`-compliant would mean that they'd have to prefix many of their type
variable names with underscores, making the documentation harder to read.
To avoid this, a new warning `-Wunused-type-variables` was created that only
encompasses unused variables in family instances. `-Wunused-matches` reverts
back to its role of only warning on unused term-level pattern names. Unlike
`-Wunused-matches`, `-Wunused-type-variables` is not implied by `-Wall`.
Fixes #11451.
Test Plan: ./validate
Reviewers: goldfire, ekmett, austin, hvr, simonpj, bgamari
Reviewed By: simonpj, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1825
GHC Trac Issues: #11451
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously there were a few obsolete references to `Data.List` and
the descriptions were lacking examples.
Fixes #11065.
Test Plan: Read it.
Reviewers: ekmett, goldfire, hvr, austin
Reviewed By: hvr
Subscribers: nomeata, thomie
Differential Revision: https://phabricator.haskell.org/D1617
GHC Trac Issues: #11065
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously types defined by `GHC.Types` and `GHC.Prim` had their
`Typeable` representations manually defined in `GHC.Typeable.Internals`.
This was terrible, resulting in a great deal of boilerplate and a number
of bugs due to missing or inconsistent representations (see #11120).
Here we take a different tack, initially proposed by Richard Eisenberg:
We wire-in the `Module`, `TrName`, and `TyCon` types, allowing them to
be used in `GHC.Types`. We then allow the usual type representation
generation logic to handle this module.
`GHC.Prim`, on the other hand, is a bit tricky as it has no object code
of its own. To handle this we instead place the type representations
for the types defined here in `GHC.Types`.
On the whole this eliminates several special-cases as well as a fair
amount of boilerplate from hand-written representations. Moreover, we
get full coverage of primitive types for free.
Test Plan: Validate
Reviewers: goldfire, simonpj, austin, hvr
Subscribers: goldfire, simonpj, thomie
Differential Revision: https://phabricator.haskell.org/D1774
GHC Trac Issues: #11120
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Kind equalities changed how `*`/`#` are represented internally, which
means that showing a `TypeRep` that contains either of those kinds
produces a rather gross-looking result, e.g.,
```
> typeOf (Proxy :: Proxy 'Just)
Proxy (TYPE 'Lifted -> Maybe (TYPE 'Lifted)) 'Just
```
We can at least special-case the `Show` instance for `TypeRep` so that
it prints `*` to represent `TYPE 'Lifted` and `#` to represent `TYPE
'Unlifted`.
Addresses one of the issues uncovered in #11334.
Test Plan: ./validate
Reviewers: simonpj, hvr, austin, goldfire, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1757
GHC Trac Issues: #11334
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously we were missing `Typeable` representations for several
wired-in types (and their promoted constructors). These include,
* `Nat`
* `Symbol`
* `':`
* `'[]`
Moreover, some constructors were incorrectly identified as being defined
in `GHC.Types` whereas they were in fact defined in `GHC.Prim`.
Ultimately this is just a temporary band-aid as there is general
agreement that we should eliminate the manual definition of these
representations entirely.
Test Plan: Validate
Reviewers: austin, hvr
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1769
GHC Trac Issues: #11120
|
|
|
|
|
|
|
| |
This refactoring exploits the fact that since AMP, in most cases,
`instance MonadPlus` can be automatically derived from the respective
`Alternative` instance. This is because `MonadPlus`'s default method
implementations are fully defined in terms of `Alternative(empty, (<>))`.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This introduces "freezing," an operation which prevents further
locations from being appended to a CallStack. Library authors may want
to prevent CallStacks from exposing implementation details, as a matter
of hygiene. For example, in
```
head [] = error "head: empty list"
ghci> head []
*** Exception: head: empty list
CallStack (from implicit params):
error, called at ...
```
including the call-site of `error` in `head` is not strictly necessary
as the error message already specifies clearly where the error came
from.
So we add a function `freezeCallStack` that wraps an existing CallStack,
preventing further call-sites from being pushed onto it. In other words,
```
pushCallStack callSite (freezeCallStack callStack) = freezeCallStack callStack
```
Now we can define `head` to not produce a CallStack at all
```
head [] =
let ?callStack = freezeCallStack emptyCallStack
in error "head: empty list"
ghci> head []
*** Exception: head: empty list
CallStack (from implicit params):
error, called at ...
```
---
1. We add the `freezeCallStack` and `emptyCallStack` and update the
definition of `CallStack` to support this functionality.
2. We add `errorWithoutStackTrace`, a variant of `error` that does not
produce a stack trace, using this feature. I think this is a sensible
wrapper function to provide in case users want it.
3. We replace uses of `error` in base with `errorWithoutStackTrace`. The
rationale is that base does not export any functions that use CallStacks
(except for `error` and `undefined`) so there's no way for the stack
traces (from Implicit CallStacks) to include user-defined functions.
They'll only contain the call to `error` itself. As base already has a
good habit of providing useful error messages that name the triggering
function, the stack trace really just adds noise to the error. (I don't
have a strong opinion on whether we should include this third commit,
but the change was very mechanical so I thought I'd include it anyway in
case there's interest)
4. Updates tests in `array` and `stm` submodules
Test Plan: ./validate, new test is T11049
Reviewers: simonpj, nomeata, goldfire, austin, hvr, bgamari
Reviewed By: simonpj
Subscribers: thomie
Projects: #ghc
Differential Revision: https://phabricator.haskell.org/D1628
GHC Trac Issues: #11049
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The following instances are added
instance Bounded a => Bounded (Const a b)
instance Enum a => Enum (Const a b)
instance Ix a => Ix (Const a b)
instance Storable a => Storable (Const a b)
instance Bounded a => Bounded (Identity a)
instance Enum a => Enum (Identity a)
instance Ix a => Ix (Identity a)
instance Semigroup a => Semigroup (Identity a)
instance Storable a => Storable (Identity a)
Reviewers: ekmett, RyanGlScott, rwbarton, hvr, austin, bgamari
Reviewed By: RyanGlScott, hvr
Subscribers: rwbarton, RyanGlScott, thomie
Differential Revision: https://phabricator.haskell.org/D1626
GHC Trac Issues: #11210
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- This part of the proposal is to add log1p, expm1, log1pexp and
log1mexp to the Floating class, and export the full Floating class
from Numeric
Reviewers: ekmett, #core_libraries_committee, bgamari, hvr, austin
Reviewed By: ekmett, #core_libraries_committee, bgamari
Subscribers: Phyx, RyanGlScott, ekmett, thomie
Differential Revision: https://phabricator.haskell.org/D1605
GHC Trac Issues: #11166
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
`Const` from `Control.Applicative` can trivially be made
kind-polymorphic in its second argument. There has been a Trac issue
about this for nearly a year now. It doesn't look like anybody objects
to it, so I figured I might as well make a patch.
Trac Issues: #10039, #10865, #11135
Differential Revision: https://phabricator.haskell.org/D1630
Reviewers: ekmett, hvr, bgamari
Subscribers: RyanGlScott, thomie
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The warnings are enabled with the flag -fwarn-unused-matches, the same
one that enables warnings on the term level.
Identifiers starting with an underscore are now always parsed as type
variables. When the NamedWildCards extension is enabled, the renamer
replaces those variables with named wildcards.
An additional NameSet nwcs is added to LocalRdrEnv. It's used to keep
names of the type variables that should be replaced with wildcards.
While renaming HsForAllTy, when a name is explicitly bound it is removed
from the nwcs NameSet. As a result, the renamer doesn't replace them in
the quantifier body. (Trac #11098)
Fixes #10982, #11098
Reviewers: alanz, bgamari, hvr, austin, jstolarek
Reviewed By: jstolarek
Subscribers: goldfire, mpickering, RyanGlScott, thomie
Differential Revision: https://phabricator.haskell.org/D1576
GHC Trac Issues: #10982
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The new instance resolves to `s ~ [Char]` as soon as we know that `s ~
[a]`, to avoid certain functions (like (++)) causing a situation where
`a` is ambiguous and (currently) unable to be defaulted.
Reviewers: #core_libraries_committee, hvr, austin, bgamari
Reviewed By: hvr, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1572
GHC Trac Issues: #10814
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
These modules were previously provided by the `transformers`
package. Hence the submodule update.
This patch was originally contributed by M Farkas-Dyck and
subsequently taken over and completed by Ryan.
The original proposal discussion can be found at
https://mail.haskell.org/pipermail/libraries/2015-July/026014.html
This addresses #11135
Differential Revision: https://phabricator.haskell.org/D1543
|
|
|
|
| |
This supercedes the Note recently written in TysWiredIn.
|
|
|
|
| |
Fixes #11178.
|
|
|
|
|
|
|
|
|
| |
This is really just doucumenting one aspect of the kind-equality patch.
See especially Note [Equality types and classes] in TysWiredIn.
Other places should just point to this Note.
Richard please check for veracity.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch began as a modest refactoring of HsType and friends, to
clarify and tidy up exactly where quantification takes place in types.
Although initially driven by making the implementation of wildcards more
tidy (and fixing a number of bugs), I gradually got drawn into a pretty
big process, which I've been doing on and off for quite a long time.
There is one compiler performance regression as a result of all
this, in perf/compiler/T3064. I still need to look into that.
* The principal driving change is described in Note [HsType binders]
in HsType. Well worth reading!
* Those data type changes drive almost everything else. In particular
we now statically know where
(a) implicit quantification only (LHsSigType),
e.g. in instance declaratios and SPECIALISE signatures
(b) implicit quantification and wildcards (LHsSigWcType)
can appear, e.g. in function type signatures
* As part of this change, HsForAllTy is (a) simplified (no wildcards)
and (b) split into HsForAllTy and HsQualTy. The two contructors
appear when and only when the correponding user-level construct
appears. Again see Note [HsType binders].
HsExplicitFlag disappears altogether.
* Other simplifications
- ExprWithTySig no longer needs an ExprWithTySigOut variant
- TypeSig no longer needs a PostRn name [name] field
for wildcards
- PatSynSig records a LHsSigType rather than the decomposed
pieces
- The mysterious 'GenericSig' is now 'ClassOpSig'
* Renamed LHsTyVarBndrs to LHsQTyVars
* There are some uninteresting knock-on changes in Haddock,
because of the HsSyn changes
I also did a bunch of loosely-related changes:
* We already had type synonyms CoercionN/CoercionR for nominal and
representational coercions. I've added similar treatment for
TcCoercionN/TcCoercionR
mkWpCastN/mkWpCastN
All just type synonyms but jolly useful.
* I record-ised ForeignImport and ForeignExport
* I improved the (poor) fix to Trac #10896, by making
TcTyClsDecls.checkValidTyCl recover from errors, but adding a
harmless, abstract TyCon to the envt if so.
* I did some significant refactoring in RnEnv.lookupSubBndrOcc,
for reasons that I have (embarrassingly) now totally forgotten.
It had to do with something to do with import and export
Updates haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Fixes #11083.
Reviewers: austin, hvr, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1477
GHC Trac Issues: #11083
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
- Document behavior on some inputs.
- Add some examples.
Reviewers: bgamari, osa1, hvr, dolio, #core_libraries_committee,
nomeata, austin
Reviewed By: bgamari, dolio, #core_libraries_committee, nomeata, austin
Subscribers: dolio, glguy, nomeata, thomie
Differential Revision: https://phabricator.haskell.org/D1450
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Problem: 'SRC_HC_OPTS += -Wall' in 'mk/warnings.mk' was getting
overwritten by 'SRC_HC_OPTS = ...' in 'mk/flavours/*.mk'.
It didn't affect the compiler or most other libraries, because most
.cabal files define 'ghc-options: -Wall'.
Bug introduced in commit
2c24fd707f8650205bb574ffac5f376239af3723, when moving validate settings
from 'mk/validate-settings.mk' to 'mk/flavours/validate.mk'.
Reviewed By: austin
Differential Revision: https://phabricator.haskell.org/D1425
|
|
|
|
| |
This missed to perform in f8ba4b55cc3a061458f5cfabf17de96128defbbb
|
|
|
|
|
|
|
|
|
| |
This change mirrors the change that occured for the recent
`semigroups-0.18` release, i.e.
https://github.com/ekmett/semigroups/commit/7a000212847b0d309892f34e4754a25ddec7100b
This removal addresses concerns raised in #10365
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is the second attempt at merging D757.
This patch implements the idea floated in Trac #9858, namely that we
should generate type-representation information at the data type
declaration site, rather than when solving a Typeable constraint.
However, this turned out quite a bit harder than I expected. I still
think it's the right thing to do, and it's done now, but it was quite
a struggle.
See particularly
* Note [Grand plan for Typeable] in TcTypeable (which is a new module)
* Note [The overall promotion story] in DataCon (clarifies existing
stuff)
The most painful bit was that to generate Typeable instances (ie
TyConRepName bindings) for every TyCon is tricky for types in ghc-prim
etc:
* We need to have enough data types around to *define* a TyCon
* Many of these types are wired-in
Also, to minimise the code generated for each data type, I wanted to
generate pure data, not CAFs with unpackCString# stuff floating about.
Performance
~~~~~~~~~~~
Three perf/compiler tests start to allocate quite a bit more. This isn't
surprising, because they all allocate zillions of data types, with
practically no other code, esp. T1969
* T1969: GHC allocates 19% more
* T4801: GHC allocates 13% more
* T5321FD: GHC allocates 13% more
* T9675: GHC allocates 11% more
* T783: GHC allocates 11% more
* T5642: GHC allocates 10% more
I'm treating this as acceptable. The payoff comes in Typeable-heavy
code.
Remaining to do
~~~~~~~~~~~~~~~
* I think that "TyCon" and "Module" are over-generic names to use for
the runtime type representations used in GHC.Typeable. Better might
be
"TrTyCon" and "TrModule". But I have not yet done this
* Add more info the the "TyCon" e.g. source location where it was
defined
* Use the new "Module" type to help with Trac Trac #10068
* It would be possible to generate TyConRepName (ie Typeable
instances) selectively rather than all the time. We'd need to persist
the information in interface files. Lacking a motivating reason I
have
not done this, but it would not be difficult.
Refactoring
~~~~~~~~~~~
As is so often the case, I ended up refactoring more than I intended.
In particular
* In TyCon, a type *family* (whether type or data) is repesented by a
FamilyTyCon
* a algebraic data type (including data/newtype instances) is
represented by AlgTyCon This wasn't true before; a data family
was represented as an AlgTyCon. There are some corresponding
changes in IfaceSyn.
* Also get rid of the (unhelpfully named) tyConParent.
* In TyCon define 'Promoted', isomorphic to Maybe, used when things are
optionally promoted; and use it elsewhere in GHC.
* Cleanup handling of knownKeyNames
* Each TyCon, including promoted TyCons, contains its TyConRepName, if
it has one. This is, in effect, the name of its Typeable instance.
Updates haddock submodule
Test Plan: Let Harbormaster validate
Reviewers: austin, hvr, goldfire
Subscribers: goldfire, thomie
Differential Revision: https://phabricator.haskell.org/D1404
GHC Trac Issues: #9858
|
|
|
|
|
|
|
|
| |
This reverts commit bef2f03e4d56d88a7e9752a7afd6a0a35616da6c.
This merge was botched
Also reverts haddock submodule.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch implements the idea floated in Trac #9858, namely that we
should generate type-representation information at the data type
declaration site, rather than when solving a Typeable constraint.
However, this turned out quite a bit harder than I expected. I still
think it's the right thing to do, and it's done now, but it was quite
a struggle.
See particularly
* Note [Grand plan for Typeable] in TcTypeable (which is a new module)
* Note [The overall promotion story] in DataCon (clarifies existing stuff)
The most painful bit was that to generate Typeable instances (ie
TyConRepName bindings) for every TyCon is tricky for types in ghc-prim
etc:
* We need to have enough data types around to *define* a TyCon
* Many of these types are wired-in
Also, to minimise the code generated for each data type, I wanted to
generate pure data, not CAFs with unpackCString# stuff floating about.
Performance
~~~~~~~~~~~
Three perf/compiler tests start to allocate quite a bit more. This isn't
surprising, because they all allocate zillions of data types, with
practically no other code, esp. T1969
* T3294: GHC allocates 110% more (filed #11030 to track this)
* T1969: GHC allocates 30% more
* T4801: GHC allocates 14% more
* T5321FD: GHC allocates 13% more
* T783: GHC allocates 12% more
* T9675: GHC allocates 12% more
* T5642: GHC allocates 10% more
* T9961: GHC allocates 6% more
* T9203: Program allocates 54% less
I'm treating this as acceptable. The payoff comes in Typeable-heavy
code.
Remaining to do
~~~~~~~~~~~~~~~
* I think that "TyCon" and "Module" are over-generic names to use for
the runtime type representations used in GHC.Typeable. Better might be
"TrTyCon" and "TrModule". But I have not yet done this
* Add more info the the "TyCon" e.g. source location where it was
defined
* Use the new "Module" type to help with Trac Trac #10068
* It would be possible to generate TyConRepName (ie Typeable
instances) selectively rather than all the time. We'd need to persist
the information in interface files. Lacking a motivating reason I have
not done this, but it would not be difficult.
Refactoring
~~~~~~~~~~~
As is so often the case, I ended up refactoring more than I intended.
In particular
* In TyCon, a type *family* (whether type or data) is repesented by a
FamilyTyCon
* a algebraic data type (including data/newtype instances) is
represented by AlgTyCon This wasn't true before; a data family
was represented as an AlgTyCon. There are some corresponding
changes in IfaceSyn.
* Also get rid of the (unhelpfully named) tyConParent.
* In TyCon define 'Promoted', isomorphic to Maybe, used when things are
optionally promoted; and use it elsewhere in GHC.
* Cleanup handling of knownKeyNames
* Each TyCon, including promoted TyCons, contains its TyConRepName, if
it has one. This is, in effect, the name of its Typeable instance.
Requires update of the haddock submodule.
Differential Revision: https://phabricator.haskell.org/D757
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This refactors `(>>)`/`(*>)`/`return`/`pure` methods into normal form.
The redundant explicit `return` method definitions are dropped
altogether.
The explicit `(>>) = (*>)` definitions can't be removed yet, as
the default implementation of `(>>)` is still in terms of `(*>)`
(even though that should have been changed according to the AMP but
wasn't -- see note in GHC.Base for details why this had to be postponed)
A nofib comparision shows this refactoring to result in minor runtime
improvements (unless those are within normal measurement fluctuations):
Program Size Allocs Runtime Elapsed TotalMem
-------------------------------------------------------------------------
Min -0.0% -0.0% -1.6% -3.9% -1.1%
Max -0.0% +0.0% +0.5% +0.5% 0.0%
Geometric Mean -0.0% -0.0% -0.4% -0.5% -0.0%
Full `nofib` report at https://phabricator.haskell.org/P68
Reviewers: quchen, alanz, austin, #core_libraries_committee, bgamari
Reviewed By: bgamari
Differential Revision: https://phabricator.haskell.org/D1316
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This can happen because the underlying primitive operations in
`integer-gmp` don't support negative shift-amounts, and since
`integer-gmp` can't throw proper exceptions and just provides a
low-level API, it simply segfaults instead...
This patch simply removes the `shift{L,R}` method definitions (and
defines `unsafeShift{L,R}` instead) whose default-impls fallback on
using `shift` which properly handles negative shift arguments.
This addresses #10571
Test Plan: harbormaster can do it
Reviewers: hvr, austin, rwbarton
Subscribers: rwbarton, thomie, bgamari
Differential Revision: https://phabricator.haskell.org/D1018
GHC Trac Issues: #10571
|
|
|
|
| |
Fixes #10571.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This implements phase 1 of the semigroup-as-monoid-superclass
proposal (https://ghc.haskell.org/wiki/Proposal/SemigroupMonoid).
The modules were migrated from the `semigroups-0.17` release mostly
as-is, except for dropping several trivial `{-# INLINE #-}`s,
removing CPP usage, and instances for types & classes provided
outside of `base` (e.g. `containers`, `deepseq`, `hashable`, `tagged`,
`bytestring`, `text`)
Differential Revision: https://phabricator.haskell.org/D1284
|
|
|
|
|
|
|
|
|
|
| |
To quote Simon Marlow,
We don't expect users to ever write code that uses mkWeak# or
finalizeWeak#, we have safe interfaces to these. Let's document the type
unsafety and fix the problem with () without introducing any overhead.
Updates stm submodule.
|
|
|
|
|
|
|
| |
Previously the types needlessly used (), which is defined ghc-prim,
leading to unfortunate import cycles. See #10867 for details.
Updates stm submodule.
|
|
|
|
|
|
|
|
|
|
| |
This allows these to be used from Text.Read.Lex import cycles.
Reviewed By: thomie, austin
Differential Revision: https://phabricator.haskell.org/D1121
GHC Trac Issues: #10444
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch adds following instances:
* Foldable ZipList
* Traversable ZipList
* Functor Complex
* Applicative Complex
* Monad Complex
* Foldable Complex
* Traversable Complex
* Generic1 Complex
* Monoid a => Monoid (Identity a)
* Storable ()
Reviewers: ekmett, fumieval, hvr, austin
Subscribers: thomie, #core_libraries_committee
Projects: #core_libraries_committee
Differential Revision: https://phabricator.haskell.org/D1049
GHC Trac Issues: #10609
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: validate
Reviewers: hvr, austin, bgamari, simonpj
Reviewed By: simonpj
Subscribers: simonpj, thomie
Differential Revision: https://phabricator.haskell.org/D1126
GHC Trac Issues: #9848
|