summaryrefslogtreecommitdiff
path: root/compiler/prelude/TysPrim.hs
diff options
context:
space:
mode:
authorBen Gamari <bgamari.foss@gmail.com>2015-10-30 20:22:42 +0100
committerBen Gamari <ben@smart-cactus.org>2015-10-30 20:22:44 +0100
commit91c6b1f54aea658b0056caec45655475897f1972 (patch)
treeaeb80a04e102e51dfd41343d4f697baf34c95739 /compiler/prelude/TysPrim.hs
parent59e728bc0b47116e3c9a8b21b14dc3198531b9a9 (diff)
downloadhaskell-91c6b1f54aea658b0056caec45655475897f1972.tar.gz
Generate Typeable info at definition sites
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
Diffstat (limited to 'compiler/prelude/TysPrim.hs')
-rw-r--r--compiler/prelude/TysPrim.hs38
1 files changed, 25 insertions, 13 deletions
diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs
index d66b48e3b7..3a6dd0341e 100644
--- a/compiler/prelude/TysPrim.hs
+++ b/compiler/prelude/TysPrim.hs
@@ -10,6 +10,8 @@
-- | This module defines TyCons that can't be expressed in Haskell.
-- They are all, therefore, wired-in TyCons. C.f module TysWiredIn
module TysPrim(
+ mkPrimTyConName, -- For implicit parameters in TysWiredIn only
+
mkTemplateTyVars,
alphaTyVars, betaTyVars, alphaTyVar, betaTyVar, gammaTyVar, deltaTyVar,
alphaTy, betaTy, gammaTy, deltaTy,
@@ -81,12 +83,11 @@ module TysPrim(
#include "HsVersions.h"
import Var ( TyVar, KindVar, mkTyVar )
-import Name ( Name, BuiltInSyntax(..), mkInternalName, mkWiredInName )
-import OccName ( mkTyVarOccFS, mkTcOccFS )
+import Name
import TyCon
import TypeRep
import SrcLoc
-import Unique ( mkAlphaTyVarUnique )
+import Unique
import PrelNames
import FastString
@@ -258,8 +259,9 @@ funTyConName :: Name
funTyConName = mkPrimTyConName (fsLit "(->)") funTyConKey funTyCon
funTyCon :: TyCon
-funTyCon = mkFunTyCon funTyConName $
- mkArrowKinds [liftedTypeKind, liftedTypeKind] liftedTypeKind
+funTyCon = mkFunTyCon funTyConName kind tc_rep_nm
+ where
+ kind = mkArrowKinds [liftedTypeKind, liftedTypeKind] liftedTypeKind
-- You might think that (->) should have type (?? -> ? -> *), and you'd be right
-- But if we do that we get kind errors when saying
-- instance Control.Arrow (->)
@@ -269,6 +271,8 @@ funTyCon = mkFunTyCon funTyConName $
-- a prefix way, thus: (->) Int# Int#. And this is unusual.
-- because they are never in scope in the source
+ tc_rep_nm = mkSpecialTyConRepName (fsLit "tcFun") funTyConName
+
-- One step to remove subkinding.
-- (->) :: * -> * -> *
-- but we should have (and want) the following typing rule for fully applied arrows
@@ -318,14 +322,21 @@ superKindTyConName, anyKindTyConName, liftedTypeKindTyConName,
constraintKindTyConName
:: Name
-superKindTyCon = mkKindTyCon superKindTyConName superKind
- -- See Note [SuperKind (BOX)]
+mk_kind_tycon :: Name -- ^ Name of the kind constructor, e.g. @*@
+ -> FastString -- ^ Name of the 'TyConRepName' function,
+ -- e.g. @tcLiftedKind :: TyCon@
+ -> TyCon -- ^ The kind constructor
+mk_kind_tycon tc_name rep_fs
+ = mkKindTyCon tc_name superKind (mkSpecialTyConRepName rep_fs tc_name)
+
+superKindTyCon = mk_kind_tycon superKindTyConName (fsLit "tcBOX")
+ -- See Note [SuperKind (BOX)]
-anyKindTyCon = mkKindTyCon anyKindTyConName superKind
-liftedTypeKindTyCon = mkKindTyCon liftedTypeKindTyConName superKind
-openTypeKindTyCon = mkKindTyCon openTypeKindTyConName superKind
-unliftedTypeKindTyCon = mkKindTyCon unliftedTypeKindTyConName superKind
-constraintKindTyCon = mkKindTyCon constraintKindTyConName superKind
+anyKindTyCon = mk_kind_tycon anyKindTyConName (fsLit "tcAnyK")
+constraintKindTyCon = mk_kind_tycon constraintKindTyConName (fsLit "tcConstraint")
+liftedTypeKindTyCon = mk_kind_tycon liftedTypeKindTyConName (fsLit "tcLiftedKind")
+openTypeKindTyCon = mk_kind_tycon openTypeKindTyConName (fsLit "tcOpenKind")
+unliftedTypeKindTyCon = mk_kind_tycon unliftedTypeKindTyConName (fsLit "tcUnliftedKind")
--------------------------
-- ... and now their names
@@ -736,6 +747,7 @@ variables with no constraints on them. It appears in similar circumstances to
Any, but at the kind level. For example:
type family Length (l :: [k]) :: Nat
+ type instance Length [] = Zero
f :: Proxy (Length []) -> Int
f = ....
@@ -776,7 +788,7 @@ anyTy = mkTyConTy anyTyCon
anyTyCon :: TyCon
anyTyCon = mkFamilyTyCon anyTyConName kind [kKiVar] Nothing
(ClosedSynFamilyTyCon Nothing)
- NoParentTyCon
+ Nothing
NotInjective
where
kind = ForAllTy kKiVar (mkTyVarTy kKiVar)