indigo-0.6.0: Convenient imperative eDSL over Lorentz.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Indigo.Frontend.Expr

Description

All the basic Expressions used in Indigo code.

Note: infix operators acting on structure follow a naming convention:

  1. the last character identifies the structure type:

  2. 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

The only exception to this convention is (.:) (for cons)

Synopsis

Basic

constExpr :: forall a. NiceConstant a => a -> Expr a Source #

varExpr :: KnownValue a => Var a -> Expr a Source #

Create an expression holding a variable.

cast :: ex :~> a => ex -> Expr a Source #

Math

add :: IsArithExpr exN exM Add n m r => exN -> exM -> Expr r Source #

sub :: IsArithExpr exN exM Sub n m r => exN -> exM -> Expr r Source #

mul :: IsArithExpr exN exM Mul n m r => exN -> exM -> Expr r Source #

div :: forall reminder exN exM n m ratio. IsDivExpr exN exM n m ratio reminder => exN -> exM -> Expr ratio Source #

mod :: forall ratio exN exM n m reminder. IsModExpr exN exM n m ratio reminder => exN -> exM -> Expr reminder Source #

even :: (ParityExpr n m, ArithOpHs EDiv n m r, exN :~> n) => exN -> Expr Bool Source #

odd :: (ParityExpr n m, ArithOpHs EDiv n m r, exN :~> n) => exN -> Expr Bool Source #

(+) :: IsArithExpr exN exM Add n m r => exN -> exM -> Expr r infixl 6 Source #

(-) :: IsArithExpr exN exM Sub n m r => exN -> exM -> Expr r infixl 6 Source #

(*) :: IsArithExpr exN exM Mul n m r => exN -> exM -> Expr r infixl 7 Source #

(/) :: forall reminder exN exM n m ratio. IsDivExpr exN exM n m ratio reminder => exN -> exM -> Expr ratio infixl 7 Source #

(%) :: forall ratio exN exM n m reminder. IsModExpr exN exM n m ratio reminder => exN -> exM -> Expr reminder infixl 7 Source #

Comparison

eq :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool Source #

neq :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool Source #

lt :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool Source #

gt :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool Source #

le :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool Source #

ge :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool Source #

(==) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool infix 4 Source #

(/=) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool infix 4 Source #

(<) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool infix 4 Source #

(>) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool infix 4 Source #

(<=) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool infix 4 Source #

(>=) :: (NiceComparable n, c :~> n, c1 :~> n) => c -> c1 -> Expr Bool infix 4 Source #

Conversion

nonZero :: (ex :~> n, NonZero n, KnownValue (Maybe n)) => ex -> Expr (Maybe n) Source #

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 r => exN -> exM -> Expr r Source #

lsr :: IsArithExpr exN exM Lsr n m r => exN -> exM -> Expr r Source #

and :: IsArithExpr exN exM And n m r => exN -> exM -> Expr r Source #

or :: IsArithExpr exN exM Or n m r => exN -> exM -> Expr r Source #

xor :: IsArithExpr exN exM Xor n m r => exN -> exM -> Expr r Source #

(<<<) :: IsArithExpr exN exM Lsl n m r => exN -> exM -> Expr r infixl 8 Source #

(>>>) :: IsArithExpr exN exM Lsr n m r => exN -> exM -> Expr r infixl 8 Source #

(&&) :: IsArithExpr exN exM And n m r => exN -> exM -> Expr r infixr 3 Source #

(||) :: IsArithExpr exN exM Or n m r => exN -> exM -> Expr r infixr 2 Source #

(^) :: IsArithExpr exN exM Xor n m r => exN -> exM -> Expr r infixr 2 Source #

Serialization

pack :: (ex :~> a, NicePackedValue a) => ex -> Expr (Packed a) Source #

unpack :: (NiceUnpackedValue a, exb :~> Packed a) => exb -> Expr (Maybe a) Source #

Pairs

pair :: (ex1 :~> n, ex2 :~> m, KnownValue (n, m)) => ex1 -> ex2 -> Expr (n, m) Source #

car :: (op :~> (n, m), KnownValue n) => op -> Expr n Source #

cdr :: (op :~> (n, m), KnownValue m) => op -> Expr m Source #

fst :: (op :~> (n, m), KnownValue n) => op -> Expr n Source #

snd :: (op :~> (n, m), KnownValue m) => op -> Expr m Source #

Maybe

some :: (ex :~> t, KnownValue (Maybe t)) => ex -> Expr (Maybe t) Source #

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 #

cons :: (ex1 :~> a, ex2 :~> List a) => ex1 -> ex2 -> Expr (List a) Source #

(.:) :: (ex1 :~> a, ex2 :~> List a) => ex1 -> ex2 -> Expr (List a) infixr 5 Source #

Containers

get :: IsGetExpr exKey exMap map => exKey -> exMap -> Expr (Maybe (GetOpValHs map)) Source #

update :: IsUpdExpr exKey exVal exMap map => (exKey, exVal) -> exMap -> Expr map Source #

insert :: (ExprInsertable c insParam, ex :~> c) => insParam -> ex -> Expr c Source #

remove :: (ExprRemovable c, exStruct :~> c, exKey :~> UpdOpKeyHs c) => exKey -> exStruct -> Expr c Source #

mem :: IsMemExpr exKey exN n => exKey -> exN -> Expr Bool Source #

size :: IsSizeExpr exN n => exN -> Expr Natural Source #

(#:) :: IsGetExpr exKey exMap map => exMap -> exKey -> Expr (Maybe (GetOpValHs map)) infixl 8 Source #

(!:) :: IsUpdExpr exKey exVal exMap map => exMap -> (exKey, exVal) -> Expr 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 #

(?:) :: IsMemExpr exKey exN n => exN -> exKey -> Expr Bool 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 #

Storages

stGet :: (StoreHasSubmap store name key value, KnownValue value, exKey :~> key, exStore :~> store) => exStore -> (Label name, exKey) -> Expr (Maybe value) Source #

stUpdate :: (StoreHasSubmap store name key value, exKey :~> key, exVal :~> Maybe value, exStore :~> store) => exStore -> (Label name, exKey, exVal) -> Expr store Source #

stInsert :: (StoreHasSubmap store name key value, exKey :~> key, exVal :~> value, exStore :~> store) => exStore -> (Label name, exKey, exVal) -> Expr store Source #

stInsertNew :: (StoreHasSubmap store name key value, Dupable key, IsError err, Buildable err, exKey :~> key, exVal :~> value, exStore :~> store) => exStore -> (Label name, err, exKey, exVal) -> Expr store Source #

stDelete :: (StoreHasSubmap store name key value, KnownValue value, exKey :~> key, exStore :~> store) => exStore -> (Label name, exKey) -> Expr store Source #

stMem :: (StoreHasSubmap store name key value, KnownValue value, exKey :~> key, exStore :~> store) => exStore -> (Label name, exKey) -> Expr Bool Source #

(#@) :: (StoreHasSubmap store name key value, KnownValue value, exKey :~> key, exStore :~> store) => exStore -> (Label name, exKey) -> Expr (Maybe value) infixr 8 Source #

(!@) :: (StoreHasSubmap store name key value, exKey :~> key, exVal :~> Maybe value, exStore :~> store) => exStore -> (Label name, exKey, exVal) -> Expr store infixl 8 Source #

(+@) :: (StoreHasSubmap store name key value, exKey :~> key, exVal :~> value, exStore :~> store) => exStore -> (Label name, exKey, exVal) -> Expr store infixr 8 Source #

(++@) :: (StoreHasSubmap store name key value, Dupable key, IsError err, Buildable err, exKey :~> key, exVal :~> value, exStore :~> store) => exStore -> (Label name, err, exKey, exVal) -> Expr store infixr 8 Source #

(-@) :: (StoreHasSubmap store name key value, KnownValue value, exKey :~> key, exStore :~> store) => exStore -> (Label name, exKey) -> Expr store infixl 8 Source #

(?@) :: (StoreHasSubmap store name key value, KnownValue value, exKey :~> key, exStore :~> 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 #

(#!) :: (HasField dt name ftype, exDt :~> dt) => exDt -> Label name -> Expr ftype infixl 8 Source #

Record and Named

name :: (ex :~> t, KnownValue (name :! t)) => Label name -> ex -> Expr (name :! t) Source #

unName :: (ex :~> (name :! t), KnownValue t) => Label name -> ex -> Expr t Source #

(!~) :: (ex :~> t, KnownValue (name :! t)) => ex -> Label name -> Expr (name :! t) infixl 8 Source #

(#~) :: (ex :~> (name :! t), KnownValue t) => ex -> Label name -> Expr t infixl 8 Source #

Contract

contract :: forall p vd addr exAddr. (NiceParameterFull p, NoExplicitDefaultEntrypoint p, IsoValue (ContractRef p), ToTAddress p vd addr, ToT addr ~ ToT Address, exAddr :~> addr) => exAddr -> 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 :~> bs, BytesLike bs) => hashExpr -> Expr (Hash Blake2b bs) Source #

sha256 :: (hashExpr :~> bs, BytesLike bs) => hashExpr -> Expr (Hash Sha256 bs) Source #

sha512 :: (hashExpr :~> bs, BytesLike bs) => hashExpr -> Expr (Hash Sha512 bs) Source #

sha3 :: (hashExpr :~> bs, BytesLike bs) => hashExpr -> Expr (Hash Sha3 bs) Source #

keccak :: (hashExpr :~> bs, BytesLike bs) => hashExpr -> Expr (Hash Keccak bs) Source #

hashKey :: keyExpr :~> PublicKey => keyExpr -> Expr KeyHash Source #

votingPower :: keyExpr :~> KeyHash => keyExpr -> Expr Natural Source #

checkSignature :: (pkExpr :~> PublicKey, sigExpr :~> TSignature bs, hashExpr :~> bs, BytesLike bs) => pkExpr -> sigExpr -> hashExpr -> Expr Bool Source #