Safe Haskell | None |
---|---|
Language | Haskell2010 |
Expr
data type and its generalizations
Synopsis
- data Expr a where
- 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, KnownValue (ArithResHs Add n m)) => Expr n -> Expr m -> Expr (ArithResHs Add n m)
- Sub :: (ArithOpHs Sub n m, KnownValue (ArithResHs Sub n m)) => Expr n -> Expr m -> Expr (ArithResHs Sub n m)
- Mul :: (ArithOpHs Mul n m, KnownValue (ArithResHs Mul n m)) => Expr n -> Expr m -> Expr (ArithResHs Mul n m)
- Div :: (EDivOpHs n m, KnownValue (EDivOpResHs n m)) => Expr n -> Expr m -> Expr (EDivOpResHs n m)
- Mod :: (EDivOpHs n m, KnownValue (EModOpResHs n m)) => Expr n -> Expr m -> Expr (EModOpResHs n m)
- 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, KnownValue (ArithResHs Lsl n m)) => Expr n -> Expr m -> Expr (ArithResHs Lsl n m)
- Lsr :: (ArithOpHs Lsr n m, KnownValue (ArithResHs Lsr n m)) => Expr n -> Expr m -> Expr (ArithResHs Lsr n m)
- 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, KnownValue (ArithResHs Or n m)) => Expr n -> Expr m -> Expr (ArithResHs Or n m)
- Xor :: (ArithOpHs Xor n m, KnownValue (ArithResHs Xor n m)) => Expr n -> Expr m -> Expr (ArithResHs Xor n m)
- And :: (ArithOpHs And n m, KnownValue (ArithResHs And n m)) => Expr n -> Expr m -> Expr (ArithResHs And n m)
- 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
- UGet :: (HasUStore name key value store, KnownValue value) => Label name -> Expr key -> Expr (UStore store) -> Expr (Maybe value)
- UInsertNew :: (HasUStore name key value store, IsError err, KnownValue (UStore store)) => Label name -> err -> Expr key -> Expr value -> Expr (UStore store) -> Expr (UStore store)
- UInsert :: (HasUStore name key value store, KnownValue (UStore store)) => Label name -> Expr key -> Expr value -> Expr (UStore store) -> Expr (UStore store)
- UMem :: (HasUStore name key val store, KnownValue val) => Label name -> Expr key -> Expr (UStore store) -> Expr Bool
- UUpdate :: (HasUStore name key val store, KnownValue (UStore store)) => Label name -> Expr key -> Expr (Maybe val) -> Expr (UStore store) -> Expr (UStore store)
- UDelete :: (HasUStore name key val store, KnownValue (UStore store)) => Label name -> Expr key -> Expr (UStore store) -> Expr (UStore 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), KnownValue dt) => Rec Expr (ConstructorFieldTypes dt) -> Expr dt
- ConstructWithoutNamed :: ComplexObjectC 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 ByteString
- Unpack :: 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, ToTAddress p addr, ToT addr ~ ToT Address) => Expr addr -> Expr (Maybe (ContractRef p))
- Self :: (NiceParameterFull p, NoExplicitDefaultEntrypoint p) => Expr (ContractRef p)
- ContractAddress :: Expr (ContractRef p) -> Expr Address
- ContractCallingUnsafe :: NiceParameter arg => EpName -> Expr Address -> Expr (Maybe (ContractRef arg))
- RunFutureContract :: NiceParameter p => Expr (FutureContract p) -> Expr (Maybe (ContractRef p))
- ImplicitAccount :: Expr KeyHash -> Expr (ContractRef ())
- ConvertEpAddressToContract :: NiceParameter 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 :: Expr PublicKey -> Expr Signature -> Expr ByteString -> Expr Bool
- Sha256 :: Expr ByteString -> Expr ByteString
- Sha512 :: Expr ByteString -> Expr ByteString
- Blake2b :: Expr ByteString -> Expr ByteString
- HashKey :: Expr PublicKey -> Expr KeyHash
- ChainId :: Expr ChainId
- Now :: Expr Timestamp
- Amount :: Expr Mutez
- Balance :: Expr Mutez
- Sender :: Expr Address
- Exec :: KnownValue b => Expr a -> Expr (Lambda a b) -> Expr b
- NonZero :: (NonZero n, KnownValue (Maybe n)) => Expr n -> Expr (Maybe n)
- type IsExpr op n = (ToExpr op, ExprType op ~ n, KnownValue n)
- class ToExpr' (Decide x) x => ToExpr x
- type ExprType a = ExprType' (Decide a) a
- type (:~>) op n = IsExpr op n
- toExpr :: forall a. ToExpr a => a -> Expr (ExprType a)
- type IsArithExpr exN exM a n m = (exN :~> n, exM :~> m, ArithOpHs a n m, KnownValue (ArithResHs a n m))
- type IsUnaryArithExpr exN a n = (exN :~> n, UnaryArithOpHs a n, KnownValue (UnaryArithResHs a n))
- type IsConcatExpr exN1 exN2 n = (exN1 :~> n, exN2 :~> n, ConcatOpHs n)
- type IsConcatListExpr exN n = (exN :~> List n, ConcatOpHs n, KnownValue n)
- type IsDivExpr exN exM n m = (exN :~> n, exM :~> m, EDivOpHs n m, KnownValue (EDivOpResHs n m))
- type IsModExpr exN exM n m = (exN :~> n, exM :~> m, EDivOpHs n m, KnownValue (EModOpResHs n m))
- type IsGetExpr exKey exMap map = (exKey :~> GetOpKeyHs map, exMap :~> map, GetOpHs map, KnownValue (GetOpValHs map))
- type IsMemExpr exKey exN n = (exKey :~> MemOpKeyHs n, exN :~> n, MemOpHs n)
- type IsSizeExpr exN n = (exN :~> n, SizeOpHs n)
- type IsSliceExpr exN n = (exN :~> n, SliceOpHs n)
- type IsUpdExpr exKey exVal exMap map = (exKey :~> UpdOpKeyHs map, exVal :~> UpdOpParamsHs map, exMap :~> map, UpdOpHs map)
- data ObjectManipulation a where
- 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
- type ObjectExpr a = IndigoObjectF (NamedFieldExpr a) a
- data NamedFieldExpr a name where
- NamedFieldExpr :: {..} -> NamedFieldExpr a name
The Expr data type
Generalizations of Expr
class ToExpr' (Decide x) x => ToExpr x Source #
Instances
ToExpr' (Decide x) x => ToExpr x Source # | |
Defined in Indigo.Internal.Expr.Types |
Arithmetic Expr
type IsArithExpr exN exM a n m = (exN :~> n, exM :~> m, ArithOpHs a n m, KnownValue (ArithResHs a n m)) Source #
type IsUnaryArithExpr exN a n = (exN :~> n, UnaryArithOpHs a n, KnownValue (UnaryArithResHs a n)) Source #
Polymorphic Expr
type IsConcatExpr exN1 exN2 n = (exN1 :~> n, exN2 :~> n, ConcatOpHs n) Source #
type IsConcatListExpr exN n = (exN :~> List n, ConcatOpHs n, KnownValue n) Source #
type IsDivExpr exN exM n m = (exN :~> n, exM :~> m, EDivOpHs n m, KnownValue (EDivOpResHs n m)) Source #
type IsModExpr exN exM n m = (exN :~> n, exM :~> m, EDivOpHs n m, KnownValue (EModOpResHs n m)) Source #
type IsGetExpr exKey exMap map = (exKey :~> GetOpKeyHs map, exMap :~> map, GetOpHs map, KnownValue (GetOpValHs map)) 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)
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 |
type ObjectExpr a = IndigoObjectF (NamedFieldExpr a) a Source #
data NamedFieldExpr a name where Source #
Auxiliary datatype where each field refers to an expression the field equals to. It's not recursive one.
NamedFieldExpr | |
|