Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data K
- data GClosure comb
- newtype Closure where
- Closure { }
- pattern DataC :: Reference -> PackedTag -> SegList -> Closure
- pattern PApV :: CombIx -> RCombInfo Val -> SegList -> Closure
- pattern CapV :: K -> Int -> SegList -> Closure
- pattern PAp :: CombIx -> GCombInfo (RComb Val) -> Seg -> Closure
- pattern Enum :: Reference -> PackedTag -> Closure
- pattern Data1 :: Reference -> PackedTag -> Val -> Closure
- pattern Data2 :: Reference -> PackedTag -> Val -> Val -> Closure
- pattern DataG :: Reference -> PackedTag -> Seg -> Closure
- pattern Captured :: K -> Int -> Seg -> Closure
- pattern Foreign :: Foreign -> Closure
- pattern BlackHole :: Closure
- pattern UnboxedTypeTag :: UnboxedTypeTag -> Closure
- data UnboxedTypeTag
- unboxedTypeTagToInt :: UnboxedTypeTag -> Int
- unboxedTypeTagFromInt :: HasCallStack => Int -> UnboxedTypeTag
- type IxClosure = GClosure CombIx
- newtype Callback = Hook (XStack -> IO ())
- data Augment
- data Dump
- data Stack = Stack {}
- type XStack = (# Int#, Int#, Int#, MutableByteArray# (PrimState IO), MutableArray# (PrimState IO) Closure #)
- pattern XStack :: Int# -> Int# -> Int# -> MutableByteArray# RealWorld -> MutableArray# RealWorld Closure -> Stack
- packXStack :: XStack -> Stack
- unpackXStack :: Stack -> XStack
- xStackIOToIO :: IOXStack -> IO Stack
- stackIOToIOX :: IO Stack -> IOXStack
- type IOXStack = State# RealWorld -> (# State# RealWorld, XStack #)
- $sel:apX:XStack :: Stack -> Int#
- $sel:fpX:XStack :: Stack -> Int#
- $sel:spX:XStack :: Stack -> Int#
- $sel:ustkX:XStack :: Stack -> MutableByteArray# RealWorld
- $sel:bstkX:XStack :: Stack -> MutableArray# RealWorld Closure
- type Off = Int
- type SZ = Int
- type FP = Int
- type Seg = (USeg, BSeg)
- type USeg = ByteArray
- type BSeg = Array Closure
- type SegList = [Val]
- data Val where
- emptyVal :: Val
- falseVal :: Val
- trueVal :: Val
- boxedVal :: BVal -> Val
- type USeq = Seq Val
- traceK :: Reference -> K -> [(Reference, Int)]
- frameDataSize :: K -> Int
- marshalToForeign :: HasCallStack => Closure -> Foreign
- unull :: USeg
- bnull :: BSeg
- nullSeg :: Seg
- peekD :: Stack -> IO Double
- peekOffD :: Stack -> Int -> IO Double
- peekC :: Stack -> IO Char
- peekOffC :: Stack -> Int -> IO Char
- poke :: DebugCallStack => Stack -> Val -> IO ()
- pokeD :: Stack -> Double -> IO ()
- pokeOffD :: Stack -> Int -> Double -> IO ()
- pokeC :: Stack -> Char -> IO ()
- pokeOffC :: Stack -> Int -> Char -> IO ()
- pokeBool :: DebugCallStack => Stack -> Bool -> IO ()
- pokeTag :: DebugCallStack => Stack -> Int -> IO ()
- peekTag :: DebugCallStack => Stack -> IO Int
- peekTagOff :: DebugCallStack => Stack -> Off -> IO Int
- peekI :: DebugCallStack => Stack -> IO Int
- peekOffI :: DebugCallStack => Stack -> Off -> IO Int
- peekN :: Stack -> IO Word64
- peekOffN :: Stack -> Int -> IO Word64
- pokeN :: Stack -> Word64 -> IO ()
- pokeOffN :: Stack -> Int -> Word64 -> IO ()
- pokeI :: Stack -> Int -> IO ()
- pokeOffI :: Stack -> Int -> Int -> IO ()
- pokeByte :: Stack -> Word8 -> IO ()
- peekBi :: BuiltinForeign b => Stack -> IO b
- peekOffBi :: BuiltinForeign b => Stack -> Int -> IO b
- pokeBi :: BuiltinForeign b => Stack -> b -> IO ()
- pokeOffBi :: BuiltinForeign b => Stack -> Int -> b -> IO ()
- peekBool :: Stack -> IO Bool
- peekOffBool :: Stack -> Int -> IO Bool
- peekOffS :: Stack -> Int -> IO USeq
- pokeS :: Stack -> USeq -> IO ()
- pokeOffS :: Stack -> Int -> USeq -> IO ()
- frameView :: Stack -> IO ()
- scount :: Seg -> Int
- closureTermRefs :: Monoid m => (Reference -> m) -> Closure -> m
- dumpAP :: Int -> Int -> Int -> Dump -> Int
- dumpFP :: Int -> Int -> Dump -> Int
- alloc :: IO Stack
- peek :: DebugCallStack => Stack -> IO Val
- upeek :: DebugCallStack => Stack -> IO UVal
- bpeek :: DebugCallStack => Stack -> IO BVal
- peekOff :: DebugCallStack => Stack -> Off -> IO Val
- upeekOff :: DebugCallStack => Stack -> Off -> IO UVal
- bpeekOff :: DebugCallStack => Stack -> Off -> IO BVal
- bpoke :: DebugCallStack => Stack -> BVal -> IO ()
- bpokeOff :: DebugCallStack => Stack -> Off -> BVal -> IO ()
- pokeOff :: DebugCallStack => Stack -> Off -> Val -> IO ()
- upokeT :: DebugCallStack => Stack -> UVal -> BVal -> IO ()
- upokeOffT :: DebugCallStack => Stack -> Off -> UVal -> BVal -> IO ()
- unsafePokeIasN :: DebugCallStack => Stack -> Int -> IO ()
- bump :: Stack -> IO Stack
- bumpn :: Stack -> SZ -> IO Stack
- grab :: Stack -> SZ -> IO (Seg, Stack)
- ensure :: Stack -> SZ -> IO Stack
- duplicate :: Stack -> IO Stack
- discardFrame :: Stack -> IO Stack
- saveFrame :: Stack -> IO (Stack, SZ, SZ)
- saveArgs :: Stack -> IO (Stack, SZ)
- restoreFrame :: Stack -> SZ -> SZ -> IO Stack
- prepareArgs :: Stack -> Args' -> IO Stack
- acceptArgs :: Stack -> Int -> IO Stack
- frameArgs :: Stack -> IO Stack
- augSeg :: Augment -> Stack -> Seg -> Maybe Args' -> IO Seg
- dumpSeg :: Stack -> Seg -> Dump -> IO Stack
- adjustArgs :: Stack -> SZ -> IO Stack
- fsize :: Stack -> SZ
- asize :: Stack -> SZ
- natTypeTag :: Closure
- intTypeTag :: Closure
- charTypeTag :: Closure
- floatTypeTag :: Closure
- hasNoAllocations :: Name -> Obligation
Documentation
GPAp !CombIx !(GCombInfo comb) !Seg | |
GEnum !Reference !PackedTag | |
GData1 !Reference !PackedTag !Val | |
GData2 !Reference !PackedTag !Val !Val | |
GDataG !Reference !PackedTag !Seg | |
GCaptured !K !Int !Seg | |
GForeign !Foreign | |
GUnboxedTypeTag !UnboxedTypeTag | |
GBlackHole |
Instances
Foldable GClosure Source # | |
Defined in Unison.Runtime.Stack fold :: Monoid m => GClosure m -> m # foldMap :: Monoid m => (a -> m) -> GClosure a -> m # foldMap' :: Monoid m => (a -> m) -> GClosure a -> m # foldr :: (a -> b -> b) -> b -> GClosure a -> b # foldr' :: (a -> b -> b) -> b -> GClosure a -> b # foldl :: (b -> a -> b) -> b -> GClosure a -> b # foldl' :: (b -> a -> b) -> b -> GClosure a -> b # foldr1 :: (a -> a -> a) -> GClosure a -> a # foldl1 :: (a -> a -> a) -> GClosure a -> a # elem :: Eq a => a -> GClosure a -> Bool # maximum :: Ord a => GClosure a -> a # minimum :: Ord a => GClosure a -> a # | |
Traversable GClosure Source # | |
Functor GClosure Source # | |
Show comb => Show (GClosure comb) Source # | |
pattern DataC :: Reference -> PackedTag -> SegList -> Closure | |
pattern PApV :: CombIx -> RCombInfo Val -> SegList -> Closure | |
pattern CapV :: K -> Int -> SegList -> Closure | |
pattern PAp :: CombIx -> GCombInfo (RComb Val) -> Seg -> Closure | |
pattern Enum :: Reference -> PackedTag -> Closure | |
pattern Data1 :: Reference -> PackedTag -> Val -> Closure | |
pattern Data2 :: Reference -> PackedTag -> Val -> Val -> Closure | |
pattern DataG :: Reference -> PackedTag -> Seg -> Closure | |
pattern Captured :: K -> Int -> Seg -> Closure | |
pattern Foreign :: Foreign -> Closure | |
pattern BlackHole :: Closure | |
pattern UnboxedTypeTag :: UnboxedTypeTag -> Closure |
data UnboxedTypeTag Source #
Instances
Show UnboxedTypeTag Source # | |
Defined in Unison.Runtime.Stack showsPrec :: Int -> UnboxedTypeTag -> ShowS # show :: UnboxedTypeTag -> String # showList :: [UnboxedTypeTag] -> ShowS # | |
Eq UnboxedTypeTag Source # | |
Defined in Unison.Runtime.Stack (==) :: UnboxedTypeTag -> UnboxedTypeTag -> Bool # (/=) :: UnboxedTypeTag -> UnboxedTypeTag -> Bool # | |
Ord UnboxedTypeTag Source # | |
Defined in Unison.Runtime.Stack compare :: UnboxedTypeTag -> UnboxedTypeTag -> Ordering # (<) :: UnboxedTypeTag -> UnboxedTypeTag -> Bool # (<=) :: UnboxedTypeTag -> UnboxedTypeTag -> Bool # (>) :: UnboxedTypeTag -> UnboxedTypeTag -> Bool # (>=) :: UnboxedTypeTag -> UnboxedTypeTag -> Bool # max :: UnboxedTypeTag -> UnboxedTypeTag -> UnboxedTypeTag # min :: UnboxedTypeTag -> UnboxedTypeTag -> UnboxedTypeTag # |
type XStack = (# Int#, Int#, Int#, MutableByteArray# (PrimState IO), MutableArray# (PrimState IO) Closure #) Source #
pattern XStack :: Int# -> Int# -> Int# -> MutableByteArray# RealWorld -> MutableArray# RealWorld Closure -> Stack Source #
packXStack :: XStack -> Stack Source #
unpackXStack :: Stack -> XStack Source #
$sel:apX:XStack :: Stack -> Int# Source #
$sel:fpX:XStack :: Stack -> Int# Source #
$sel:spX:XStack :: Stack -> Int# Source #
A runtime value, which is either a boxed or unboxed value, but we may not know which.
Val | |
|
pattern CharVal :: Char -> Val | |
pattern NatVal :: Word64 -> Val | |
pattern DoubleVal :: Double -> Val | |
pattern IntVal :: Int -> Val | |
pattern BoolVal :: Bool -> Val | |
pattern UnboxedVal :: Int -> UnboxedTypeTag -> Val | |
pattern BoxedVal :: Closure -> Val | Matches a Val which is known to be boxed, and returns the closure portion. |
frameDataSize :: K -> Int Source #
marshalToForeign :: HasCallStack => Closure -> Foreign Source #
pokeTag :: DebugCallStack => Stack -> Int -> IO () Source #
Store an unboxed tag to later match on. Often used to indicate the constructor of a data type that's been unpacked onto the stack, or some tag we're about to branch on.
pokeI :: Stack -> Int -> IO () Source #
Note: This is for poking an unboxed value that has the UNISON type int
, not just any unboxed data.
bpoke :: DebugCallStack => Stack -> BVal -> IO () Source #
Store a boxed value. We don't bother nulling out the unboxed stack, it's extra work and there's nothing to garbage collect.
unsafePokeIasN :: DebugCallStack => Stack -> Int -> IO () Source #
Sometimes we get back an int from a foreign call which we want to use as a Nat. If we know it's positive and smaller than 2^63 then we can safely store the Int directly as a Nat without checks.
Unboxed type tags
natTypeTag :: Closure Source #
intTypeTag :: Closure Source #
hasNoAllocations :: Name -> Obligation Source #