curly-system-0.3.3: System-specific code generation libraries for the Curly compiler

Safe HaskellNone
LanguageHaskell2010

Curly.System.Base

Synopsis

Documentation

newtype RegID Source #

Constructors

RegID Int 

Instances

data Value Source #

Instances

class IsLocus t where Source #

Minimal complete definition

toLocus

Methods

toLocus :: t -> Locus Source #

Instances

newtype V t Source #

Constructors

V t 

Instances

IsLocus l => IsValue (V l) Source # 

Methods

toValue :: V l -> Value Source #

(!%) :: IsLocus l => l -> (OffsetStride, Offset) -> Locus infixl 8 Source #

(!) :: IsLocus l => l -> Offset -> Locus infixl 8 Source #

newtype ASMT s m a Source #

Constructors

ASMT (StateT (Runtime s) (CounterT BinaryCode BinAddress m) a) 

Instances

Monad m => MonadCounter BinaryCode BinAddress (ASMT s m) Source # 
MonadReader r m => MonadReader r (ASMT s m) Source # 

Methods

ask :: ASMT s m r #

local :: (r -> r) -> ASMT s m a -> ASMT s m a #

Monad m => MonadWriter BinaryCode (ASMT s m) Source # 

Methods

tell :: BinaryCode -> ASMT s m () #

listen :: ASMT s m a -> ASMT s m (BinaryCode, a) #

censor :: ASMT s m (a, BinaryCode -> BinaryCode) -> ASMT s m a #

MonadTrans (ASMT s) Source # 

Methods

lift :: Monad m => m a -> ASMT s m a #

Monad m => MonadState (Runtime s) (ASMT s m) Source # 

Methods

get :: ASMT s m (Runtime s) #

put :: Runtime s -> ASMT s m () #

modify :: (Runtime s -> Runtime s) -> ASMT s m () #

Functor m => Functor (ASMT s m) Source # 

Methods

map :: (a -> b) -> ASMT s m a -> ASMT s m b #

Monad m => SemiApplicative (ASMT s m) Source # 

Methods

(<*>) :: ASMT s m (a -> b) -> ASMT s m a -> ASMT s m b #

Monad m => Applicative (ASMT s m) Source # 
Monad m => Monad (ASMT s m) Source # 

Methods

join :: ASMT s m (ASMT s m a) -> ASMT s m a #

(>>=) :: ASMT s m a -> (a -> ASMT s m b) -> ASMT s m b #

MonadFix m => MonadFix (ASMT s m) Source # 

Methods

mfix :: (a -> ASMT s m a) -> ASMT s m a #

Unit m => Unit (ASMT s m) Source # 

Methods

pure :: a -> ASMT s m a #

MonadFix m => MonadASM (ASMT s m) s Source # 

class (MonadCounter BinaryCode BinAddress m, MonadFix m, MonadState (Runtime s) m) => MonadASM m s | m -> s Source #

Instances

MonadFix m => MonadASM (ASMT s m) s Source # 

runASMT :: MonadFix m => Runtime s -> ASMT s m a -> m (a, Runtime s, BinaryCode) Source #

align :: MonadASM m s => Int -> Word8 -> m () Source #

reserve :: MonadASM m s => Int -> Word8 -> m () Source #

inSection :: MonadASM m s => Section -> m a -> m a Source #

rawProgram :: MonadASM m s => [Section] -> m b -> m b Source #

type INSTR0 = forall m s. MonadASM m s => m () Source #

type INSTR1 a = forall m s. MonadASM m s => a -> m () Source #

type INSTR2 a b = forall m s. MonadASM m s => a -> b -> m () Source #

type INSTR3 a b c = forall m s. MonadASM m s => a -> b -> c -> m () Source #

type INSTR4 a b c d = forall m s. MonadASM m s => a -> b -> c -> d -> m () Source #

type INSTR5 a b c d e = forall m s. MonadASM m s => a -> b -> c -> d -> e -> m () Source #

type BUILTIN_INSTR = forall m s. MonadASM m s => Builtin -> Maybe (m (BinAddress, Value)) Source #

type CCALL = forall m s. MonadASM m s => Maybe Locus -> BinAddress -> [m Value] -> m () Source #

type ALLOC_BYTES = forall m s. MonadASM m s => Locus -> Value -> m () Source #

getOrDefine :: (?sys :: VonNeumannMachine, MonadASM m s) => Section -> String -> m () -> m BinAddress Source #

builtinArgs :: (?sys :: VonNeumannMachine, MonadASM m s) => Int -> m [Locus] Source #

(<--) :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsValue v) => l -> v -> m () infix 3 Source #

setThunkVal :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsValue v, IsValue v') => l -> v -> v' -> m () Source #

(<==) :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsLocus l') => l -> l' -> m () infix 3 Source #

ifcmp_hint :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v, IsValue v') => Maybe Bool -> (Bool, Ordering) -> v -> v' -> m () -> m () Source #

itecmp_hint :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v, IsValue v') => Maybe Bool -> (Bool, Ordering) -> v -> v' -> m () -> m () -> m () Source #

ifcmp :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v, IsValue v') => (Bool, Ordering) -> v -> v' -> m () -> m () Source #

itecmp :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v, IsValue v') => (Bool, Ordering) -> v -> v' -> m () -> m () -> m () Source #

jmp :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v) => v -> m () Source #

call :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v) => v -> m () Source #

ret :: (?sys :: VonNeumannMachine, MonadASM m s) => m () Source #

tailCall :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus v, IsValue v) => v -> m () Source #

load :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l) => l -> BinAddress -> m () Source #

store :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v) => BinAddress -> v -> m () Source #

add :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsValue v) => l -> v -> m () Source #

sub :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsValue v) => l -> v -> m () Source #

ccall :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l) => Maybe l -> BinAddress -> [m Value] -> m () Source #

ccall0 :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l) => Maybe l -> BinAddress -> m () Source #

ccall1 :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsValue v) => Maybe l -> BinAddress -> m v -> m () Source #

ccall2 :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsValue v, IsValue v') => Maybe l -> BinAddress -> m v -> m v' -> m () Source #

ccall3 :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l, IsValue v, IsValue v', IsValue v'') => Maybe l -> BinAddress -> m v -> m v' -> m v'' -> m () Source #

wordSize :: (?sys :: VonNeumannMachine, Num n) => n Source #

pageSize :: (?sys :: VonNeumannMachine, Num n) => n Source #

pushThunk :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l) => l -> m () Source #

popThunk :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l) => l -> m () Source #

callThunk :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v) => v -> m () Source #

callWithStackArgs :: (?sys :: VonNeumannMachine, MonadASM m s, IsValue v, IsValue v') => v -> [m v'] -> m () Source #

destReg :: (?sys :: VonNeumannMachine) => RegID Source #

The destination register, a pointer to the thunk where the result of the current computation should be stored.

thisReg :: (?sys :: VonNeumannMachine) => RegID Source #

The object register, a pointer to the thunk that is currently being evaluated.

allocBytes :: (?sysHooks :: SystemHooks, IsLocus l, IsValue v, MonadASM m s) => l -> v -> m () Source #

pushing :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l) => [l] -> m a -> m a Source #

rotateL :: (?sys :: VonNeumannMachine, MonadASM m s, IsLocus l) => [l] -> m () Source #

setDest :: (?sys :: VonNeumannMachine, IsValue v, IsValue v', MonadASM m s) => v -> v' -> m () Source #

newtype Standalone Source #

Constructors

Standalone 

Fields