{-# LANGUAGE OverloadedStrings #-}

-- | JS symbol generation
module GHC.StgToJS.Symbols where

import GHC.Prelude

import GHC.JS.JStg.Syntax
import GHC.JS.Ident

import GHC.Data.FastString
import GHC.Unit.Module
import GHC.Utils.Word64 (intToWord64)
import Data.ByteString (ByteString)
import Data.Word (Word64)
import qualified Data.ByteString.Char8   as BSC
import qualified Data.ByteString.Builder as BSB
import qualified Data.ByteString.Lazy    as BSL

import Data.Array
import Data.Semigroup ((<>))

-- | Hexadecimal representation of an int
--
-- Used for the sub indices.
intBS :: Int -> ByteString
intBS :: Int -> ByteString
intBS = Word64 -> ByteString
word64BS (Word64 -> ByteString) -> (Int -> Word64) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word64
HasDebugCallStack => Int -> Word64
intToWord64

-- | Hexadecimal representation of a 64-bit word
--
-- Used for uniques. We could use base-62 as GHC usually does but this is likely
-- faster.
word64BS :: Word64 -> ByteString
word64BS :: Word64 -> ByteString
word64BS = LazyByteString -> ByteString
BSL.toStrict (LazyByteString -> ByteString)
-> (Word64 -> LazyByteString) -> Word64 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> LazyByteString
BSB.toLazyByteString (Builder -> LazyByteString)
-> (Word64 -> Builder) -> Word64 -> LazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Builder
BSB.word64Hex

-- | Return z-encoded unit:module
unitModuleStringZ :: Module -> ByteString
unitModuleStringZ :: Module -> ByteString
unitModuleStringZ Module
mod = [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
  [ FastZString -> ByteString
fastZStringToByteString (FastString -> FastZString
zEncodeFS (UnitId -> FastString
unitIdFS (Module -> UnitId
moduleUnitId Module
mod)))
  , String -> ByteString
BSC.pack String
"ZC" -- z-encoding for ":"
  , FastZString -> ByteString
fastZStringToByteString (FastString -> FastZString
zEncodeFS (ModuleName -> FastString
moduleNameFS (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName Module
mod)))
  ]

-- | the global linkable unit of a module exports this symbol, depend on it to
--   include that unit (used for cost centres)
moduleGlobalSymbol :: Module -> FastString
moduleGlobalSymbol :: Module -> FastString
moduleGlobalSymbol Module
m = ByteString -> FastString
mkFastStringByteString (ByteString -> FastString) -> ByteString -> FastString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
  [ ByteString
hdB
  , Module -> ByteString
unitModuleStringZ Module
m
  , String -> ByteString
BSC.pack String
"_<global>"
  ]

moduleExportsSymbol :: Module -> FastString
moduleExportsSymbol :: Module -> FastString
moduleExportsSymbol Module
m = ByteString -> FastString
mkFastStringByteString (ByteString -> FastString) -> ByteString -> FastString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
  [ ByteString
hdB
  , Module -> ByteString
unitModuleStringZ Module
m
  , String -> ByteString
BSC.pack String
"_<exports>"
  ]

-- | Make JS symbol corresponding to the given Haskell symbol in the given
-- module
mkJsSymbolBS :: Bool -> Module -> FastString -> ByteString
mkJsSymbolBS :: Bool -> Module -> FastString -> ByteString
mkJsSymbolBS Bool
exported Module
mod FastString
s = [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
  [ if Bool
exported then ByteString
hdB else ByteString
hddB
  , Module -> ByteString
unitModuleStringZ Module
mod
  , String -> ByteString
BSC.pack String
"zi" -- z-encoding of "."
  , FastZString -> ByteString
fastZStringToByteString (FastString -> FastZString
zEncodeFS FastString
s)
  ]

-- | Make JS symbol corresponding to the given Haskell symbol in the given
-- module
mkJsSymbol :: Bool -> Module -> FastString -> FastString
mkJsSymbol :: Bool -> Module -> FastString -> FastString
mkJsSymbol Bool
exported Module
mod FastString
s = ByteString -> FastString
mkFastStringByteString (Bool -> Module -> FastString -> ByteString
mkJsSymbolBS Bool
exported Module
mod FastString
s)

-- | Make JS symbol for given module and unique.
mkFreshJsSymbol :: Module -> Int -> FastString
mkFreshJsSymbol :: Module -> Int -> FastString
mkFreshJsSymbol Module
mod Int
i = ByteString -> FastString
mkFastStringByteString (ByteString -> FastString) -> ByteString -> FastString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
  [ ByteString
hddB
  , Module -> ByteString
unitModuleStringZ Module
mod
  , String -> ByteString
BSC.pack String
"_"
  , Int -> ByteString
intBS Int
i
  ]

-- | Make symbol "h$XYZ" or "h$$XYZ"
mkRawSymbol :: Bool -> FastString -> FastString
mkRawSymbol :: Bool -> FastString -> FastString
mkRawSymbol Bool
exported FastString
fs
  | Bool
exported  = ByteString -> FastString
mkFastStringByteString (ByteString -> FastString) -> ByteString -> FastString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat [ ByteString
hdB,  FastString -> ByteString
bytesFS FastString
fs ]
  | Bool
otherwise = ByteString -> FastString
mkFastStringByteString (ByteString -> FastString) -> ByteString -> FastString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat [ ByteString
hddB, FastString -> ByteString
bytesFS FastString
fs ]

-- | "h$$" constant string
hddB :: ByteString
hddB :: ByteString
hddB = String -> ByteString
BSC.pack String
"h$$"

-- | "h$" constant string
hdB :: ByteString
hdB :: ByteString
hdB = Int -> ByteString -> ByteString
BSC.take Int
2 ByteString
hddB

hd :: JStgExpr
hd :: JStgExpr
hd = FastString -> JStgExpr
global FastString
hdStr

hdStr :: FastString
hdStr :: FastString
hdStr = ByteString -> FastString
mkFastStringByteString ByteString
hdB

hdlB :: ByteString
hdlB :: ByteString
hdlB = String -> ByteString
BSC.pack String
"h$l"

----------------------------------------- Runtime -------------------------------
hdApply :: JStgExpr
hdApply :: JStgExpr
hdApply = FastString -> JStgExpr
global FastString
hdApplyStr

hdApplyStr :: FastString
hdApplyStr :: FastString
hdApplyStr = String -> FastString
fsLit String
"h$apply"

hdMoveRegs2 :: FastString
hdMoveRegs2 :: FastString
hdMoveRegs2 = String -> FastString
fsLit String
"h$moveRegs2"

hdPapGen :: JStgExpr
hdPapGen :: JStgExpr
hdPapGen = FastString -> JStgExpr
global FastString
hdPapGenStr

hdPapGenStr :: FastString
hdPapGenStr :: FastString
hdPapGenStr = String -> FastString
fsLit String
"h$pap_gen"

hdSetReg :: JStgExpr
hdSetReg :: JStgExpr
hdSetReg = FastString -> JStgExpr
global FastString
hdSetRegStr

hdSetRegStr :: FastString
hdSetRegStr :: FastString
hdSetRegStr = String -> FastString
fsLit String
"h$setReg"

hdGetReg :: JStgExpr
hdGetReg :: JStgExpr
hdGetReg = FastString -> JStgExpr
global FastString
hdGetRegStr

hdGetRegStr :: FastString
hdGetRegStr :: FastString
hdGetRegStr = String -> FastString
fsLit String
"h$getReg"

hdResetRegisters :: Ident
hdResetRegisters :: Ident
hdResetRegisters = FastString -> Ident
name FastString
"h$resetRegisters"

hdResetResultVars :: Ident
hdResetResultVars :: Ident
hdResetResultVars = FastString -> Ident
name FastString
"h$resetResultVars"

hdInitClosure :: FastString
hdInitClosure :: FastString
hdInitClosure = String -> FastString
fsLit String
"h$init_closure"

hdRegs :: JStgExpr
hdRegs :: JStgExpr
hdRegs = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRegsStr)

hdRegsStr :: Ident
hdRegsStr :: Ident
hdRegsStr = FastString -> Ident
name FastString
"h$regs"

hdReturn :: JStgExpr
hdReturn :: JStgExpr
hdReturn = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdReturnStr)

hdReturnStr :: Ident
hdReturnStr :: Ident
hdReturnStr = FastString -> Ident
name FastString
"h$return"

hdStack :: JStgExpr
hdStack :: JStgExpr
hdStack = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdStackStr)

hdStackStr :: Ident
hdStackStr :: Ident
hdStackStr = FastString -> Ident
name FastString
"h$stack"

hdStackPtr :: JStgExpr
hdStackPtr :: JStgExpr
hdStackPtr = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdStackPtrStr)

hdStackPtrStr :: Ident
hdStackPtrStr :: Ident
hdStackPtrStr = FastString -> Ident
name FastString
"h$sp"

hdBlackHoleTrap :: JStgExpr
hdBlackHoleTrap :: JStgExpr
hdBlackHoleTrap = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdBlackHoleTrapStr)

hdBlackHoleTrapStr :: Ident
hdBlackHoleTrapStr :: Ident
hdBlackHoleTrapStr = FastString -> Ident
name FastString
"h$blackholeTrap"

hdBlockOnBlackHoleStr :: FastString
hdBlockOnBlackHoleStr :: FastString
hdBlockOnBlackHoleStr = FastString
"h$blockOnBlackhole"

hdBlackHoleLNE :: JStgExpr
hdBlackHoleLNE :: JStgExpr
hdBlackHoleLNE = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdBlackHoleLNEStr)

hdBlackHoleLNEStr :: Ident
hdBlackHoleLNEStr :: Ident
hdBlackHoleLNEStr = FastString -> Ident
name FastString
"h$bh_lne"

hdClosureTypeName :: JStgExpr
hdClosureTypeName :: JStgExpr
hdClosureTypeName = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdClosureTypeNameStr)

hdClosureTypeNameStr :: Ident
hdClosureTypeNameStr :: Ident
hdClosureTypeNameStr = FastString -> Ident
name FastString
"h$closureTypeName"

hdBh :: JStgExpr
hdBh :: JStgExpr
hdBh = FastString -> JStgExpr
global FastString
hdBhStr

hdBhStr :: FastString
hdBhStr :: FastString
hdBhStr = String -> FastString
fsLit String
"h$bh"

hdBlackHole :: JStgExpr
hdBlackHole :: JStgExpr
hdBlackHole = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdBlackHoleStr)

hdBlackHoleStr :: Ident
hdBlackHoleStr :: Ident
hdBlackHoleStr = FastString -> Ident
name FastString
"h$blackhole"

hdUpdFrame :: JStgExpr
hdUpdFrame :: JStgExpr
hdUpdFrame = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdUpdFrameStr)

hdUpdFrameStr :: Ident
hdUpdFrameStr :: Ident
hdUpdFrameStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$upd_frame"

hdCSel :: JStgExpr
hdCSel :: JStgExpr
hdCSel = FastString -> JStgExpr
global FastString
hdCSelStr

hdCSelStr :: FastString
hdCSelStr :: FastString
hdCSelStr = FastString
"h$c_sel_"

hdEntry :: Ident
hdEntry :: Ident
hdEntry = FastString -> Ident
name FastString
hdEntryStr

hdEntryStr :: FastString
hdEntryStr :: FastString
hdEntryStr = String -> FastString
fsLit String
"h$e"

hdApGen :: JStgExpr
hdApGen :: JStgExpr
hdApGen = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdApGenStr)

hdApGenStr :: Ident
hdApGenStr :: Ident
hdApGenStr = FastString -> Ident
name FastString
"h$ap_gen"

hdApGenFastStr :: Ident
hdApGenFastStr :: Ident
hdApGenFastStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit (String -> FastString) -> String -> FastString
forall a b. (a -> b) -> a -> b
$ FastString -> String
unpackFS (Ident -> FastString
identFS Ident
hdApGenStr) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"_fast"

hdLog :: JStgExpr
hdLog :: JStgExpr
hdLog = FastString -> JStgExpr
global FastString
hdLogStr

hdLogStr :: FastString
hdLogStr :: FastString
hdLogStr = String -> FastString
fsLit String
"h$log"

hdMkFunctionPtr :: JStgExpr
hdMkFunctionPtr :: JStgExpr
hdMkFunctionPtr = FastString -> JStgExpr
global FastString
"h$mkFunctionPtr"

hdInitStatic :: JStgExpr
hdInitStatic :: JStgExpr
hdInitStatic = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdInitStaticStr)

hdInitStaticStr :: Ident
hdInitStaticStr :: Ident
hdInitStaticStr = FastString -> Ident
name FastString
"h$initStatic"

hdHsSptInsert :: JStgExpr
hdHsSptInsert :: JStgExpr
hdHsSptInsert = FastString -> JStgExpr
global FastString
"h$hs_spt_insert"

hdCurrentThread :: JStgExpr
hdCurrentThread :: JStgExpr
hdCurrentThread = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdCurrentThreadStr)

hdCurrentThreadStr :: Ident
hdCurrentThreadStr :: Ident
hdCurrentThreadStr = FastString -> Ident
name FastString
"h$currentThread"

hdWakeupThread :: FastString
hdWakeupThread :: FastString
hdWakeupThread = String -> FastString
fsLit String
"h$wakeupThread"

hdPaps :: JStgExpr
hdPaps :: JStgExpr
hdPaps = FastString -> JStgExpr
global FastString
hdPapsStr

hdPapsStr :: FastString
hdPapsStr :: FastString
hdPapsStr = String -> FastString
fsLit String
"h$paps"

hdPapStr_ :: FastString
hdPapStr_ :: FastString
hdPapStr_ = String -> FastString
fsLit String
"h$pap_"

hdLazyEntryStr :: Ident
hdLazyEntryStr :: Ident
hdLazyEntryStr = FastString -> Ident
name FastString
"h$lazy_e"

hdUnboxEntry :: JStgExpr
hdUnboxEntry :: JStgExpr
hdUnboxEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdUnboxEntryStr)

hdUnboxEntryStr :: Ident
hdUnboxEntryStr :: Ident
hdUnboxEntryStr = FastString -> Ident
name FastString
"h$unbox_e"

hdMaskFrame :: JStgExpr
hdMaskFrame :: JStgExpr
hdMaskFrame = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdMaskFrameStr)

hdMaskFrameStr :: Ident
hdMaskFrameStr :: Ident
hdMaskFrameStr = FastString -> Ident
name FastString
"h$maskFrame"

hdUnMaskFrameStr :: Ident
hdUnMaskFrameStr :: Ident
hdUnMaskFrameStr = FastString -> Ident
name FastString
"h$unmaskFrame"

hdReturnF :: JStgExpr
hdReturnF :: JStgExpr
hdReturnF = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdReturnFStr)

hdReturnFStr :: Ident
hdReturnFStr :: Ident
hdReturnFStr = FastString -> Ident
name FastString
"h$returnf"

hdResumeEntryStr :: Ident
hdResumeEntryStr :: Ident
hdResumeEntryStr = FastString -> Ident
name FastString
"h$resume_e"

hdFlushStdout :: JStgExpr
hdFlushStdout :: JStgExpr
hdFlushStdout = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdFlushStdoutStr)

hdFlushStdoutStr :: Ident
hdFlushStdoutStr :: Ident
hdFlushStdoutStr = FastString -> Ident
name FastString
"h$flushStdout"

hdFlushStdoutEntry :: JStgExpr
hdFlushStdoutEntry :: JStgExpr
hdFlushStdoutEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdFlushStdoutEntryStr)

hdFlushStdoutEntryStr :: Ident
hdFlushStdoutEntryStr :: Ident
hdFlushStdoutEntryStr = FastString -> Ident
name FastString
"h$flushStdout_e"

hdRunIOEntry :: JStgExpr
hdRunIOEntry :: JStgExpr
hdRunIOEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRunIOEntryStr)

hdRunIOEntryStr :: Ident
hdRunIOEntryStr :: Ident
hdRunIOEntryStr = FastString -> Ident
name FastString
"h$runio_e"

hdReduce :: JStgExpr
hdReduce :: JStgExpr
hdReduce = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdReduceStr)

hdReduceStr :: Ident
hdReduceStr :: Ident
hdReduceStr = FastString -> Ident
name FastString
"h$reduce"

hdThrowStr :: FastString
hdThrowStr :: FastString
hdThrowStr = String -> FastString
fsLit String
"h$throw"

hdRaiseAsyncFrame :: JStgExpr
hdRaiseAsyncFrame :: JStgExpr
hdRaiseAsyncFrame = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRaiseAsyncFrameStr)

hdRaiseAsyncFrameStr :: Ident
hdRaiseAsyncFrameStr :: Ident
hdRaiseAsyncFrameStr = FastString -> Ident
name FastString
"h$raiseAsync_frame"

hdRaiseAsyncEntry :: JStgExpr
hdRaiseAsyncEntry :: JStgExpr
hdRaiseAsyncEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRaiseAsyncEntryStr)

hdRaiseAsyncEntryStr :: Ident
hdRaiseAsyncEntryStr :: Ident
hdRaiseAsyncEntryStr = FastString -> Ident
name FastString
"h$raiseAsync_e"

hdRaiseEntry :: JStgExpr
hdRaiseEntry :: JStgExpr
hdRaiseEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRaiseEntryStr)

hdRaiseEntryStr :: Ident
hdRaiseEntryStr :: Ident
hdRaiseEntryStr = FastString -> Ident
name FastString
"h$raise_e"

hdKeepAliveEntry :: JStgExpr
hdKeepAliveEntry :: JStgExpr
hdKeepAliveEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdKeepAliveEntryStr)

hdKeepAliveEntryStr :: Ident
hdKeepAliveEntryStr :: Ident
hdKeepAliveEntryStr = FastString -> Ident
name FastString
"h$keepAlive_e"

hdSelect2Return :: JStgExpr
hdSelect2Return :: JStgExpr
hdSelect2Return = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdSelect2ReturnStr)

hdSelect2ReturnStr :: Ident
hdSelect2ReturnStr :: Ident
hdSelect2ReturnStr = FastString -> Ident
name FastString
"h$select2_ret"

hdSelect2Entry :: JStgExpr
hdSelect2Entry :: JStgExpr
hdSelect2Entry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdSelect2EntryStr)

hdSelect2EntryStr :: Ident
hdSelect2EntryStr :: Ident
hdSelect2EntryStr = FastString -> Ident
name FastString
"h$select2_e"

hdSelect1Ret :: JStgExpr
hdSelect1Ret :: JStgExpr
hdSelect1Ret = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdSelect1RetStr)

hdSelect1RetStr :: Ident
hdSelect1RetStr :: Ident
hdSelect1RetStr = FastString -> Ident
name FastString
"h$select1_ret"

hdSelect1EntryStr :: Ident
hdSelect1EntryStr :: Ident
hdSelect1EntryStr = FastString -> Ident
name FastString
"h$select1_e"

hdStaticThunkStr :: FastString
hdStaticThunkStr :: FastString
hdStaticThunkStr = String -> FastString
fsLit String
"h$static_thunk"

hdStaticThunksStr
  , hdStaticThunksArrStr
  , hdCAFsStr
  , hdCAFsResetStr :: Ident
hdStaticThunksStr :: Ident
hdStaticThunksStr    = FastString -> Ident
name FastString
"h$staticThunks"
hdStaticThunksArrStr :: Ident
hdStaticThunksArrStr = FastString -> Ident
name FastString
"h$staticThunksArr"
hdCAFsStr :: Ident
hdCAFsStr            = FastString -> Ident
name FastString
"h$CAFs"
hdCAFsResetStr :: Ident
hdCAFsResetStr       = FastString -> Ident
name FastString
"h$CAFsReset"

hdUpdThunkEntryStr :: Ident
hdUpdThunkEntryStr :: Ident
hdUpdThunkEntryStr = FastString -> Ident
name FastString
"h$upd_thunk_e"

hdAp3EntryStr :: Ident
hdAp3EntryStr :: Ident
hdAp3EntryStr = FastString -> Ident
name FastString
"h$ap3_e"

hdAp2EntryStr :: Ident
hdAp2EntryStr :: Ident
hdAp2EntryStr = FastString -> Ident
name FastString
"h$ap2_e"

hdAp1EntryStr :: Ident
hdAp1EntryStr :: Ident
hdAp1EntryStr = FastString -> Ident
name FastString
"h$ap1_e"

hdDataToTagEntryStr :: Ident
hdDataToTagEntryStr :: Ident
hdDataToTagEntryStr = FastString -> Ident
name FastString
"h$dataToTag_e"

hdTagToEnum :: FastString
hdTagToEnum :: FastString
hdTagToEnum = String -> FastString
fsLit String
"h$tagToEnum"

hdCatchEntryStr :: Ident
hdCatchEntryStr :: Ident
hdCatchEntryStr = FastString -> Ident
name FastString
"h$catch_e"

hdNoopStr :: Ident
hdNoopStr :: Ident
hdNoopStr = FastString -> Ident
name FastString
"h$noop"

hdNoopEntry :: JStgExpr
hdNoopEntry :: JStgExpr
hdNoopEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdNoopEntryStr)

hdNoopEntryStr :: Ident
hdNoopEntryStr :: Ident
hdNoopEntryStr = FastString -> Ident
name FastString
"h$noop_e"

hdC0 :: JStgExpr
hdC0 :: JStgExpr
hdC0 = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdC0Str)

hdC :: JStgExpr
hdC :: JStgExpr
hdC = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdCStr)

hdC0Str :: Ident
hdC0Str :: Ident
hdC0Str = FastString -> Ident
name FastString
"h$c0"

hdCStr :: Ident
hdCStr :: Ident
hdCStr = FastString -> Ident
name FastString
"h$c"

hdData2Entry :: Ident
hdData2Entry :: Ident
hdData2Entry = FastString -> Ident
name FastString
"h$data2_e"

hdData1Entry :: Ident
hdData1Entry :: Ident
hdData1Entry = FastString -> Ident
name FastString
"h$data1_e"

hdTrueEntry :: Ident
hdTrueEntry :: Ident
hdTrueEntry = FastString -> Ident
name FastString
"h$true_e"

hdFalseEntry :: Ident
hdFalseEntry :: Ident
hdFalseEntry = FastString -> Ident
name FastString
"h$false_e"

hdDoneMainEntry :: JStgExpr
hdDoneMainEntry :: JStgExpr
hdDoneMainEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdDoneMainEntryStr)

hdDoneMainEntryStr :: Ident
hdDoneMainEntryStr :: Ident
hdDoneMainEntryStr = FastString -> Ident
name FastString
"h$doneMain_e"

hdDoneMain :: JStgExpr
hdDoneMain :: JStgExpr
hdDoneMain = FastString -> JStgExpr
global FastString
"h$doneMain"

hdDone :: Ident
hdDone :: Ident
hdDone = FastString -> Ident
name FastString
"h$done"

hdExitProcess :: FastString
hdExitProcess :: FastString
hdExitProcess = FastString
"h$exitProcess"

hdTraceAlloc :: FastString
hdTraceAlloc :: FastString
hdTraceAlloc = String -> FastString
fsLit String
"h$traceAlloc"

hdDebugAllocNotifyAlloc :: FastString
hdDebugAllocNotifyAlloc :: FastString
hdDebugAllocNotifyAlloc = String -> FastString
fsLit String
"h$debugAlloc_notifyAlloc"

hdRtsTraceForeign
  , hdRtsProfiling
  , hdCtFun
  , hdCtCon
  , hdCtThunk
  , hdCtPap
  , hdCtBlackhole
  , hdCtStackFrame
  , hdCtVtPtr
  , hdVtVoid
  , hdVtInt
  , hdVtDouble
  , hdVtLong
  , hdVtAddr
  , hdVtObj
  , hdVtArr :: Ident
hdRtsTraceForeign :: Ident
hdRtsTraceForeign = FastString -> Ident
name FastString
"h$rts_traceForeign"
hdRtsProfiling :: Ident
hdRtsProfiling    = FastString -> Ident
name FastString
"h$rts_profiling"
hdCtFun :: Ident
hdCtFun           = FastString -> Ident
name FastString
"h$ct_fun"
hdCtCon :: Ident
hdCtCon           = FastString -> Ident
name FastString
"h$ct_con"
hdCtThunk :: Ident
hdCtThunk         = FastString -> Ident
name FastString
"h$ct_thunk"
hdCtPap :: Ident
hdCtPap           = FastString -> Ident
name FastString
"h$ct_pap"
hdCtBlackhole :: Ident
hdCtBlackhole     = FastString -> Ident
name FastString
"h$ct_blackhole"
hdCtStackFrame :: Ident
hdCtStackFrame    = FastString -> Ident
name FastString
"h$ct_stackframe"
hdCtVtPtr :: Ident
hdCtVtPtr         = FastString -> Ident
name FastString
"h$vt_ptr"
hdVtVoid :: Ident
hdVtVoid          = FastString -> Ident
name FastString
"h$vt_void"
hdVtInt :: Ident
hdVtInt           = FastString -> Ident
name FastString
"h$vt_int"
hdVtDouble :: Ident
hdVtDouble        = FastString -> Ident
name FastString
"h$vt_double"
hdVtLong :: Ident
hdVtLong          = FastString -> Ident
name FastString
"h$vt_long"
hdVtAddr :: Ident
hdVtAddr          = FastString -> Ident
name FastString
"h$vt_addr"
hdVtObj :: Ident
hdVtObj           = FastString -> Ident
name FastString
"h$vt_obj"
hdVtArr :: Ident
hdVtArr           = FastString -> Ident
name FastString
"h$vt_arr"


hdLoads :: Array Int Ident
hdLoads :: Array Int Ident
hdLoads = (Int, Int) -> [Ident] -> Array Int Ident
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
1,Int
32) [ FastString -> Ident
name (FastString -> Ident)
-> (ByteString -> FastString) -> ByteString -> Ident
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> FastString
mkFastStringByteString (ByteString -> Ident) -> ByteString -> Ident
forall a b. (a -> b) -> a -> b
$ ByteString
hdlB ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> String -> ByteString
BSC.pack (Int -> String
forall a. Show a => a -> String
show Int
n)
                           | Int
n <- [Int
1..Int
32::Int]
                           ]

----------------------------------------- Precompiled Aps ----------------------
hdAp00 :: JStgExpr
hdAp00 :: JStgExpr
hdAp00 = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdAp00Str)

hdAp00Str :: Ident
hdAp00Str :: Ident
hdAp00Str = FastString -> Ident
name FastString
"h$ap_0_0"

hdAp00FastStr :: FastString
hdAp00FastStr :: FastString
hdAp00FastStr = String -> FastString
fsLit String
"h$ap_0_0_fast"

hdAp11Fast :: FastString
hdAp11Fast :: FastString
hdAp11Fast = String -> FastString
fsLit String
"h$ap_1_1_fast"

hdAp10 :: JStgExpr
hdAp10 :: JStgExpr
hdAp10 = FastString -> JStgExpr
global FastString
"h$ap_1_0"

hdAp33FastStr :: FastString
hdAp33FastStr :: FastString
hdAp33FastStr = String -> FastString
fsLit String
"h$ap_3_3_fast"

hdAp22FastStr :: FastString
hdAp22FastStr :: FastString
hdAp22FastStr = String -> FastString
fsLit String
"h$ap_2_2_fast"

----------------------------------------- ByteArray -----------------------------
hdNewByteArrayStr :: FastString
hdNewByteArrayStr :: FastString
hdNewByteArrayStr = FastString
"h$newByteArray"

hdCopyMutableByteArrayStr :: FastString
hdCopyMutableByteArrayStr :: FastString
hdCopyMutableByteArrayStr = FastString
"h$copyMutableByteArray"

hdCheckOverlapByteArrayStr :: FastString
hdCheckOverlapByteArrayStr :: FastString
hdCheckOverlapByteArrayStr = FastString
"h$checkOverlapByteArray"

hdShrinkMutableCharArrayStr :: FastString
hdShrinkMutableCharArrayStr :: FastString
hdShrinkMutableCharArrayStr = FastString
"h$shrinkMutableCharArray"

----------------------------------------- EventLog -----------------------------
hdTraceEventStr :: FastString
hdTraceEventStr :: FastString
hdTraceEventStr = FastString
"h$traceEvent"

hdTraceEventBinaryStr :: FastString
hdTraceEventBinaryStr :: FastString
hdTraceEventBinaryStr = FastString
"h$traceEventBinary"

hdTraceMarkerStr :: FastString
hdTraceMarkerStr :: FastString
hdTraceMarkerStr = FastString
"h$traceMarker"

----------------------------------------- FFI ----------------------------------
hdThrowJSException :: JStgExpr
hdThrowJSException :: JStgExpr
hdThrowJSException = FastString -> JStgExpr
global (FastString -> JStgExpr) -> FastString -> JStgExpr
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$throwJSException"

hdUnboxFFIResult :: JStgExpr
hdUnboxFFIResult :: JStgExpr
hdUnboxFFIResult = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdUnboxFFIResultStr)

hdUnboxFFIResultStr :: Ident
hdUnboxFFIResultStr :: Ident
hdUnboxFFIResultStr = FastString -> Ident
name FastString
"h$unboxFFIResult"

hdMkForeignCallback :: JStgExpr
hdMkForeignCallback :: JStgExpr
hdMkForeignCallback = FastString -> JStgExpr
global (FastString -> JStgExpr) -> FastString -> JStgExpr
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$mkForeignCallback"

hdTraceForeign :: JStgExpr
hdTraceForeign :: JStgExpr
hdTraceForeign = FastString -> JStgExpr
global (FastString -> JStgExpr) -> FastString -> JStgExpr
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$traceForeign"

hdBuildObject :: JStgExpr
hdBuildObject :: JStgExpr
hdBuildObject = FastString -> JStgExpr
global FastString
hdBuildObjectStr

hdBuildObjectStr :: FastString
hdBuildObjectStr :: FastString
hdBuildObjectStr = String -> FastString
fsLit String
"h$buildObject"

hdCallDynamicStr :: FastString
hdCallDynamicStr :: FastString
hdCallDynamicStr = String -> FastString
fsLit String
"h$callDynamic"

except :: JStgExpr
except :: JStgExpr
except = FastString -> JStgExpr
global (FastString -> JStgExpr) -> FastString -> JStgExpr
forall a b. (a -> b) -> a -> b
$ Ident -> FastString
identFS Ident
exceptStr

exceptStr :: Ident
exceptStr :: Ident
exceptStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"except"

excepStr :: FastString
excepStr :: FastString
excepStr = String -> FastString
fsLit String
"excep"

----------------------------------------- Accessors -----------------------------

-- for almost all other symbols that are faststrings we turn 'foo' into 'fooStr'
-- because these are overloaded with JStgExpr's. But for accessors we leave
-- these as FastStrings because they will become Idents after the refactor.
mv :: FastString
mv :: FastString
mv = String -> FastString
fsLit String
"mv"

lngth :: FastString
lngth :: FastString
lngth = String -> FastString
fsLit String
"length"

-- | only for byte arrays. This is a JS byte array method
len :: FastString
len :: FastString
len = String -> FastString
fsLit String
"len"

slice :: FastString
slice :: FastString
slice = String -> FastString
fsLit String
"slice"

this :: JStgExpr
this :: JStgExpr
this = FastString -> JStgExpr
global FastString
"this"

arr :: FastString
arr :: FastString
arr = String -> FastString
fsLit String
"arr"

dv :: FastString
dv :: FastString
dv = String -> FastString
fsLit String
"dv"

d1, d2, d3 :: JStgExpr
d1 :: JStgExpr
d1 = FastString -> JStgExpr
global FastString
d1Str
d2 :: JStgExpr
d2 = FastString -> JStgExpr
global FastString
d2Str
d3 :: JStgExpr
d3 = FastString -> JStgExpr
global FastString
d3Str

d1Str, d2Str, d3Str :: FastString
d1Str :: FastString
d1Str = String -> FastString
fsLit String
"d1"
d2Str :: FastString
d2Str = String -> FastString
fsLit String
"d2"
d3Str :: FastString
d3Str = String -> FastString
fsLit String
"d3"

getInt16 :: FastString
getInt16 :: FastString
getInt16 = FastString
"getInt16"

getUint16 :: FastString
getUint16 :: FastString
getUint16 = FastString
"getUint16"

getInt32 :: FastString
getInt32 :: FastString
getInt32 = FastString
"getInt32"

getUint32 :: FastString
getUint32 :: FastString
getUint32 = FastString
"getUint32"

getFloat32 :: FastString
getFloat32 :: FastString
getFloat32 = FastString
"getFloat32"

getFloat64 :: FastString
getFloat64 :: FastString
getFloat64 = FastString
"getFloat64"

setInt16 :: FastString
setInt16 :: FastString
setInt16 = FastString
"setInt16"

setUint16 :: FastString
setUint16 :: FastString
setUint16 = FastString
"setUint16"

setInt32 :: FastString
setInt32 :: FastString
setInt32 = FastString
"setInt32"

setUint32 :: FastString
setUint32 :: FastString
setUint32 = FastString
"setUint32"

setFloat32 :: FastString
setFloat32 :: FastString
setFloat32 = FastString
"setFloat32"

setFloat64 :: FastString
setFloat64 :: FastString
setFloat64 = FastString
"setFloat64"

i3, u8, u1, f6, f3 :: FastString
i3 :: FastString
i3 = FastString
"i3"
u8 :: FastString
u8 = FastString
"u8"
u1 :: FastString
u1 = FastString
"u1"
f6 :: FastString
f6 = FastString
"f6"
f3 :: FastString
f3 = FastString
"f3"

val :: FastString
val :: FastString
val = String -> FastString
fsLit String
"val"

label :: FastString
label :: FastString
label = String -> FastString
fsLit String
"label"

mask :: FastString
mask :: FastString
mask = String -> FastString
fsLit String
"mask"

unMask :: FastString
unMask :: FastString
unMask = String -> FastString
fsLit String
"unmask"

resume :: FastString
resume :: FastString
resume = FastString
"resume"

f :: FastString
f :: FastString
f = String -> FastString
fsLit String
"f"

n :: FastString
n :: FastString
n = String -> FastString
fsLit String
"n"

hasOwnProperty :: FastString
hasOwnProperty :: FastString
hasOwnProperty = String -> FastString
fsLit String
"hasOwnProperty"

hdCollectProps :: FastString
hdCollectProps :: FastString
hdCollectProps = String -> FastString
fsLit String
"h$collectProps"

replace :: FastString
replace :: FastString
replace = String -> FastString
fsLit String
"replace"

substring :: FastString
substring :: FastString
substring = String -> FastString
fsLit String
"substring"

trace :: FastString
trace :: FastString
trace = String -> FastString
fsLit String
"trace"

apply :: FastString
apply :: FastString
apply = String -> FastString
fsLit String
"apply"

----------------------------------------- STM ----------------------------------
hdMVar :: JStgExpr
hdMVar :: JStgExpr
hdMVar = FastString -> JStgExpr
global FastString
hdMVarStr

hdMVarStr :: FastString
hdMVarStr :: FastString
hdMVarStr = String -> FastString
fsLit String
"h$MVar"

hdTakeMVar :: JStgExpr
hdTakeMVar :: JStgExpr
hdTakeMVar = FastString -> JStgExpr
global FastString
hdTakeMVarStr

hdTakeMVarStr :: FastString
hdTakeMVarStr :: FastString
hdTakeMVarStr = String -> FastString
fsLit String
"h$takeMVar"

hdTryTakeMVarStr :: FastString
hdTryTakeMVarStr :: FastString
hdTryTakeMVarStr = String -> FastString
fsLit String
"h$tryTakeMVar"

hdPutMVarStr :: FastString
hdPutMVarStr :: FastString
hdPutMVarStr = String -> FastString
fsLit String
"h$putMVar"

hdTryPutMVarStr :: FastString
hdTryPutMVarStr :: FastString
hdTryPutMVarStr = String -> FastString
fsLit String
"h$tryPutMVar"

hdNewTVar :: FastString
hdNewTVar :: FastString
hdNewTVar = String -> FastString
fsLit String
"h$newTVar"

hdReadTVar :: FastString
hdReadTVar :: FastString
hdReadTVar = String -> FastString
fsLit String
"h$readTVar"

hdReadTVarIO :: FastString
hdReadTVarIO :: FastString
hdReadTVarIO = String -> FastString
fsLit String
"h$readTVarIO"

hdWriteTVar :: FastString
hdWriteTVar :: FastString
hdWriteTVar = String -> FastString
fsLit String
"h$writeTVar"

hdReadMVarStr :: FastString
hdReadMVarStr :: FastString
hdReadMVarStr = String -> FastString
fsLit String
"h$readMVar"

hdStmRemoveBlockedThreadStr :: FastString
hdStmRemoveBlockedThreadStr :: FastString
hdStmRemoveBlockedThreadStr = String -> FastString
fsLit String
"h$stmRemoveBlockedThread"

hdStmStartTransactionStr :: FastString
hdStmStartTransactionStr :: FastString
hdStmStartTransactionStr = String -> FastString
fsLit String
"h$stmStartTransaction"

hdAtomicallyEntry :: JStgExpr
hdAtomicallyEntry :: JStgExpr
hdAtomicallyEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdAtomicallyEntryStr)

hdAtomicallyEntryStr :: Ident
hdAtomicallyEntryStr :: Ident
hdAtomicallyEntryStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$atomically_e"

hdAtomicallyStr :: FastString
hdAtomicallyStr :: FastString
hdAtomicallyStr = FastString
"h$atomically"

hdStgResumeRetryEntry :: JStgExpr
hdStgResumeRetryEntry :: JStgExpr
hdStgResumeRetryEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdStgResumeRetryEntryStr)

hdStgResumeRetryEntryStr :: Ident
hdStgResumeRetryEntryStr :: Ident
hdStgResumeRetryEntryStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$stmResumeRetry_e"

hdStmCommitTransactionStr :: FastString
hdStmCommitTransactionStr :: FastString
hdStmCommitTransactionStr = String -> FastString
fsLit String
"h$stmCommitTransaction"

hdStmValidateTransactionStr :: FastString
hdStmValidateTransactionStr :: FastString
hdStmValidateTransactionStr = FastString
"h$stmValidateTransaction"

hdStmCatchRetryEntry :: JStgExpr
hdStmCatchRetryEntry :: JStgExpr
hdStmCatchRetryEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdStmCatchRetryEntryStr)

hdStmCatchRetryEntryStr :: Ident
hdStmCatchRetryEntryStr :: Ident
hdStmCatchRetryEntryStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$stmCatchRetry_e"

hdStmRetryStr :: FastString
hdStmRetryStr :: FastString
hdStmRetryStr = String -> FastString
fsLit String
"h$stmRetry"

hdStmCatchRetryStr :: FastString
hdStmCatchRetryStr :: FastString
hdStmCatchRetryStr = String -> FastString
fsLit String
"h$stmCatchRetry"

hdStmCatchEntry :: JStgExpr
hdStmCatchEntry :: JStgExpr
hdStmCatchEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdStmCatchEntryStr)

hdCatchStmStr :: FastString
hdCatchStmStr :: FastString
hdCatchStmStr = String -> FastString
fsLit String
"h$catchStm"

hdStmCatchEntryStr :: Ident
hdStmCatchEntryStr :: Ident
hdStmCatchEntryStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$catchStm_e"

hdRetryInterrupted :: JStgExpr
hdRetryInterrupted :: JStgExpr
hdRetryInterrupted = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRetryInterruptedStr)

hdRetryInterruptedStr :: Ident
hdRetryInterruptedStr :: Ident
hdRetryInterruptedStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$retryInterrupted"

hdMaskUnintFrame :: JStgExpr
hdMaskUnintFrame :: JStgExpr
hdMaskUnintFrame = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdMaskUnintFrameStr)

hdMaskUnintFrameStr :: Ident
hdMaskUnintFrameStr :: Ident
hdMaskUnintFrameStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$maskUnintFrame"

hdReschedule :: JStgExpr
hdReschedule :: JStgExpr
hdReschedule = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRescheduleStr)

hdRescheduleStr :: Ident
hdRescheduleStr :: Ident
hdRescheduleStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$reschedule"

hdRestoreThread :: JStgExpr
hdRestoreThread :: JStgExpr
hdRestoreThread = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdRestoreThreadStr)

hdRestoreThreadStr :: Ident
hdRestoreThreadStr :: Ident
hdRestoreThreadStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$restoreThread"

hdFinishedThread :: FastString
hdFinishedThread :: FastString
hdFinishedThread = String -> FastString
fsLit String
"h$finishThread"

----------------------------------------- Z-Encodings ---------------------------
hdPrimOpStr :: FastString
hdPrimOpStr :: FastString
hdPrimOpStr = String -> FastString
fsLit String
"h$primop_"

wrapperColonStr :: FastString
wrapperColonStr :: FastString
wrapperColonStr = String -> FastString
fsLit String
"ghczuwrapperZC" -- equivalent non-z-encoding => ghc_wrapper:

hdInternalExceptionTypeDivZero :: JStgExpr
hdInternalExceptionTypeDivZero :: JStgExpr
hdInternalExceptionTypeDivZero = FastString -> JStgExpr
global FastString
"h$ghczminternalZCGHCziInternalziExceptionziTypezidivZZeroException"

hdInternalExceptionTypeOverflow :: JStgExpr
hdInternalExceptionTypeOverflow :: JStgExpr
hdInternalExceptionTypeOverflow = FastString -> JStgExpr
global FastString
"h$ghczminternalZCGHCziInternalziExceptionziTypezioverflowException"

hdInternalExceptionTypeUnderflow :: JStgExpr
hdInternalExceptionTypeUnderflow :: JStgExpr
hdInternalExceptionTypeUnderflow = FastString -> JStgExpr
global FastString
"h$ghczminternalZCGHCziInternalziExceptionziTypeziunderflowException"

hdInternalExceptionControlExceptionBaseNonTermination :: JStgExpr
hdInternalExceptionControlExceptionBaseNonTermination :: JStgExpr
hdInternalExceptionControlExceptionBaseNonTermination = FastString -> JStgExpr
global FastString
"h$ghczminternalZCGHCziInternalziControlziExceptionziBasezinonTermination"

hdGhcInternalIOHandleFlush :: JStgExpr
hdGhcInternalIOHandleFlush :: JStgExpr
hdGhcInternalIOHandleFlush = FastString -> JStgExpr
global FastString
"h$ghczminternalZCGHCziInternalziIOziHandlezihFlush"

hdGhcInternalIOHandleFDStdout :: JStgExpr
hdGhcInternalIOHandleFDStdout :: JStgExpr
hdGhcInternalIOHandleFDStdout = FastString -> JStgExpr
global FastString
"h$ghczminternalZCGHCziInternalziIOziHandleziFDzistdout"

hdGhcInternalJSPrimValConEntryStr :: FastString
hdGhcInternalJSPrimValConEntryStr :: FastString
hdGhcInternalJSPrimValConEntryStr = String -> FastString
fsLit String
"h$ghczminternalZCGHCziInternalziJSziPrimziJSVal_con_e"

----------------------------------------- Profiling -----------------------------
hdBuildCCSPtrStr :: FastString
hdBuildCCSPtrStr :: FastString
hdBuildCCSPtrStr = FastString
"h$buildCCSPtr"

hdClearCCSStr :: FastString
hdClearCCSStr :: FastString
hdClearCCSStr = FastString
"h$clearCCS"

hdRestoreCCSStr :: FastString
hdRestoreCCSStr :: FastString
hdRestoreCCSStr = String -> FastString
fsLit String
"h$restoreCCS"

hdSetCcsEntry :: JStgExpr
hdSetCcsEntry :: JStgExpr
hdSetCcsEntry = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdSetCcsEntryStr)

hdSetCcsEntryStr :: Ident
hdSetCcsEntryStr :: Ident
hdSetCcsEntryStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$setCcs_e"

ccStr :: FastString
ccStr :: FastString
ccStr = String -> FastString
fsLit String
"cc"
----------------------------------------- Others -------------------------------
unknown :: FastString
unknown :: FastString
unknown = String -> FastString
fsLit String
"<unknown>"

typeof :: FastString
typeof :: FastString
typeof = String -> FastString
fsLit String
"typeof"

hdRawStr :: FastString
hdRawStr :: FastString
hdRawStr = String -> FastString
fsLit String
"h$rstr"

throwStr :: FastString
throwStr :: FastString
throwStr = String -> FastString
fsLit String
"throw"

hdCheckObj :: JStgExpr
hdCheckObj :: JStgExpr
hdCheckObj = FastString -> JStgExpr
global (FastString -> JStgExpr) -> FastString -> JStgExpr
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$checkObj"

console :: JStgExpr
console :: JStgExpr
console = FastString -> JStgExpr
global FastString
consoleStr

consoleStr :: FastString
consoleStr :: FastString
consoleStr = String -> FastString
fsLit String
"console"

arguments :: JStgExpr
arguments :: JStgExpr
arguments = FastString -> JStgExpr
global FastString
argumentsStr

argumentsStr :: FastString
argumentsStr :: FastString
argumentsStr = String -> FastString
fsLit String
"arguments"

hdReportHeapOverflow :: JStgExpr
hdReportHeapOverflow :: JStgExpr
hdReportHeapOverflow = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdReportHeapOverflowStr)

hdReportHeapOverflowStr :: Ident
hdReportHeapOverflowStr :: Ident
hdReportHeapOverflowStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$reportHeapOverflow"

hdReportStackOverflow :: JStgExpr
hdReportStackOverflow :: JStgExpr
hdReportStackOverflow = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdReportStackOverflowStr)

hdReportStackOverflowStr :: Ident
hdReportStackOverflowStr :: Ident
hdReportStackOverflowStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$reportStackOverflow"

hdDumpRes :: JStgExpr
hdDumpRes :: JStgExpr
hdDumpRes = FastString -> JStgExpr
global (Ident -> FastString
identFS Ident
hdDumpResStr)

hdDumpResStr :: Ident
hdDumpResStr :: Ident
hdDumpResStr = FastString -> Ident
name (FastString -> Ident) -> FastString -> Ident
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit String
"h$dumpRes"

ghcjsArray :: FastString
ghcjsArray :: FastString
ghcjsArray = String -> FastString
fsLit String
"__ghcjsArray"

----------------------------------------- Compact -------------------------------

hdCompactSize :: FastString
hdCompactSize :: FastString
hdCompactSize = String -> FastString
fsLit String
"h$compactSize"

hdCompactAddWithSharing :: FastString
hdCompactAddWithSharing :: FastString
hdCompactAddWithSharing = String -> FastString
fsLit String
"h$compactAddWithSharing"

hdCompactAdd :: FastString
hdCompactAdd :: FastString
hdCompactAdd = String -> FastString
fsLit String
"h$compactAdd"

hdCompactFixupPointers :: FastString
hdCompactFixupPointers :: FastString
hdCompactFixupPointers = String -> FastString
fsLit String
"h$compactFixupPointers"

hdCompactAllocateBlock :: FastString
hdCompactAllocateBlock :: FastString
hdCompactAllocateBlock = String -> FastString
fsLit String
"h$compactAllocateBlock"

hdCompactGetNextBlock :: FastString
hdCompactGetNextBlock :: FastString
hdCompactGetNextBlock = String -> FastString
fsLit String
"h$compactGetNextBlock"

hdCompactGetFirstBlock :: FastString
hdCompactGetFirstBlock :: FastString
hdCompactGetFirstBlock = String -> FastString
fsLit String
"h$compactGetFirstBlock"

hdCompactContainsAny :: FastString
hdCompactContainsAny :: FastString
hdCompactContainsAny = String -> FastString
fsLit String
"h$compactContainsAny"

hdCompactContains :: FastString
hdCompactContains :: FastString
hdCompactContains = String -> FastString
fsLit String
"h$compactContains"

hdCompactResize :: FastString
hdCompactResize :: FastString
hdCompactResize = String -> FastString
fsLit String
"h$compactResize"

hdCompactNew :: FastString
hdCompactNew :: FastString
hdCompactNew = String -> FastString
fsLit String
"h$compactNew"

----------------------------------------- Stable Pointers -----------------------

hdStableNameInt :: FastString
hdStableNameInt :: FastString
hdStableNameInt = String -> FastString
fsLit String
"h$stableNameInt"

hdMakeStableName :: FastString
hdMakeStableName :: FastString
hdMakeStableName = String -> FastString
fsLit String
"h$makeStableName"

hdDeRefStablePtr :: FastString
hdDeRefStablePtr :: FastString
hdDeRefStablePtr = String -> FastString
fsLit String
"h$deRefStablePtr"

hdStablePtrBuf :: JStgExpr
hdStablePtrBuf :: JStgExpr
hdStablePtrBuf = FastString -> JStgExpr
global FastString
"h$stablePtrBuf"

hdMakeStablePtrStr :: FastString
hdMakeStablePtrStr :: FastString
hdMakeStablePtrStr = String -> FastString
fsLit String
"h$makeStablePtr"

------------------------------- Weak Pointers -----------------------------------

hdKeepAlive :: FastString
hdKeepAlive :: FastString
hdKeepAlive = String -> FastString
fsLit String
"h$keepAlive"

hdFinalizeWeak :: FastString
hdFinalizeWeak :: FastString
hdFinalizeWeak = String -> FastString
fsLit String
"h$finalizeWeak"

hdMakeWeakNoFinalizer :: FastString
hdMakeWeakNoFinalizer :: FastString
hdMakeWeakNoFinalizer = String -> FastString
fsLit String
"h$makeWeakNoFinalizer"

hdMakeWeak :: FastString
hdMakeWeak :: FastString
hdMakeWeak = String -> FastString
fsLit String
"h$makeWeak"

------------------------------- Concurrency Primitives -------------------------

hdGetThreadLabel :: FastString
hdGetThreadLabel :: FastString
hdGetThreadLabel = String -> FastString
fsLit String
"h$getThreadLabel"

hdListThreads :: FastString
hdListThreads :: FastString
hdListThreads = String -> FastString
fsLit String
"h$listThreads"

hdThreadStatus :: FastString
hdThreadStatus :: FastString
hdThreadStatus = String -> FastString
fsLit String
"h$threadStatus"

hdYield :: FastString
hdYield :: FastString
hdYield = String -> FastString
fsLit String
"h$yield"

hdKillThread :: FastString
hdKillThread :: FastString
hdKillThread = String -> FastString
fsLit String
"h$killThread"

hdFork :: FastString
hdFork :: FastString
hdFork = String -> FastString
fsLit String
"h$fork"

------------------------------- Delay/Wait Ops ---------------------------------

hdWaitWrite :: FastString
hdWaitWrite :: FastString
hdWaitWrite = String -> FastString
fsLit String
"h$waitWrite"

hdWaitRead :: FastString
hdWaitRead :: FastString
hdWaitRead = String -> FastString
fsLit String
"h$waitRead"

hdDelayThread :: FastString
hdDelayThread :: FastString
hdDelayThread = String -> FastString
fsLit String
"h$delayThread"

------------------------------- Exceptions --------------------------------------

hdCatchStr :: FastString
hdCatchStr :: FastString
hdCatchStr = String -> FastString
fsLit String
"h$catch"

hdMaskAsyncStr :: FastString
hdMaskAsyncStr :: FastString
hdMaskAsyncStr = String -> FastString
fsLit String
"h$maskAsync"

hdMaskUnintAsyncStr :: FastString
hdMaskUnintAsyncStr :: FastString
hdMaskUnintAsyncStr = String -> FastString
fsLit String
"h$maskUnintAsync"

hdUnmaskAsyncStr :: FastString
hdUnmaskAsyncStr :: FastString
hdUnmaskAsyncStr = String -> FastString
fsLit String
"h$unmaskAsync"

------------------------------- Mutable variables --------------------------------------

hdMutVarStr :: FastString
hdMutVarStr :: FastString
hdMutVarStr = String -> FastString
fsLit String
"h$MutVar"

hdAtomicModifyMutVar2Str :: FastString
hdAtomicModifyMutVar2Str :: FastString
hdAtomicModifyMutVar2Str = String -> FastString
fsLit String
"h$atomicModifyMutVar2"

hdAtomicModifyMutVarStr :: FastString
hdAtomicModifyMutVarStr :: FastString
hdAtomicModifyMutVarStr = String -> FastString
fsLit String
"h$atomicModifyMutVar"

------------------------------- Addr# ------------------------------------------

hdComparePointerStr :: FastString
hdComparePointerStr :: FastString
hdComparePointerStr = String -> FastString
fsLit String
"h$comparePointer"

------------------------------- Byte Arrays -------------------------------------

hdCompareByteArraysStr :: FastString
hdCompareByteArraysStr :: FastString
hdCompareByteArraysStr = String -> FastString
fsLit String
"h$compareByteArrays"

hdResizeMutableByteArrayStr :: FastString
hdResizeMutableByteArrayStr :: FastString
hdResizeMutableByteArrayStr = String -> FastString
fsLit String
"h$resizeMutableByteArray"

hdShrinkMutableByteArrayStr :: FastString
hdShrinkMutableByteArrayStr :: FastString
hdShrinkMutableByteArrayStr = String -> FastString
fsLit String
"h$shrinkMutableByteArray"

------------------------------- Arrays ------------------------------------------

hdCopyMutableArrayStr :: FastString
hdCopyMutableArrayStr :: FastString
hdCopyMutableArrayStr = String -> FastString
fsLit String
"h$copyMutableArray"

hdNewArrayStr :: FastString
hdNewArrayStr :: FastString
hdNewArrayStr = String -> FastString
fsLit String
"h$newArray"

hdSliceArrayStr :: FastString
hdSliceArrayStr :: FastString
hdSliceArrayStr = String -> FastString
fsLit String
"h$sliceArray"

------------------------------ Float --------------------------------------------

hdDecodeFloatIntStr :: FastString
hdDecodeFloatIntStr :: FastString
hdDecodeFloatIntStr = String -> FastString
fsLit String
"h$decodeFloatInt"

hdCastFloatToWord32Str :: FastString
hdCastFloatToWord32Str :: FastString
hdCastFloatToWord32Str = String -> FastString
fsLit String
"h$castFloatToWord32"

hdCastWord32ToFloatStr :: FastString
hdCastWord32ToFloatStr :: FastString
hdCastWord32ToFloatStr = String -> FastString
fsLit String
"h$castWord32ToFloat"

------------------------------ Double -------------------------------------------

hdDecodeDouble2IntStr :: FastString
hdDecodeDouble2IntStr :: FastString
hdDecodeDouble2IntStr = String -> FastString
fsLit String
"h$decodeDouble2Int"

hdDecodeDoubleInt64Str :: FastString
hdDecodeDoubleInt64Str :: FastString
hdDecodeDoubleInt64Str = String -> FastString
fsLit String
"h$decodeDoubleInt64"

hdCastDoubleToWord64Str :: FastString
hdCastDoubleToWord64Str :: FastString
hdCastDoubleToWord64Str = String -> FastString
fsLit String
"h$castDoubleToWord64"

hdCastWord64ToDoubleStr :: FastString
hdCastWord64ToDoubleStr :: FastString
hdCastWord64ToDoubleStr = String -> FastString
fsLit String
"h$castWord64ToDouble"

------------------------------ Word -------------------------------------------

hdReverseWordStr :: FastString
hdReverseWordStr :: FastString
hdReverseWordStr = String -> FastString
fsLit String
"h$reverseWord"

hdClz8Str
  , hdClz16Str
  , hdClz32Str
  , hdClz64Str
  , hdCtz8Str
  , hdCtz16Str
  , hdCtz32Str
  , hdCtz64Str :: FastString

hdClz8Str :: FastString
hdClz8Str  = String -> FastString
fsLit String
"h$clz8"
hdClz16Str :: FastString
hdClz16Str = String -> FastString
fsLit String
"h$clz16"
hdClz32Str :: FastString
hdClz32Str = String -> FastString
fsLit String
"h$clz32"
hdClz64Str :: FastString
hdClz64Str = String -> FastString
fsLit String
"h$clz64"
hdCtz8Str :: FastString
hdCtz8Str  = String -> FastString
fsLit String
"h$ctz8"
hdCtz16Str :: FastString
hdCtz16Str = String -> FastString
fsLit String
"h$ctz16"
hdCtz32Str :: FastString
hdCtz32Str = String -> FastString
fsLit String
"h$ctz32"
hdCtz64Str :: FastString
hdCtz64Str = String -> FastString
fsLit String
"h$ctz64"

hdBSwap64Str :: FastString
hdBSwap64Str :: FastString
hdBSwap64Str = FastString
"h$bswap64"

hdPExit8Str
  , hdPExit16Str
  , hdPExit32Str
  , hdPExit64Str
  , hdPDep8Str
  , hdPDep16Str
  , hdPDep32Str
  , hdPDep64Str :: FastString

hdPExit8Str :: FastString
hdPExit8Str  = String -> FastString
fsLit String
"h$pext8"
hdPExit16Str :: FastString
hdPExit16Str = String -> FastString
fsLit String
"h$pext16"
hdPExit32Str :: FastString
hdPExit32Str = String -> FastString
fsLit String
"h$pext32"
hdPExit64Str :: FastString
hdPExit64Str = String -> FastString
fsLit String
"h$pext64"
hdPDep8Str :: FastString
hdPDep8Str   = String -> FastString
fsLit String
"h$pdep8"
hdPDep16Str :: FastString
hdPDep16Str  = String -> FastString
fsLit String
"h$pdep16"
hdPDep32Str :: FastString
hdPDep32Str  = String -> FastString
fsLit String
"h$pdep32"
hdPDep64Str :: FastString
hdPDep64Str  = String -> FastString
fsLit String
"h$pdep64"

hdPopCntTab :: JStgExpr
hdPopCntTab :: JStgExpr
hdPopCntTab = FastString -> JStgExpr
global FastString
"h$popCntTab"

hdPopCnt32Str :: FastString
hdPopCnt32Str :: FastString
hdPopCnt32Str = String -> FastString
fsLit String
"h$popCnt32"

hdPopCnt64Str :: FastString
hdPopCnt64Str :: FastString
hdPopCnt64Str = String -> FastString
fsLit String
"h$popCnt64"

hdQuotRem2Word32Str :: FastString
hdQuotRem2Word32Str :: FastString
hdQuotRem2Word32Str = String -> FastString
fsLit String
"h$quotRem2Word32"

hdQuotRemWord32Str :: FastString
hdQuotRemWord32Str :: FastString
hdQuotRemWord32Str = String -> FastString
fsLit String
"h$quotRemWord32"

hdRemWord32Str :: FastString
hdRemWord32Str :: FastString
hdRemWord32Str = String -> FastString
fsLit String
"h$remWord32"

hdQuotWord32Str :: FastString
hdQuotWord32Str :: FastString
hdQuotWord32Str = String -> FastString
fsLit String
"h$quotWord32"

hdMul2Word32Str :: FastString
hdMul2Word32Str :: FastString
hdMul2Word32Str = String -> FastString
fsLit String
"h$mul2Word32"

hdMulImulStr :: FastString
hdMulImulStr :: FastString
hdMulImulStr = String -> FastString
fsLit String
"Math.imul"

hdWordAdd2 :: FastString
hdWordAdd2 :: FastString
hdWordAdd2 = String -> FastString
fsLit String
"h$wordAdd2"

hdHsPlusWord64Str :: FastString
hdHsPlusWord64Str :: FastString
hdHsPlusWord64Str = String -> FastString
fsLit String
"h$hs_plusWord64"

hdHsMinusWord64Str :: FastString
hdHsMinusWord64Str :: FastString
hdHsMinusWord64Str = String -> FastString
fsLit String
"h$hs_minusWord64"

hdHsTimesWord64Str :: FastString
hdHsTimesWord64Str :: FastString
hdHsTimesWord64Str = String -> FastString
fsLit String
"h$hs_timesWord64"

hdHsQuotWord64Str :: FastString
hdHsQuotWord64Str :: FastString
hdHsQuotWord64Str = String -> FastString
fsLit String
"h$hs_quotWord64"

hdHsRemWord64Str :: FastString
hdHsRemWord64Str :: FastString
hdHsRemWord64Str = String -> FastString
fsLit String
"h$hs_remWord64"

hdHsUncheckedShiftRWord64Str :: FastString
hdHsUncheckedShiftRWord64Str :: FastString
hdHsUncheckedShiftRWord64Str = String -> FastString
fsLit String
"h$hs_uncheckedShiftRWord64"

hdHsUncheckedShiftLWord64Str :: FastString
hdHsUncheckedShiftLWord64Str :: FastString
hdHsUncheckedShiftLWord64Str = String -> FastString
fsLit String
"h$hs_uncheckedShiftLWord64"

hdHsPlusInt64Str :: FastString
hdHsPlusInt64Str :: FastString
hdHsPlusInt64Str = String -> FastString
fsLit String
"h$hs_plusInt64"

hdHsMinusInt64Str :: FastString
hdHsMinusInt64Str :: FastString
hdHsMinusInt64Str = String -> FastString
fsLit String
"h$hs_minusInt64"

hdHsTimesInt64Str :: FastString
hdHsTimesInt64Str :: FastString
hdHsTimesInt64Str = String -> FastString
fsLit String
"h$hs_timesInt64"

hdHsQuotInt64Str :: FastString
hdHsQuotInt64Str :: FastString
hdHsQuotInt64Str = String -> FastString
fsLit String
"h$hs_quotInt64"

hdHsRemInt64Str :: FastString
hdHsRemInt64Str :: FastString
hdHsRemInt64Str = String -> FastString
fsLit String
"h$hs_remInt64"

hdHsUncheckedShiftLLInt64Str :: FastString
hdHsUncheckedShiftLLInt64Str :: FastString
hdHsUncheckedShiftLLInt64Str = String -> FastString
fsLit String
"h$hs_uncheckedShiftLLInt64"

hdHsUncheckedShiftRAInt64Str :: FastString
hdHsUncheckedShiftRAInt64Str :: FastString
hdHsUncheckedShiftRAInt64Str = String -> FastString
fsLit String
"h$hs_uncheckedShiftRAInt64"

hdHsUncheckedShiftRLInt64Str :: FastString
hdHsUncheckedShiftRLInt64Str :: FastString
hdHsUncheckedShiftRLInt64Str = String -> FastString
fsLit String
"h$hs_uncheckedShiftRLInt64"

hdHsTimesInt2Str :: FastString
hdHsTimesInt2Str :: FastString
hdHsTimesInt2Str = String -> FastString
fsLit String
"h$hs_timesInt2"

------------------------------ Linker -------------------------------------------

hdEncodeModifiedUtf8Str :: FastString
hdEncodeModifiedUtf8Str :: FastString
hdEncodeModifiedUtf8Str = String -> FastString
fsLit String
"h$encodeModifiedUtf8"

hdRawStringDataStr :: FastString
hdRawStringDataStr :: FastString
hdRawStringDataStr = String -> FastString
fsLit String
"h$rawStringData"

hdPStr :: FastString
hdPStr :: FastString
hdPStr = String -> FastString
fsLit String
"h$p"

hdDStr :: FastString
hdDStr :: FastString
hdDStr = String -> FastString
fsLit String
"h$d"

hdDiStr :: FastString
hdDiStr :: FastString
hdDiStr = String -> FastString
fsLit String
"h$di"

hdStcStr :: FastString
hdStcStr :: FastString
hdStcStr = String -> FastString
fsLit String
"h$stc"

hdStlStr :: FastString
hdStlStr :: FastString
hdStlStr = String -> FastString
fsLit String
"h$stl"

hdStiStr :: FastString
hdStiStr :: FastString
hdStiStr = String -> FastString
fsLit String
"h$sti"

hdStrStr :: FastString
hdStrStr :: FastString
hdStrStr = String -> FastString
fsLit String
"h$str"