Safe Haskell | None |
---|---|
Language | Haskell2010 |
All the basic Expr
essions used in Indigo code.
Note: infix operators acting on structure follow a naming convention:
the last character identifies the structure type:
the preceding characters identify the action:
#
for get, lookup or from!
for set, update or to+
for insert++
for insertNew-
for remove?
for mem or elem
Synopsis
- constExpr :: NiceConstant a => a -> Expr a
- varExpr :: KnownValue a => Var a -> Expr a
- cast :: ex :~> a => ex -> Expr a
- add :: IsArithExpr exN exM Add n m => exN -> exM -> Expr (ArithResHs Add n m)
- sub :: IsArithExpr exN exM Sub n m => exN -> exM -> Expr (ArithResHs Sub n m)
- mul :: IsArithExpr exN exM Mul n m => exN -> exM -> Expr (ArithResHs Mul n m)
- div :: IsDivExpr exN exM n m => exN -> exM -> Expr (EDivOpResHs n m)
- mod :: IsModExpr exN exM n m => exN -> exM -> Expr (EModOpResHs n m)
- neg :: IsUnaryArithExpr exN Neg n => exN -> Expr (UnaryArithResHs Neg n)
- abs :: IsUnaryArithExpr exN Abs n => exN -> Expr (UnaryArithResHs Abs n)
- (+) :: IsArithExpr exN exM Add n m => exN -> exM -> Expr (ArithResHs Add n m)
- (-) :: IsArithExpr exN exM Sub n m => exN -> exM -> Expr (ArithResHs Sub n m)
- (*) :: IsArithExpr exN exM Mul n m => exN -> exM -> Expr (ArithResHs Mul n m)
- (/) :: IsDivExpr exN exM n m => exN -> exM -> Expr (EDivOpResHs n m)
- (%) :: IsModExpr exN exM n m => exN -> exM -> Expr (EModOpResHs n m)
- eq :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- neq :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- lt :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- gt :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- le :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- ge :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- (==) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- (/=) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- (<) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- (>) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- (<=) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- (>=) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool
- isNat :: ex :~> Integer => ex -> Expr (Maybe Natural)
- toInt :: ex :~> Natural => ex -> Expr Integer
- nonZero :: (ex :~> n, NonZero n, KnownValue (Maybe n)) => ex -> Expr (Maybe n)
- coerce :: forall b a ex. (Castable_ a b, KnownValue b, ex :~> a) => ex -> Expr b
- forcedCoerce :: forall b a ex. (MichelsonCoercible a b, KnownValue b, ex :~> a) => ex -> Expr b
- lsl :: IsArithExpr exN exM Lsl n m => exN -> exM -> Expr (ArithResHs Lsl n m)
- lsr :: IsArithExpr exN exM Lsr n m => exN -> exM -> Expr (ArithResHs Lsr n m)
- and :: IsArithExpr exN exM And n m => exN -> exM -> Expr (ArithResHs And n m)
- or :: IsArithExpr exN exM Or n m => exN -> exM -> Expr (ArithResHs Or n m)
- xor :: IsArithExpr exN exM Xor n m => exN -> exM -> Expr (ArithResHs Xor n m)
- not :: IsUnaryArithExpr exN Not n => exN -> Expr (UnaryArithResHs Not n)
- (<<<) :: IsArithExpr exN exM Lsl n m => exN -> exM -> Expr (ArithResHs Lsl n m)
- (>>>) :: IsArithExpr exN exM Lsr n m => exN -> exM -> Expr (ArithResHs Lsr n m)
- (&&) :: IsArithExpr exN exM And n m => exN -> exM -> Expr (ArithResHs And n m)
- (||) :: IsArithExpr exN exM Or n m => exN -> exM -> Expr (ArithResHs Or n m)
- (^) :: IsArithExpr exN exM Xor n m => exN -> exM -> Expr (ArithResHs Xor n m)
- pack :: (ex :~> a, NicePackedValue a) => ex -> Expr ByteString
- unpack :: (NiceUnpackedValue a, exb :~> ByteString) => exb -> Expr (Maybe a)
- pair :: (ex1 :~> n, ex2 :~> m, KnownValue (n, m)) => ex1 -> ex2 -> Expr (n, m)
- car :: (op :~> (n, m), KnownValue n) => op -> Expr n
- cdr :: (op :~> (n, m), KnownValue m) => op -> Expr m
- fst :: (op :~> (n, m), KnownValue n) => op -> Expr n
- snd :: (op :~> (n, m), KnownValue m) => op -> Expr m
- some :: (ex :~> t, KnownValue (Maybe t)) => ex -> Expr (Maybe t)
- none :: KnownValue t => Expr (Maybe t)
- right :: (ex :~> x, KnownValue y, KnownValue (Either y x)) => ex -> Expr (Either y x)
- left :: (ex :~> y, KnownValue x, KnownValue (Either y x)) => ex -> Expr (Either y x)
- slice :: (an :~> Natural, bn :~> Natural, IsSliceExpr ex c) => (an, bn) -> ex -> Expr (Maybe c)
- concat :: IsConcatExpr exN1 exN2 n => exN1 -> exN2 -> Expr n
- (<>) :: IsConcatExpr exN1 exN2 n => exN1 -> exN2 -> Expr n
- concatAll :: IsConcatListExpr exN n => exN -> Expr n
- nil :: KnownValue a => Expr (List a)
- cons :: (ex1 :~> a, ex2 :~> List a) => ex1 -> ex2 -> Expr (List a)
- (.:) :: (ex1 :~> a, ex2 :~> List a) => ex1 -> ex2 -> Expr (List a)
- get :: IsGetExpr exKey exMap map => exKey -> exMap -> Expr (Maybe (GetOpValHs map))
- update :: IsUpdExpr exKey exVal exMap map => (exKey, exVal) -> exMap -> Expr map
- insert :: (ExprInsertable c insParam, ex :~> c) => insParam -> ex -> Expr c
- remove :: (ExprRemovable c, exStruct :~> c, exKey :~> UpdOpKeyHs c) => exKey -> exStruct -> Expr c
- mem :: IsMemExpr exKey exN n => exKey -> exN -> Expr Bool
- size :: IsSizeExpr exN n => exN -> Expr Natural
- (#:) :: IsGetExpr exKey exMap map => exMap -> exKey -> Expr (Maybe (GetOpValHs map))
- (!:) :: IsUpdExpr exKey exVal exMap map => exMap -> (exKey, exVal) -> Expr map
- (+:) :: (ExprInsertable c exParam, exStructure :~> c) => exStructure -> exParam -> Expr c
- (-:) :: (ExprRemovable c, exStruct :~> c, exKey :~> UpdOpKeyHs c) => exStruct -> exKey -> Expr c
- (?:) :: IsMemExpr exKey exN n => exN -> exKey -> Expr Bool
- empty :: (ExprMagma c, NiceComparable (UpdOpKeyHs c), KnownValue c) => Expr c
- emptyBigMap :: (KnownValue value, NiceComparable key, KnownValue (BigMap key value)) => Expr (BigMap key value)
- emptyMap :: (KnownValue value, NiceComparable key, KnownValue (Map key value)) => Expr (Map key value)
- emptySet :: (NiceComparable key, KnownValue (Set key)) => Expr (Set key)
- uGet :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (Maybe value)
- uUpdate :: (HasUStore name key value store, exKey :~> key, exVal :~> Maybe value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store)
- uInsert :: (HasUStore name key value store, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store)
- uInsertNew :: (HasUStore name key value store, IsError err, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, err, exKey, exVal) -> Expr (UStore store)
- uDelete :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (UStore store)
- uMem :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr Bool
- (#@) :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (Maybe value)
- (!@) :: (HasUStore name key value store, exKey :~> key, exVal :~> Maybe value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store)
- (+@) :: (HasUStore name key value store, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store)
- (++@) :: (HasUStore name key value store, IsError err, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, err, exKey, exVal) -> Expr (UStore store)
- (-@) :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (UStore store)
- (?@) :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr Bool
- wrap :: (InstrWrapOneC dt name, exField :~> CtorOnlyField name dt, KnownValue dt) => Label name -> exField -> Expr dt
- unwrap :: (InstrUnwrapC dt name, exDt :~> dt, KnownValue (CtorOnlyField name dt)) => Label name -> exDt -> Expr (CtorOnlyField name dt)
- (!!) :: (HasField dt name ftype, exDt :~> dt, exFld :~> ftype) => exDt -> (Label name, exFld) -> Expr dt
- (#!) :: (HasField dt name ftype, exDt :~> dt) => exDt -> Label name -> Expr ftype
- name :: (ex :~> t, KnownValue (name :! t)) => Label name -> ex -> Expr (name :! t)
- unName :: (ex :~> (name :! t), KnownValue t) => Label name -> ex -> Expr t
- (!~) :: (ex :~> t, KnownValue (name :! t)) => ex -> Label name -> Expr (name :! t)
- (#~) :: (ex :~> (name :! t), KnownValue t) => ex -> Label name -> Expr t
- construct :: (InstrConstructC dt, KnownValue dt, RMap (ConstructorFieldTypes dt), fields ~ Rec Expr (ConstructorFieldTypes dt), RecFromTuple fields) => IsoRecTuple fields -> Expr dt
- constructRec :: (InstrConstructC dt, RMap (ConstructorFieldTypes dt), KnownValue dt) => Rec Expr (ConstructorFieldTypes dt) -> Expr dt
- contract :: (NiceParameterFull p, NoExplicitDefaultEntrypoint p, ToTAddress p addr, ToT addr ~ ToT Address, exAddr :~> addr) => exAddr -> Expr (Maybe (ContractRef p))
- self :: (NiceParameterFull p, NoExplicitDefaultEntrypoint p) => Expr (ContractRef p)
- contractAddress :: exc :~> ContractRef p => exc -> Expr Address
- contractCallingUnsafe :: (NiceParameter arg, exAddr :~> Address) => EpName -> exAddr -> Expr (Maybe (ContractRef arg))
- contractCallingString :: (NiceParameter arg, exAddr :~> Address) => MText -> exAddr -> Expr (Maybe (ContractRef arg))
- runFutureContract :: (NiceParameter p, conExpr :~> FutureContract p) => conExpr -> Expr (Maybe (ContractRef p))
- implicitAccount :: exkh :~> KeyHash => exkh -> Expr (ContractRef ())
- convertEpAddressToContract :: (NiceParameter p, epExpr :~> EpAddress) => epExpr -> Expr (Maybe (ContractRef p))
- makeView :: (KnownValue (View a r), exa :~> a, exCRef :~> ContractRef r) => exa -> exCRef -> Expr (View a r)
- makeVoid :: (KnownValue (Void_ a b), exa :~> a, exCRef :~> Lambda b b) => exa -> exCRef -> Expr (Void_ a b)
- now :: Expr Timestamp
- amount :: Expr Mutez
- sender :: Expr Address
- blake2b :: hashExpr :~> ByteString => hashExpr -> Expr ByteString
- sha256 :: hashExpr :~> ByteString => hashExpr -> Expr ByteString
- sha512 :: hashExpr :~> ByteString => hashExpr -> Expr ByteString
- hashKey :: keyExpr :~> PublicKey => keyExpr -> Expr KeyHash
- chainId :: Expr ChainId
- balance :: Expr Mutez
- checkSignature :: (pkExpr :~> PublicKey, sigExpr :~> Signature, hashExpr :~> ByteString) => pkExpr -> sigExpr -> hashExpr -> Expr Bool
Basic
constExpr :: NiceConstant a => a -> Expr a Source #
Math
add :: IsArithExpr exN exM Add n m => exN -> exM -> Expr (ArithResHs Add n m) Source #
sub :: IsArithExpr exN exM Sub n m => exN -> exM -> Expr (ArithResHs Sub n m) Source #
mul :: IsArithExpr exN exM Mul n m => exN -> exM -> Expr (ArithResHs Mul n m) Source #
neg :: IsUnaryArithExpr exN Neg n => exN -> Expr (UnaryArithResHs Neg n) Source #
abs :: IsUnaryArithExpr exN Abs n => exN -> Expr (UnaryArithResHs Abs n) Source #
(+) :: IsArithExpr exN exM Add n m => exN -> exM -> Expr (ArithResHs Add n m) infixl 6 Source #
(-) :: IsArithExpr exN exM Sub n m => exN -> exM -> Expr (ArithResHs Sub n m) infixl 6 Source #
(*) :: IsArithExpr exN exM Mul n m => exN -> exM -> Expr (ArithResHs Mul n m) infixl 7 Source #
Comparison
Conversion
coerce :: forall b a ex. (Castable_ a b, KnownValue b, ex :~> a) => ex -> Expr b Source #
Convert between types that have the same Michelson representation and an
explicit permission for that in the face of CanCastTo
constraint.
forcedCoerce :: forall b a ex. (MichelsonCoercible a b, KnownValue b, ex :~> a) => ex -> Expr b Source #
Convert between expressions of types that have the same Michelson representation.
Bits and boolean
lsl :: IsArithExpr exN exM Lsl n m => exN -> exM -> Expr (ArithResHs Lsl n m) Source #
lsr :: IsArithExpr exN exM Lsr n m => exN -> exM -> Expr (ArithResHs Lsr n m) Source #
and :: IsArithExpr exN exM And n m => exN -> exM -> Expr (ArithResHs And n m) Source #
or :: IsArithExpr exN exM Or n m => exN -> exM -> Expr (ArithResHs Or n m) Source #
xor :: IsArithExpr exN exM Xor n m => exN -> exM -> Expr (ArithResHs Xor n m) Source #
not :: IsUnaryArithExpr exN Not n => exN -> Expr (UnaryArithResHs Not n) Source #
(<<<) :: IsArithExpr exN exM Lsl n m => exN -> exM -> Expr (ArithResHs Lsl n m) infixl 8 Source #
(>>>) :: IsArithExpr exN exM Lsr n m => exN -> exM -> Expr (ArithResHs Lsr n m) infixl 8 Source #
(&&) :: IsArithExpr exN exM And n m => exN -> exM -> Expr (ArithResHs And n m) infixr 3 Source #
(||) :: IsArithExpr exN exM Or n m => exN -> exM -> Expr (ArithResHs Or n m) infixr 2 Source #
(^) :: IsArithExpr exN exM Xor n m => exN -> exM -> Expr (ArithResHs Xor n m) infixr 2 Source #
Serialization
pack :: (ex :~> a, NicePackedValue a) => ex -> Expr ByteString Source #
unpack :: (NiceUnpackedValue a, exb :~> ByteString) => exb -> Expr (Maybe a) Source #
Pairs
Maybe
Either
right :: (ex :~> x, KnownValue y, KnownValue (Either y x)) => ex -> Expr (Either y x) Source #
left :: (ex :~> y, KnownValue x, KnownValue (Either y x)) => ex -> Expr (Either y x) Source #
Bytes and string
slice :: (an :~> Natural, bn :~> Natural, IsSliceExpr ex c) => (an, bn) -> ex -> Expr (Maybe c) Source #
concat :: IsConcatExpr exN1 exN2 n => exN1 -> exN2 -> Expr n Source #
(<>) :: IsConcatExpr exN1 exN2 n => exN1 -> exN2 -> Expr n infixr 6 Source #
List
concatAll :: IsConcatListExpr exN n => exN -> Expr n Source #
Containers
remove :: (ExprRemovable c, exStruct :~> c, exKey :~> UpdOpKeyHs c) => exKey -> exStruct -> Expr c Source #
(#:) :: IsGetExpr exKey exMap map => exMap -> exKey -> Expr (Maybe (GetOpValHs map)) infixl 8 Source #
(+:) :: (ExprInsertable c exParam, exStructure :~> c) => exStructure -> exParam -> Expr c infixl 8 Source #
(-:) :: (ExprRemovable c, exStruct :~> c, exKey :~> UpdOpKeyHs c) => exStruct -> exKey -> Expr c infixl 8 Source #
empty :: (ExprMagma c, NiceComparable (UpdOpKeyHs c), KnownValue c) => Expr c Source #
emptyBigMap :: (KnownValue value, NiceComparable key, KnownValue (BigMap key value)) => Expr (BigMap key value) Source #
emptyMap :: (KnownValue value, NiceComparable key, KnownValue (Map key value)) => Expr (Map key value) Source #
emptySet :: (NiceComparable key, KnownValue (Set key)) => Expr (Set key) Source #
UStore
uGet :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (Maybe value) Source #
uUpdate :: (HasUStore name key value store, exKey :~> key, exVal :~> Maybe value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store) Source #
uInsert :: (HasUStore name key value store, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store) Source #
uInsertNew :: (HasUStore name key value store, IsError err, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, err, exKey, exVal) -> Expr (UStore store) Source #
uDelete :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (UStore store) Source #
uMem :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr Bool Source #
(#@) :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (Maybe value) infixr 8 Source #
(!@) :: (HasUStore name key value store, exKey :~> key, exVal :~> Maybe value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store) infixl 8 Source #
(+@) :: (HasUStore name key value store, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, exKey, exVal) -> Expr (UStore store) infixr 8 Source #
(++@) :: (HasUStore name key value store, IsError err, exKey :~> key, exVal :~> value, exStore :~> UStore store) => exStore -> (Label name, err, exKey, exVal) -> Expr (UStore store) infixr 8 Source #
(-@) :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr (UStore store) infixl 8 Source #
(?@) :: (HasUStore name key value store, exKey :~> key, exStore :~> UStore store) => exStore -> (Label name, exKey) -> Expr Bool infixl 8 Source #
Sum types
wrap :: (InstrWrapOneC dt name, exField :~> CtorOnlyField name dt, KnownValue dt) => Label name -> exField -> Expr dt Source #
unwrap :: (InstrUnwrapC dt name, exDt :~> dt, KnownValue (CtorOnlyField name dt)) => Label name -> exDt -> Expr (CtorOnlyField name dt) Source #
HasField
(!!) :: (HasField dt name ftype, exDt :~> dt, exFld :~> ftype) => exDt -> (Label name, exFld) -> Expr dt infixl 8 Source #
Record and Named
(!~) :: (ex :~> t, KnownValue (name :! t)) => ex -> Label name -> Expr (name :! t) infixl 8 Source #
construct :: (InstrConstructC dt, KnownValue dt, RMap (ConstructorFieldTypes dt), fields ~ Rec Expr (ConstructorFieldTypes dt), RecFromTuple fields) => IsoRecTuple fields -> Expr dt Source #
constructRec :: (InstrConstructC dt, RMap (ConstructorFieldTypes dt), KnownValue dt) => Rec Expr (ConstructorFieldTypes dt) -> Expr dt Source #
Contract
contract :: (NiceParameterFull p, NoExplicitDefaultEntrypoint p, ToTAddress p addr, ToT addr ~ ToT Address, exAddr :~> addr) => exAddr -> Expr (Maybe (ContractRef p)) Source #
self :: (NiceParameterFull p, NoExplicitDefaultEntrypoint p) => Expr (ContractRef p) Source #
contractAddress :: exc :~> ContractRef p => exc -> Expr Address Source #
contractCallingUnsafe :: (NiceParameter arg, exAddr :~> Address) => EpName -> exAddr -> Expr (Maybe (ContractRef arg)) Source #
contractCallingString :: (NiceParameter arg, exAddr :~> Address) => MText -> exAddr -> Expr (Maybe (ContractRef arg)) Source #
runFutureContract :: (NiceParameter p, conExpr :~> FutureContract p) => conExpr -> Expr (Maybe (ContractRef p)) Source #
implicitAccount :: exkh :~> KeyHash => exkh -> Expr (ContractRef ()) Source #
convertEpAddressToContract :: (NiceParameter p, epExpr :~> EpAddress) => epExpr -> Expr (Maybe (ContractRef p)) Source #
makeView :: (KnownValue (View a r), exa :~> a, exCRef :~> ContractRef r) => exa -> exCRef -> Expr (View a r) Source #
makeVoid :: (KnownValue (Void_ a b), exa :~> a, exCRef :~> Lambda b b) => exa -> exCRef -> Expr (Void_ a b) Source #
Auxiliary
blake2b :: hashExpr :~> ByteString => hashExpr -> Expr ByteString Source #
sha256 :: hashExpr :~> ByteString => hashExpr -> Expr ByteString Source #
sha512 :: hashExpr :~> ByteString => hashExpr -> Expr ByteString Source #