morley-0.3.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.Instr

Synopsis

Documentation

nop :: s :-> s Source #

drop :: (a & s) :-> s Source #

dup :: (a & s) :-> (a & (a & s)) Source #

swap :: (a & (b & s)) :-> (b & (a & s)) Source #

push :: forall t s. (KnownValue t, NoOperation t, NoBigMap t, IsoValue t) => t -> s :-> (t & s) Source #

some :: (a & s) :-> (Maybe a & s) Source #

none :: forall a s. KnownValue a => s :-> (Maybe a & s) Source #

unit :: s :-> (() & s) Source #

ifNone :: (s :-> s') -> ((a & s) :-> s') -> (Maybe a & s) :-> s' Source #

pair :: (a & (b & s)) :-> ((a, b) & s) Source #

car :: ((a, b) & s) :-> (a & s) Source #

cdr :: ((a, b) & s) :-> (b & s) Source #

left :: forall a b s. KnownValue b => (a & s) :-> (Either a b & s) Source #

right :: forall a b s. KnownValue a => (b & s) :-> (Either a b & s) Source #

ifLeft :: ((a & s) :-> s') -> ((b & s) :-> s') -> (Either a b & s) :-> s' Source #

nil :: KnownValue p => s :-> (List p & s) Source #

cons :: (a & (List a & s)) :-> (List a & s) Source #

size :: SizeOpHs c => (c & s) :-> (Natural & s) Source #

emptySet :: KnownCValue e => s :-> (Set e & s) Source #

emptyMap :: (KnownCValue k, KnownValue v) => s :-> (Map k v & s) Source #

map :: (MapOpHs c, IsoMapOpRes c b) => ((MapOpInpHs c & s) :-> (b & s)) -> (c & s) :-> (MapOpResHs c b & s) Source #

iter :: IterOpHs c => ((IterOpElHs c & s) :-> s) -> (c & s) :-> s Source #

mem :: MemOpHs c => (MemOpKeyHs c & (c & s)) :-> (Bool & s) Source #

get :: GetOpHs c => (GetOpKeyHs c & (c & s)) :-> (Maybe (GetOpValHs c) & s) Source #

update :: UpdOpHs c => (UpdOpKeyHs c & (UpdOpParamsHs c & (c & s))) :-> (c & s) Source #

failingWhenPresent :: forall c k s v st e. (MemOpHs c, k ~ MemOpKeyHs c, KnownValue e, st ~ (k & (v & (c & s)))) => (forall s0. (k ': s0) :-> (e ': s0)) -> st :-> st Source #

Helper instruction.

Checks whether given key present in the storage and fails if it is. This instruction leaves stack intact.

updateNew :: forall c k s e. (UpdOpHs c, MemOpHs c, k ~ UpdOpKeyHs c, k ~ MemOpKeyHs c, KnownValue e) => (forall s0. (k ': s0) :-> (e ': s0)) -> (k & (UpdOpParamsHs c & (c & s))) :-> (c & s) Source #

Like update, but throw an error on attempt to overwrite existing entry.

if_ :: (s :-> s') -> (s :-> s') -> (Bool & s) :-> s' Source #

ifCons :: ((a & (List a & s)) :-> s') -> (s :-> s') -> (List a & s) :-> s' Source #

loop :: (s :-> (Bool & s)) -> (Bool & s) :-> s Source #

loopLeft :: ((a & s) :-> (Either a b & s)) -> (Either a b & s) :-> (b & s) Source #

lambda :: (KnownValue i, KnownValue o) => Lambda i o -> s :-> (Lambda i o & s) Source #

exec :: (a & (Lambda a b & s)) :-> (b & s) Source #

dip :: forall a s s'. (s :-> s') -> (a & s) :-> (a & s') Source #

failWith :: KnownValue a => (a & s) :-> t Source #

failText :: MText -> s :-> t Source #

Fail with a given message.

failTagged :: KnownValue a => MText -> (a & s) :-> t Source #

Fail with a given message and the top of the current stack.

failUsing :: (IsoValue a, KnownValue a, NoOperation a, NoBigMap a) => a -> s :-> t Source #

Fail with the given Haskell value.

failUnexpected :: HasCallStack => MText -> s :-> t Source #

Fail, providing a reference to the place in the code where this function is called.

Like error in Haskell code, this instruction is for internal errors only.

cast :: KnownValue a => (a & s) :-> (a & s) Source #

pack :: forall a s. (KnownValue a, NoOperation a, NoBigMap a) => (a & s) :-> (ByteString & s) Source #

unpack :: forall a s. (KnownValue a, NoOperation a, NoBigMap a) => (ByteString & s) :-> (Maybe a & s) Source #

concat :: ConcatOpHs c => (c & (c & s)) :-> (c & s) Source #

concat' :: ConcatOpHs c => (List c & s) :-> (c & s) Source #

slice :: SliceOpHs c => (Natural & (Natural & (c & s))) :-> (Maybe c & s) Source #

add :: ArithOpHs Add n m => (n & (m & s)) :-> (ArithResHs Add n m & s) Source #

sub :: ArithOpHs Sub n m => (n & (m & s)) :-> (ArithResHs Sub n m & s) Source #

rsub :: ArithOpHs Sub n m => (m & (n & s)) :-> (ArithResHs Sub n m & s) Source #

mul :: ArithOpHs Mul n m => (n & (m & s)) :-> (ArithResHs Mul n m & s) Source #

ediv :: EDivOpHs n m => (n & (m & s)) :-> (Maybe (EDivOpResHs n m, EModOpResHs n m) & s) Source #

lsl :: ArithOpHs Lsl n m => (n & (m & s)) :-> (ArithResHs Lsl n m & s) Source #

lsr :: ArithOpHs Lsr n m => (n & (m & s)) :-> (ArithResHs Lsr n m & s) Source #

or :: ArithOpHs Or n m => (n & (m & s)) :-> (ArithResHs Or n m & s) Source #

and :: ArithOpHs And n m => (n & (m & s)) :-> (ArithResHs And n m & s) Source #

xor :: ArithOpHs Xor n m => (n & (m & s)) :-> (ArithResHs Xor n m & s) Source #

compare :: ArithOpHs Compare n m => (n & (m & s)) :-> (ArithResHs Compare n m & s) Source #

self :: forall cp s. s :-> (ContractAddr cp & s) Source #

transferTokens :: forall p s. (KnownValue p, NoOperation p, NoBigMap p) => (p & (Mutez & (ContractAddr p & s))) :-> (Operation & s) Source #

createContract :: forall p g s. (KnownValue p, NoOperation p, KnownValue g, NoOperation g, NoBigMap p, CanHaveBigMap g) => ('[(p, g)] :-> '[(List Operation, g)]) -> (KeyHash & (Maybe KeyHash & (Bool & (Bool & (Mutez & (g & s)))))) :-> (Operation & (Address & s)) Source #

source :: s :-> (Address & s) Source #

Warning: Using source is considered a bad practice. Consider using sender instead until further investigation

class LorentzFunctor (c :: Type -> Type) where Source #

Methods

lmap :: KnownValue b => ((a ': s) :-> (b ': s)) -> (c a ': s) :-> (c b ': s) Source #

Instances
LorentzFunctor Maybe Source # 
Instance details

Defined in Lorentz.Instr

Methods

lmap :: KnownValue b => ((a ': s) :-> (b ': s)) -> (Maybe a ': s) :-> (Maybe b ': s) Source #