ghc-9.6.1: The GHC API
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file LICENSE)
MaintainerJeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Sylvain Henry <sylvain.henry@iohk.io> Josh Meredith <josh.meredith@iohk.io>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.StgToJS.Stack

Contents

Description

Utilities and wrappers for Stack manipulation in JS Land.

In general, functions suffixed with a tick do the actual work, functions suffixed with an I are identical to the non-I versions but work on Idents

The stack in JS land is held in the special JS array 'h$stack' and the stack pointer is held in 'h$sp'. The top of the stack thus exists at 'h$stack[h$sp]'. h$stack[h$sp + i] where i > 0, moves deeper into the stack into older entries, whereas h$stack[h$sp - i] moves towards the top of the stack.

The stack layout algorithm is slightly peculiar. It makes an effort to remember recently popped things so that if these values need to be pushed then they can be quickly. The implementation for this is storing these values above the stack pointer, and the pushing will skip slots that we know we will use and fill in slots marked as unknown. Thus, you may find that our push and pop functions do some non-traditional stack manipulation such as adding slots in pop or removing slots in push.

Synopsis

Documentation

resetSlots :: G a -> G a Source #

Run the action, m, with no stack info

isolateSlots :: G a -> G a Source #

run the action, m, with current stack info, but don't let modifications propagate

setSlots :: [StackSlot] -> G () Source #

overwrite our stack knowledge

getSlots :: G [StackSlot] Source #

retrieve our current stack knowledge

addSlots :: [StackSlot] -> G () Source #

add knowledge about the stack slots

dropSlots :: Int -> G () Source #

drop n slots from our stack knowledge

addUnknownSlots :: Int -> G () Source #

add n unknown slots to our stack knowledge

adjSpN :: Int -> G JStat Source #

Shrink the stack and stack pointer. NB: This function is unsafe when the input n, is negative. This function wraps around adjSpN which actually performs the work.

adjSpN' :: Int -> JStat Source #

Shrink the stack pointer by n. The stack grows downward so substract

adjSp' :: Int -> JStat Source #

Grow the stack pointer by n without modifying the stack depth. The stack is just a JS array so we add to grow (instead of the traditional subtract)

adjSp :: Int -> G JStat Source #

Wrapper which adjusts the stack pointer and modifies the stack depth tracked in G. See also adjSp' which actually does the stack pointer manipulation.

pushNN :: Array Integer Ident Source #

Partial Push functions. Like pushN except these push functions skip slots. For example, function h$pp33(x1, x2) { h$sp += 6; h$stack[(h$sp - 5)] = x1; h$stack[(h$sp - 0)] = x2; };

The 33rd entry skips slots 1-4 to bind the top of the stack and the 6th slot. See pushOptimized and pushOptimized' for use cases.

pushNN' :: Array Integer JExpr Source #

Like pushN' but for the partial push functions

pushN' :: Array Int JExpr Source #

Convert all function symbols in pushN to global top-level functions. This is a hack which converts the function symbols to variables. This hack is caught in prettyBlock' to turn these into global functions.

pushN :: Array Int Ident Source #

A constant array that holds global function symbols which do N pushes onto the stack. For example: function h$p1(x1) { ++h$sp; h$stack[(h$sp - 0)] = x1; }; function h$p2(x1, x2) { h$sp += 2; h$stack[(h$sp - 1)] = x1; h$stack[(h$sp - 0)] = x2; };

and so on up to 32.

pushOptimized Source #

Arguments

:: [(JExpr, Bool)]

contents of the slots, True if same value is already there

-> G JStat 

optimized push that reuses existing values on stack automatically chooses an optimized partial push (h$ppN) function when possible.

pushLneFrame :: HasDebugCallStack => Int -> ExprCtx -> G JStat Source #

push a let-no-escape frame onto the stack

popN :: Int -> G JStat Source #

Blindly pop N slots

popSkip Source #

Arguments

:: Int

number of slots to skip

-> [JExpr]

assign stack slot values to these

-> JStat 

Pop things, don't update the stack knowledge in G

popSkipI :: Int -> [(Ident, StackSlot)] -> G JStat Source #

Pop but preserve the first N slots

loadSkip :: Int -> [JExpr] -> JStat Source #

Load 'length (xs :: [JExpr])' things from the stack at offset 'n :: Int'. This function does no stack pointer manipulation, it merely indexes into the stack and loads payloads into xs.

Thunk update

updateThunk :: G JStat Source #

Wrapper around updateThunk', performs the stack manipulation before updating the Thunk.

updateThunk' :: StgToJSConfig -> JStat Source #

Update a thunk by checking StgToJSConfig. If the config inlines black holes then update inline, else make an explicit call to the black hole handler.

bhStats :: StgToJSConfig -> Bool -> JStat Source #

Generate statements to update the current node with a blackhole