Safe Haskell | None |
---|---|
Language | Haskell2010 |
Module, containing type classes for operating with Michelson values in the context of polymorphic stack type operations.
Synopsis
- class EDivOp (n :: T) (m :: T) where
- class MemOp (c :: T) where
- class MapOp (c :: T) where
- class IterOp (c :: T) where
- class SizeOp (c :: T) where
- class GetOp (c :: T) where
- class UpdOp (c :: T) where
- class SliceOp (c :: T) where
- class ConcatOp (c :: T) where
- evalConcat :: Value' instr c -> Value' instr c -> Value' instr c
- evalConcat' :: [Value' instr c] -> Value' instr c
- divMich :: Integral a => a -> a -> a
- modMich :: Integral a => a -> a -> a
Documentation
class EDivOp (n :: T) (m :: T) where Source #
convergeEDiv :: Notes n -> Notes m -> Either AnnConvergeError (Notes ('TOption ('TPair (EDivOpRes n m) (EModOpRes n m)))) Source #
Converge the notes of given operands.
evalEDivOp :: Value' instr n -> Value' instr m -> Value' instr ('TOption ('TPair (EDivOpRes n m) (EModOpRes n m))) Source #
Instances
class MapOp (c :: T) where Source #
mapOpToList :: Value' instr c -> [Value' instr (MapOpInp c)] Source #
mapOpFromList :: KnownT b => Value' instr c -> [Value' instr b] -> Value' instr (MapOpRes c b) Source #
Instances
MapOp ('TList e) Source # | |
Defined in Michelson.Typed.Polymorphic | |
MapOp ('TMap k v) Source # | |
Defined in Michelson.Typed.Polymorphic |
class GetOp (c :: T) where Source #
evalGet :: Value' instr (GetOpKey c) -> Value' instr c -> Maybe (Value' instr (GetOpVal c)) Source #
class UpdOp (c :: T) where Source #
evalUpd :: Value' instr (UpdOpKey c) -> Value' instr (UpdOpParams c) -> Value' instr c -> Value' instr c Source #
Instances
UpdOp ('TSet a) Source # | |
Defined in Michelson.Typed.Polymorphic | |
UpdOp ('TMap k v) Source # | |
Defined in Michelson.Typed.Polymorphic | |
UpdOp ('TBigMap k v) Source # | |
Defined in Michelson.Typed.Polymorphic |
class ConcatOp (c :: T) where Source #
evalConcat :: Value' instr c -> Value' instr c -> Value' instr c Source #
evalConcat' :: [Value' instr c] -> Value' instr c Source #