summaryrefslogtreecommitdiff
path: root/compiler/prelude/TysWiredIn.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/prelude/TysWiredIn.hs')
-rw-r--r--compiler/prelude/TysWiredIn.hs76
1 files changed, 61 insertions, 15 deletions
diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs
index b334967009..a954f0472f 100644
--- a/compiler/prelude/TysWiredIn.hs
+++ b/compiler/prelude/TysWiredIn.hs
@@ -73,7 +73,9 @@ module TysWiredIn (
unitTyCon, unitDataCon, unitDataConId, unitTy, unitTyConKey,
pairTyCon,
unboxedUnitTyCon, unboxedUnitDataCon,
+ -- ** Constraint tuples
cTupleTyConName, cTupleTyConNames, isCTupleTyConName,
+ cTupleDataConName, cTupleDataConNames,
-- * Any
anyTyCon, anyTy, anyTypeOfKind,
@@ -127,6 +129,7 @@ import {-# SOURCE #-} MkId( mkDataConWorkId, mkDictSelId )
-- friends:
import PrelNames
import TysPrim
+import {-# SOURCE #-} KnownUniques
-- others:
import CoAxiom
@@ -195,12 +198,13 @@ names in PrelNames, so they use wTcQual, wDataQual, etc
-- See also Note [Known-key names]
wiredInTyCons :: [TyCon]
-wiredInTyCons = [ unitTyCon -- Not treated like other tuples, because
- -- it's defined in GHC.Base, and there's only
- -- one of it. We put it in wiredInTyCons so
- -- that it'll pre-populate the name cache, so
- -- the special case in lookupOrigNameCache
- -- doesn't need to look out for it
+wiredInTyCons = [ -- Units are not treated like other tuples, because then
+ -- are defined in GHC.Base, and there's only a few of them. We
+ -- put them in wiredInTyCons so that they will pre-populate
+ -- the name cache, so the parser in isBuiltInOcc_maybe doesn't
+ -- need to look out for them.
+ unitTyCon
+ , unboxedUnitTyCon
, anyTyCon
, boolTyCon
, charTyCon
@@ -523,15 +527,21 @@ pcDataConWithFixity' declared_infix dc_name wrk_key rri tyvars ex_tyvars arg_tys
no_bang = HsSrcBang Nothing NoSrcUnpack NoSrcStrict
- modu = ASSERT( isExternalName dc_name )
- nameModule dc_name
- dc_occ = nameOccName dc_name
- wrk_occ = mkDataConWorkerOcc dc_occ
- wrk_name = mkWiredInName modu wrk_occ wrk_key
- (AnId (dataConWorkId data_con)) UserSyntax
+ wrk_name = mkDataConWorkerName data_con wrk_key
prom_info = mkPrelTyConRepName dc_name
+mkDataConWorkerName :: DataCon -> Unique -> Name
+mkDataConWorkerName data_con wrk_key =
+ mkWiredInName modu wrk_occ wrk_key
+ (AnId (dataConWorkId data_con)) UserSyntax
+ where
+ modu = ASSERT( isExternalName dc_name )
+ nameModule dc_name
+ dc_name = dataConName data_con
+ dc_occ = nameOccName dc_name
+ wrk_occ = mkDataConWorkerOcc dc_occ
+
-- used for RuntimeRep and friends
pcSpecialDataCon :: Name -> [Type] -> TyCon -> RuntimeRepInfo -> DataCon
pcSpecialDataCon dc_name arg_tys tycon rri
@@ -623,6 +633,11 @@ Note [How tuples work] See also Note [Known-key names] in PrelNames
between BoxedTuple and ConstraintTuple (same OccName!), so tuples
are not serialised into interface files using OccNames at all.
+* Serialization to interface files works via the usual mechanism for known-key
+ things: instead of serializing the OccName we just serialize the key. During
+ deserialization we lookup the Name associated with the unique with the logic
+ in KnownUniques. See Note [Symbol table representation of names] for details.
+
Note [One-tuples]
~~~~~~~~~~~~~~~~~
GHC supports both boxed and unboxed one-tuples:
@@ -650,27 +665,51 @@ decl in GHC.Classes, so I think this part may not work properly. But
it's unused I think.
-}
--- | Built in syntax isn't "in scope" so these OccNames map to wired-in Names
+-- | Built-in syntax isn't "in scope" so these OccNames map to wired-in Names
-- with BuiltInSyntax. However, this should only be necessary while resolving
-- names produced by Template Haskell splices since we take care to encode
-- built-in syntax names specially in interface files. See
-- Note [Symbol table representation of names].
+--
+-- Moreover, there is no need to include names of things that the user can't
+-- write (e.g. type representation bindings like $tc(,,,)).
isBuiltInOcc_maybe :: OccName -> Maybe Name
isBuiltInOcc_maybe occ =
case name of
"[]" -> Just $ choose_ns listTyConName nilDataConName
":" -> Just consDataConName
+
"[::]" -> Just parrTyConName
+
+ -- boxed tuple data/tycon
"()" -> Just $ tup_name Boxed 0
- "(##)" -> Just $ tup_name Unboxed 0
_ | Just rest <- "(" `stripPrefix` name
, (commas, rest') <- BS.span (==',') rest
, ")" <- rest'
-> Just $ tup_name Boxed (1+BS.length commas)
+
+ -- unboxed tuple data/tycon
+ "(##)" -> Just $ tup_name Unboxed 0
_ | Just rest <- "(#" `stripPrefix` name
, (commas, rest') <- BS.span (==',') rest
, "#)" <- rest'
-> Just $ tup_name Unboxed (1+BS.length commas)
+
+ -- unboxed sum tycon
+ _ | Just rest <- "(#" `stripPrefix` name
+ , (pipes, rest') <- BS.span (=='|') rest
+ , "#)" <- rest'
+ -> Just $ tyConName $ sumTyCon (1+BS.length pipes)
+
+ -- unboxed sum datacon
+ _ | Just rest <- "(#" `stripPrefix` name
+ , (pipes1, rest') <- BS.span (=='|') rest
+ , Just rest'' <- "_" `stripPrefix` rest'
+ , (pipes2, rest''') <- BS.span (=='|') rest''
+ , "#)" <- rest'''
+ -> let arity = BS.length pipes1 + BS.length pipes2
+ alt = BS.length pipes1 + 1
+ in Just $ dataConName $ sumDataCon alt arity
_ -> Nothing
where
-- TODO: Drop when bytestring 0.10.8 can be assumed
@@ -725,7 +764,6 @@ cTupleTyConName :: Arity -> Name
cTupleTyConName arity
= mkExternalName (mkCTupleTyConUnique arity) gHC_CLASSES
(mkCTupleOcc tcName arity) noSrcSpan
- -- The corresponding DataCon does not have a known-key name
cTupleTyConNames :: [Name]
cTupleTyConNames = map cTupleTyConName (0 : [2..mAX_CTUPLE_SIZE])
@@ -740,6 +778,14 @@ isCTupleTyConName n
nameModule n == gHC_CLASSES
&& n `elemNameSet` cTupleTyConNameSet
+cTupleDataConName :: Arity -> Name
+cTupleDataConName arity
+ = mkExternalName (mkCTupleDataConUnique arity) gHC_CLASSES
+ (mkCTupleOcc dataName arity) noSrcSpan
+
+cTupleDataConNames :: [Name]
+cTupleDataConNames = map cTupleDataConName (0 : [2..mAX_CTUPLE_SIZE])
+
tupleTyCon :: Boxity -> Arity -> TyCon
tupleTyCon sort i | i > mAX_TUPLE_SIZE = fst (mk_tuple sort i) -- Build one specially
tupleTyCon Boxed i = fst (boxedTupleArr ! i)