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

Indigo.Common.Expr

Description

Expr data type and its generalizations

Synopsis

The Expr data type

data Expr a where Source #

Constructors

C :: NiceConstant a => a -> Expr a 
V :: KnownValue a => Var a -> Expr a 
ObjMan :: ObjectManipulation a -> Expr a 
Cast :: KnownValue a => Expr a -> Expr a 
Size :: SizeOpHs c => Expr c -> Expr Natural 
Update :: (UpdOpHs c, KnownValue c) => Expr c -> Expr (UpdOpKeyHs c) -> Expr (UpdOpParamsHs c) -> Expr c 
Add :: (ArithOpHs Add n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
Sub :: (ArithOpHs Sub n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
Mul :: (ArithOpHs Mul n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
Div :: (KnownValue ratio, ArithOpHs EDiv n m (Maybe (ratio, reminder))) => Expr n -> Expr m -> Proxy reminder -> Expr ratio 
Mod :: (KnownValue reminder, ArithOpHs EDiv n m (Maybe (ratio, reminder))) => Expr n -> Expr m -> Proxy ratio -> Expr reminder 
Abs :: (UnaryArithOpHs Abs n, KnownValue (UnaryArithResHs Abs n)) => Expr n -> Expr (UnaryArithResHs Abs n) 
Neg :: (UnaryArithOpHs Neg n, KnownValue (UnaryArithResHs Neg n)) => Expr n -> Expr (UnaryArithResHs Neg n) 
Lsl :: (ArithOpHs Lsl n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
Lsr :: (ArithOpHs Lsr n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
Eq' :: NiceComparable n => Expr n -> Expr n -> Expr Bool 
Neq :: NiceComparable n => Expr n -> Expr n -> Expr Bool 
Le :: NiceComparable n => Expr n -> Expr n -> Expr Bool 
Lt :: NiceComparable n => Expr n -> Expr n -> Expr Bool 
Ge :: NiceComparable n => Expr n -> Expr n -> Expr Bool 
Gt :: NiceComparable n => Expr n -> Expr n -> Expr Bool 
Or :: (ArithOpHs Or n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
Xor :: (ArithOpHs Xor n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
And :: (ArithOpHs And n m r, KnownValue r) => Expr n -> Expr m -> Expr r 
Not :: (UnaryArithOpHs Not n, KnownValue (UnaryArithResHs Not n)) => Expr n -> Expr (UnaryArithResHs Not n) 
Int' :: Expr Natural -> Expr Integer 
IsNat :: Expr Integer -> Expr (Maybe Natural) 
Coerce :: (Castable_ a b, KnownValue b) => Expr a -> Expr b 
ForcedCoerce :: (MichelsonCoercible a b, KnownValue b) => Expr a -> Expr b 
Fst :: KnownValue n => Expr (n, m) -> Expr n 
Snd :: KnownValue m => Expr (n, m) -> Expr m 
Pair :: KnownValue (n, m) => Expr n -> Expr m -> Expr (n, m) 
Some :: KnownValue (Maybe t) => Expr t -> Expr (Maybe t) 
None :: KnownValue t => Expr (Maybe t) 
Right' :: (KnownValue y, KnownValue (Either y x)) => Expr x -> Expr (Either y x) 
Left' :: (KnownValue x, KnownValue (Either y x)) => Expr y -> Expr (Either y x) 
Mem :: MemOpHs c => Expr (MemOpKeyHs c) -> Expr c -> Expr Bool 
StGet :: (StoreHasSubmap store name key value, KnownValue value) => Label name -> Expr key -> Expr store -> Expr (Maybe value) 
StInsertNew :: (StoreHasSubmap store name key value, KnownValue store, Dupable key, IsError err, Buildable err) => Label name -> err -> Expr key -> Expr value -> Expr store -> Expr store 
StInsert :: (StoreHasSubmap store name key value, KnownValue store) => Label name -> Expr key -> Expr value -> Expr store -> Expr store 
StMem :: (StoreHasSubmap store name key val, KnownValue val) => Label name -> Expr key -> Expr store -> Expr Bool 
StUpdate :: (StoreHasSubmap store name key val, KnownValue store) => Label name -> Expr key -> Expr (Maybe val) -> Expr store -> Expr store 
StDelete :: (StoreHasSubmap store name key val, KnownValue store, KnownValue val) => Label name -> Expr key -> Expr store -> Expr store 
Wrap :: (InstrWrapOneC dt name, KnownValue dt) => Label name -> Expr (CtorOnlyField name dt) -> Expr dt 
Unwrap :: (InstrUnwrapC dt name, KnownValue (CtorOnlyField name dt)) => Label name -> Expr dt -> Expr (CtorOnlyField name dt) 
Construct :: (InstrConstructC dt, RMap (ConstructorFieldTypes dt), RecordToList (ConstructorFieldTypes dt), KnownValue dt) => Proxy dt -> Rec Expr (ConstructorFieldTypes dt) -> Expr dt 
ConstructWithoutNamed :: ComplexObjectC dt => Proxy dt -> Rec Expr (FieldTypes dt) -> Expr dt 
Name :: KnownValue (name :! t) => Label name -> Expr t -> Expr (name :! t) 
UnName :: KnownValue t => Label name -> Expr (name :! t) -> Expr t 
EmptySet :: (NiceComparable key, KnownValue (Set key)) => Expr (Set key) 
Get :: (GetOpHs c, KnownValue (Maybe (GetOpValHs c)), KnownValue (GetOpValHs c)) => Expr (GetOpKeyHs c) -> Expr c -> Expr (Maybe (GetOpValHs c)) 
EmptyMap :: (KnownValue value, NiceComparable key, KnownValue (Map key value)) => Expr (Map key value) 
EmptyBigMap :: (KnownValue value, NiceComparable key, KnownValue (BigMap key value)) => Expr (BigMap key value) 
Pack :: NicePackedValue a => Expr a -> Expr (Packed a) 
Unpack :: NiceUnpackedValue a => Expr (Packed a) -> Expr (Maybe a) 
PackRaw :: NicePackedValue a => Expr a -> Expr ByteString 
UnpackRaw :: NiceUnpackedValue a => Expr ByteString -> Expr (Maybe a) 
Cons :: KnownValue (List a) => Expr a -> Expr (List a) -> Expr (List a) 
Nil :: KnownValue a => Expr (List a) 
Concat :: (ConcatOpHs c, KnownValue c) => Expr c -> Expr c -> Expr c 
Concat' :: (ConcatOpHs c, KnownValue c) => Expr (List c) -> Expr c 
Slice :: (SliceOpHs c, KnownValue c) => Expr Natural -> Expr Natural -> Expr c -> Expr (Maybe c) 
Contract :: (NiceParameterFull p, NoExplicitDefaultEntrypoint p, IsoValue (ContractRef p), ToTAddress p vd addr, ToT addr ~ ToT Address) => Proxy vd -> Expr addr -> Expr (Maybe (ContractRef p)) 
Self :: (NiceParameterFull p, NoExplicitDefaultEntrypoint p, IsoValue (ContractRef p), IsNotInView) => Expr (ContractRef p) 
SelfAddress :: Expr Address 
ContractAddress :: Expr (ContractRef p) -> Expr Address 
ContractCallingUnsafe :: (NiceParameter arg, IsoValue (ContractRef arg)) => EpName -> Expr Address -> Expr (Maybe (ContractRef arg)) 
RunFutureContract :: (NiceParameter p, IsoValue (ContractRef p)) => Expr (FutureContract p) -> Expr (Maybe (ContractRef p)) 
ImplicitAccount :: Expr KeyHash -> Expr (ContractRef ()) 
ConvertEpAddressToContract :: (NiceParameter p, IsoValue (ContractRef p)) => Expr EpAddress -> Expr (Maybe (ContractRef p)) 
MakeView :: KnownValue (View_ a r) => Expr a -> Expr (ContractRef r) -> Expr (View_ a r) 
MakeVoid :: KnownValue (Void_ a b) => Expr a -> Expr (Lambda b b) -> Expr (Void_ a b) 
CheckSignature :: BytesLike bs => Expr PublicKey -> Expr (TSignature bs) -> Expr bs -> Expr Bool 
Sha256 :: BytesLike bs => Expr bs -> Expr (Hash Sha256 bs) 
Sha512 :: BytesLike bs => Expr bs -> Expr (Hash Sha512 bs) 
Blake2b :: BytesLike bs => Expr bs -> Expr (Hash Blake2b bs) 
Sha3 :: BytesLike bs => Expr bs -> Expr (Hash Sha3 bs) 
Keccak :: BytesLike bs => Expr bs -> Expr (Hash Keccak bs) 
HashKey :: Expr PublicKey -> Expr KeyHash 
ChainId :: Expr ChainId 
Level :: Expr Natural 
Now :: Expr Timestamp 
Amount :: Expr Mutez 
Balance :: Expr Mutez 
Sender :: Expr Address 
VotingPower :: Expr KeyHash -> Expr Natural 
TotalVotingPower :: Expr Natural 
Exec :: KnownValue b => Expr a -> Expr (Lambda a b) -> Expr b 
NonZero :: (NonZero n, KnownValue (Maybe n)) => Expr n -> Expr (Maybe n) 

Instances

Instances details
Buildable (Expr a) Source # 
Instance details

Defined in Indigo.Common.Expr

Methods

build :: Expr a -> Builder #

Generalizations of Expr

type IsExpr op n = (ToExpr op, ExprType op ~ n, KnownValue n) Source #

class ToExpr' (Decide x) x => ToExpr x Source #

Instances

Instances details
ToExpr' (Decide x) x => ToExpr x Source # 
Instance details

Defined in Indigo.Common.Expr

type ExprType a = ExprType' (Decide a) a Source #

type (:~>) op n = IsExpr op n Source #

toExpr :: forall a. ToExpr a => a -> Expr (ExprType a) Source #

Arithmetic Expr

type IsArithExpr exN exM a n m r = (exN :~> n, exM :~> m, ArithOpHs a n m r, KnownValue r) Source #

Polymorphic Expr

type IsConcatExpr exN1 exN2 n = (exN1 :~> n, exN2 :~> n, ConcatOpHs n) Source #

type IsDivExpr exN exM n m ratio reminder = (exN :~> n, exM :~> m, KnownValue ratio, ArithOpHs EDiv n m (Maybe (ratio, reminder))) Source #

type IsModExpr exN exM n m ratio reminder = (exN :~> n, exM :~> m, KnownValue reminder, ArithOpHs EDiv n m (Maybe (ratio, reminder))) Source #

type IsGetExpr exKey exMap map = (exKey :~> GetOpKeyHs map, exMap :~> map, GetOpHs map, KnownValue (GetOpValHs map)) Source #

type IsMemExpr exKey exN n = (exKey :~> MemOpKeyHs n, exN :~> n, MemOpHs n) Source #

type IsSizeExpr exN n = (exN :~> n, SizeOpHs n) Source #

type IsSliceExpr exN n = (exN :~> n, SliceOpHs n) Source #

type IsUpdExpr exKey exVal exMap map = (exKey :~> UpdOpKeyHs map, exVal :~> UpdOpParamsHs map, exMap :~> map, UpdOpHs map) Source #

data ObjectManipulation a where Source #

Datatype describing access to an inner fields of object, like object !. field1 !. field2 ~. (field3, value3) ~. (field4, value4)

Constructors

Object :: Expr a -> ObjectManipulation a 
ToField :: HasField dt fname ftype => ObjectManipulation dt -> Label fname -> ObjectManipulation ftype 
SetField :: HasField dt fname ftype => ObjectManipulation dt -> Label fname -> Expr ftype -> ObjectManipulation dt 

Instances

Instances details
Buildable (ObjectManipulation a) Source # 
Instance details

Defined in Indigo.Common.Expr

data NamedFieldExpr a name where Source #

Auxiliary datatype where each field refers to an expression the field equals to. It's not recursive one.

Constructors

NamedFieldExpr 

Fields