| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Language.SSVM.Types
Synopsis
- type DArray = Array Int StackItem
- data StackItem
- showType :: StackItem -> String
- showItem :: StackItem -> String
- showPrint :: StackItem -> String
- showCode :: Code -> String
- type Stack = [StackItem]
- type Marks = Map String Int
- showMarks :: Marks -> String
- data Code = Code {}
- class (Data a, Typeable a) => StackType a where
- data Instruction
- data Definition = Definition Int Stack
- data VMState = VMState {}
- emptyVMState :: VMState
- type VM a = StateT VMState IO a
Documentation
Stack item
Constructors
| SInteger Integer | |
| SString String | |
| SInstruction Instruction | |
| SArray DArray | |
| Quote StackItem | 
Instances
| Eq StackItem Source # | |
| Data StackItem Source # | |
| Defined in Language.SSVM.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StackItem -> c StackItem # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StackItem # toConstr :: StackItem -> Constr # dataTypeOf :: StackItem -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StackItem) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StackItem) # gmapT :: (forall b. Data b => b -> b) -> StackItem -> StackItem # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StackItem -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StackItem -> r # gmapQ :: (forall d. Data d => d -> u) -> StackItem -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StackItem -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StackItem -> m StackItem # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StackItem -> m StackItem # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StackItem -> m StackItem # | |
| Show StackItem Source # | |
| StackType DArray Source # | |
VM code
Instances
| Eq Code Source # | |
| Data Code Source # | |
| Defined in Language.SSVM.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Code -> c Code # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Code # dataTypeOf :: Code -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Code) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Code) # gmapT :: (forall b. Data b => b -> b) -> Code -> Code # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Code -> r # gmapQ :: (forall d. Data d => d -> u) -> Code -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Code -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Code -> m Code # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Code -> m Code # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Code -> m Code # | |
| Show Code Source # | |
| Semigroup Code Source # | |
| Monoid Code Source # | |
data Instruction Source #
VM instructions
Constructors
| NOP | Do nothing | 
| PUSH StackItem | |
| DROP | |
| DUP | |
| SWAP | |
| OVER | |
| PRINTALL | |
| ADD | |
| MUL | |
| DIV | |
| REM | |
| SUB | |
| NEG | |
| ABS | |
| CMP | |
| DEFINE | |
| COLON | |
| CALL String | Call named user-defined word | 
| VARIABLE | |
| ASSIGN | |
| READ | |
| INPUT | |
| MARK | |
| GETMARK String | |
| GOTO | |
| JZ | |
| JNZ | |
| JGT | |
| JLT | |
| JGE | |
| JLE | |
| ARRAY | |
| READ_ARRAY | |
| ASSIGN_ARRAY | 
Instances
| Eq Instruction Source # | |
| Defined in Language.SSVM.Types | |
| Data Instruction Source # | |
| Defined in Language.SSVM.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Instruction -> c Instruction # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Instruction # toConstr :: Instruction -> Constr # dataTypeOf :: Instruction -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Instruction) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Instruction) # gmapT :: (forall b. Data b => b -> b) -> Instruction -> Instruction # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Instruction -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Instruction -> r # gmapQ :: (forall d. Data d => d -> u) -> Instruction -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Instruction -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction # | |
| Show Instruction Source # | |
| Defined in Language.SSVM.Types Methods showsPrec :: Int -> Instruction -> ShowS # show :: Instruction -> String # showList :: [Instruction] -> ShowS # | |
| StackType Instruction Source # | |
| Defined in Language.SSVM.Types | |
data Definition Source #
Word definition
Constructors
| Definition Int Stack | 
Instances
| Eq Definition Source # | |
| Defined in Language.SSVM.Types | |
| Show Definition Source # | |
| Defined in Language.SSVM.Types Methods showsPrec :: Int -> Definition -> ShowS # show :: Definition -> String # showList :: [Definition] -> ShowS # | |
VM state
Constructors
| VMState | |
| Fields 
 | |
emptyVMState :: VMState Source #
Starting VM state