summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorBen Gamari <bgamari.foss@gmail.com>2016-01-13 14:53:02 +0100
committerBen Gamari <ben@smart-cactus.org>2016-01-13 14:53:03 +0100
commitac3cf68c378410724973e64be7198bb8720a6809 (patch)
tree7c7868b4411f7062391df13af0a8f1e47d13266b /libraries
parentd44bc5c061e3f0ba459f835aba683c0366187b74 (diff)
downloadhaskell-ac3cf68c378410724973e64be7198bb8720a6809.tar.gz
Add missing type representations
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
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/Data/Typeable/Internal.hs28
-rw-r--r--libraries/ghc-prim/GHC/Types.hs8
2 files changed, 29 insertions, 7 deletions
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 86ced96b12..548df304c0 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -41,11 +41,13 @@ module Data.Typeable.Internal (
mkTyCon3, mkTyCon3#,
rnfTyCon,
+ -- ** Representations for wired-in types
tcBool, tc'True, tc'False,
tcOrdering, tc'LT, tc'EQ, tc'GT,
tcChar, tcInt, tcWord, tcFloat, tcDouble, tcFun,
tcIO, tcSPEC, tcTyCon, tcModule, tcTrName,
- tcCoercible, tcList, tcHEq,
+ tcCoercible, tcHEq, tcSymbol, tcNat,
+ tcList, tc'Nil, tc'Cons,
tcConstraint,
tcTYPE, tcLevity, tc'Lifted, tc'Unlifted,
@@ -401,11 +403,15 @@ mkGhcTypesTyCon :: Addr# -> TyCon
{-# INLINE mkGhcTypesTyCon #-}
mkGhcTypesTyCon name = mkTyCon3# "ghc-prim"# "GHC.Types"# name
+mkGhcPrimTyCon :: Addr# -> TyCon
+{-# INLINE mkGhcPrimTyCon #-}
+mkGhcPrimTyCon name = mkTyCon3# "ghc-prim"# "GHC.Prim"# name
+
tcBool, tc'True, tc'False,
tcOrdering, tc'GT, tc'EQ, tc'LT,
tcChar, tcInt, tcWord, tcFloat, tcDouble, tcFun,
tcIO, tcSPEC, tcTyCon, tcModule, tcTrName,
- tcCoercible, tcHEq, tcList :: TyCon
+ tcCoercible, tcHEq, tcNat, tcSymbol :: TyCon
tcBool = mkGhcTypesTyCon "Bool"# -- Bool is promotable
tc'True = mkGhcTypesTyCon "'True"#
@@ -415,26 +421,34 @@ tc'GT = mkGhcTypesTyCon "'GT"#
tc'EQ = mkGhcTypesTyCon "'EQ"#
tc'LT = mkGhcTypesTyCon "'LT"#
--- None of the rest are promotable (see TysWiredIn)
+-- Most of the rest are promotable (see TysWiredIn)
tcChar = mkGhcTypesTyCon "Char"#
tcInt = mkGhcTypesTyCon "Int"#
tcWord = mkGhcTypesTyCon "Word"#
tcFloat = mkGhcTypesTyCon "Float"#
tcDouble = mkGhcTypesTyCon "Double"#
+tcNat = mkGhcTypesTyCon "Nat"#
+tcSymbol = mkGhcTypesTyCon "Symbol"#
tcSPEC = mkGhcTypesTyCon "SPEC"#
tcIO = mkGhcTypesTyCon "IO"#
+tcCoercible = mkGhcTypesTyCon "Coercible"#
tcTyCon = mkGhcTypesTyCon "TyCon"#
tcModule = mkGhcTypesTyCon "Module"#
tcTrName = mkGhcTypesTyCon "TrName"#
-tcCoercible = mkGhcTypesTyCon "Coercible"#
-tcFun = mkGhcTypesTyCon "->"#
-tcList = mkGhcTypesTyCon "[]"# -- Type rep for the list type constructor
+tcFun = mkGhcPrimTyCon "->"#
tcHEq = mkGhcTypesTyCon "~~"# -- Type rep for the (~~) type constructor
+tcList, tc'Nil, tc'Cons :: TyCon
+tcList = mkGhcTypesTyCon "[]"# -- Type rep for the list type constructor
+-- note that, because tc': isn't a valid identifier, we override the names of
+-- these representations in TysWiredIn.tyConRepModOcc.
+tc'Nil = mkGhcTypesTyCon "'[]"#
+tc'Cons = mkGhcTypesTyCon "':"#
+
tcConstraint, tcTYPE, tcLevity, tc'Lifted, tc'Unlifted :: TyCon
tcConstraint = mkGhcTypesTyCon "Constraint"#
-tcTYPE = mkGhcTypesTyCon "TYPE"#
+tcTYPE = mkGhcPrimTyCon "TYPE"#
tcLevity = mkGhcTypesTyCon "Levity"#
tc'Lifted = mkGhcTypesTyCon "'Lifted"#
tc'Unlifted = mkGhcTypesTyCon "'Unlifted"#
diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs
index b30db97400..2ce4c7ee7e 100644
--- a/libraries/ghc-prim/GHC/Types.hs
+++ b/libraries/ghc-prim/GHC/Types.hs
@@ -43,6 +43,10 @@ import GHC.Prim
infixr 5 :
+-- Take note: All types defined here must have associated type representations
+-- defined in Data.Typeable.Internal.
+-- See Note [Representation of types defined in GHC.Types] below.
+
{- *********************************************************************
* *
Kinds
@@ -367,6 +371,10 @@ Note [Representations of types defined in GHC.Types]
The representations for the types defined in GHC.Types are
defined in GHC.Typeable.Internal.
+Any types defined here must also have a corresponding TyCon representation
+defined in Data.Typeable.Internal. Also, if the type is promotable it must also
+have a TyCon for each promoted data constructor.
+
-}
#include "MachDeps.h"