Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
obsidiansystems
GHC
Commits
04230c64
Commit
04230c64
authored
Jul 31, 2008
by
batterseapower
Browse files
Document TysWiredIn and follow OccName changes
parent
21dcb917
Changes
1
Hide whitespace changes
Inline
Side-by-side
compiler/prelude/TysWiredIn.lhs
View file @
04230c64
...
...
@@ -3,49 +3,54 @@
%
\section[TysWiredIn]{Wired-in knowledge about {\em non-primitive} types}
This module is about types that can be defined in Haskell, but which
must be wired into the compiler nonetheless.
This module tracks the ``state interface'' document, ``GHC prelude:
types and operations.''
\begin{code}
-- | This module is about types that can be defined in Haskell, but which
-- must be wired into the compiler nonetheless.
module TysWiredIn (
-- * All wired in things
wiredInTyCons,
-- * Bool
boolTy, boolTyCon, boolTyCon_RDR, boolTyConName,
trueDataCon, trueDataConId, true_RDR,
falseDataCon, falseDataConId, false_RDR,
-- * Char
charTyCon, charDataCon, charTyCon_RDR,
charTy, stringTy, charTyConName,
-- * Double
doubleTyCon, doubleDataCon, doubleTy, doubleTyConName,
-- * Float
floatTyCon, floatDataCon, floatTy, floatTyConName,
-- * Int
intTyCon, intDataCon, intTyCon_RDR, intDataCon_RDR, intTyConName,
intTy,
-- * Word
wordTyCon, wordDataCon, wordTyConName, wordTy,
-- * List
listTyCon, nilDataCon, consDataCon,
listTyCon_RDR, consDataCon_RDR, listTyConName,
mkListTy,
--
t
uples
--
* T
uples
mkTupleTy,
tupleTyCon, tupleCon,
unitTyCon, unitDataCon, unitDataConId, pairTyCon,
unboxedSingletonTyCon, unboxedSingletonDataCon,
unboxedPairTyCon, unboxedPairDataCon,
boxedTupleArr, unboxedTupleArr,
-- * Unit
unitTy,
--
p
arallel arrays
--
* P
arallel arrays
mkPArrTy,
parrTyCon, parrFakeCon, isPArrTyCon, isPArrFakeCon,
parrTyCon_RDR, parrTyConName
...
...
@@ -63,8 +68,8 @@ import Module ( Module )
import RdrName
import Name ( Name, BuiltInSyntax(..), nameUnique, nameOccName,
nameModule, mkWiredInName )
import OccName ( mkOcc
NameFS, tcName, dataName, mkTuple
Occ,
mkDataConWorkerOcc
)
import OccName ( mk
Tc
Occ
FS, mkDataOccFS, mkTupleOcc, mkDataConWorker
Occ,
tcName, dataName
)
import DataCon ( DataCon, mkDataCon, dataConWorkId, dataConSourceArity )
import Var
import TyCon ( TyCon, AlgTyConRhs(DataTyCon), tyConDataCons,
...
...
@@ -136,13 +141,13 @@ wiredInTyCons = [ unitTyCon -- Not treated like other tuples, because
\begin{code}
mkWiredInTyConName :: BuiltInSyntax -> Module -> FastString -> Unique -> TyCon -> Name
mkWiredInTyConName built_in modu fs unique tycon
= mkWiredInName modu (mkOcc
NameFS tcName
fs) unique
= mkWiredInName modu (mk
Tc
Occ
FS
fs) unique
(ATyCon tycon) -- Relevant TyCon
built_in
mkWiredInDataConName :: BuiltInSyntax -> Module -> FastString -> Unique -> DataCon -> Name
mkWiredInDataConName built_in modu fs unique datacon
= mkWiredInName modu (mk
OccNameFS dataName
fs) unique
= mkWiredInName modu (mk
DataOccFS
fs) unique
(ADataCon datacon) -- Relevant DataCon
built_in
...
...
@@ -474,6 +479,7 @@ listTyCon = pcRecDataTyCon listTyConName alpha_tyvar [nilDataCon, consDataCon]
nilDataCon :: DataCon
nilDataCon = pcDataCon nilDataConName alpha_tyvar [] listTyCon
consDataCon :: DataCon
consDataCon = pcDataConWithFixity True {- Declared infix -}
consDataConName
...
...
@@ -546,19 +552,17 @@ unitTy = mkTupleTy Boxed 0 []
Special syntax for parallel arrays needs some wired in definitions.
\begin{code}
-- construct a type representing the application of the parallel array
-- constructor
--
-- | Construct a type representing the application of the parallel array constructor
mkPArrTy :: Type -> Type
mkPArrTy ty = mkTyConApp parrTyCon [ty]
--
r
epresents the type constructor of parallel arrays
--
| R
epresents the type constructor of parallel arrays
--
-- *
t
his must match the definition in
`
PrelPArr
'
-- *
T
his must match the definition in
@
PrelPArr
@
--
-- NB: Although the constructor is given here, it will not be accessible in
-- user code as it is not in the environment of any compiled module except
--
`
PrelPArr
'
.
--
@
PrelPArr
@
.
--
parrTyCon :: TyCon
parrTyCon = pcNonRecDataTyCon parrTyConName alpha_tyvar [parrDataCon]
...
...
@@ -573,14 +577,13 @@ parrDataCon = pcDataCon
alpha_ty]
parrTyCon
-- check whether a type constructor is the constructor for parallel arrays
--
-- | Check whether a type constructor is the constructor for parallel arrays
isPArrTyCon :: TyCon -> Bool
isPArrTyCon tc = tyConName tc == parrTyConName
--
f
ake array constructors
--
| F
ake array constructors
--
--
*
t
hese constructors are never really used to represent array values;
-- *
T
hese constructors are never really used to represent array values;
-- however, they are very convenient during desugaring (and, in particular,
-- in the pattern matching compiler) to treat array pattern just like
-- yet another constructor pattern
...
...
@@ -604,12 +607,11 @@ mkPArrFakeCon arity = data_con
tyvar = head alphaTyVars
tyvarTys = replicate arity $ mkTyVarTy tyvar
nameStr = mkFastString ("MkPArr" ++ show arity)
name = mkWiredInName gHC_PARR (mk
OccNameFS dataName
nameStr) unique
name = mkWiredInName gHC_PARR (mk
DataOccFS
nameStr) unique
(ADataCon data_con) UserSyntax
unique = mkPArrDataConUnique arity
-- checks whether a data constructor is a fake constructor for parallel arrays
--
-- | Checks whether a data constructor is a fake constructor for parallel arrays
isPArrFakeCon :: DataCon -> Bool
isPArrFakeCon dcon = dcon == parrFakeCon (dataConSourceArity dcon)
\end{code}
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment