{-# LANGUAGE CPP #-}
module PrelNames (
Unique, Uniquable(..), hasKey,
module PrelNames,
) where
#include "GhclibHsVersions.h"
import GhcPrelude
import Module
import OccName
import RdrName
import Unique
import Name
import SrcLoc
import FastString
allNameStrings :: [String]
allNameStrings :: [String]
allNameStrings = [ Char
cChar -> String -> String
forall a. a -> [a] -> [a]
:String
cs | String
cs <- String
"" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
allNameStrings, Char
c <- [Char
'a'..Char
'z'] ]
itName :: Unique -> SrcSpan -> Name
itName :: Unique -> SrcSpan -> Name
itName Unique
uniq SrcSpan
loc = Unique -> OccName -> SrcSpan -> Name
mkInternalName Unique
uniq (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
varName (String -> FastString
fsLit String
"it")) SrcSpan
loc
mkUnboundName :: OccName -> Name
mkUnboundName :: OccName -> Name
mkUnboundName OccName
occ = Unique -> OccName -> SrcSpan -> Name
mkInternalName Unique
unboundKey OccName
occ SrcSpan
noSrcSpan
isUnboundName :: Name -> Bool
isUnboundName :: Name -> Bool
isUnboundName Name
name = Name
name Name -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
unboundKey
basicKnownKeyNames :: [Name]
basicKnownKeyNames :: [Name]
basicKnownKeyNames
= [Name]
genericTyConNames
[Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [
Name
eqClassName,
Name
ordClassName,
Name
boundedClassName,
Name
numClassName,
Name
enumClassName,
Name
monadClassName,
Name
functorClassName,
Name
realClassName,
Name
integralClassName,
Name
fractionalClassName,
Name
floatingClassName,
Name
realFracClassName,
Name
realFloatClassName,
Name
dataClassName,
Name
isStringClassName,
Name
applicativeClassName,
Name
alternativeClassName,
Name
foldableClassName,
Name
traversableClassName,
Name
semigroupClassName, Name
sappendName,
Name
monoidClassName, Name
memptyName, Name
mappendName, Name
mconcatName,
Name
ioTyConName, Name
ioDataConName,
Name
runMainIOName,
Name
runRWName,
Name
trModuleTyConName, Name
trModuleDataConName,
Name
trNameTyConName, Name
trNameSDataConName, Name
trNameDDataConName,
Name
trTyConTyConName, Name
trTyConDataConName,
Name
typeableClassName,
Name
typeRepTyConName,
Name
someTypeRepTyConName,
Name
someTypeRepDataConName,
Name
kindRepTyConName,
Name
kindRepTyConAppDataConName,
Name
kindRepVarDataConName,
Name
kindRepAppDataConName,
Name
kindRepFunDataConName,
Name
kindRepTYPEDataConName,
Name
kindRepTypeLitSDataConName,
Name
kindRepTypeLitDDataConName,
Name
typeLitSortTyConName,
Name
typeLitSymbolDataConName,
Name
typeLitNatDataConName,
Name
typeRepIdName,
Name
mkTrTypeName,
Name
mkTrConName,
Name
mkTrAppName,
Name
mkTrFunName,
Name
typeSymbolTypeRepName, Name
typeNatTypeRepName,
Name
trGhcPrimModuleName,
Name
starKindRepName,
Name
starArrStarKindRepName,
Name
starArrStarArrStarKindRepName,
Name
toDynName,
Name
negateName, Name
minusName, Name
geName, Name
eqName,
Name
rationalTyConName,
Name
ratioTyConName, Name
ratioDataConName,
Name
fromRationalName, Name
fromIntegerName,
Name
toIntegerName, Name
toRationalName,
Name
fromIntegralName, Name
realToFracName,
Name
divIntName, Name
modIntName,
Name
fromStringName,
Name
enumFromName, Name
enumFromThenName,
Name
enumFromThenToName, Name
enumFromToName,
Name
pureAName, Name
apAName, Name
thenAName,
Name
fmapName,
Name
thenIOName, Name
bindIOName, Name
returnIOName, Name
failIOName, Name
bindMName, Name
thenMName,
Name
returnMName, Name
joinMName,
Name
monadFailClassName, Name
failMName,
Name
monadFixClassName, Name
mfixName,
Name
arrAName, Name
composeAName, Name
firstAName,
Name
appAName, Name
choiceAName, Name
loopAName,
Name
ixClassName,
Name
showClassName,
Name
readClassName,
Name
newStablePtrName,
Name
groupWithName,
Name
unpackCStringName,
Name
unpackCStringFoldrName, Name
unpackCStringUtf8Name,
Name
isListClassName,
Name
fromListName,
Name
fromListNName,
Name
toListName,
Name
concatName, Name
filterName, Name
mapName,
Name
zipName, Name
foldrName, Name
buildName, Name
augmentName, Name
appendName,
Name
stablePtrTyConName, Name
ptrTyConName, Name
funPtrTyConName,
Name
int8TyConName, Name
int16TyConName, Name
int32TyConName, Name
int64TyConName,
Name
word16TyConName, Name
word32TyConName, Name
word64TyConName,
Name
otherwiseIdName, Name
inlineIdName,
Name
eqStringName, Name
assertName, Name
breakpointName, Name
breakpointCondName,
Name
breakpointAutoName, Name
opaqueTyConName,
Name
assertErrorName, Name
traceName,
Name
printName, Name
fstName, Name
sndName,
Name
dollarName,
Name
integerTyConName, Name
mkIntegerName,
Name
integerToWord64Name, Name
integerToInt64Name,
Name
word64ToIntegerName, Name
int64ToIntegerName,
Name
plusIntegerName, Name
timesIntegerName, Name
smallIntegerName,
Name
wordToIntegerName,
Name
integerToWordName, Name
integerToIntName, Name
minusIntegerName,
Name
negateIntegerName, Name
eqIntegerPrimName, Name
neqIntegerPrimName,
Name
absIntegerName, Name
signumIntegerName,
Name
leIntegerPrimName, Name
gtIntegerPrimName, Name
ltIntegerPrimName, Name
geIntegerPrimName,
Name
compareIntegerName, Name
quotRemIntegerName, Name
divModIntegerName,
Name
quotIntegerName, Name
remIntegerName, Name
divIntegerName, Name
modIntegerName,
Name
floatFromIntegerName, Name
doubleFromIntegerName,
Name
encodeFloatIntegerName, Name
encodeDoubleIntegerName,
Name
decodeDoubleIntegerName,
Name
gcdIntegerName, Name
lcmIntegerName,
Name
andIntegerName, Name
orIntegerName, Name
xorIntegerName, Name
complementIntegerName,
Name
shiftLIntegerName, Name
shiftRIntegerName, Name
bitIntegerName,
Name
integerSDataConName,Name
naturalSDataConName,
Name
naturalTyConName,
Name
naturalFromIntegerName, Name
naturalToIntegerName,
Name
plusNaturalName, Name
minusNaturalName, Name
timesNaturalName, Name
mkNaturalName,
Name
wordToNaturalName,
Name
rationalToFloatName,
Name
rationalToDoubleName,
Name
randomClassName, Name
randomGenClassName, Name
monadPlusClassName,
Name
knownNatClassName, Name
knownSymbolClassName,
Name
isLabelClassName,
Name
ipClassName,
Name
hasFieldClassName,
Name
callStackTyConName,
Name
emptyCallStackName, Name
pushCallStackName,
Name
srcLocDataConName,
Name
toAnnotationWrapperName
, Name
orderingTyConName
, Name
ordLTDataConName, Name
ordEQDataConName, Name
ordGTDataConName
, Name
specTyConName
, Name
eitherTyConName, Name
leftDataConName, Name
rightDataConName
, Name
pluginTyConName
, Name
frontendPluginTyConName
, Name
genClassName, Name
gen1ClassName
, Name
datatypeClassName, Name
constructorClassName, Name
selectorClassName
, Name
guardMName
, Name
liftMName
, Name
mzipName
, Name
ghciIoClassName, Name
ghciStepIoMName
, Name
makeStaticName
, Name
staticPtrTyConName
, Name
staticPtrDataConName, Name
staticPtrInfoDataConName
, Name
fromStaticPtrName
, Name
fingerprintDataConName
, Name
errorMessageTypeErrorFamName
, Name
typeErrorTextDataConName
, Name
typeErrorAppendDataConName
, Name
typeErrorVAppendDataConName
, Name
typeErrorShowTypeDataConName
]
genericTyConNames :: [Name]
genericTyConNames :: [Name]
genericTyConNames = [
Name
v1TyConName, Name
u1TyConName, Name
par1TyConName, Name
rec1TyConName,
Name
k1TyConName, Name
m1TyConName, Name
sumTyConName, Name
prodTyConName,
Name
compTyConName, Name
rTyConName, Name
dTyConName,
Name
cTyConName, Name
sTyConName, Name
rec0TyConName,
Name
d1TyConName, Name
c1TyConName, Name
s1TyConName, Name
noSelTyConName,
Name
repTyConName, Name
rep1TyConName, Name
uRecTyConName,
Name
uAddrTyConName, Name
uCharTyConName, Name
uDoubleTyConName,
Name
uFloatTyConName, Name
uIntTyConName, Name
uWordTyConName,
Name
prefixIDataConName, Name
infixIDataConName, Name
leftAssociativeDataConName,
Name
rightAssociativeDataConName, Name
notAssociativeDataConName,
Name
sourceUnpackDataConName, Name
sourceNoUnpackDataConName,
Name
noSourceUnpackednessDataConName, Name
sourceLazyDataConName,
Name
sourceStrictDataConName, Name
noSourceStrictnessDataConName,
Name
decidedLazyDataConName, Name
decidedStrictDataConName, Name
decidedUnpackDataConName,
Name
metaDataDataConName, Name
metaConsDataConName, Name
metaSelDataConName
]
pRELUDE :: Module
pRELUDE :: Module
pRELUDE = ModuleName -> Module
mkBaseModule_ ModuleName
pRELUDE_NAME
gHC_PRIM, gHC_TYPES, gHC_GENERICS, gHC_MAGIC,
gHC_CLASSES, gHC_PRIMOPWRAPPERS, gHC_BASE, gHC_ENUM,
gHC_GHCI, gHC_GHCI_HELPERS, gHC_CSTRING,
gHC_SHOW, gHC_READ, gHC_NUM, gHC_MAYBE, gHC_INTEGER_TYPE, gHC_NATURAL,
gHC_LIST, gHC_TUPLE, dATA_TUPLE, dATA_EITHER, dATA_STRING,
dATA_FOLDABLE, dATA_TRAVERSABLE,
gHC_CONC, gHC_IO, gHC_IO_Exception,
gHC_ST, gHC_ARR, gHC_STABLE, gHC_PTR, gHC_ERR, gHC_REAL,
gHC_FLOAT, gHC_TOP_HANDLER, sYSTEM_IO, dYNAMIC,
tYPEABLE, tYPEABLE_INTERNAL, gENERICS,
rEAD_PREC, lEX, gHC_INT, gHC_WORD, mONAD, mONAD_FIX, mONAD_ZIP, mONAD_FAIL,
aRROW, cONTROL_APPLICATIVE, gHC_DESUGAR, rANDOM, gHC_EXTS,
cONTROL_EXCEPTION_BASE, gHC_TYPELITS, gHC_TYPENATS, dATA_TYPE_EQUALITY,
dATA_COERCE, dEBUG_TRACE :: Module
gHC_PRIM :: Module
gHC_PRIM = FastString -> Module
mkPrimModule (String -> FastString
fsLit String
"GHC.Prim")
gHC_TYPES :: Module
gHC_TYPES = FastString -> Module
mkPrimModule (String -> FastString
fsLit String
"GHC.Types")
gHC_MAGIC :: Module
gHC_MAGIC = FastString -> Module
mkPrimModule (String -> FastString
fsLit String
"GHC.Magic")
gHC_CSTRING :: Module
gHC_CSTRING = FastString -> Module
mkPrimModule (String -> FastString
fsLit String
"GHC.CString")
gHC_CLASSES :: Module
gHC_CLASSES = FastString -> Module
mkPrimModule (String -> FastString
fsLit String
"GHC.Classes")
gHC_PRIMOPWRAPPERS :: Module
gHC_PRIMOPWRAPPERS = FastString -> Module
mkPrimModule (String -> FastString
fsLit String
"GHC.PrimopWrappers")
gHC_BASE :: Module
gHC_BASE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Base")
gHC_ENUM :: Module
gHC_ENUM = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Enum")
gHC_GHCI :: Module
gHC_GHCI = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.GHCi")
gHC_GHCI_HELPERS :: Module
gHC_GHCI_HELPERS= FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.GHCi.Helpers")
gHC_SHOW :: Module
gHC_SHOW = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Show")
gHC_READ :: Module
gHC_READ = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Read")
gHC_NUM :: Module
gHC_NUM = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Num")
gHC_MAYBE :: Module
gHC_MAYBE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Maybe")
gHC_INTEGER_TYPE :: Module
gHC_INTEGER_TYPE= FastString -> Module
mkIntegerModule (String -> FastString
fsLit String
"GHC.Integer.Type")
gHC_NATURAL :: Module
gHC_NATURAL = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Natural")
gHC_LIST :: Module
gHC_LIST = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.List")
gHC_TUPLE :: Module
gHC_TUPLE = FastString -> Module
mkPrimModule (String -> FastString
fsLit String
"GHC.Tuple")
dATA_TUPLE :: Module
dATA_TUPLE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Tuple")
dATA_EITHER :: Module
dATA_EITHER = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Either")
dATA_STRING :: Module
dATA_STRING = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.String")
dATA_FOLDABLE :: Module
dATA_FOLDABLE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Foldable")
dATA_TRAVERSABLE :: Module
dATA_TRAVERSABLE= FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Traversable")
gHC_CONC :: Module
gHC_CONC = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Conc")
gHC_IO :: Module
gHC_IO = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.IO")
gHC_IO_Exception :: Module
gHC_IO_Exception = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.IO.Exception")
gHC_ST :: Module
gHC_ST = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.ST")
gHC_ARR :: Module
gHC_ARR = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Arr")
gHC_STABLE :: Module
gHC_STABLE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Stable")
gHC_PTR :: Module
gHC_PTR = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Ptr")
gHC_ERR :: Module
gHC_ERR = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Err")
gHC_REAL :: Module
gHC_REAL = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Real")
gHC_FLOAT :: Module
gHC_FLOAT = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Float")
gHC_TOP_HANDLER :: Module
gHC_TOP_HANDLER = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.TopHandler")
sYSTEM_IO :: Module
sYSTEM_IO = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"System.IO")
dYNAMIC :: Module
dYNAMIC = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Dynamic")
tYPEABLE :: Module
tYPEABLE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Typeable")
tYPEABLE_INTERNAL :: Module
tYPEABLE_INTERNAL = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Typeable.Internal")
gENERICS :: Module
gENERICS = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Data")
rEAD_PREC :: Module
rEAD_PREC = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Text.ParserCombinators.ReadPrec")
lEX :: Module
lEX = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Text.Read.Lex")
gHC_INT :: Module
gHC_INT = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Int")
gHC_WORD :: Module
gHC_WORD = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Word")
mONAD :: Module
mONAD = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Control.Monad")
mONAD_FIX :: Module
mONAD_FIX = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Control.Monad.Fix")
mONAD_ZIP :: Module
mONAD_ZIP = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Control.Monad.Zip")
mONAD_FAIL :: Module
mONAD_FAIL = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Control.Monad.Fail")
aRROW :: Module
aRROW = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Control.Arrow")
cONTROL_APPLICATIVE :: Module
cONTROL_APPLICATIVE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Control.Applicative")
gHC_DESUGAR :: Module
gHC_DESUGAR = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Desugar")
rANDOM :: Module
rANDOM = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"System.Random")
gHC_EXTS :: Module
gHC_EXTS = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Exts")
cONTROL_EXCEPTION_BASE :: Module
cONTROL_EXCEPTION_BASE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Control.Exception.Base")
gHC_GENERICS :: Module
gHC_GENERICS = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Generics")
gHC_TYPELITS :: Module
gHC_TYPELITS = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.TypeLits")
gHC_TYPENATS :: Module
gHC_TYPENATS = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.TypeNats")
dATA_TYPE_EQUALITY :: Module
dATA_TYPE_EQUALITY = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Type.Equality")
dATA_COERCE :: Module
dATA_COERCE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Data.Coerce")
dEBUG_TRACE :: Module
dEBUG_TRACE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"Debug.Trace")
gHC_SRCLOC :: Module
gHC_SRCLOC :: Module
gHC_SRCLOC = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.SrcLoc")
gHC_STACK, gHC_STACK_TYPES :: Module
gHC_STACK :: Module
gHC_STACK = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Stack")
gHC_STACK_TYPES :: Module
gHC_STACK_TYPES = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Stack.Types")
gHC_STATICPTR :: Module
gHC_STATICPTR :: Module
gHC_STATICPTR = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.StaticPtr")
gHC_STATICPTR_INTERNAL :: Module
gHC_STATICPTR_INTERNAL :: Module
gHC_STATICPTR_INTERNAL = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.StaticPtr.Internal")
gHC_FINGERPRINT_TYPE :: Module
gHC_FINGERPRINT_TYPE :: Module
gHC_FINGERPRINT_TYPE = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Fingerprint.Type")
gHC_OVER_LABELS :: Module
gHC_OVER_LABELS :: Module
gHC_OVER_LABELS = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.OverloadedLabels")
gHC_RECORDS :: Module
gHC_RECORDS :: Module
gHC_RECORDS = FastString -> Module
mkBaseModule (String -> FastString
fsLit String
"GHC.Records")
mAIN, rOOT_MAIN :: Module
mAIN :: Module
mAIN = ModuleName -> Module
mkMainModule_ ModuleName
mAIN_NAME
rOOT_MAIN :: Module
rOOT_MAIN = FastString -> Module
mkMainModule (String -> FastString
fsLit String
":Main")
mkInteractiveModule :: Int -> Module
mkInteractiveModule :: Int -> Module
mkInteractiveModule Int
n = UnitId -> ModuleName -> Module
mkModule UnitId
interactiveUnitId (String -> ModuleName
mkModuleName (String
"Ghci" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n))
pRELUDE_NAME, mAIN_NAME :: ModuleName
pRELUDE_NAME :: ModuleName
pRELUDE_NAME = FastString -> ModuleName
mkModuleNameFS (String -> FastString
fsLit String
"Prelude")
mAIN_NAME :: ModuleName
mAIN_NAME = FastString -> ModuleName
mkModuleNameFS (String -> FastString
fsLit String
"Main")
dATA_ARRAY_PARALLEL_NAME, dATA_ARRAY_PARALLEL_PRIM_NAME :: ModuleName
dATA_ARRAY_PARALLEL_NAME :: ModuleName
dATA_ARRAY_PARALLEL_NAME = FastString -> ModuleName
mkModuleNameFS (String -> FastString
fsLit String
"Data.Array.Parallel")
dATA_ARRAY_PARALLEL_PRIM_NAME :: ModuleName
dATA_ARRAY_PARALLEL_PRIM_NAME = FastString -> ModuleName
mkModuleNameFS (String -> FastString
fsLit String
"Data.Array.Parallel.Prim")
mkPrimModule :: FastString -> Module
mkPrimModule :: FastString -> Module
mkPrimModule FastString
m = UnitId -> ModuleName -> Module
mkModule UnitId
primUnitId (FastString -> ModuleName
mkModuleNameFS FastString
m)
mkIntegerModule :: FastString -> Module
mkIntegerModule :: FastString -> Module
mkIntegerModule FastString
m = UnitId -> ModuleName -> Module
mkModule UnitId
integerUnitId (FastString -> ModuleName
mkModuleNameFS FastString
m)
mkBaseModule :: FastString -> Module
mkBaseModule :: FastString -> Module
mkBaseModule FastString
m = UnitId -> ModuleName -> Module
mkModule UnitId
baseUnitId (FastString -> ModuleName
mkModuleNameFS FastString
m)
mkBaseModule_ :: ModuleName -> Module
mkBaseModule_ :: ModuleName -> Module
mkBaseModule_ ModuleName
m = UnitId -> ModuleName -> Module
mkModule UnitId
baseUnitId ModuleName
m
mkThisGhcModule :: FastString -> Module
mkThisGhcModule :: FastString -> Module
mkThisGhcModule FastString
m = UnitId -> ModuleName -> Module
mkModule UnitId
thisGhcUnitId (FastString -> ModuleName
mkModuleNameFS FastString
m)
mkThisGhcModule_ :: ModuleName -> Module
mkThisGhcModule_ :: ModuleName -> Module
mkThisGhcModule_ ModuleName
m = UnitId -> ModuleName -> Module
mkModule UnitId
thisGhcUnitId ModuleName
m
mkMainModule :: FastString -> Module
mkMainModule :: FastString -> Module
mkMainModule FastString
m = UnitId -> ModuleName -> Module
mkModule UnitId
mainUnitId (FastString -> ModuleName
mkModuleNameFS FastString
m)
mkMainModule_ :: ModuleName -> Module
mkMainModule_ :: ModuleName -> Module
mkMainModule_ ModuleName
m = UnitId -> ModuleName -> Module
mkModule UnitId
mainUnitId ModuleName
m
main_RDR_Unqual :: RdrName
main_RDR_Unqual :: RdrName
main_RDR_Unqual = NameSpace -> FastString -> RdrName
mkUnqual NameSpace
varName (String -> FastString
fsLit String
"main")
eq_RDR, ge_RDR, le_RDR, lt_RDR, gt_RDR, compare_RDR,
ltTag_RDR, eqTag_RDR, gtTag_RDR :: RdrName
eq_RDR :: RdrName
eq_RDR = Name -> RdrName
nameRdrName Name
eqName
ge_RDR :: RdrName
ge_RDR = Name -> RdrName
nameRdrName Name
geName
le_RDR :: RdrName
le_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_CLASSES (String -> FastString
fsLit String
"<=")
lt_RDR :: RdrName
lt_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_CLASSES (String -> FastString
fsLit String
"<")
gt_RDR :: RdrName
gt_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_CLASSES (String -> FastString
fsLit String
">")
compare_RDR :: RdrName
compare_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_CLASSES (String -> FastString
fsLit String
"compare")
ltTag_RDR :: RdrName
ltTag_RDR = Name -> RdrName
nameRdrName Name
ordLTDataConName
eqTag_RDR :: RdrName
eqTag_RDR = Name -> RdrName
nameRdrName Name
ordEQDataConName
gtTag_RDR :: RdrName
gtTag_RDR = Name -> RdrName
nameRdrName Name
ordGTDataConName
eqClass_RDR, numClass_RDR, ordClass_RDR, enumClass_RDR, monadClass_RDR
:: RdrName
eqClass_RDR :: RdrName
eqClass_RDR = Name -> RdrName
nameRdrName Name
eqClassName
numClass_RDR :: RdrName
numClass_RDR = Name -> RdrName
nameRdrName Name
numClassName
ordClass_RDR :: RdrName
ordClass_RDR = Name -> RdrName
nameRdrName Name
ordClassName
enumClass_RDR :: RdrName
enumClass_RDR = Name -> RdrName
nameRdrName Name
enumClassName
monadClass_RDR :: RdrName
monadClass_RDR = Name -> RdrName
nameRdrName Name
monadClassName
map_RDR, append_RDR :: RdrName
map_RDR :: RdrName
map_RDR = Name -> RdrName
nameRdrName Name
mapName
append_RDR :: RdrName
append_RDR = Name -> RdrName
nameRdrName Name
appendName
foldr_RDR, build_RDR, returnM_RDR, bindM_RDR, failM_RDR
:: RdrName
foldr_RDR :: RdrName
foldr_RDR = Name -> RdrName
nameRdrName Name
foldrName
build_RDR :: RdrName
build_RDR = Name -> RdrName
nameRdrName Name
buildName
returnM_RDR :: RdrName
returnM_RDR = Name -> RdrName
nameRdrName Name
returnMName
bindM_RDR :: RdrName
bindM_RDR = Name -> RdrName
nameRdrName Name
bindMName
failM_RDR :: RdrName
failM_RDR = Name -> RdrName
nameRdrName Name
failMName
left_RDR, right_RDR :: RdrName
left_RDR :: RdrName
left_RDR = Name -> RdrName
nameRdrName Name
leftDataConName
right_RDR :: RdrName
right_RDR = Name -> RdrName
nameRdrName Name
rightDataConName
fromEnum_RDR, toEnum_RDR :: RdrName
= Module -> FastString -> RdrName
varQual_RDR Module
gHC_ENUM (String -> FastString
fsLit String
"fromEnum")
toEnum_RDR :: RdrName
toEnum_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ENUM (String -> FastString
fsLit String
"toEnum")
enumFrom_RDR, enumFromTo_RDR, enumFromThen_RDR, enumFromThenTo_RDR :: RdrName
enumFrom_RDR :: RdrName
enumFrom_RDR = Name -> RdrName
nameRdrName Name
enumFromName
enumFromTo_RDR :: RdrName
enumFromTo_RDR = Name -> RdrName
nameRdrName Name
enumFromToName
enumFromThen_RDR :: RdrName
enumFromThen_RDR = Name -> RdrName
nameRdrName Name
enumFromThenName
enumFromThenTo_RDR :: RdrName
enumFromThenTo_RDR = Name -> RdrName
nameRdrName Name
enumFromThenToName
ratioDataCon_RDR, plusInteger_RDR, timesInteger_RDR :: RdrName
ratioDataCon_RDR :: RdrName
ratioDataCon_RDR = Name -> RdrName
nameRdrName Name
ratioDataConName
plusInteger_RDR :: RdrName
plusInteger_RDR = Name -> RdrName
nameRdrName Name
plusIntegerName
timesInteger_RDR :: RdrName
timesInteger_RDR = Name -> RdrName
nameRdrName Name
timesIntegerName
ioDataCon_RDR :: RdrName
ioDataCon_RDR :: RdrName
ioDataCon_RDR = Name -> RdrName
nameRdrName Name
ioDataConName
eqString_RDR, unpackCString_RDR, unpackCStringFoldr_RDR,
unpackCStringUtf8_RDR :: RdrName
eqString_RDR :: RdrName
eqString_RDR = Name -> RdrName
nameRdrName Name
eqStringName
unpackCString_RDR :: RdrName
unpackCString_RDR = Name -> RdrName
nameRdrName Name
unpackCStringName
unpackCStringFoldr_RDR :: RdrName
unpackCStringFoldr_RDR = Name -> RdrName
nameRdrName Name
unpackCStringFoldrName
unpackCStringUtf8_RDR :: RdrName
unpackCStringUtf8_RDR = Name -> RdrName
nameRdrName Name
unpackCStringUtf8Name
newStablePtr_RDR :: RdrName
newStablePtr_RDR :: RdrName
newStablePtr_RDR = Name -> RdrName
nameRdrName Name
newStablePtrName
bindIO_RDR, returnIO_RDR :: RdrName
bindIO_RDR :: RdrName
bindIO_RDR = Name -> RdrName
nameRdrName Name
bindIOName
returnIO_RDR :: RdrName
returnIO_RDR = Name -> RdrName
nameRdrName Name
returnIOName
fromInteger_RDR, fromRational_RDR, minus_RDR, times_RDR, plus_RDR :: RdrName
fromInteger_RDR :: RdrName
fromInteger_RDR = Name -> RdrName
nameRdrName Name
fromIntegerName
fromRational_RDR :: RdrName
fromRational_RDR = Name -> RdrName
nameRdrName Name
fromRationalName
minus_RDR :: RdrName
minus_RDR = Name -> RdrName
nameRdrName Name
minusName
times_RDR :: RdrName
times_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_NUM (String -> FastString
fsLit String
"*")
plus_RDR :: RdrName
plus_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_NUM (String -> FastString
fsLit String
"+")
toInteger_RDR, toRational_RDR, fromIntegral_RDR :: RdrName
toInteger_RDR :: RdrName
toInteger_RDR = Name -> RdrName
nameRdrName Name
toIntegerName
toRational_RDR :: RdrName
toRational_RDR = Name -> RdrName
nameRdrName Name
toRationalName
fromIntegral_RDR :: RdrName
fromIntegral_RDR = Name -> RdrName
nameRdrName Name
fromIntegralName
stringTy_RDR, fromString_RDR :: RdrName
stringTy_RDR :: RdrName
stringTy_RDR = Module -> FastString -> RdrName
tcQual_RDR Module
gHC_BASE (String -> FastString
fsLit String
"String")
fromString_RDR :: RdrName
fromString_RDR = Name -> RdrName
nameRdrName Name
fromStringName
fromList_RDR, fromListN_RDR, toList_RDR :: RdrName
fromList_RDR :: RdrName
fromList_RDR = Name -> RdrName
nameRdrName Name
fromListName
fromListN_RDR :: RdrName
fromListN_RDR = Name -> RdrName
nameRdrName Name
fromListNName
toList_RDR :: RdrName
toList_RDR = Name -> RdrName
nameRdrName Name
toListName
compose_RDR :: RdrName
compose_RDR :: RdrName
compose_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_BASE (String -> FastString
fsLit String
".")
not_RDR, getTag_RDR, succ_RDR, pred_RDR, minBound_RDR, maxBound_RDR,
and_RDR, range_RDR, inRange_RDR, index_RDR,
unsafeIndex_RDR, unsafeRangeSize_RDR :: RdrName
and_RDR :: RdrName
and_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_CLASSES (String -> FastString
fsLit String
"&&")
not_RDR :: RdrName
not_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_CLASSES (String -> FastString
fsLit String
"not")
getTag_RDR :: RdrName
getTag_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_BASE (String -> FastString
fsLit String
"getTag")
succ_RDR :: RdrName
succ_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ENUM (String -> FastString
fsLit String
"succ")
pred_RDR :: RdrName
pred_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ENUM (String -> FastString
fsLit String
"pred")
minBound_RDR :: RdrName
minBound_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ENUM (String -> FastString
fsLit String
"minBound")
maxBound_RDR :: RdrName
maxBound_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ENUM (String -> FastString
fsLit String
"maxBound")
range_RDR :: RdrName
range_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ARR (String -> FastString
fsLit String
"range")
inRange_RDR :: RdrName
inRange_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ARR (String -> FastString
fsLit String
"inRange")
index_RDR :: RdrName
index_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ARR (String -> FastString
fsLit String
"index")
unsafeIndex_RDR :: RdrName
unsafeIndex_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ARR (String -> FastString
fsLit String
"unsafeIndex")
unsafeRangeSize_RDR :: RdrName
unsafeRangeSize_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ARR (String -> FastString
fsLit String
"unsafeRangeSize")
readList_RDR, readListDefault_RDR, readListPrec_RDR, readListPrecDefault_RDR,
readPrec_RDR, parens_RDR, choose_RDR, lexP_RDR, expectP_RDR :: RdrName
readList_RDR :: RdrName
readList_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readList")
readListDefault_RDR :: RdrName
readListDefault_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readListDefault")
readListPrec_RDR :: RdrName
readListPrec_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readListPrec")
readListPrecDefault_RDR :: RdrName
readListPrecDefault_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readListPrecDefault")
readPrec_RDR :: RdrName
readPrec_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readPrec")
parens_RDR :: RdrName
parens_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"parens")
choose_RDR :: RdrName
choose_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"choose")
lexP_RDR :: RdrName
lexP_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"lexP")
expectP_RDR :: RdrName
expectP_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"expectP")
readField_RDR, readFieldHash_RDR, readSymField_RDR :: RdrName
readField_RDR :: RdrName
readField_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readField")
readFieldHash_RDR :: RdrName
readFieldHash_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readFieldHash")
readSymField_RDR :: RdrName
readSymField_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_READ (String -> FastString
fsLit String
"readSymField")
punc_RDR, ident_RDR, symbol_RDR :: RdrName
punc_RDR :: RdrName
punc_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
lEX (String -> FastString
fsLit String
"Punc")
ident_RDR :: RdrName
ident_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
lEX (String -> FastString
fsLit String
"Ident")
symbol_RDR :: RdrName
symbol_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
lEX (String -> FastString
fsLit String
"Symbol")
step_RDR, alt_RDR, reset_RDR, prec_RDR, pfail_RDR :: RdrName
step_RDR :: RdrName
step_RDR = Module -> FastString -> RdrName
varQual_RDR Module
rEAD_PREC (String -> FastString
fsLit String
"step")
alt_RDR :: RdrName
alt_RDR = Module -> FastString -> RdrName
varQual_RDR Module
rEAD_PREC (String -> FastString
fsLit String
"+++")
reset_RDR :: RdrName
reset_RDR = Module -> FastString -> RdrName
varQual_RDR Module
rEAD_PREC (String -> FastString
fsLit String
"reset")
prec_RDR :: RdrName
prec_RDR = Module -> FastString -> RdrName
varQual_RDR Module
rEAD_PREC (String -> FastString
fsLit String
"prec")
pfail_RDR :: RdrName
pfail_RDR = Module -> FastString -> RdrName
varQual_RDR Module
rEAD_PREC (String -> FastString
fsLit String
"pfail")
showsPrec_RDR, shows_RDR, showString_RDR,
showSpace_RDR, showCommaSpace_RDR, showParen_RDR :: RdrName
showsPrec_RDR :: RdrName
showsPrec_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_SHOW (String -> FastString
fsLit String
"showsPrec")
shows_RDR :: RdrName
shows_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_SHOW (String -> FastString
fsLit String
"shows")
showString_RDR :: RdrName
showString_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_SHOW (String -> FastString
fsLit String
"showString")
showSpace_RDR :: RdrName
showSpace_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_SHOW (String -> FastString
fsLit String
"showSpace")
showCommaSpace_RDR :: RdrName
showCommaSpace_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_SHOW (String -> FastString
fsLit String
"showCommaSpace")
showParen_RDR :: RdrName
showParen_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_SHOW (String -> FastString
fsLit String
"showParen")
undefined_RDR :: RdrName
undefined_RDR :: RdrName
undefined_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ERR (String -> FastString
fsLit String
"undefined")
error_RDR :: RdrName
error_RDR :: RdrName
error_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_ERR (String -> FastString
fsLit String
"error")
u1DataCon_RDR, par1DataCon_RDR, rec1DataCon_RDR,
k1DataCon_RDR, m1DataCon_RDR, l1DataCon_RDR, r1DataCon_RDR,
prodDataCon_RDR, comp1DataCon_RDR,
unPar1_RDR, unRec1_RDR, unK1_RDR, unComp1_RDR,
from_RDR, from1_RDR, to_RDR, to1_RDR,
datatypeName_RDR, moduleName_RDR, packageName_RDR, isNewtypeName_RDR,
conName_RDR, conFixity_RDR, conIsRecord_RDR, selName_RDR,
prefixDataCon_RDR, infixDataCon_RDR, leftAssocDataCon_RDR,
rightAssocDataCon_RDR, notAssocDataCon_RDR,
uAddrDataCon_RDR, uCharDataCon_RDR, uDoubleDataCon_RDR,
uFloatDataCon_RDR, uIntDataCon_RDR, uWordDataCon_RDR,
uAddrHash_RDR, uCharHash_RDR, uDoubleHash_RDR,
uFloatHash_RDR, uIntHash_RDR, uWordHash_RDR :: RdrName
u1DataCon_RDR :: RdrName
u1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"U1")
par1DataCon_RDR :: RdrName
par1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"Par1")
rec1DataCon_RDR :: RdrName
rec1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"Rec1")
k1DataCon_RDR :: RdrName
k1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"K1")
m1DataCon_RDR :: RdrName
m1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"M1")
l1DataCon_RDR :: RdrName
l1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"L1")
r1DataCon_RDR :: RdrName
r1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"R1")
prodDataCon_RDR :: RdrName
prodDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
":*:")
comp1DataCon_RDR :: RdrName
comp1DataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"Comp1")
unPar1_RDR :: RdrName
unPar1_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"unPar1")
unRec1_RDR :: RdrName
unRec1_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"unRec1")
unK1_RDR :: RdrName
unK1_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"unK1")
unComp1_RDR :: RdrName
unComp1_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"unComp1")
from_RDR :: RdrName
from_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"from")
from1_RDR :: RdrName
from1_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"from1")
to_RDR :: RdrName
to_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"to")
to1_RDR :: RdrName
to1_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"to1")
datatypeName_RDR :: RdrName
datatypeName_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"datatypeName")
moduleName_RDR :: RdrName
moduleName_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"moduleName")
packageName_RDR :: RdrName
packageName_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"packageName")
isNewtypeName_RDR :: RdrName
isNewtypeName_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"isNewtype")
selName_RDR :: RdrName
selName_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"selName")
conName_RDR :: RdrName
conName_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"conName")
conFixity_RDR :: RdrName
conFixity_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"conFixity")
conIsRecord_RDR :: RdrName
conIsRecord_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"conIsRecord")
prefixDataCon_RDR :: RdrName
prefixDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"Prefix")
infixDataCon_RDR :: RdrName
infixDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"Infix")
leftAssocDataCon_RDR :: RdrName
leftAssocDataCon_RDR = Name -> RdrName
nameRdrName Name
leftAssociativeDataConName
rightAssocDataCon_RDR :: RdrName
rightAssocDataCon_RDR = Name -> RdrName
nameRdrName Name
rightAssociativeDataConName
notAssocDataCon_RDR :: RdrName
notAssocDataCon_RDR = Name -> RdrName
nameRdrName Name
notAssociativeDataConName
uAddrDataCon_RDR :: RdrName
uAddrDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"UAddr")
uCharDataCon_RDR :: RdrName
uCharDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"UChar")
uDoubleDataCon_RDR :: RdrName
uDoubleDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"UDouble")
uFloatDataCon_RDR :: RdrName
uFloatDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"UFloat")
uIntDataCon_RDR :: RdrName
uIntDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"UInt")
uWordDataCon_RDR :: RdrName
uWordDataCon_RDR = Module -> FastString -> RdrName
dataQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"UWord")
uAddrHash_RDR :: RdrName
uAddrHash_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"uAddr#")
uCharHash_RDR :: RdrName
uCharHash_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"uChar#")
uDoubleHash_RDR :: RdrName
uDoubleHash_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"uDouble#")
uFloatHash_RDR :: RdrName
uFloatHash_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"uFloat#")
uIntHash_RDR :: RdrName
uIntHash_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"uInt#")
uWordHash_RDR :: RdrName
uWordHash_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_GENERICS (String -> FastString
fsLit String
"uWord#")
fmap_RDR, replace_RDR, pure_RDR, ap_RDR, liftA2_RDR, foldable_foldr_RDR,
foldMap_RDR, null_RDR, all_RDR, traverse_RDR, mempty_RDR,
mappend_RDR :: RdrName
fmap_RDR :: RdrName
fmap_RDR = Name -> RdrName
nameRdrName Name
fmapName
replace_RDR :: RdrName
replace_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_BASE (String -> FastString
fsLit String
"<$")
pure_RDR :: RdrName
pure_RDR = Name -> RdrName
nameRdrName Name
pureAName
ap_RDR :: RdrName
ap_RDR = Name -> RdrName
nameRdrName Name
apAName
liftA2_RDR :: RdrName
liftA2_RDR = Module -> FastString -> RdrName
varQual_RDR Module
gHC_BASE (String -> FastString
fsLit String
"liftA2")
foldable_foldr_RDR :: RdrName
foldable_foldr_RDR = Module -> FastString -> RdrName
varQual_RDR Module
dATA_FOLDABLE (String -> FastString
fsLit String
"foldr")
foldMap_RDR :: RdrName
foldMap_RDR = Module -> FastString -> RdrName
varQual_RDR Module
dATA_FOLDABLE (String -> FastString
fsLit String
"foldMap")
null_RDR :: RdrName
null_RDR = Module -> FastString -> RdrName
varQual_RDR Module
dATA_FOLDABLE (String -> FastString
fsLit String
"null")
all_RDR :: RdrName
all_RDR = Module -> FastString -> RdrName
varQual_RDR Module
dATA_FOLDABLE (String -> FastString
fsLit String
"all")
traverse_RDR :: RdrName
traverse_RDR = Module -> FastString -> RdrName
varQual_RDR Module
dATA_TRAVERSABLE (String -> FastString
fsLit String
"traverse")
mempty_RDR :: RdrName
mempty_RDR = Name -> RdrName
nameRdrName Name
memptyName
mappend_RDR :: RdrName
mappend_RDR = Name -> RdrName
nameRdrName Name
mappendName
varQual_RDR, tcQual_RDR, clsQual_RDR, dataQual_RDR
:: Module -> FastString -> RdrName
varQual_RDR :: Module -> FastString -> RdrName
varQual_RDR Module
mod FastString
str = Module -> OccName -> RdrName
mkOrig Module
mod (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
varName FastString
str)
tcQual_RDR :: Module -> FastString -> RdrName
tcQual_RDR Module
mod FastString
str = Module -> OccName -> RdrName
mkOrig Module
mod (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
tcName FastString
str)
clsQual_RDR :: Module -> FastString -> RdrName
clsQual_RDR Module
mod FastString
str = Module -> OccName -> RdrName
mkOrig Module
mod (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
clsName FastString
str)
dataQual_RDR :: Module -> FastString -> RdrName
dataQual_RDR Module
mod FastString
str = Module -> OccName -> RdrName
mkOrig Module
mod (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
dataName FastString
str)
wildCardName :: Name
wildCardName :: Name
wildCardName = Unique -> FastString -> Name
mkSystemVarName Unique
wildCardKey (String -> FastString
fsLit String
"wild")
runMainIOName, runRWName :: Name
runMainIOName :: Name
runMainIOName = Module -> FastString -> Unique -> Name
varQual Module
gHC_TOP_HANDLER (String -> FastString
fsLit String
"runMainIO") Unique
runMainKey
runRWName :: Name
runRWName = Module -> FastString -> Unique -> Name
varQual Module
gHC_MAGIC (String -> FastString
fsLit String
"runRW#") Unique
runRWKey
orderingTyConName, ordLTDataConName, ordEQDataConName, ordGTDataConName :: Name
orderingTyConName :: Name
orderingTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"Ordering") Unique
orderingTyConKey
ordLTDataConName :: Name
ordLTDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"LT") Unique
ordLTDataConKey
ordEQDataConName :: Name
ordEQDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"EQ") Unique
ordEQDataConKey
ordGTDataConName :: Name
ordGTDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"GT") Unique
ordGTDataConKey
specTyConName :: Name
specTyConName :: Name
specTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"SPEC") Unique
specTyConKey
eitherTyConName, leftDataConName, rightDataConName :: Name
eitherTyConName :: Name
eitherTyConName = Module -> FastString -> Unique -> Name
tcQual Module
dATA_EITHER (String -> FastString
fsLit String
"Either") Unique
eitherTyConKey
leftDataConName :: Name
leftDataConName = Module -> FastString -> Unique -> Name
dcQual Module
dATA_EITHER (String -> FastString
fsLit String
"Left") Unique
leftDataConKey
rightDataConName :: Name
rightDataConName = Module -> FastString -> Unique -> Name
dcQual Module
dATA_EITHER (String -> FastString
fsLit String
"Right") Unique
rightDataConKey
v1TyConName, u1TyConName, par1TyConName, rec1TyConName,
k1TyConName, m1TyConName, sumTyConName, prodTyConName,
compTyConName, rTyConName, dTyConName,
cTyConName, sTyConName, rec0TyConName,
d1TyConName, c1TyConName, s1TyConName, noSelTyConName,
repTyConName, rep1TyConName, uRecTyConName,
uAddrTyConName, uCharTyConName, uDoubleTyConName,
uFloatTyConName, uIntTyConName, uWordTyConName,
prefixIDataConName, infixIDataConName, leftAssociativeDataConName,
rightAssociativeDataConName, notAssociativeDataConName,
sourceUnpackDataConName, sourceNoUnpackDataConName,
noSourceUnpackednessDataConName, sourceLazyDataConName,
sourceStrictDataConName, noSourceStrictnessDataConName,
decidedLazyDataConName, decidedStrictDataConName, decidedUnpackDataConName,
metaDataDataConName, metaConsDataConName, metaSelDataConName :: Name
v1TyConName :: Name
v1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"V1") Unique
v1TyConKey
u1TyConName :: Name
u1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"U1") Unique
u1TyConKey
par1TyConName :: Name
par1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Par1") Unique
par1TyConKey
rec1TyConName :: Name
rec1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Rec1") Unique
rec1TyConKey
k1TyConName :: Name
k1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"K1") Unique
k1TyConKey
m1TyConName :: Name
m1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"M1") Unique
m1TyConKey
sumTyConName :: Name
sumTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
":+:") Unique
sumTyConKey
prodTyConName :: Name
prodTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
":*:") Unique
prodTyConKey
compTyConName :: Name
compTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
":.:") Unique
compTyConKey
rTyConName :: Name
rTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"R") Unique
rTyConKey
dTyConName :: Name
dTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"D") Unique
dTyConKey
cTyConName :: Name
cTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"C") Unique
cTyConKey
sTyConName :: Name
sTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"S") Unique
sTyConKey
rec0TyConName :: Name
rec0TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Rec0") Unique
rec0TyConKey
d1TyConName :: Name
d1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"D1") Unique
d1TyConKey
c1TyConName :: Name
c1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"C1") Unique
c1TyConKey
s1TyConName :: Name
s1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"S1") Unique
s1TyConKey
noSelTyConName :: Name
noSelTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"NoSelector") Unique
noSelTyConKey
repTyConName :: Name
repTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Rep") Unique
repTyConKey
rep1TyConName :: Name
rep1TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Rep1") Unique
rep1TyConKey
uRecTyConName :: Name
uRecTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"URec") Unique
uRecTyConKey
uAddrTyConName :: Name
uAddrTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"UAddr") Unique
uAddrTyConKey
uCharTyConName :: Name
uCharTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"UChar") Unique
uCharTyConKey
uDoubleTyConName :: Name
uDoubleTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"UDouble") Unique
uDoubleTyConKey
uFloatTyConName :: Name
uFloatTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"UFloat") Unique
uFloatTyConKey
uIntTyConName :: Name
uIntTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"UInt") Unique
uIntTyConKey
uWordTyConName :: Name
uWordTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"UWord") Unique
uWordTyConKey
prefixIDataConName :: Name
prefixIDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"PrefixI") Unique
prefixIDataConKey
infixIDataConName :: Name
infixIDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"InfixI") Unique
infixIDataConKey
leftAssociativeDataConName :: Name
leftAssociativeDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"LeftAssociative") Unique
leftAssociativeDataConKey
rightAssociativeDataConName :: Name
rightAssociativeDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"RightAssociative") Unique
rightAssociativeDataConKey
notAssociativeDataConName :: Name
notAssociativeDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"NotAssociative") Unique
notAssociativeDataConKey
sourceUnpackDataConName :: Name
sourceUnpackDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"SourceUnpack") Unique
sourceUnpackDataConKey
sourceNoUnpackDataConName :: Name
sourceNoUnpackDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"SourceNoUnpack") Unique
sourceNoUnpackDataConKey
noSourceUnpackednessDataConName :: Name
noSourceUnpackednessDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"NoSourceUnpackedness") Unique
noSourceUnpackednessDataConKey
sourceLazyDataConName :: Name
sourceLazyDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"SourceLazy") Unique
sourceLazyDataConKey
sourceStrictDataConName :: Name
sourceStrictDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"SourceStrict") Unique
sourceStrictDataConKey
noSourceStrictnessDataConName :: Name
noSourceStrictnessDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"NoSourceStrictness") Unique
noSourceStrictnessDataConKey
decidedLazyDataConName :: Name
decidedLazyDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"DecidedLazy") Unique
decidedLazyDataConKey
decidedStrictDataConName :: Name
decidedStrictDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"DecidedStrict") Unique
decidedStrictDataConKey
decidedUnpackDataConName :: Name
decidedUnpackDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"DecidedUnpack") Unique
decidedUnpackDataConKey
metaDataDataConName :: Name
metaDataDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"MetaData") Unique
metaDataDataConKey
metaConsDataConName :: Name
metaConsDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"MetaCons") Unique
metaConsDataConKey
metaSelDataConName :: Name
metaSelDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_GENERICS (String -> FastString
fsLit String
"MetaSel") Unique
metaSelDataConKey
divIntName, modIntName :: Name
divIntName :: Name
divIntName = Module -> FastString -> Unique -> Name
varQual Module
gHC_CLASSES (String -> FastString
fsLit String
"divInt#") Unique
divIntIdKey
modIntName :: Name
modIntName = Module -> FastString -> Unique -> Name
varQual Module
gHC_CLASSES (String -> FastString
fsLit String
"modInt#") Unique
modIntIdKey
unpackCStringName, unpackCStringFoldrName,
unpackCStringUtf8Name, eqStringName :: Name
unpackCStringName :: Name
unpackCStringName = Module -> FastString -> Unique -> Name
varQual Module
gHC_CSTRING (String -> FastString
fsLit String
"unpackCString#") Unique
unpackCStringIdKey
unpackCStringFoldrName :: Name
unpackCStringFoldrName = Module -> FastString -> Unique -> Name
varQual Module
gHC_CSTRING (String -> FastString
fsLit String
"unpackFoldrCString#") Unique
unpackCStringFoldrIdKey
unpackCStringUtf8Name :: Name
unpackCStringUtf8Name = Module -> FastString -> Unique -> Name
varQual Module
gHC_CSTRING (String -> FastString
fsLit String
"unpackCStringUtf8#") Unique
unpackCStringUtf8IdKey
eqStringName :: Name
eqStringName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"eqString") Unique
eqStringIdKey
inlineIdName :: Name
inlineIdName :: Name
inlineIdName = Module -> FastString -> Unique -> Name
varQual Module
gHC_MAGIC (String -> FastString
fsLit String
"inline") Unique
inlineIdKey
fmapName, eqClassName, eqName, ordClassName, geName, functorClassName :: Name
eqClassName :: Name
eqClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_CLASSES (String -> FastString
fsLit String
"Eq") Unique
eqClassKey
eqName :: Name
eqName = Module -> FastString -> Unique -> Name
varQual Module
gHC_CLASSES (String -> FastString
fsLit String
"==") Unique
eqClassOpKey
ordClassName :: Name
ordClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_CLASSES (String -> FastString
fsLit String
"Ord") Unique
ordClassKey
geName :: Name
geName = Module -> FastString -> Unique -> Name
varQual Module
gHC_CLASSES (String -> FastString
fsLit String
">=") Unique
geClassOpKey
functorClassName :: Name
functorClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_BASE (String -> FastString
fsLit String
"Functor") Unique
functorClassKey
fmapName :: Name
fmapName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"fmap") Unique
fmapClassOpKey
monadClassName, thenMName, bindMName, returnMName :: Name
monadClassName :: Name
monadClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_BASE (String -> FastString
fsLit String
"Monad") Unique
monadClassKey
thenMName :: Name
thenMName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
">>") Unique
thenMClassOpKey
bindMName :: Name
bindMName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
">>=") Unique
bindMClassOpKey
returnMName :: Name
returnMName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"return") Unique
returnMClassOpKey
monadFailClassName, failMName :: Name
monadFailClassName :: Name
monadFailClassName = Module -> FastString -> Unique -> Name
clsQual Module
mONAD_FAIL (String -> FastString
fsLit String
"MonadFail") Unique
monadFailClassKey
failMName :: Name
failMName = Module -> FastString -> Unique -> Name
varQual Module
mONAD_FAIL (String -> FastString
fsLit String
"fail") Unique
failMClassOpKey
applicativeClassName, pureAName, apAName, thenAName :: Name
applicativeClassName :: Name
applicativeClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_BASE (String -> FastString
fsLit String
"Applicative") Unique
applicativeClassKey
apAName :: Name
apAName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"<*>") Unique
apAClassOpKey
pureAName :: Name
pureAName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"pure") Unique
pureAClassOpKey
thenAName :: Name
thenAName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"*>") Unique
thenAClassOpKey
foldableClassName, traversableClassName :: Name
foldableClassName :: Name
foldableClassName = Module -> FastString -> Unique -> Name
clsQual Module
dATA_FOLDABLE (String -> FastString
fsLit String
"Foldable") Unique
foldableClassKey
traversableClassName :: Name
traversableClassName = Module -> FastString -> Unique -> Name
clsQual Module
dATA_TRAVERSABLE (String -> FastString
fsLit String
"Traversable") Unique
traversableClassKey
semigroupClassName, sappendName :: Name
semigroupClassName :: Name
semigroupClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_BASE (String -> FastString
fsLit String
"Semigroup") Unique
semigroupClassKey
sappendName :: Name
sappendName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"<>") Unique
sappendClassOpKey
monoidClassName, memptyName, mappendName, mconcatName :: Name
monoidClassName :: Name
monoidClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_BASE (String -> FastString
fsLit String
"Monoid") Unique
monoidClassKey
memptyName :: Name
memptyName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"mempty") Unique
memptyClassOpKey
mappendName :: Name
mappendName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"mappend") Unique
mappendClassOpKey
mconcatName :: Name
mconcatName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"mconcat") Unique
mconcatClassOpKey
joinMName, alternativeClassName :: Name
joinMName :: Name
joinMName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"join") Unique
joinMIdKey
alternativeClassName :: Name
alternativeClassName = Module -> FastString -> Unique -> Name
clsQual Module
mONAD (String -> FastString
fsLit String
"Alternative") Unique
alternativeClassKey
joinMIdKey, apAClassOpKey, pureAClassOpKey, thenAClassOpKey,
alternativeClassKey :: Unique
joinMIdKey :: Unique
joinMIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
750
apAClassOpKey :: Unique
apAClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
751
pureAClassOpKey :: Unique
pureAClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
752
thenAClassOpKey :: Unique
thenAClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
753
alternativeClassKey :: Unique
alternativeClassKey = Int -> Unique
mkPreludeMiscIdUnique Int
754
groupWithName :: Name
groupWithName :: Name
groupWithName = Module -> FastString -> Unique -> Name
varQual Module
gHC_EXTS (String -> FastString
fsLit String
"groupWith") Unique
groupWithIdKey
fromStringName, otherwiseIdName, foldrName, buildName, augmentName,
mapName, appendName, assertName,
breakpointName, breakpointCondName, breakpointAutoName,
opaqueTyConName, dollarName :: Name
dollarName :: Name
dollarName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"$") Unique
dollarIdKey
otherwiseIdName :: Name
otherwiseIdName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"otherwise") Unique
otherwiseIdKey
foldrName :: Name
foldrName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"foldr") Unique
foldrIdKey
buildName :: Name
buildName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"build") Unique
buildIdKey
augmentName :: Name
augmentName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"augment") Unique
augmentIdKey
mapName :: Name
mapName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"map") Unique
mapIdKey
appendName :: Name
appendName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"++") Unique
appendIdKey
assertName :: Name
assertName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"assert") Unique
assertIdKey
breakpointName :: Name
breakpointName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"breakpoint") Unique
breakpointIdKey
breakpointCondName :: Name
breakpointCondName= Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"breakpointCond") Unique
breakpointCondIdKey
breakpointAutoName :: Name
breakpointAutoName= Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"breakpointAuto") Unique
breakpointAutoIdKey
opaqueTyConName :: Name
opaqueTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_BASE (String -> FastString
fsLit String
"Opaque") Unique
opaqueTyConKey
fromStringName :: Name
fromStringName = Module -> FastString -> Unique -> Name
varQual Module
dATA_STRING (String -> FastString
fsLit String
"fromString") Unique
fromStringClassOpKey
breakpointJumpName :: Name
breakpointJumpName :: Name
breakpointJumpName
= Unique -> OccName -> SrcSpan -> Name
mkInternalName
Unique
breakpointJumpIdKey
(NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
varName (String -> FastString
fsLit String
"breakpointJump"))
SrcSpan
noSrcSpan
breakpointCondJumpName :: Name
breakpointCondJumpName :: Name
breakpointCondJumpName
= Unique -> OccName -> SrcSpan -> Name
mkInternalName
Unique
breakpointCondJumpIdKey
(NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
varName (String -> FastString
fsLit String
"breakpointCondJump"))
SrcSpan
noSrcSpan
breakpointAutoJumpName :: Name
breakpointAutoJumpName :: Name
breakpointAutoJumpName
= Unique -> OccName -> SrcSpan -> Name
mkInternalName
Unique
breakpointAutoJumpIdKey
(NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
varName (String -> FastString
fsLit String
"breakpointAutoJump"))
SrcSpan
noSrcSpan
fstName, sndName :: Name
fstName :: Name
fstName = Module -> FastString -> Unique -> Name
varQual Module
dATA_TUPLE (String -> FastString
fsLit String
"fst") Unique
fstIdKey
sndName :: Name
sndName = Module -> FastString -> Unique -> Name
varQual Module
dATA_TUPLE (String -> FastString
fsLit String
"snd") Unique
sndIdKey
numClassName, fromIntegerName, minusName, negateName :: Name
numClassName :: Name
numClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_NUM (String -> FastString
fsLit String
"Num") Unique
numClassKey
fromIntegerName :: Name
fromIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NUM (String -> FastString
fsLit String
"fromInteger") Unique
fromIntegerClassOpKey
minusName :: Name
minusName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NUM (String -> FastString
fsLit String
"-") Unique
minusClassOpKey
negateName :: Name
negateName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NUM (String -> FastString
fsLit String
"negate") Unique
negateClassOpKey
integerTyConName, mkIntegerName, integerSDataConName,
integerToWord64Name, integerToInt64Name,
word64ToIntegerName, int64ToIntegerName,
plusIntegerName, timesIntegerName, smallIntegerName,
wordToIntegerName,
integerToWordName, integerToIntName, minusIntegerName,
negateIntegerName, eqIntegerPrimName, neqIntegerPrimName,
absIntegerName, signumIntegerName,
leIntegerPrimName, gtIntegerPrimName, ltIntegerPrimName, geIntegerPrimName,
compareIntegerName, quotRemIntegerName, divModIntegerName,
quotIntegerName, remIntegerName, divIntegerName, modIntegerName,
floatFromIntegerName, doubleFromIntegerName,
encodeFloatIntegerName, encodeDoubleIntegerName,
decodeDoubleIntegerName,
gcdIntegerName, lcmIntegerName,
andIntegerName, orIntegerName, xorIntegerName, complementIntegerName,
shiftLIntegerName, shiftRIntegerName, bitIntegerName :: Name
integerTyConName :: Name
integerTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"Integer") Unique
integerTyConKey
integerSDataConName :: Name
integerSDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"S#") Unique
integerSDataConKey
mkIntegerName :: Name
mkIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"mkInteger") Unique
mkIntegerIdKey
integerToWord64Name :: Name
integerToWord64Name = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"integerToWord64") Unique
integerToWord64IdKey
integerToInt64Name :: Name
integerToInt64Name = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"integerToInt64") Unique
integerToInt64IdKey
word64ToIntegerName :: Name
word64ToIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"word64ToInteger") Unique
word64ToIntegerIdKey
int64ToIntegerName :: Name
int64ToIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"int64ToInteger") Unique
int64ToIntegerIdKey
plusIntegerName :: Name
plusIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"plusInteger") Unique
plusIntegerIdKey
timesIntegerName :: Name
timesIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"timesInteger") Unique
timesIntegerIdKey
smallIntegerName :: Name
smallIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"smallInteger") Unique
smallIntegerIdKey
wordToIntegerName :: Name
wordToIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"wordToInteger") Unique
wordToIntegerIdKey
integerToWordName :: Name
integerToWordName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"integerToWord") Unique
integerToWordIdKey
integerToIntName :: Name
integerToIntName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"integerToInt") Unique
integerToIntIdKey
minusIntegerName :: Name
minusIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"minusInteger") Unique
minusIntegerIdKey
negateIntegerName :: Name
negateIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"negateInteger") Unique
negateIntegerIdKey
eqIntegerPrimName :: Name
eqIntegerPrimName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"eqInteger#") Unique
eqIntegerPrimIdKey
neqIntegerPrimName :: Name
neqIntegerPrimName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"neqInteger#") Unique
neqIntegerPrimIdKey
absIntegerName :: Name
absIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"absInteger") Unique
absIntegerIdKey
signumIntegerName :: Name
signumIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"signumInteger") Unique
signumIntegerIdKey
leIntegerPrimName :: Name
leIntegerPrimName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"leInteger#") Unique
leIntegerPrimIdKey
gtIntegerPrimName :: Name
gtIntegerPrimName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"gtInteger#") Unique
gtIntegerPrimIdKey
ltIntegerPrimName :: Name
ltIntegerPrimName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"ltInteger#") Unique
ltIntegerPrimIdKey
geIntegerPrimName :: Name
geIntegerPrimName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"geInteger#") Unique
geIntegerPrimIdKey
compareIntegerName :: Name
compareIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"compareInteger") Unique
compareIntegerIdKey
quotRemIntegerName :: Name
quotRemIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"quotRemInteger") Unique
quotRemIntegerIdKey
divModIntegerName :: Name
divModIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"divModInteger") Unique
divModIntegerIdKey
quotIntegerName :: Name
quotIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"quotInteger") Unique
quotIntegerIdKey
remIntegerName :: Name
remIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"remInteger") Unique
remIntegerIdKey
divIntegerName :: Name
divIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"divInteger") Unique
divIntegerIdKey
modIntegerName :: Name
modIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"modInteger") Unique
modIntegerIdKey
floatFromIntegerName :: Name
floatFromIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"floatFromInteger") Unique
floatFromIntegerIdKey
doubleFromIntegerName :: Name
doubleFromIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"doubleFromInteger") Unique
doubleFromIntegerIdKey
encodeFloatIntegerName :: Name
encodeFloatIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"encodeFloatInteger") Unique
encodeFloatIntegerIdKey
encodeDoubleIntegerName :: Name
encodeDoubleIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"encodeDoubleInteger") Unique
encodeDoubleIntegerIdKey
decodeDoubleIntegerName :: Name
decodeDoubleIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"decodeDoubleInteger") Unique
decodeDoubleIntegerIdKey
gcdIntegerName :: Name
gcdIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"gcdInteger") Unique
gcdIntegerIdKey
lcmIntegerName :: Name
lcmIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"lcmInteger") Unique
lcmIntegerIdKey
andIntegerName :: Name
andIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"andInteger") Unique
andIntegerIdKey
orIntegerName :: Name
orIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"orInteger") Unique
orIntegerIdKey
xorIntegerName :: Name
xorIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"xorInteger") Unique
xorIntegerIdKey
complementIntegerName :: Name
complementIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"complementInteger") Unique
complementIntegerIdKey
shiftLIntegerName :: Name
shiftLIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"shiftLInteger") Unique
shiftLIntegerIdKey
shiftRIntegerName :: Name
shiftRIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"shiftRInteger") Unique
shiftRIntegerIdKey
bitIntegerName :: Name
bitIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_INTEGER_TYPE (String -> FastString
fsLit String
"bitInteger") Unique
bitIntegerIdKey
naturalTyConName, naturalSDataConName :: Name
naturalTyConName :: Name
naturalTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_NATURAL (String -> FastString
fsLit String
"Natural") Unique
naturalTyConKey
naturalSDataConName :: Name
naturalSDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_NATURAL (String -> FastString
fsLit String
"NatS#") Unique
naturalSDataConKey
naturalFromIntegerName :: Name
naturalFromIntegerName :: Name
naturalFromIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NATURAL (String -> FastString
fsLit String
"naturalFromInteger") Unique
naturalFromIntegerIdKey
naturalToIntegerName, plusNaturalName, minusNaturalName, timesNaturalName,
mkNaturalName, wordToNaturalName :: Name
naturalToIntegerName :: Name
naturalToIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NATURAL (String -> FastString
fsLit String
"naturalToInteger") Unique
naturalToIntegerIdKey
plusNaturalName :: Name
plusNaturalName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NATURAL (String -> FastString
fsLit String
"plusNatural") Unique
plusNaturalIdKey
minusNaturalName :: Name
minusNaturalName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NATURAL (String -> FastString
fsLit String
"minusNatural") Unique
minusNaturalIdKey
timesNaturalName :: Name
timesNaturalName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NATURAL (String -> FastString
fsLit String
"timesNatural") Unique
timesNaturalIdKey
mkNaturalName :: Name
mkNaturalName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NATURAL (String -> FastString
fsLit String
"mkNatural") Unique
mkNaturalIdKey
wordToNaturalName :: Name
wordToNaturalName = Module -> FastString -> Unique -> Name
varQual Module
gHC_NATURAL (String -> FastString
fsLit String
"wordToNatural#") Unique
wordToNaturalIdKey
rationalTyConName, ratioTyConName, ratioDataConName, realClassName,
integralClassName, realFracClassName, fractionalClassName,
fromRationalName, toIntegerName, toRationalName, fromIntegralName,
realToFracName :: Name
rationalTyConName :: Name
rationalTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_REAL (String -> FastString
fsLit String
"Rational") Unique
rationalTyConKey
ratioTyConName :: Name
ratioTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_REAL (String -> FastString
fsLit String
"Ratio") Unique
ratioTyConKey
ratioDataConName :: Name
ratioDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_REAL (String -> FastString
fsLit String
":%") Unique
ratioDataConKey
realClassName :: Name
realClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_REAL (String -> FastString
fsLit String
"Real") Unique
realClassKey
integralClassName :: Name
integralClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_REAL (String -> FastString
fsLit String
"Integral") Unique
integralClassKey
realFracClassName :: Name
realFracClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_REAL (String -> FastString
fsLit String
"RealFrac") Unique
realFracClassKey
fractionalClassName :: Name
fractionalClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_REAL (String -> FastString
fsLit String
"Fractional") Unique
fractionalClassKey
fromRationalName :: Name
fromRationalName = Module -> FastString -> Unique -> Name
varQual Module
gHC_REAL (String -> FastString
fsLit String
"fromRational") Unique
fromRationalClassOpKey
toIntegerName :: Name
toIntegerName = Module -> FastString -> Unique -> Name
varQual Module
gHC_REAL (String -> FastString
fsLit String
"toInteger") Unique
toIntegerClassOpKey
toRationalName :: Name
toRationalName = Module -> FastString -> Unique -> Name
varQual Module
gHC_REAL (String -> FastString
fsLit String
"toRational") Unique
toRationalClassOpKey
fromIntegralName :: Name
fromIntegralName = Module -> FastString -> Unique -> Name
varQual Module
gHC_REAL (String -> FastString
fsLit String
"fromIntegral")Unique
fromIntegralIdKey
realToFracName :: Name
realToFracName = Module -> FastString -> Unique -> Name
varQual Module
gHC_REAL (String -> FastString
fsLit String
"realToFrac") Unique
realToFracIdKey
floatingClassName, realFloatClassName :: Name
floatingClassName :: Name
floatingClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_FLOAT (String -> FastString
fsLit String
"Floating") Unique
floatingClassKey
realFloatClassName :: Name
realFloatClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_FLOAT (String -> FastString
fsLit String
"RealFloat") Unique
realFloatClassKey
rationalToFloatName, rationalToDoubleName :: Name
rationalToFloatName :: Name
rationalToFloatName = Module -> FastString -> Unique -> Name
varQual Module
gHC_FLOAT (String -> FastString
fsLit String
"rationalToFloat") Unique
rationalToFloatIdKey
rationalToDoubleName :: Name
rationalToDoubleName = Module -> FastString -> Unique -> Name
varQual Module
gHC_FLOAT (String -> FastString
fsLit String
"rationalToDouble") Unique
rationalToDoubleIdKey
ixClassName :: Name
ixClassName :: Name
ixClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_ARR (String -> FastString
fsLit String
"Ix") Unique
ixClassKey
trModuleTyConName
, trModuleDataConName
, trNameTyConName
, trNameSDataConName
, trNameDDataConName
, trTyConTyConName
, trTyConDataConName
:: Name
trModuleTyConName :: Name
trModuleTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"Module") Unique
trModuleTyConKey
trModuleDataConName :: Name
trModuleDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"Module") Unique
trModuleDataConKey
trNameTyConName :: Name
trNameTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TrName") Unique
trNameTyConKey
trNameSDataConName :: Name
trNameSDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TrNameS") Unique
trNameSDataConKey
trNameDDataConName :: Name
trNameDDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TrNameD") Unique
trNameDDataConKey
trTyConTyConName :: Name
trTyConTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TyCon") Unique
trTyConTyConKey
trTyConDataConName :: Name
trTyConDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TyCon") Unique
trTyConDataConKey
kindRepTyConName
, kindRepTyConAppDataConName
, kindRepVarDataConName
, kindRepAppDataConName
, kindRepFunDataConName
, kindRepTYPEDataConName
, kindRepTypeLitSDataConName
, kindRepTypeLitDDataConName
:: Name
kindRepTyConName :: Name
kindRepTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRep") Unique
kindRepTyConKey
kindRepTyConAppDataConName :: Name
kindRepTyConAppDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRepTyConApp") Unique
kindRepTyConAppDataConKey
kindRepVarDataConName :: Name
kindRepVarDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRepVar") Unique
kindRepVarDataConKey
kindRepAppDataConName :: Name
kindRepAppDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRepApp") Unique
kindRepAppDataConKey
kindRepFunDataConName :: Name
kindRepFunDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRepFun") Unique
kindRepFunDataConKey
kindRepTYPEDataConName :: Name
kindRepTYPEDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRepTYPE") Unique
kindRepTYPEDataConKey
kindRepTypeLitSDataConName :: Name
kindRepTypeLitSDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRepTypeLitS") Unique
kindRepTypeLitSDataConKey
kindRepTypeLitDDataConName :: Name
kindRepTypeLitDDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"KindRepTypeLitD") Unique
kindRepTypeLitDDataConKey
typeLitSortTyConName
, typeLitSymbolDataConName
, typeLitNatDataConName
:: Name
typeLitSortTyConName :: Name
typeLitSortTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TypeLitSort") Unique
typeLitSortTyConKey
typeLitSymbolDataConName :: Name
typeLitSymbolDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TypeLitSymbol") Unique
typeLitSymbolDataConKey
typeLitNatDataConName :: Name
typeLitNatDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"TypeLitNat") Unique
typeLitNatDataConKey
typeableClassName
, typeRepTyConName
, someTypeRepTyConName
, someTypeRepDataConName
, mkTrTypeName
, mkTrConName
, mkTrAppName
, mkTrFunName
, typeRepIdName
, typeNatTypeRepName
, typeSymbolTypeRepName
, trGhcPrimModuleName
:: Name
typeableClassName :: Name
typeableClassName = Module -> FastString -> Unique -> Name
clsQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"Typeable") Unique
typeableClassKey
typeRepTyConName :: Name
typeRepTyConName = Module -> FastString -> Unique -> Name
tcQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"TypeRep") Unique
typeRepTyConKey
someTypeRepTyConName :: Name
someTypeRepTyConName = Module -> FastString -> Unique -> Name
tcQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"SomeTypeRep") Unique
someTypeRepTyConKey
someTypeRepDataConName :: Name
someTypeRepDataConName = Module -> FastString -> Unique -> Name
dcQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"SomeTypeRep") Unique
someTypeRepDataConKey
typeRepIdName :: Name
typeRepIdName = Module -> FastString -> Unique -> Name
varQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"typeRep#") Unique
typeRepIdKey
mkTrTypeName :: Name
mkTrTypeName = Module -> FastString -> Unique -> Name
varQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"mkTrType") Unique
mkTrTypeKey
mkTrConName :: Name
mkTrConName = Module -> FastString -> Unique -> Name
varQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"mkTrCon") Unique
mkTrConKey
mkTrAppName :: Name
mkTrAppName = Module -> FastString -> Unique -> Name
varQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"mkTrApp") Unique
mkTrAppKey
mkTrFunName :: Name
mkTrFunName = Module -> FastString -> Unique -> Name
varQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"mkTrFun") Unique
mkTrFunKey
typeNatTypeRepName :: Name
typeNatTypeRepName = Module -> FastString -> Unique -> Name
varQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"typeNatTypeRep") Unique
typeNatTypeRepKey
typeSymbolTypeRepName :: Name
typeSymbolTypeRepName = Module -> FastString -> Unique -> Name
varQual Module
tYPEABLE_INTERNAL (String -> FastString
fsLit String
"typeSymbolTypeRep") Unique
typeSymbolTypeRepKey
trGhcPrimModuleName :: Name
trGhcPrimModuleName = Module -> FastString -> Unique -> Name
varQual Module
gHC_TYPES (String -> FastString
fsLit String
"tr$ModuleGHCPrim") Unique
trGhcPrimModuleKey
starKindRepName, starArrStarKindRepName, starArrStarArrStarKindRepName :: Name
starKindRepName :: Name
starKindRepName = Module -> FastString -> Unique -> Name
varQual Module
gHC_TYPES (String -> FastString
fsLit String
"krep$*") Unique
starKindRepKey
starArrStarKindRepName :: Name
starArrStarKindRepName = Module -> FastString -> Unique -> Name
varQual Module
gHC_TYPES (String -> FastString
fsLit String
"krep$*Arr*") Unique
starArrStarKindRepKey
starArrStarArrStarKindRepName :: Name
starArrStarArrStarKindRepName = Module -> FastString -> Unique -> Name
varQual Module
gHC_TYPES (String -> FastString
fsLit String
"krep$*->*->*") Unique
starArrStarArrStarKindRepKey
errorMessageTypeErrorFamName
, typeErrorTextDataConName
, typeErrorAppendDataConName
, typeErrorVAppendDataConName
, typeErrorShowTypeDataConName
:: Name
errorMessageTypeErrorFamName :: Name
errorMessageTypeErrorFamName =
Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPELITS (String -> FastString
fsLit String
"TypeError") Unique
errorMessageTypeErrorFamKey
typeErrorTextDataConName :: Name
typeErrorTextDataConName =
Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPELITS (String -> FastString
fsLit String
"Text") Unique
typeErrorTextDataConKey
typeErrorAppendDataConName :: Name
typeErrorAppendDataConName =
Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPELITS (String -> FastString
fsLit String
":<>:") Unique
typeErrorAppendDataConKey
typeErrorVAppendDataConName :: Name
typeErrorVAppendDataConName =
Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPELITS (String -> FastString
fsLit String
":$$:") Unique
typeErrorVAppendDataConKey
typeErrorShowTypeDataConName :: Name
typeErrorShowTypeDataConName =
Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPELITS (String -> FastString
fsLit String
"ShowType") Unique
typeErrorShowTypeDataConKey
toDynName :: Name
toDynName :: Name
toDynName = Module -> FastString -> Unique -> Name
varQual Module
dYNAMIC (String -> FastString
fsLit String
"toDyn") Unique
toDynIdKey
dataClassName :: Name
dataClassName :: Name
dataClassName = Module -> FastString -> Unique -> Name
clsQual Module
gENERICS (String -> FastString
fsLit String
"Data") Unique
dataClassKey
assertErrorName :: Name
assertErrorName :: Name
assertErrorName = Module -> FastString -> Unique -> Name
varQual Module
gHC_IO_Exception (String -> FastString
fsLit String
"assertError") Unique
assertErrorIdKey
traceName :: Name
traceName :: Name
traceName = Module -> FastString -> Unique -> Name
varQual Module
dEBUG_TRACE (String -> FastString
fsLit String
"trace") Unique
traceKey
enumClassName, enumFromName, enumFromToName, enumFromThenName,
enumFromThenToName, boundedClassName :: Name
enumClassName :: Name
enumClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_ENUM (String -> FastString
fsLit String
"Enum") Unique
enumClassKey
enumFromName :: Name
enumFromName = Module -> FastString -> Unique -> Name
varQual Module
gHC_ENUM (String -> FastString
fsLit String
"enumFrom") Unique
enumFromClassOpKey
enumFromToName :: Name
enumFromToName = Module -> FastString -> Unique -> Name
varQual Module
gHC_ENUM (String -> FastString
fsLit String
"enumFromTo") Unique
enumFromToClassOpKey
enumFromThenName :: Name
enumFromThenName = Module -> FastString -> Unique -> Name
varQual Module
gHC_ENUM (String -> FastString
fsLit String
"enumFromThen") Unique
enumFromThenClassOpKey
enumFromThenToName :: Name
enumFromThenToName = Module -> FastString -> Unique -> Name
varQual Module
gHC_ENUM (String -> FastString
fsLit String
"enumFromThenTo") Unique
enumFromThenToClassOpKey
boundedClassName :: Name
boundedClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_ENUM (String -> FastString
fsLit String
"Bounded") Unique
boundedClassKey
concatName, filterName, zipName :: Name
concatName :: Name
concatName = Module -> FastString -> Unique -> Name
varQual Module
gHC_LIST (String -> FastString
fsLit String
"concat") Unique
concatIdKey
filterName :: Name
filterName = Module -> FastString -> Unique -> Name
varQual Module
gHC_LIST (String -> FastString
fsLit String
"filter") Unique
filterIdKey
zipName :: Name
zipName = Module -> FastString -> Unique -> Name
varQual Module
gHC_LIST (String -> FastString
fsLit String
"zip") Unique
zipIdKey
isListClassName, fromListName, fromListNName, toListName :: Name
isListClassName :: Name
isListClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_EXTS (String -> FastString
fsLit String
"IsList") Unique
isListClassKey
fromListName :: Name
fromListName = Module -> FastString -> Unique -> Name
varQual Module
gHC_EXTS (String -> FastString
fsLit String
"fromList") Unique
fromListClassOpKey
fromListNName :: Name
fromListNName = Module -> FastString -> Unique -> Name
varQual Module
gHC_EXTS (String -> FastString
fsLit String
"fromListN") Unique
fromListNClassOpKey
toListName :: Name
toListName = Module -> FastString -> Unique -> Name
varQual Module
gHC_EXTS (String -> FastString
fsLit String
"toList") Unique
toListClassOpKey
showClassName :: Name
showClassName :: Name
showClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_SHOW (String -> FastString
fsLit String
"Show") Unique
showClassKey
readClassName :: Name
readClassName :: Name
readClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_READ (String -> FastString
fsLit String
"Read") Unique
readClassKey
genClassName, gen1ClassName, datatypeClassName, constructorClassName,
selectorClassName :: Name
genClassName :: Name
genClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Generic") Unique
genClassKey
gen1ClassName :: Name
gen1ClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Generic1") Unique
gen1ClassKey
datatypeClassName :: Name
datatypeClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Datatype") Unique
datatypeClassKey
constructorClassName :: Name
constructorClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Constructor") Unique
constructorClassKey
selectorClassName :: Name
selectorClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_GENERICS (String -> FastString
fsLit String
"Selector") Unique
selectorClassKey
genericClassNames :: [Name]
genericClassNames :: [Name]
genericClassNames = [Name
genClassName, Name
gen1ClassName]
ghciIoClassName, ghciStepIoMName :: Name
ghciIoClassName :: Name
ghciIoClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_GHCI (String -> FastString
fsLit String
"GHCiSandboxIO") Unique
ghciIoClassKey
ghciStepIoMName :: Name
ghciStepIoMName = Module -> FastString -> Unique -> Name
varQual Module
gHC_GHCI (String -> FastString
fsLit String
"ghciStepIO") Unique
ghciStepIoMClassOpKey
ioTyConName, ioDataConName,
thenIOName, bindIOName, returnIOName, failIOName :: Name
ioTyConName :: Name
ioTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_TYPES (String -> FastString
fsLit String
"IO") Unique
ioTyConKey
ioDataConName :: Name
ioDataConName = Module -> FastString -> Unique -> Name
dcQual Module
gHC_TYPES (String -> FastString
fsLit String
"IO") Unique
ioDataConKey
thenIOName :: Name
thenIOName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"thenIO") Unique
thenIOIdKey
bindIOName :: Name
bindIOName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"bindIO") Unique
bindIOIdKey
returnIOName :: Name
returnIOName = Module -> FastString -> Unique -> Name
varQual Module
gHC_BASE (String -> FastString
fsLit String
"returnIO") Unique
returnIOIdKey
failIOName :: Name
failIOName = Module -> FastString -> Unique -> Name
varQual Module
gHC_IO (String -> FastString
fsLit String
"failIO") Unique
failIOIdKey
printName :: Name
printName :: Name
printName = Module -> FastString -> Unique -> Name
varQual Module
sYSTEM_IO (String -> FastString
fsLit String
"print") Unique
printIdKey
int8TyConName, int16TyConName, int32TyConName, int64TyConName :: Name
int8TyConName :: Name
int8TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_INT (String -> FastString
fsLit String
"Int8") Unique
int8TyConKey
int16TyConName :: Name
int16TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_INT (String -> FastString
fsLit String
"Int16") Unique
int16TyConKey
int32TyConName :: Name
int32TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_INT (String -> FastString
fsLit String
"Int32") Unique
int32TyConKey
int64TyConName :: Name
int64TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_INT (String -> FastString
fsLit String
"Int64") Unique
int64TyConKey
word16TyConName, word32TyConName, word64TyConName :: Name
word16TyConName :: Name
word16TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_WORD (String -> FastString
fsLit String
"Word16") Unique
word16TyConKey
word32TyConName :: Name
word32TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_WORD (String -> FastString
fsLit String
"Word32") Unique
word32TyConKey
word64TyConName :: Name
word64TyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_WORD (String -> FastString
fsLit String
"Word64") Unique
word64TyConKey
ptrTyConName, funPtrTyConName :: Name
ptrTyConName :: Name
ptrTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_PTR (String -> FastString
fsLit String
"Ptr") Unique
ptrTyConKey
funPtrTyConName :: Name
funPtrTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_PTR (String -> FastString
fsLit String
"FunPtr") Unique
funPtrTyConKey
stablePtrTyConName, newStablePtrName :: Name
stablePtrTyConName :: Name
stablePtrTyConName = Module -> FastString -> Unique -> Name
tcQual Module
gHC_STABLE (String -> FastString
fsLit String
"StablePtr") Unique
stablePtrTyConKey
newStablePtrName :: Name
newStablePtrName = Module -> FastString -> Unique -> Name
varQual Module
gHC_STABLE (String -> FastString
fsLit String
"newStablePtr") Unique
newStablePtrIdKey
monadFixClassName, mfixName :: Name
monadFixClassName :: Name
monadFixClassName = Module -> FastString -> Unique -> Name
clsQual Module
mONAD_FIX (String -> FastString
fsLit String
"MonadFix") Unique
monadFixClassKey
mfixName :: Name
mfixName = Module -> FastString -> Unique -> Name
varQual Module
mONAD_FIX (String -> FastString
fsLit String
"mfix") Unique
mfixIdKey
arrAName, composeAName, firstAName, appAName, choiceAName, loopAName :: Name
arrAName :: Name
arrAName = Module -> FastString -> Unique -> Name
varQual Module
aRROW (String -> FastString
fsLit String
"arr") Unique
arrAIdKey
composeAName :: Name
composeAName = Module -> FastString -> Unique -> Name
varQual Module
gHC_DESUGAR (String -> FastString
fsLit String
">>>") Unique
composeAIdKey
firstAName :: Name
firstAName = Module -> FastString -> Unique -> Name
varQual Module
aRROW (String -> FastString
fsLit String
"first") Unique
firstAIdKey
appAName :: Name
appAName = Module -> FastString -> Unique -> Name
varQual Module
aRROW (String -> FastString
fsLit String
"app") Unique
appAIdKey
choiceAName :: Name
choiceAName = Module -> FastString -> Unique -> Name
varQual Module
aRROW (String -> FastString
fsLit String
"|||") Unique
choiceAIdKey
loopAName :: Name
loopAName = Module -> FastString -> Unique -> Name
varQual Module
aRROW (String -> FastString
fsLit String
"loop") Unique
loopAIdKey
guardMName, liftMName, mzipName :: Name
guardMName :: Name
guardMName = Module -> FastString -> Unique -> Name
varQual Module
mONAD (String -> FastString
fsLit String
"guard") Unique
guardMIdKey
liftMName :: Name
liftMName = Module -> FastString -> Unique -> Name
varQual Module
mONAD (String -> FastString
fsLit String
"liftM") Unique
liftMIdKey
mzipName :: Name
mzipName = Module -> FastString -> Unique -> Name
varQual Module
mONAD_ZIP (String -> FastString
fsLit String
"mzip") Unique
mzipIdKey
toAnnotationWrapperName :: Name
toAnnotationWrapperName :: Name
toAnnotationWrapperName = Module -> FastString -> Unique -> Name
varQual Module
gHC_DESUGAR (String -> FastString
fsLit String
"toAnnotationWrapper") Unique
toAnnotationWrapperIdKey
monadPlusClassName, randomClassName, randomGenClassName,
isStringClassName :: Name
monadPlusClassName :: Name
monadPlusClassName = Module -> FastString -> Unique -> Name
clsQual Module
mONAD (String -> FastString
fsLit String
"MonadPlus") Unique
monadPlusClassKey
randomClassName :: Name
randomClassName = Module -> FastString -> Unique -> Name
clsQual Module
rANDOM (String -> FastString
fsLit String
"Random") Unique
randomClassKey
randomGenClassName :: Name
randomGenClassName = Module -> FastString -> Unique -> Name
clsQual Module
rANDOM (String -> FastString
fsLit String
"RandomGen") Unique
randomGenClassKey
isStringClassName :: Name
isStringClassName = Module -> FastString -> Unique -> Name
clsQual Module
dATA_STRING (String -> FastString
fsLit String
"IsString") Unique
isStringClassKey
knownNatClassName :: Name
knownNatClassName :: Name
knownNatClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_TYPENATS (String -> FastString
fsLit String
"KnownNat") Unique
knownNatClassNameKey
knownSymbolClassName :: Name
knownSymbolClassName :: Name
knownSymbolClassName = Module -> FastString -> Unique -> Name
clsQual Module
gHC_TYPELITS (String -> FastString
fsLit String
"KnownSymbol") Unique
knownSymbolClassNameKey
isLabelClassName :: Name
isLabelClassName :: Name
isLabelClassName
= Module -> FastString -> Unique -> Name
clsQual Module
gHC_OVER_LABELS (String -> FastString
fsLit String
"IsLabel") Unique
isLabelClassNameKey
ipClassName :: Name
ipClassName :: Name
ipClassName
= Module -> FastString -> Unique -> Name
clsQual Module
gHC_CLASSES (String -> FastString
fsLit String
"IP") Unique
ipClassKey
hasFieldClassName :: Name
hasFieldClassName :: Name
hasFieldClassName
= Module -> FastString -> Unique -> Name
clsQual Module
gHC_RECORDS (String -> FastString
fsLit String
"HasField") Unique
hasFieldClassNameKey
callStackTyConName, emptyCallStackName, pushCallStackName,
srcLocDataConName :: Name
callStackTyConName :: Name
callStackTyConName
= Module -> FastString -> Unique -> Name
tcQual Module
gHC_STACK_TYPES (String -> FastString
fsLit String
"CallStack") Unique
callStackTyConKey
emptyCallStackName :: Name
emptyCallStackName
= Module -> FastString -> Unique -> Name
varQual Module
gHC_STACK_TYPES (String -> FastString
fsLit String
"emptyCallStack") Unique
emptyCallStackKey
pushCallStackName :: Name
pushCallStackName
= Module -> FastString -> Unique -> Name
varQual Module
gHC_STACK_TYPES (String -> FastString
fsLit String
"pushCallStack") Unique
pushCallStackKey
srcLocDataConName :: Name
srcLocDataConName
= Module -> FastString -> Unique -> Name
dcQual Module
gHC_STACK_TYPES (String -> FastString
fsLit String
"SrcLoc") Unique
srcLocDataConKey
pLUGINS :: Module
pLUGINS :: Module
pLUGINS = FastString -> Module
mkThisGhcModule (String -> FastString
fsLit String
"Plugins")
pluginTyConName :: Name
pluginTyConName :: Name
pluginTyConName = Module -> FastString -> Unique -> Name
tcQual Module
pLUGINS (String -> FastString
fsLit String
"Plugin") Unique
pluginTyConKey
frontendPluginTyConName :: Name
frontendPluginTyConName :: Name
frontendPluginTyConName = Module -> FastString -> Unique -> Name
tcQual Module
pLUGINS (String -> FastString
fsLit String
"FrontendPlugin") Unique
frontendPluginTyConKey
makeStaticName :: Name
makeStaticName :: Name
makeStaticName =
Module -> FastString -> Unique -> Name
varQual Module
gHC_STATICPTR_INTERNAL (String -> FastString
fsLit String
"makeStatic") Unique
makeStaticKey
staticPtrInfoTyConName :: Name
staticPtrInfoTyConName :: Name
staticPtrInfoTyConName =
Module -> FastString -> Unique -> Name
tcQual Module
gHC_STATICPTR (String -> FastString
fsLit String
"StaticPtrInfo") Unique
staticPtrInfoTyConKey
staticPtrInfoDataConName :: Name
staticPtrInfoDataConName :: Name
staticPtrInfoDataConName =
Module -> FastString -> Unique -> Name
dcQual Module
gHC_STATICPTR (String -> FastString
fsLit String
"StaticPtrInfo") Unique
staticPtrInfoDataConKey
staticPtrTyConName :: Name
staticPtrTyConName :: Name
staticPtrTyConName =
Module -> FastString -> Unique -> Name
tcQual Module
gHC_STATICPTR (String -> FastString
fsLit String
"StaticPtr") Unique
staticPtrTyConKey
staticPtrDataConName :: Name
staticPtrDataConName :: Name
staticPtrDataConName =
Module -> FastString -> Unique -> Name
dcQual Module
gHC_STATICPTR (String -> FastString
fsLit String
"StaticPtr") Unique
staticPtrDataConKey
fromStaticPtrName :: Name
fromStaticPtrName :: Name
fromStaticPtrName =
Module -> FastString -> Unique -> Name
varQual Module
gHC_STATICPTR (String -> FastString
fsLit String
"fromStaticPtr") Unique
fromStaticPtrClassOpKey
fingerprintDataConName :: Name
fingerprintDataConName :: Name
fingerprintDataConName =
Module -> FastString -> Unique -> Name
dcQual Module
gHC_FINGERPRINT_TYPE (String -> FastString
fsLit String
"Fingerprint") Unique
fingerprintDataConKey
varQual, tcQual, clsQual, dcQual :: Module -> FastString -> Unique -> Name
varQual :: Module -> FastString -> Unique -> Name
varQual = NameSpace -> Module -> FastString -> Unique -> Name
mk_known_key_name NameSpace
varName
tcQual :: Module -> FastString -> Unique -> Name
tcQual = NameSpace -> Module -> FastString -> Unique -> Name
mk_known_key_name NameSpace
tcName
clsQual :: Module -> FastString -> Unique -> Name
clsQual = NameSpace -> Module -> FastString -> Unique -> Name
mk_known_key_name NameSpace
clsName
dcQual :: Module -> FastString -> Unique -> Name
dcQual = NameSpace -> Module -> FastString -> Unique -> Name
mk_known_key_name NameSpace
dataName
mk_known_key_name :: NameSpace -> Module -> FastString -> Unique -> Name
mk_known_key_name :: NameSpace -> Module -> FastString -> Unique -> Name
mk_known_key_name NameSpace
space Module
modu FastString
str Unique
unique
= Unique -> Module -> OccName -> SrcSpan -> Name
mkExternalName Unique
unique Module
modu (NameSpace -> FastString -> OccName
mkOccNameFS NameSpace
space FastString
str) SrcSpan
noSrcSpan
boundedClassKey, enumClassKey, eqClassKey, floatingClassKey,
fractionalClassKey, integralClassKey, monadClassKey, dataClassKey,
functorClassKey, numClassKey, ordClassKey, readClassKey, realClassKey,
realFloatClassKey, realFracClassKey, showClassKey, ixClassKey :: Unique
boundedClassKey :: Unique
boundedClassKey = Int -> Unique
mkPreludeClassUnique Int
1
enumClassKey :: Unique
enumClassKey = Int -> Unique
mkPreludeClassUnique Int
2
eqClassKey :: Unique
eqClassKey = Int -> Unique
mkPreludeClassUnique Int
3
floatingClassKey :: Unique
floatingClassKey = Int -> Unique
mkPreludeClassUnique Int
5
fractionalClassKey :: Unique
fractionalClassKey = Int -> Unique
mkPreludeClassUnique Int
6
integralClassKey :: Unique
integralClassKey = Int -> Unique
mkPreludeClassUnique Int
7
monadClassKey :: Unique
monadClassKey = Int -> Unique
mkPreludeClassUnique Int
8
dataClassKey :: Unique
dataClassKey = Int -> Unique
mkPreludeClassUnique Int
9
functorClassKey :: Unique
functorClassKey = Int -> Unique
mkPreludeClassUnique Int
10
numClassKey :: Unique
numClassKey = Int -> Unique
mkPreludeClassUnique Int
11
ordClassKey :: Unique
ordClassKey = Int -> Unique
mkPreludeClassUnique Int
12
readClassKey :: Unique
readClassKey = Int -> Unique
mkPreludeClassUnique Int
13
realClassKey :: Unique
realClassKey = Int -> Unique
mkPreludeClassUnique Int
14
realFloatClassKey :: Unique
realFloatClassKey = Int -> Unique
mkPreludeClassUnique Int
15
realFracClassKey :: Unique
realFracClassKey = Int -> Unique
mkPreludeClassUnique Int
16
showClassKey :: Unique
showClassKey = Int -> Unique
mkPreludeClassUnique Int
17
ixClassKey :: Unique
ixClassKey = Int -> Unique
mkPreludeClassUnique Int
18
typeableClassKey, typeable1ClassKey, typeable2ClassKey, typeable3ClassKey,
typeable4ClassKey, typeable5ClassKey, typeable6ClassKey, typeable7ClassKey
:: Unique
typeableClassKey :: Unique
typeableClassKey = Int -> Unique
mkPreludeClassUnique Int
20
typeable1ClassKey :: Unique
typeable1ClassKey = Int -> Unique
mkPreludeClassUnique Int
21
typeable2ClassKey :: Unique
typeable2ClassKey = Int -> Unique
mkPreludeClassUnique Int
22
typeable3ClassKey :: Unique
typeable3ClassKey = Int -> Unique
mkPreludeClassUnique Int
23
typeable4ClassKey :: Unique
typeable4ClassKey = Int -> Unique
mkPreludeClassUnique Int
24
typeable5ClassKey :: Unique
typeable5ClassKey = Int -> Unique
mkPreludeClassUnique Int
25
typeable6ClassKey :: Unique
typeable6ClassKey = Int -> Unique
mkPreludeClassUnique Int
26
typeable7ClassKey :: Unique
typeable7ClassKey = Int -> Unique
mkPreludeClassUnique Int
27
monadFixClassKey :: Unique
monadFixClassKey :: Unique
monadFixClassKey = Int -> Unique
mkPreludeClassUnique Int
28
monadFailClassKey :: Unique
monadFailClassKey :: Unique
monadFailClassKey = Int -> Unique
mkPreludeClassUnique Int
29
monadPlusClassKey, randomClassKey, randomGenClassKey :: Unique
monadPlusClassKey :: Unique
monadPlusClassKey = Int -> Unique
mkPreludeClassUnique Int
30
randomClassKey :: Unique
randomClassKey = Int -> Unique
mkPreludeClassUnique Int
31
randomGenClassKey :: Unique
randomGenClassKey = Int -> Unique
mkPreludeClassUnique Int
32
isStringClassKey :: Unique
isStringClassKey :: Unique
isStringClassKey = Int -> Unique
mkPreludeClassUnique Int
33
applicativeClassKey, foldableClassKey, traversableClassKey :: Unique
applicativeClassKey :: Unique
applicativeClassKey = Int -> Unique
mkPreludeClassUnique Int
34
foldableClassKey :: Unique
foldableClassKey = Int -> Unique
mkPreludeClassUnique Int
35
traversableClassKey :: Unique
traversableClassKey = Int -> Unique
mkPreludeClassUnique Int
36
genClassKey, gen1ClassKey, datatypeClassKey, constructorClassKey,
selectorClassKey :: Unique
genClassKey :: Unique
genClassKey = Int -> Unique
mkPreludeClassUnique Int
37
gen1ClassKey :: Unique
gen1ClassKey = Int -> Unique
mkPreludeClassUnique Int
38
datatypeClassKey :: Unique
datatypeClassKey = Int -> Unique
mkPreludeClassUnique Int
39
constructorClassKey :: Unique
constructorClassKey = Int -> Unique
mkPreludeClassUnique Int
40
selectorClassKey :: Unique
selectorClassKey = Int -> Unique
mkPreludeClassUnique Int
41
knownNatClassNameKey :: Unique
knownNatClassNameKey :: Unique
knownNatClassNameKey = Int -> Unique
mkPreludeClassUnique Int
42
knownSymbolClassNameKey :: Unique
knownSymbolClassNameKey :: Unique
knownSymbolClassNameKey = Int -> Unique
mkPreludeClassUnique Int
43
ghciIoClassKey :: Unique
ghciIoClassKey :: Unique
ghciIoClassKey = Int -> Unique
mkPreludeClassUnique Int
44
isLabelClassNameKey :: Unique
isLabelClassNameKey :: Unique
isLabelClassNameKey = Int -> Unique
mkPreludeClassUnique Int
45
semigroupClassKey, monoidClassKey :: Unique
semigroupClassKey :: Unique
semigroupClassKey = Int -> Unique
mkPreludeClassUnique Int
46
monoidClassKey :: Unique
monoidClassKey = Int -> Unique
mkPreludeClassUnique Int
47
ipClassKey :: Unique
ipClassKey :: Unique
ipClassKey = Int -> Unique
mkPreludeClassUnique Int
48
hasFieldClassNameKey :: Unique
hasFieldClassNameKey :: Unique
hasFieldClassNameKey = Int -> Unique
mkPreludeClassUnique Int
49
addrPrimTyConKey, arrayPrimTyConKey, arrayArrayPrimTyConKey, boolTyConKey,
byteArrayPrimTyConKey, charPrimTyConKey, charTyConKey, doublePrimTyConKey,
doubleTyConKey, floatPrimTyConKey, floatTyConKey, funTyConKey,
intPrimTyConKey, intTyConKey, int8TyConKey, int16TyConKey,
int8PrimTyConKey, int16PrimTyConKey, int32PrimTyConKey, int32TyConKey,
int64PrimTyConKey, int64TyConKey,
integerTyConKey, naturalTyConKey,
listTyConKey, foreignObjPrimTyConKey, maybeTyConKey,
weakPrimTyConKey, mutableArrayPrimTyConKey, mutableArrayArrayPrimTyConKey,
mutableByteArrayPrimTyConKey, orderingTyConKey, mVarPrimTyConKey,
ratioTyConKey, rationalTyConKey, realWorldTyConKey, stablePtrPrimTyConKey,
stablePtrTyConKey, eqTyConKey, heqTyConKey,
smallArrayPrimTyConKey, smallMutableArrayPrimTyConKey :: Unique
addrPrimTyConKey :: Unique
addrPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
1
arrayPrimTyConKey :: Unique
arrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
3
boolTyConKey :: Unique
boolTyConKey = Int -> Unique
mkPreludeTyConUnique Int
4
byteArrayPrimTyConKey :: Unique
byteArrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
5
charPrimTyConKey :: Unique
charPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
7
charTyConKey :: Unique
charTyConKey = Int -> Unique
mkPreludeTyConUnique Int
8
doublePrimTyConKey :: Unique
doublePrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
9
doubleTyConKey :: Unique
doubleTyConKey = Int -> Unique
mkPreludeTyConUnique Int
10
floatPrimTyConKey :: Unique
floatPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
11
floatTyConKey :: Unique
floatTyConKey = Int -> Unique
mkPreludeTyConUnique Int
12
funTyConKey :: Unique
funTyConKey = Int -> Unique
mkPreludeTyConUnique Int
13
intPrimTyConKey :: Unique
intPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
14
intTyConKey :: Unique
intTyConKey = Int -> Unique
mkPreludeTyConUnique Int
15
int8PrimTyConKey :: Unique
int8PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
16
int8TyConKey :: Unique
int8TyConKey = Int -> Unique
mkPreludeTyConUnique Int
17
int16PrimTyConKey :: Unique
int16PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
18
int16TyConKey :: Unique
int16TyConKey = Int -> Unique
mkPreludeTyConUnique Int
19
int32PrimTyConKey :: Unique
int32PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
20
int32TyConKey :: Unique
int32TyConKey = Int -> Unique
mkPreludeTyConUnique Int
21
int64PrimTyConKey :: Unique
int64PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
22
int64TyConKey :: Unique
int64TyConKey = Int -> Unique
mkPreludeTyConUnique Int
23
integerTyConKey :: Unique
integerTyConKey = Int -> Unique
mkPreludeTyConUnique Int
24
naturalTyConKey :: Unique
naturalTyConKey = Int -> Unique
mkPreludeTyConUnique Int
25
listTyConKey :: Unique
listTyConKey = Int -> Unique
mkPreludeTyConUnique Int
26
foreignObjPrimTyConKey :: Unique
foreignObjPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
27
maybeTyConKey :: Unique
maybeTyConKey = Int -> Unique
mkPreludeTyConUnique Int
28
weakPrimTyConKey :: Unique
weakPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
29
mutableArrayPrimTyConKey :: Unique
mutableArrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
30
mutableByteArrayPrimTyConKey :: Unique
mutableByteArrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
31
orderingTyConKey :: Unique
orderingTyConKey = Int -> Unique
mkPreludeTyConUnique Int
32
mVarPrimTyConKey :: Unique
mVarPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
33
ratioTyConKey :: Unique
ratioTyConKey = Int -> Unique
mkPreludeTyConUnique Int
34
rationalTyConKey :: Unique
rationalTyConKey = Int -> Unique
mkPreludeTyConUnique Int
35
realWorldTyConKey :: Unique
realWorldTyConKey = Int -> Unique
mkPreludeTyConUnique Int
36
stablePtrPrimTyConKey :: Unique
stablePtrPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
37
stablePtrTyConKey :: Unique
stablePtrTyConKey = Int -> Unique
mkPreludeTyConUnique Int
38
eqTyConKey :: Unique
eqTyConKey = Int -> Unique
mkPreludeTyConUnique Int
40
heqTyConKey :: Unique
heqTyConKey = Int -> Unique
mkPreludeTyConUnique Int
41
arrayArrayPrimTyConKey :: Unique
arrayArrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
42
mutableArrayArrayPrimTyConKey :: Unique
mutableArrayArrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
43
statePrimTyConKey, stableNamePrimTyConKey, stableNameTyConKey,
mutVarPrimTyConKey, ioTyConKey,
wordPrimTyConKey, wordTyConKey, word8PrimTyConKey, word8TyConKey,
word16PrimTyConKey, word16TyConKey, word32PrimTyConKey, word32TyConKey,
word64PrimTyConKey, word64TyConKey,
liftedConKey, unliftedConKey, anyBoxConKey, kindConKey, boxityConKey,
typeConKey, threadIdPrimTyConKey, bcoPrimTyConKey, ptrTyConKey,
funPtrTyConKey, tVarPrimTyConKey, eqPrimTyConKey,
eqReprPrimTyConKey, eqPhantPrimTyConKey, voidPrimTyConKey,
compactPrimTyConKey :: Unique
statePrimTyConKey :: Unique
statePrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
50
stableNamePrimTyConKey :: Unique
stableNamePrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
51
stableNameTyConKey :: Unique
stableNameTyConKey = Int -> Unique
mkPreludeTyConUnique Int
52
eqPrimTyConKey :: Unique
eqPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
53
eqReprPrimTyConKey :: Unique
eqReprPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
54
eqPhantPrimTyConKey :: Unique
eqPhantPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
55
mutVarPrimTyConKey :: Unique
mutVarPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
56
ioTyConKey :: Unique
ioTyConKey = Int -> Unique
mkPreludeTyConUnique Int
57
voidPrimTyConKey :: Unique
voidPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
58
wordPrimTyConKey :: Unique
wordPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
59
wordTyConKey :: Unique
wordTyConKey = Int -> Unique
mkPreludeTyConUnique Int
60
word8PrimTyConKey :: Unique
word8PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
61
word8TyConKey :: Unique
word8TyConKey = Int -> Unique
mkPreludeTyConUnique Int
62
word16PrimTyConKey :: Unique
word16PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
63
word16TyConKey :: Unique
word16TyConKey = Int -> Unique
mkPreludeTyConUnique Int
64
word32PrimTyConKey :: Unique
word32PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
65
word32TyConKey :: Unique
word32TyConKey = Int -> Unique
mkPreludeTyConUnique Int
66
word64PrimTyConKey :: Unique
word64PrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
67
word64TyConKey :: Unique
word64TyConKey = Int -> Unique
mkPreludeTyConUnique Int
68
liftedConKey :: Unique
liftedConKey = Int -> Unique
mkPreludeTyConUnique Int
69
unliftedConKey :: Unique
unliftedConKey = Int -> Unique
mkPreludeTyConUnique Int
70
anyBoxConKey :: Unique
anyBoxConKey = Int -> Unique
mkPreludeTyConUnique Int
71
kindConKey :: Unique
kindConKey = Int -> Unique
mkPreludeTyConUnique Int
72
boxityConKey :: Unique
boxityConKey = Int -> Unique
mkPreludeTyConUnique Int
73
typeConKey :: Unique
typeConKey = Int -> Unique
mkPreludeTyConUnique Int
74
threadIdPrimTyConKey :: Unique
threadIdPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
75
bcoPrimTyConKey :: Unique
bcoPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
76
ptrTyConKey :: Unique
ptrTyConKey = Int -> Unique
mkPreludeTyConUnique Int
77
funPtrTyConKey :: Unique
funPtrTyConKey = Int -> Unique
mkPreludeTyConUnique Int
78
tVarPrimTyConKey :: Unique
tVarPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
79
compactPrimTyConKey :: Unique
compactPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
80
objectTyConKey :: Unique
objectTyConKey :: Unique
objectTyConKey = Int -> Unique
mkPreludeTyConUnique Int
83
eitherTyConKey :: Unique
eitherTyConKey :: Unique
eitherTyConKey = Int -> Unique
mkPreludeTyConUnique Int
84
liftedTypeKindTyConKey, tYPETyConKey,
constraintKindTyConKey, runtimeRepTyConKey,
vecCountTyConKey, vecElemTyConKey :: Unique
liftedTypeKindTyConKey :: Unique
liftedTypeKindTyConKey = Int -> Unique
mkPreludeTyConUnique Int
87
tYPETyConKey :: Unique
tYPETyConKey = Int -> Unique
mkPreludeTyConUnique Int
88
constraintKindTyConKey :: Unique
constraintKindTyConKey = Int -> Unique
mkPreludeTyConUnique Int
92
runtimeRepTyConKey :: Unique
runtimeRepTyConKey = Int -> Unique
mkPreludeTyConUnique Int
95
vecCountTyConKey :: Unique
vecCountTyConKey = Int -> Unique
mkPreludeTyConUnique Int
96
vecElemTyConKey :: Unique
vecElemTyConKey = Int -> Unique
mkPreludeTyConUnique Int
97
pluginTyConKey, frontendPluginTyConKey :: Unique
pluginTyConKey :: Unique
pluginTyConKey = Int -> Unique
mkPreludeTyConUnique Int
102
frontendPluginTyConKey :: Unique
frontendPluginTyConKey = Int -> Unique
mkPreludeTyConUnique Int
103
unknownTyConKey, unknown1TyConKey, unknown2TyConKey, unknown3TyConKey,
opaqueTyConKey :: Unique
unknownTyConKey :: Unique
unknownTyConKey = Int -> Unique
mkPreludeTyConUnique Int
129
unknown1TyConKey :: Unique
unknown1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
130
unknown2TyConKey :: Unique
unknown2TyConKey = Int -> Unique
mkPreludeTyConUnique Int
131
unknown3TyConKey :: Unique
unknown3TyConKey = Int -> Unique
mkPreludeTyConUnique Int
132
opaqueTyConKey :: Unique
opaqueTyConKey = Int -> Unique
mkPreludeTyConUnique Int
133
v1TyConKey, u1TyConKey, par1TyConKey, rec1TyConKey,
k1TyConKey, m1TyConKey, sumTyConKey, prodTyConKey,
compTyConKey, rTyConKey, dTyConKey,
cTyConKey, sTyConKey, rec0TyConKey,
d1TyConKey, c1TyConKey, s1TyConKey, noSelTyConKey,
repTyConKey, rep1TyConKey, uRecTyConKey,
uAddrTyConKey, uCharTyConKey, uDoubleTyConKey,
uFloatTyConKey, uIntTyConKey, uWordTyConKey :: Unique
v1TyConKey :: Unique
v1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
135
u1TyConKey :: Unique
u1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
136
par1TyConKey :: Unique
par1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
137
rec1TyConKey :: Unique
rec1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
138
k1TyConKey :: Unique
k1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
139
m1TyConKey :: Unique
m1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
140
sumTyConKey :: Unique
sumTyConKey = Int -> Unique
mkPreludeTyConUnique Int
141
prodTyConKey :: Unique
prodTyConKey = Int -> Unique
mkPreludeTyConUnique Int
142
compTyConKey :: Unique
compTyConKey = Int -> Unique
mkPreludeTyConUnique Int
143
rTyConKey :: Unique
rTyConKey = Int -> Unique
mkPreludeTyConUnique Int
144
dTyConKey :: Unique
dTyConKey = Int -> Unique
mkPreludeTyConUnique Int
146
cTyConKey :: Unique
cTyConKey = Int -> Unique
mkPreludeTyConUnique Int
147
sTyConKey :: Unique
sTyConKey = Int -> Unique
mkPreludeTyConUnique Int
148
rec0TyConKey :: Unique
rec0TyConKey = Int -> Unique
mkPreludeTyConUnique Int
149
d1TyConKey :: Unique
d1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
151
c1TyConKey :: Unique
c1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
152
s1TyConKey :: Unique
s1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
153
noSelTyConKey :: Unique
noSelTyConKey = Int -> Unique
mkPreludeTyConUnique Int
154
repTyConKey :: Unique
repTyConKey = Int -> Unique
mkPreludeTyConUnique Int
155
rep1TyConKey :: Unique
rep1TyConKey = Int -> Unique
mkPreludeTyConUnique Int
156
uRecTyConKey :: Unique
uRecTyConKey = Int -> Unique
mkPreludeTyConUnique Int
157
uAddrTyConKey :: Unique
uAddrTyConKey = Int -> Unique
mkPreludeTyConUnique Int
158
uCharTyConKey :: Unique
uCharTyConKey = Int -> Unique
mkPreludeTyConUnique Int
159
uDoubleTyConKey :: Unique
uDoubleTyConKey = Int -> Unique
mkPreludeTyConUnique Int
160
uFloatTyConKey :: Unique
uFloatTyConKey = Int -> Unique
mkPreludeTyConUnique Int
161
uIntTyConKey :: Unique
uIntTyConKey = Int -> Unique
mkPreludeTyConUnique Int
162
uWordTyConKey :: Unique
uWordTyConKey = Int -> Unique
mkPreludeTyConUnique Int
163
typeNatKindConNameKey, typeSymbolKindConNameKey,
typeNatAddTyFamNameKey, typeNatMulTyFamNameKey, typeNatExpTyFamNameKey,
typeNatLeqTyFamNameKey, typeNatSubTyFamNameKey
, typeSymbolCmpTyFamNameKey, typeNatCmpTyFamNameKey
, typeNatDivTyFamNameKey
, typeNatModTyFamNameKey
, typeNatLogTyFamNameKey
:: Unique
typeNatKindConNameKey :: Unique
typeNatKindConNameKey = Int -> Unique
mkPreludeTyConUnique Int
164
typeSymbolKindConNameKey :: Unique
typeSymbolKindConNameKey = Int -> Unique
mkPreludeTyConUnique Int
165
typeNatAddTyFamNameKey :: Unique
typeNatAddTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
166
typeNatMulTyFamNameKey :: Unique
typeNatMulTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
167
typeNatExpTyFamNameKey :: Unique
typeNatExpTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
168
typeNatLeqTyFamNameKey :: Unique
typeNatLeqTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
169
typeNatSubTyFamNameKey :: Unique
typeNatSubTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
170
typeSymbolCmpTyFamNameKey :: Unique
typeSymbolCmpTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
171
typeNatCmpTyFamNameKey :: Unique
typeNatCmpTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
172
typeNatDivTyFamNameKey :: Unique
typeNatDivTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
173
typeNatModTyFamNameKey :: Unique
typeNatModTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
174
typeNatLogTyFamNameKey :: Unique
typeNatLogTyFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
175
errorMessageTypeErrorFamKey :: Unique
errorMessageTypeErrorFamKey :: Unique
errorMessageTypeErrorFamKey = Int -> Unique
mkPreludeTyConUnique Int
176
ntTyConKey:: Unique
ntTyConKey :: Unique
ntTyConKey = Int -> Unique
mkPreludeTyConUnique Int
177
coercibleTyConKey :: Unique
coercibleTyConKey :: Unique
coercibleTyConKey = Int -> Unique
mkPreludeTyConUnique Int
178
proxyPrimTyConKey :: Unique
proxyPrimTyConKey :: Unique
proxyPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
179
specTyConKey :: Unique
specTyConKey :: Unique
specTyConKey = Int -> Unique
mkPreludeTyConUnique Int
180
anyTyConKey :: Unique
anyTyConKey :: Unique
anyTyConKey = Int -> Unique
mkPreludeTyConUnique Int
181
smallArrayPrimTyConKey :: Unique
smallArrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
182
smallMutableArrayPrimTyConKey :: Unique
smallMutableArrayPrimTyConKey = Int -> Unique
mkPreludeTyConUnique Int
183
staticPtrTyConKey :: Unique
staticPtrTyConKey :: Unique
staticPtrTyConKey = Int -> Unique
mkPreludeTyConUnique Int
184
staticPtrInfoTyConKey :: Unique
staticPtrInfoTyConKey :: Unique
staticPtrInfoTyConKey = Int -> Unique
mkPreludeTyConUnique Int
185
callStackTyConKey :: Unique
callStackTyConKey :: Unique
callStackTyConKey = Int -> Unique
mkPreludeTyConUnique Int
186
typeRepTyConKey, someTypeRepTyConKey, someTypeRepDataConKey :: Unique
typeRepTyConKey :: Unique
typeRepTyConKey = Int -> Unique
mkPreludeTyConUnique Int
187
someTypeRepTyConKey :: Unique
someTypeRepTyConKey = Int -> Unique
mkPreludeTyConUnique Int
188
someTypeRepDataConKey :: Unique
someTypeRepDataConKey = Int -> Unique
mkPreludeTyConUnique Int
189
typeSymbolAppendFamNameKey :: Unique
typeSymbolAppendFamNameKey :: Unique
typeSymbolAppendFamNameKey = Int -> Unique
mkPreludeTyConUnique Int
190
#include "primop-vector-uniques.hs-incl"
charDataConKey, consDataConKey, doubleDataConKey, falseDataConKey,
floatDataConKey, intDataConKey, integerSDataConKey, nilDataConKey,
ratioDataConKey, stableNameDataConKey, trueDataConKey, wordDataConKey,
word8DataConKey, ioDataConKey, integerDataConKey, heqDataConKey,
coercibleDataConKey, eqDataConKey, nothingDataConKey, justDataConKey :: Unique
charDataConKey :: Unique
charDataConKey = Int -> Unique
mkPreludeDataConUnique Int
1
consDataConKey :: Unique
consDataConKey = Int -> Unique
mkPreludeDataConUnique Int
2
doubleDataConKey :: Unique
doubleDataConKey = Int -> Unique
mkPreludeDataConUnique Int
3
falseDataConKey :: Unique
falseDataConKey = Int -> Unique
mkPreludeDataConUnique Int
4
floatDataConKey :: Unique
floatDataConKey = Int -> Unique
mkPreludeDataConUnique Int
5
intDataConKey :: Unique
intDataConKey = Int -> Unique
mkPreludeDataConUnique Int
6
integerSDataConKey :: Unique
integerSDataConKey = Int -> Unique
mkPreludeDataConUnique Int
7
nothingDataConKey :: Unique
nothingDataConKey = Int -> Unique
mkPreludeDataConUnique Int
8
justDataConKey :: Unique
justDataConKey = Int -> Unique
mkPreludeDataConUnique Int
9
eqDataConKey :: Unique
eqDataConKey = Int -> Unique
mkPreludeDataConUnique Int
10
nilDataConKey :: Unique
nilDataConKey = Int -> Unique
mkPreludeDataConUnique Int
11
ratioDataConKey :: Unique
ratioDataConKey = Int -> Unique
mkPreludeDataConUnique Int
12
word8DataConKey :: Unique
word8DataConKey = Int -> Unique
mkPreludeDataConUnique Int
13
stableNameDataConKey :: Unique
stableNameDataConKey = Int -> Unique
mkPreludeDataConUnique Int
14
trueDataConKey :: Unique
trueDataConKey = Int -> Unique
mkPreludeDataConUnique Int
15
wordDataConKey :: Unique
wordDataConKey = Int -> Unique
mkPreludeDataConUnique Int
16
ioDataConKey :: Unique
ioDataConKey = Int -> Unique
mkPreludeDataConUnique Int
17
integerDataConKey :: Unique
integerDataConKey = Int -> Unique
mkPreludeDataConUnique Int
18
heqDataConKey :: Unique
heqDataConKey = Int -> Unique
mkPreludeDataConUnique Int
19
crossDataConKey, inlDataConKey, inrDataConKey, genUnitDataConKey :: Unique
crossDataConKey :: Unique
crossDataConKey = Int -> Unique
mkPreludeDataConUnique Int
20
inlDataConKey :: Unique
inlDataConKey = Int -> Unique
mkPreludeDataConUnique Int
21
inrDataConKey :: Unique
inrDataConKey = Int -> Unique
mkPreludeDataConUnique Int
22
genUnitDataConKey :: Unique
genUnitDataConKey = Int -> Unique
mkPreludeDataConUnique Int
23
leftDataConKey, rightDataConKey :: Unique
leftDataConKey :: Unique
leftDataConKey = Int -> Unique
mkPreludeDataConUnique Int
25
rightDataConKey :: Unique
rightDataConKey = Int -> Unique
mkPreludeDataConUnique Int
26
ordLTDataConKey, ordEQDataConKey, ordGTDataConKey :: Unique
ordLTDataConKey :: Unique
ordLTDataConKey = Int -> Unique
mkPreludeDataConUnique Int
27
ordEQDataConKey :: Unique
ordEQDataConKey = Int -> Unique
mkPreludeDataConUnique Int
28
ordGTDataConKey :: Unique
ordGTDataConKey = Int -> Unique
mkPreludeDataConUnique Int
29
coercibleDataConKey :: Unique
coercibleDataConKey = Int -> Unique
mkPreludeDataConUnique Int
32
staticPtrDataConKey :: Unique
staticPtrDataConKey :: Unique
staticPtrDataConKey = Int -> Unique
mkPreludeDataConUnique Int
33
staticPtrInfoDataConKey :: Unique
staticPtrInfoDataConKey :: Unique
staticPtrInfoDataConKey = Int -> Unique
mkPreludeDataConUnique Int
34
fingerprintDataConKey :: Unique
fingerprintDataConKey :: Unique
fingerprintDataConKey = Int -> Unique
mkPreludeDataConUnique Int
35
srcLocDataConKey :: Unique
srcLocDataConKey :: Unique
srcLocDataConKey = Int -> Unique
mkPreludeDataConUnique Int
37
trTyConTyConKey, trTyConDataConKey,
trModuleTyConKey, trModuleDataConKey,
trNameTyConKey, trNameSDataConKey, trNameDDataConKey,
trGhcPrimModuleKey, kindRepTyConKey,
typeLitSortTyConKey :: Unique
trTyConTyConKey :: Unique
trTyConTyConKey = Int -> Unique
mkPreludeDataConUnique Int
40
trTyConDataConKey :: Unique
trTyConDataConKey = Int -> Unique
mkPreludeDataConUnique Int
41
trModuleTyConKey :: Unique
trModuleTyConKey = Int -> Unique
mkPreludeDataConUnique Int
42
trModuleDataConKey :: Unique
trModuleDataConKey = Int -> Unique
mkPreludeDataConUnique Int
43
trNameTyConKey :: Unique
trNameTyConKey = Int -> Unique
mkPreludeDataConUnique Int
44
trNameSDataConKey :: Unique
trNameSDataConKey = Int -> Unique
mkPreludeDataConUnique Int
45
trNameDDataConKey :: Unique
trNameDDataConKey = Int -> Unique
mkPreludeDataConUnique Int
46
trGhcPrimModuleKey :: Unique
trGhcPrimModuleKey = Int -> Unique
mkPreludeDataConUnique Int
47
kindRepTyConKey :: Unique
kindRepTyConKey = Int -> Unique
mkPreludeDataConUnique Int
48
typeLitSortTyConKey :: Unique
typeLitSortTyConKey = Int -> Unique
mkPreludeDataConUnique Int
49
typeErrorTextDataConKey,
typeErrorAppendDataConKey,
typeErrorVAppendDataConKey,
typeErrorShowTypeDataConKey
:: Unique
typeErrorTextDataConKey :: Unique
typeErrorTextDataConKey = Int -> Unique
mkPreludeDataConUnique Int
50
typeErrorAppendDataConKey :: Unique
typeErrorAppendDataConKey = Int -> Unique
mkPreludeDataConUnique Int
51
typeErrorVAppendDataConKey :: Unique
typeErrorVAppendDataConKey = Int -> Unique
mkPreludeDataConUnique Int
52
typeErrorShowTypeDataConKey :: Unique
typeErrorShowTypeDataConKey = Int -> Unique
mkPreludeDataConUnique Int
53
prefixIDataConKey, infixIDataConKey, leftAssociativeDataConKey,
rightAssociativeDataConKey, notAssociativeDataConKey,
sourceUnpackDataConKey, sourceNoUnpackDataConKey,
noSourceUnpackednessDataConKey, sourceLazyDataConKey,
sourceStrictDataConKey, noSourceStrictnessDataConKey,
decidedLazyDataConKey, decidedStrictDataConKey, decidedUnpackDataConKey,
metaDataDataConKey, metaConsDataConKey, metaSelDataConKey :: Unique
prefixIDataConKey :: Unique
prefixIDataConKey = Int -> Unique
mkPreludeDataConUnique Int
54
infixIDataConKey :: Unique
infixIDataConKey = Int -> Unique
mkPreludeDataConUnique Int
55
leftAssociativeDataConKey :: Unique
leftAssociativeDataConKey = Int -> Unique
mkPreludeDataConUnique Int
56
rightAssociativeDataConKey :: Unique
rightAssociativeDataConKey = Int -> Unique
mkPreludeDataConUnique Int
57
notAssociativeDataConKey :: Unique
notAssociativeDataConKey = Int -> Unique
mkPreludeDataConUnique Int
58
sourceUnpackDataConKey :: Unique
sourceUnpackDataConKey = Int -> Unique
mkPreludeDataConUnique Int
59
sourceNoUnpackDataConKey :: Unique
sourceNoUnpackDataConKey = Int -> Unique
mkPreludeDataConUnique Int
60
noSourceUnpackednessDataConKey :: Unique
noSourceUnpackednessDataConKey = Int -> Unique
mkPreludeDataConUnique Int
61
sourceLazyDataConKey :: Unique
sourceLazyDataConKey = Int -> Unique
mkPreludeDataConUnique Int
62
sourceStrictDataConKey :: Unique
sourceStrictDataConKey = Int -> Unique
mkPreludeDataConUnique Int
63
noSourceStrictnessDataConKey :: Unique
noSourceStrictnessDataConKey = Int -> Unique
mkPreludeDataConUnique Int
64
decidedLazyDataConKey :: Unique
decidedLazyDataConKey = Int -> Unique
mkPreludeDataConUnique Int
65
decidedStrictDataConKey :: Unique
decidedStrictDataConKey = Int -> Unique
mkPreludeDataConUnique Int
66
decidedUnpackDataConKey :: Unique
decidedUnpackDataConKey = Int -> Unique
mkPreludeDataConUnique Int
67
metaDataDataConKey :: Unique
metaDataDataConKey = Int -> Unique
mkPreludeDataConUnique Int
68
metaConsDataConKey :: Unique
metaConsDataConKey = Int -> Unique
mkPreludeDataConUnique Int
69
metaSelDataConKey :: Unique
metaSelDataConKey = Int -> Unique
mkPreludeDataConUnique Int
70
vecRepDataConKey, tupleRepDataConKey, sumRepDataConKey :: Unique
vecRepDataConKey :: Unique
vecRepDataConKey = Int -> Unique
mkPreludeDataConUnique Int
71
tupleRepDataConKey :: Unique
tupleRepDataConKey = Int -> Unique
mkPreludeDataConUnique Int
72
sumRepDataConKey :: Unique
sumRepDataConKey = Int -> Unique
mkPreludeDataConUnique Int
73
runtimeRepSimpleDataConKeys, unliftedSimpleRepDataConKeys, unliftedRepDataConKeys :: [Unique]
liftedRepDataConKey :: Unique
runtimeRepSimpleDataConKeys :: [Unique]
runtimeRepSimpleDataConKeys@(Unique
liftedRepDataConKey : [Unique]
unliftedSimpleRepDataConKeys)
= (Int -> Unique) -> [Int] -> [Unique]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Unique
mkPreludeDataConUnique [Int
74..Int
86]
unliftedRepDataConKeys :: [Unique]
unliftedRepDataConKeys = Unique
vecRepDataConKey Unique -> [Unique] -> [Unique]
forall a. a -> [a] -> [a]
:
Unique
tupleRepDataConKey Unique -> [Unique] -> [Unique]
forall a. a -> [a] -> [a]
:
Unique
sumRepDataConKey Unique -> [Unique] -> [Unique]
forall a. a -> [a] -> [a]
:
[Unique]
unliftedSimpleRepDataConKeys
vecCountDataConKeys :: [Unique]
vecCountDataConKeys :: [Unique]
vecCountDataConKeys = (Int -> Unique) -> [Int] -> [Unique]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Unique
mkPreludeDataConUnique [Int
87..Int
92]
vecElemDataConKeys :: [Unique]
vecElemDataConKeys :: [Unique]
vecElemDataConKeys = (Int -> Unique) -> [Int] -> [Unique]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Unique
mkPreludeDataConUnique [Int
93..Int
102]
kindRepTyConAppDataConKey, kindRepVarDataConKey, kindRepAppDataConKey,
kindRepFunDataConKey, kindRepTYPEDataConKey,
kindRepTypeLitSDataConKey, kindRepTypeLitDDataConKey
:: Unique
kindRepTyConAppDataConKey :: Unique
kindRepTyConAppDataConKey = Int -> Unique
mkPreludeDataConUnique Int
103
kindRepVarDataConKey :: Unique
kindRepVarDataConKey = Int -> Unique
mkPreludeDataConUnique Int
104
kindRepAppDataConKey :: Unique
kindRepAppDataConKey = Int -> Unique
mkPreludeDataConUnique Int
105
kindRepFunDataConKey :: Unique
kindRepFunDataConKey = Int -> Unique
mkPreludeDataConUnique Int
106
kindRepTYPEDataConKey :: Unique
kindRepTYPEDataConKey = Int -> Unique
mkPreludeDataConUnique Int
107
kindRepTypeLitSDataConKey :: Unique
kindRepTypeLitSDataConKey = Int -> Unique
mkPreludeDataConUnique Int
108
kindRepTypeLitDDataConKey :: Unique
kindRepTypeLitDDataConKey = Int -> Unique
mkPreludeDataConUnique Int
109
typeLitSymbolDataConKey, typeLitNatDataConKey :: Unique
typeLitSymbolDataConKey :: Unique
typeLitSymbolDataConKey = Int -> Unique
mkPreludeDataConUnique Int
110
typeLitNatDataConKey :: Unique
typeLitNatDataConKey = Int -> Unique
mkPreludeDataConUnique Int
111
wildCardKey, absentErrorIdKey, augmentIdKey, appendIdKey,
buildIdKey, errorIdKey, foldrIdKey, recSelErrorIdKey,
seqIdKey, eqStringIdKey,
noMethodBindingErrorIdKey, nonExhaustiveGuardsErrorIdKey,
runtimeErrorIdKey, patErrorIdKey, voidPrimIdKey,
realWorldPrimIdKey, recConErrorIdKey,
unpackCStringUtf8IdKey, unpackCStringAppendIdKey,
unpackCStringFoldrIdKey, unpackCStringIdKey,
typeErrorIdKey, divIntIdKey, modIntIdKey,
absentSumFieldErrorIdKey :: Unique
wildCardKey :: Unique
wildCardKey = Int -> Unique
mkPreludeMiscIdUnique Int
0
absentErrorIdKey :: Unique
absentErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
1
augmentIdKey :: Unique
augmentIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
2
appendIdKey :: Unique
appendIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
3
buildIdKey :: Unique
buildIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
4
errorIdKey :: Unique
errorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
5
foldrIdKey :: Unique
foldrIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
6
recSelErrorIdKey :: Unique
recSelErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
7
seqIdKey :: Unique
seqIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
8
eqStringIdKey :: Unique
eqStringIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
10
noMethodBindingErrorIdKey :: Unique
noMethodBindingErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
11
nonExhaustiveGuardsErrorIdKey :: Unique
nonExhaustiveGuardsErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
12
runtimeErrorIdKey :: Unique
runtimeErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
13
patErrorIdKey :: Unique
patErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
14
realWorldPrimIdKey :: Unique
realWorldPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
15
recConErrorIdKey :: Unique
recConErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
16
unpackCStringUtf8IdKey :: Unique
unpackCStringUtf8IdKey = Int -> Unique
mkPreludeMiscIdUnique Int
17
unpackCStringAppendIdKey :: Unique
unpackCStringAppendIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
18
unpackCStringFoldrIdKey :: Unique
unpackCStringFoldrIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
19
unpackCStringIdKey :: Unique
unpackCStringIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
20
voidPrimIdKey :: Unique
voidPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
21
typeErrorIdKey :: Unique
typeErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
22
divIntIdKey :: Unique
divIntIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
23
modIntIdKey :: Unique
modIntIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
24
absentSumFieldErrorIdKey :: Unique
absentSumFieldErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
9
unsafeCoerceIdKey, concatIdKey, filterIdKey, zipIdKey, bindIOIdKey,
returnIOIdKey, newStablePtrIdKey,
printIdKey, failIOIdKey, nullAddrIdKey, voidArgIdKey,
fstIdKey, sndIdKey, otherwiseIdKey, assertIdKey :: Unique
unsafeCoerceIdKey :: Unique
unsafeCoerceIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
30
concatIdKey :: Unique
concatIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
31
filterIdKey :: Unique
filterIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
32
zipIdKey :: Unique
zipIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
33
bindIOIdKey :: Unique
bindIOIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
34
returnIOIdKey :: Unique
returnIOIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
35
newStablePtrIdKey :: Unique
newStablePtrIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
36
printIdKey :: Unique
printIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
37
failIOIdKey :: Unique
failIOIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
38
nullAddrIdKey :: Unique
nullAddrIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
39
voidArgIdKey :: Unique
voidArgIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
40
fstIdKey :: Unique
fstIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
41
sndIdKey :: Unique
sndIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
42
otherwiseIdKey :: Unique
otherwiseIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
43
assertIdKey :: Unique
assertIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
44
mkIntegerIdKey, smallIntegerIdKey, wordToIntegerIdKey,
integerToWordIdKey, integerToIntIdKey,
integerToWord64IdKey, integerToInt64IdKey,
word64ToIntegerIdKey, int64ToIntegerIdKey,
plusIntegerIdKey, timesIntegerIdKey, minusIntegerIdKey,
negateIntegerIdKey,
eqIntegerPrimIdKey, neqIntegerPrimIdKey, absIntegerIdKey, signumIntegerIdKey,
leIntegerPrimIdKey, gtIntegerPrimIdKey, ltIntegerPrimIdKey, geIntegerPrimIdKey,
compareIntegerIdKey, quotRemIntegerIdKey, divModIntegerIdKey,
quotIntegerIdKey, remIntegerIdKey, divIntegerIdKey, modIntegerIdKey,
floatFromIntegerIdKey, doubleFromIntegerIdKey,
encodeFloatIntegerIdKey, encodeDoubleIntegerIdKey,
decodeDoubleIntegerIdKey,
gcdIntegerIdKey, lcmIntegerIdKey,
andIntegerIdKey, orIntegerIdKey, xorIntegerIdKey, complementIntegerIdKey,
shiftLIntegerIdKey, shiftRIntegerIdKey :: Unique
mkIntegerIdKey :: Unique
mkIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
60
smallIntegerIdKey :: Unique
smallIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
61
integerToWordIdKey :: Unique
integerToWordIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
62
integerToIntIdKey :: Unique
integerToIntIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
63
integerToWord64IdKey :: Unique
integerToWord64IdKey = Int -> Unique
mkPreludeMiscIdUnique Int
64
integerToInt64IdKey :: Unique
integerToInt64IdKey = Int -> Unique
mkPreludeMiscIdUnique Int
65
plusIntegerIdKey :: Unique
plusIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
66
timesIntegerIdKey :: Unique
timesIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
67
minusIntegerIdKey :: Unique
minusIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
68
negateIntegerIdKey :: Unique
negateIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
69
eqIntegerPrimIdKey :: Unique
eqIntegerPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
70
neqIntegerPrimIdKey :: Unique
neqIntegerPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
71
absIntegerIdKey :: Unique
absIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
72
signumIntegerIdKey :: Unique
signumIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
73
leIntegerPrimIdKey :: Unique
leIntegerPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
74
gtIntegerPrimIdKey :: Unique
gtIntegerPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
75
ltIntegerPrimIdKey :: Unique
ltIntegerPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
76
geIntegerPrimIdKey :: Unique
geIntegerPrimIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
77
compareIntegerIdKey :: Unique
compareIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
78
quotIntegerIdKey :: Unique
quotIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
79
remIntegerIdKey :: Unique
remIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
80
divIntegerIdKey :: Unique
divIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
81
modIntegerIdKey :: Unique
modIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
82
divModIntegerIdKey :: Unique
divModIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
83
quotRemIntegerIdKey :: Unique
quotRemIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
84
floatFromIntegerIdKey :: Unique
floatFromIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
85
doubleFromIntegerIdKey :: Unique
doubleFromIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
86
encodeFloatIntegerIdKey :: Unique
encodeFloatIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
87
encodeDoubleIntegerIdKey :: Unique
encodeDoubleIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
88
gcdIntegerIdKey :: Unique
gcdIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
89
lcmIntegerIdKey :: Unique
lcmIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
90
andIntegerIdKey :: Unique
andIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
91
orIntegerIdKey :: Unique
orIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
92
xorIntegerIdKey :: Unique
xorIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
93
complementIntegerIdKey :: Unique
complementIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
94
shiftLIntegerIdKey :: Unique
shiftLIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
95
shiftRIntegerIdKey :: Unique
shiftRIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
96
wordToIntegerIdKey :: Unique
wordToIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
97
word64ToIntegerIdKey :: Unique
word64ToIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
98
int64ToIntegerIdKey :: Unique
int64ToIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
99
decodeDoubleIntegerIdKey :: Unique
decodeDoubleIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
100
rootMainKey, runMainKey :: Unique
rootMainKey :: Unique
rootMainKey = Int -> Unique
mkPreludeMiscIdUnique Int
101
runMainKey :: Unique
runMainKey = Int -> Unique
mkPreludeMiscIdUnique Int
102
thenIOIdKey, lazyIdKey, assertErrorIdKey, oneShotKey, runRWKey :: Unique
thenIOIdKey :: Unique
thenIOIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
103
lazyIdKey :: Unique
lazyIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
104
assertErrorIdKey :: Unique
assertErrorIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
105
oneShotKey :: Unique
oneShotKey = Int -> Unique
mkPreludeMiscIdUnique Int
106
runRWKey :: Unique
runRWKey = Int -> Unique
mkPreludeMiscIdUnique Int
107
traceKey :: Unique
traceKey :: Unique
traceKey = Int -> Unique
mkPreludeMiscIdUnique Int
108
breakpointIdKey, breakpointCondIdKey, breakpointAutoIdKey,
breakpointJumpIdKey, breakpointCondJumpIdKey,
breakpointAutoJumpIdKey :: Unique
breakpointIdKey :: Unique
breakpointIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
110
breakpointCondIdKey :: Unique
breakpointCondIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
111
breakpointAutoIdKey :: Unique
breakpointAutoIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
112
breakpointJumpIdKey :: Unique
breakpointJumpIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
113
breakpointCondJumpIdKey :: Unique
breakpointCondJumpIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
114
breakpointAutoJumpIdKey :: Unique
breakpointAutoJumpIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
115
inlineIdKey, noinlineIdKey :: Unique
inlineIdKey :: Unique
inlineIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
120
mapIdKey, groupWithIdKey, dollarIdKey :: Unique
mapIdKey :: Unique
mapIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
121
groupWithIdKey :: Unique
groupWithIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
122
dollarIdKey :: Unique
dollarIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
123
coercionTokenIdKey :: Unique
coercionTokenIdKey :: Unique
coercionTokenIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
124
noinlineIdKey :: Unique
noinlineIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
125
rationalToFloatIdKey, rationalToDoubleIdKey :: Unique
rationalToFloatIdKey :: Unique
rationalToFloatIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
130
rationalToDoubleIdKey :: Unique
rationalToDoubleIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
131
unmarshalObjectIdKey, marshalObjectIdKey, marshalStringIdKey,
unmarshalStringIdKey, checkDotnetResNameIdKey :: Unique
unmarshalObjectIdKey :: Unique
unmarshalObjectIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
150
marshalObjectIdKey :: Unique
marshalObjectIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
151
marshalStringIdKey :: Unique
marshalStringIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
152
unmarshalStringIdKey :: Unique
unmarshalStringIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
153
checkDotnetResNameIdKey :: Unique
checkDotnetResNameIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
154
undefinedKey :: Unique
undefinedKey :: Unique
undefinedKey = Int -> Unique
mkPreludeMiscIdUnique Int
155
magicDictKey :: Unique
magicDictKey :: Unique
magicDictKey = Int -> Unique
mkPreludeMiscIdUnique Int
156
coerceKey :: Unique
coerceKey :: Unique
coerceKey = Int -> Unique
mkPreludeMiscIdUnique Int
157
unboundKey :: Unique
unboundKey :: Unique
unboundKey = Int -> Unique
mkPreludeMiscIdUnique Int
158
fromIntegerClassOpKey, minusClassOpKey, fromRationalClassOpKey,
enumFromClassOpKey, enumFromThenClassOpKey, enumFromToClassOpKey,
enumFromThenToClassOpKey, eqClassOpKey, geClassOpKey, negateClassOpKey,
bindMClassOpKey, thenMClassOpKey, returnMClassOpKey, fmapClassOpKey
:: Unique
fromIntegerClassOpKey :: Unique
fromIntegerClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
160
minusClassOpKey :: Unique
minusClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
161
fromRationalClassOpKey :: Unique
fromRationalClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
162
enumFromClassOpKey :: Unique
enumFromClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
163
enumFromThenClassOpKey :: Unique
enumFromThenClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
164
enumFromToClassOpKey :: Unique
enumFromToClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
165
enumFromThenToClassOpKey :: Unique
enumFromThenToClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
166
eqClassOpKey :: Unique
eqClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
167
geClassOpKey :: Unique
geClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
168
negateClassOpKey :: Unique
negateClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
169
bindMClassOpKey :: Unique
bindMClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
171
thenMClassOpKey :: Unique
thenMClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
172
fmapClassOpKey :: Unique
fmapClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
173
returnMClassOpKey :: Unique
returnMClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
174
mfixIdKey :: Unique
mfixIdKey :: Unique
mfixIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
175
failMClassOpKey :: Unique
failMClassOpKey :: Unique
failMClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
176
arrAIdKey, composeAIdKey, firstAIdKey, appAIdKey, choiceAIdKey,
loopAIdKey :: Unique
arrAIdKey :: Unique
arrAIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
180
composeAIdKey :: Unique
composeAIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
181
firstAIdKey :: Unique
firstAIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
182
appAIdKey :: Unique
appAIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
183
choiceAIdKey :: Unique
choiceAIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
184
loopAIdKey :: Unique
loopAIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
185
fromStringClassOpKey :: Unique
fromStringClassOpKey :: Unique
fromStringClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
186
toAnnotationWrapperIdKey :: Unique
toAnnotationWrapperIdKey :: Unique
toAnnotationWrapperIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
187
fromIntegralIdKey, realToFracIdKey, toIntegerClassOpKey, toRationalClassOpKey :: Unique
fromIntegralIdKey :: Unique
fromIntegralIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
190
realToFracIdKey :: Unique
realToFracIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
191
toIntegerClassOpKey :: Unique
toIntegerClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
192
toRationalClassOpKey :: Unique
toRationalClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
193
guardMIdKey, liftMIdKey, mzipIdKey :: Unique
guardMIdKey :: Unique
guardMIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
194
liftMIdKey :: Unique
liftMIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
195
mzipIdKey :: Unique
mzipIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
196
ghciStepIoMClassOpKey :: Unique
ghciStepIoMClassOpKey :: Unique
ghciStepIoMClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
197
isListClassKey, fromListClassOpKey, fromListNClassOpKey, toListClassOpKey :: Unique
isListClassKey :: Unique
isListClassKey = Int -> Unique
mkPreludeMiscIdUnique Int
198
fromListClassOpKey :: Unique
fromListClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
199
fromListNClassOpKey :: Unique
fromListNClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
500
toListClassOpKey :: Unique
toListClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
501
proxyHashKey :: Unique
proxyHashKey :: Unique
proxyHashKey = Int -> Unique
mkPreludeMiscIdUnique Int
502
mkTyConKey
, mkTrTypeKey
, mkTrConKey
, mkTrAppKey
, mkTrFunKey
, typeNatTypeRepKey
, typeSymbolTypeRepKey
, typeRepIdKey
:: Unique
mkTyConKey :: Unique
mkTyConKey = Int -> Unique
mkPreludeMiscIdUnique Int
503
mkTrTypeKey :: Unique
mkTrTypeKey = Int -> Unique
mkPreludeMiscIdUnique Int
504
mkTrConKey :: Unique
mkTrConKey = Int -> Unique
mkPreludeMiscIdUnique Int
505
mkTrAppKey :: Unique
mkTrAppKey = Int -> Unique
mkPreludeMiscIdUnique Int
506
typeNatTypeRepKey :: Unique
typeNatTypeRepKey = Int -> Unique
mkPreludeMiscIdUnique Int
507
typeSymbolTypeRepKey :: Unique
typeSymbolTypeRepKey = Int -> Unique
mkPreludeMiscIdUnique Int
508
typeRepIdKey :: Unique
typeRepIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
509
mkTrFunKey :: Unique
mkTrFunKey = Int -> Unique
mkPreludeMiscIdUnique Int
510
trTYPEKey
,trTYPE'PtrRepLiftedKey
, trRuntimeRepKey
, tr'PtrRepLiftedKey
:: Unique
trTYPEKey :: Unique
trTYPEKey = Int -> Unique
mkPreludeMiscIdUnique Int
511
trTYPE'PtrRepLiftedKey :: Unique
trTYPE'PtrRepLiftedKey = Int -> Unique
mkPreludeMiscIdUnique Int
512
trRuntimeRepKey :: Unique
trRuntimeRepKey = Int -> Unique
mkPreludeMiscIdUnique Int
513
tr'PtrRepLiftedKey :: Unique
tr'PtrRepLiftedKey = Int -> Unique
mkPreludeMiscIdUnique Int
514
starKindRepKey, starArrStarKindRepKey, starArrStarArrStarKindRepKey :: Unique
starKindRepKey :: Unique
starKindRepKey = Int -> Unique
mkPreludeMiscIdUnique Int
520
starArrStarKindRepKey :: Unique
starArrStarKindRepKey = Int -> Unique
mkPreludeMiscIdUnique Int
521
starArrStarArrStarKindRepKey :: Unique
starArrStarArrStarKindRepKey = Int -> Unique
mkPreludeMiscIdUnique Int
522
toDynIdKey :: Unique
toDynIdKey :: Unique
toDynIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
523
bitIntegerIdKey :: Unique
bitIntegerIdKey :: Unique
bitIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
550
heqSCSelIdKey, eqSCSelIdKey, coercibleSCSelIdKey :: Unique
eqSCSelIdKey :: Unique
eqSCSelIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
551
heqSCSelIdKey :: Unique
heqSCSelIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
552
coercibleSCSelIdKey :: Unique
coercibleSCSelIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
553
sappendClassOpKey :: Unique
sappendClassOpKey :: Unique
sappendClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
554
memptyClassOpKey, mappendClassOpKey, mconcatClassOpKey :: Unique
memptyClassOpKey :: Unique
memptyClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
555
mappendClassOpKey :: Unique
mappendClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
556
mconcatClassOpKey :: Unique
mconcatClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
557
emptyCallStackKey, pushCallStackKey :: Unique
emptyCallStackKey :: Unique
emptyCallStackKey = Int -> Unique
mkPreludeMiscIdUnique Int
558
pushCallStackKey :: Unique
pushCallStackKey = Int -> Unique
mkPreludeMiscIdUnique Int
559
fromStaticPtrClassOpKey :: Unique
fromStaticPtrClassOpKey :: Unique
fromStaticPtrClassOpKey = Int -> Unique
mkPreludeMiscIdUnique Int
560
makeStaticKey :: Unique
makeStaticKey :: Unique
makeStaticKey = Int -> Unique
mkPreludeMiscIdUnique Int
561
naturalFromIntegerIdKey, naturalToIntegerIdKey, plusNaturalIdKey,
minusNaturalIdKey, timesNaturalIdKey, mkNaturalIdKey,
naturalSDataConKey, wordToNaturalIdKey :: Unique
naturalFromIntegerIdKey :: Unique
naturalFromIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
562
naturalToIntegerIdKey :: Unique
naturalToIntegerIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
563
plusNaturalIdKey :: Unique
plusNaturalIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
564
minusNaturalIdKey :: Unique
minusNaturalIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
565
timesNaturalIdKey :: Unique
timesNaturalIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
566
mkNaturalIdKey :: Unique
mkNaturalIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
567
naturalSDataConKey :: Unique
naturalSDataConKey = Int -> Unique
mkPreludeMiscIdUnique Int
568
wordToNaturalIdKey :: Unique
wordToNaturalIdKey = Int -> Unique
mkPreludeMiscIdUnique Int
569
numericClassKeys :: [Unique]
numericClassKeys :: [Unique]
numericClassKeys =
[ Unique
numClassKey
, Unique
realClassKey
, Unique
integralClassKey
]
[Unique] -> [Unique] -> [Unique]
forall a. [a] -> [a] -> [a]
++ [Unique]
fractionalClassKeys
fractionalClassKeys :: [Unique]
fractionalClassKeys :: [Unique]
fractionalClassKeys =
[ Unique
fractionalClassKey
, Unique
floatingClassKey
, Unique
realFracClassKey
, Unique
realFloatClassKey
]
standardClassKeys :: [Unique]
standardClassKeys :: [Unique]
standardClassKeys = [Unique]
derivableClassKeys [Unique] -> [Unique] -> [Unique]
forall a. [a] -> [a] -> [a]
++ [Unique]
numericClassKeys
[Unique] -> [Unique] -> [Unique]
forall a. [a] -> [a] -> [a]
++ [Unique
randomClassKey, Unique
randomGenClassKey,
Unique
functorClassKey,
Unique
monadClassKey, Unique
monadPlusClassKey, Unique
monadFailClassKey,
Unique
semigroupClassKey, Unique
monoidClassKey,
Unique
isStringClassKey,
Unique
applicativeClassKey, Unique
foldableClassKey,
Unique
traversableClassKey, Unique
alternativeClassKey
]
derivableClassKeys :: [Unique]
derivableClassKeys :: [Unique]
derivableClassKeys
= [ Unique
eqClassKey, Unique
ordClassKey, Unique
enumClassKey, Unique
ixClassKey,
Unique
boundedClassKey, Unique
showClassKey, Unique
readClassKey ]
interactiveClassNames :: [Name]
interactiveClassNames :: [Name]
interactiveClassNames
= [ Name
showClassName, Name
eqClassName, Name
ordClassName, Name
foldableClassName
, Name
traversableClassName ]
interactiveClassKeys :: [Unique]
interactiveClassKeys :: [Unique]
interactiveClassKeys = (Name -> Unique) -> [Name] -> [Unique]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Unique
forall a. Uniquable a => a -> Unique
getUnique [Name]
interactiveClassNames
pretendNameIsInScope :: Name -> Bool
pretendNameIsInScope :: Name -> Bool
pretendNameIsInScope Name
n
= (Unique -> Bool) -> [Unique] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Name
n Name -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey`)
[ Unique
liftedTypeKindTyConKey, Unique
tYPETyConKey
, Unique
runtimeRepTyConKey, Unique
liftedRepDataConKey ]