morley-1.20.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Typed.Arith

Contents

Description

Module, containing some boilerplate for support of arithmetic operations in Michelson language.

Synopsis

Documentation

class (Typeable n, Typeable m) => ArithOp aop (n :: T) (m :: T) where Source #

Class for binary arithmetic operation.

Takes binary operation marker as op parameter, types of left operand n and right operand m.

Typeable constraints in superclass are necessary for error messages.

Minimal complete definition

evalOp

Associated Types

type ArithRes aop n m :: T Source #

Type family ArithRes denotes the type resulting from computing operation op from operands of types n and m.

For instance, adding integer to natural produces integer, which is reflected in following instance of type family: ArithRes Add CNat CInt = CInt.

Methods

evalOp :: proxy aop -> Value' instr n -> Value' instr m -> Either (ArithError (Value' instr n) (Value' instr m)) (Value' instr (ArithRes aop n m)) Source #

Evaluate arithmetic operation on given operands.

commutativityProof :: Maybe $ Dict (ArithRes aop n m ~ ArithRes aop m n, ArithOp aop m n) Source #

An operation can marked as commutative, it does not affect its runtime behavior, but enables certain optimization in the optimizer. We conservatively consider operations non-commutative by default.

Note that there is one unusual case: AND works with int : nat but not with nat : int. That's how it's specified in Michelson.

Instances

Instances details
ArithOp Add 'TBls12381Fr 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TBls12381Fr 'TBls12381Fr :: T Source #

ArithOp Add 'TBls12381G1 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TBls12381G1 'TBls12381G1 :: T Source #

ArithOp Add 'TBls12381G2 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TBls12381G2 'TBls12381G2 :: T Source #

ArithOp Add 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes Add 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TInt 'TInt ~ ArithRes Add 'TInt 'TInt, ArithOp Add 'TInt 'TInt) Source #

ArithOp Add 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes Add 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TInt 'TNat ~ ArithRes Add 'TNat 'TInt, ArithOp Add 'TNat 'TInt) Source #

ArithOp Add 'TInt 'TTimestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TInt 'TTimestamp :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TInt -> Value' instr 'TTimestamp -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TTimestamp)) (Value' instr (ArithRes Add 'TInt 'TTimestamp)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TInt 'TTimestamp ~ ArithRes Add 'TTimestamp 'TInt, ArithOp Add 'TTimestamp 'TInt) Source #

ArithOp Add 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TMutez 'TMutez :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TMutez -> Value' instr 'TMutez -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TMutez)) (Value' instr (ArithRes Add 'TMutez 'TMutez)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TMutez 'TMutez ~ ArithRes Add 'TMutez 'TMutez, ArithOp Add 'TMutez 'TMutez) Source #

ArithOp Add 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes Add 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TNat 'TInt ~ ArithRes Add 'TInt 'TNat, ArithOp Add 'TInt 'TNat) Source #

ArithOp Add 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Add 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TNat 'TNat ~ ArithRes Add 'TNat 'TNat, ArithOp Add 'TNat 'TNat) Source #

ArithOp Add 'TTimestamp 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TTimestamp 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TTimestamp -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TTimestamp) (Value' instr 'TInt)) (Value' instr (ArithRes Add 'TTimestamp 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TTimestamp 'TInt ~ ArithRes Add 'TInt 'TTimestamp, ArithOp Add 'TInt 'TTimestamp) Source #

ArithOp And 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TBool 'TBool :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TBool -> Value' instr 'TBool -> Either (ArithError (Value' instr 'TBool) (Value' instr 'TBool)) (Value' instr (ArithRes And 'TBool 'TBool)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TBool 'TBool ~ ArithRes And 'TBool 'TBool, ArithOp And 'TBool 'TBool) Source #

ArithOp And 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TBytes 'TBytes :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TBytes -> Value' instr 'TBytes -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TBytes)) (Value' instr (ArithRes And 'TBytes 'TBytes)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TBytes 'TBytes ~ ArithRes And 'TBytes 'TBytes, ArithOp And 'TBytes 'TBytes) Source #

ArithOp And 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes And 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TInt 'TNat ~ ArithRes And 'TNat 'TInt, ArithOp And 'TNat 'TInt) Source #

ArithOp And 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes And 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TNat 'TNat ~ ArithRes And 'TNat 'TNat, ArithOp And 'TNat 'TNat) Source #

ArithOp EDiv 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes EDiv 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TInt 'TInt ~ ArithRes EDiv 'TInt 'TInt, ArithOp EDiv 'TInt 'TInt) Source #

ArithOp EDiv 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes EDiv 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TInt 'TNat ~ ArithRes EDiv 'TNat 'TInt, ArithOp EDiv 'TNat 'TInt) Source #

ArithOp EDiv 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TMutez 'TMutez :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TMutez -> Value' instr 'TMutez -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TMutez)) (Value' instr (ArithRes EDiv 'TMutez 'TMutez)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TMutez 'TMutez ~ ArithRes EDiv 'TMutez 'TMutez, ArithOp EDiv 'TMutez 'TMutez) Source #

ArithOp EDiv 'TMutez 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TMutez 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TMutez -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TNat)) (Value' instr (ArithRes EDiv 'TMutez 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TMutez 'TNat ~ ArithRes EDiv 'TNat 'TMutez, ArithOp EDiv 'TNat 'TMutez) Source #

ArithOp EDiv 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes EDiv 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TNat 'TInt ~ ArithRes EDiv 'TInt 'TNat, ArithOp EDiv 'TInt 'TNat) Source #

ArithOp EDiv 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes EDiv 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TNat 'TNat ~ ArithRes EDiv 'TNat 'TNat, ArithOp EDiv 'TNat 'TNat) Source #

ArithOp Lsl 'TBytes 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsl 'TBytes 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsl -> Value' instr 'TBytes -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TNat)) (Value' instr (ArithRes Lsl 'TBytes 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsl 'TBytes 'TNat ~ ArithRes Lsl 'TNat 'TBytes, ArithOp Lsl 'TNat 'TBytes) Source #

ArithOp Lsl 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsl 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsl -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Lsl 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsl 'TNat 'TNat ~ ArithRes Lsl 'TNat 'TNat, ArithOp Lsl 'TNat 'TNat) Source #

ArithOp Lsr 'TBytes 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsr 'TBytes 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsr -> Value' instr 'TBytes -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TNat)) (Value' instr (ArithRes Lsr 'TBytes 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsr 'TBytes 'TNat ~ ArithRes Lsr 'TNat 'TBytes, ArithOp Lsr 'TNat 'TBytes) Source #

ArithOp Lsr 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsr 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsr -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Lsr 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsr 'TNat 'TNat ~ ArithRes Lsr 'TNat 'TNat, ArithOp Lsr 'TNat 'TNat) Source #

ArithOp Mul 'TBls12381Fr 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TBls12381Fr :: T Source #

(Bottom, Bls12381MulBadOrder Bls12381Fr Bls12381G1 :: Constraint) => ArithOp Mul 'TBls12381Fr 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TBls12381G1 :: T Source #

(Bottom, Bls12381MulBadOrder Bls12381Fr Bls12381G2 :: Constraint) => ArithOp Mul 'TBls12381Fr 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TBls12381G2 :: T Source #

ArithOp Mul 'TBls12381Fr 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TInt :: T Source #

ArithOp Mul 'TBls12381Fr 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TNat :: T Source #

ArithOp Mul 'TBls12381G1 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381G1 'TBls12381Fr :: T Source #

ArithOp Mul 'TBls12381G2 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381G2 'TBls12381Fr :: T Source #

ArithOp Mul 'TInt 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TInt 'TBls12381Fr :: T Source #

ArithOp Mul 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes Mul 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TInt 'TInt ~ ArithRes Mul 'TInt 'TInt, ArithOp Mul 'TInt 'TInt) Source #

ArithOp Mul 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes Mul 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TInt 'TNat ~ ArithRes Mul 'TNat 'TInt, ArithOp Mul 'TNat 'TInt) Source #

ArithOp Mul 'TMutez 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TMutez 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TMutez -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TNat)) (Value' instr (ArithRes Mul 'TMutez 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TMutez 'TNat ~ ArithRes Mul 'TNat 'TMutez, ArithOp Mul 'TNat 'TMutez) Source #

ArithOp Mul 'TNat 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TBls12381Fr :: T Source #

ArithOp Mul 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes Mul 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TNat 'TInt ~ ArithRes Mul 'TInt 'TNat, ArithOp Mul 'TInt 'TNat) Source #

ArithOp Mul 'TNat 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TMutez :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TNat -> Value' instr 'TMutez -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TMutez)) (Value' instr (ArithRes Mul 'TNat 'TMutez)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TNat 'TMutez ~ ArithRes Mul 'TMutez 'TNat, ArithOp Mul 'TMutez 'TNat) Source #

ArithOp Mul 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Mul 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TNat 'TNat ~ ArithRes Mul 'TNat 'TNat, ArithOp Mul 'TNat 'TNat) Source #

ArithOp Or 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Or 'TBool 'TBool :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Or -> Value' instr 'TBool -> Value' instr 'TBool -> Either (ArithError (Value' instr 'TBool) (Value' instr 'TBool)) (Value' instr (ArithRes Or 'TBool 'TBool)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Or 'TBool 'TBool ~ ArithRes Or 'TBool 'TBool, ArithOp Or 'TBool 'TBool) Source #

ArithOp Or 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Or 'TBytes 'TBytes :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Or -> Value' instr 'TBytes -> Value' instr 'TBytes -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TBytes)) (Value' instr (ArithRes Or 'TBytes 'TBytes)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Or 'TBytes 'TBytes ~ ArithRes Or 'TBytes 'TBytes, ArithOp Or 'TBytes 'TBytes) Source #

ArithOp Or 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Or 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Or -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Or 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Or 'TNat 'TNat ~ ArithRes Or 'TNat 'TNat, ArithOp Or 'TNat 'TNat) Source #

ArithOp Sub 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes Sub 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TInt 'TInt ~ ArithRes Sub 'TInt 'TInt, ArithOp Sub 'TInt 'TInt) Source #

ArithOp Sub 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes Sub 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TInt 'TNat ~ ArithRes Sub 'TNat 'TInt, ArithOp Sub 'TNat 'TInt) Source #

ArithOp Sub 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes Sub 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TNat 'TInt ~ ArithRes Sub 'TInt 'TNat, ArithOp Sub 'TInt 'TNat) Source #

ArithOp Sub 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Sub 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TNat 'TNat ~ ArithRes Sub 'TNat 'TNat, ArithOp Sub 'TNat 'TNat) Source #

ArithOp Sub 'TTimestamp 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TTimestamp 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TTimestamp -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TTimestamp) (Value' instr 'TInt)) (Value' instr (ArithRes Sub 'TTimestamp 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TTimestamp 'TInt ~ ArithRes Sub 'TInt 'TTimestamp, ArithOp Sub 'TInt 'TTimestamp) Source #

ArithOp Sub 'TTimestamp 'TTimestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TTimestamp 'TTimestamp :: T Source #

ArithOp SubMutez 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes SubMutez 'TMutez 'TMutez :: T Source #

ArithOp Xor 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Xor 'TBool 'TBool :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Xor -> Value' instr 'TBool -> Value' instr 'TBool -> Either (ArithError (Value' instr 'TBool) (Value' instr 'TBool)) (Value' instr (ArithRes Xor 'TBool 'TBool)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Xor 'TBool 'TBool ~ ArithRes Xor 'TBool 'TBool, ArithOp Xor 'TBool 'TBool) Source #

ArithOp Xor 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Xor 'TBytes 'TBytes :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Xor -> Value' instr 'TBytes -> Value' instr 'TBytes -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TBytes)) (Value' instr (ArithRes Xor 'TBytes 'TBytes)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Xor 'TBytes 'TBytes ~ ArithRes Xor 'TBytes 'TBytes, ArithOp Xor 'TBytes 'TBytes) Source #

ArithOp Xor 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Xor 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Xor -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Xor 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Xor 'TNat 'TNat ~ ArithRes Xor 'TNat 'TNat, ArithOp Xor 'TNat 'TNat) Source #

class UnaryArithOp aop (n :: T) where Source #

Class for unary arithmetic operation.

Associated Types

type UnaryArithRes aop n :: T Source #

Methods

evalUnaryArithOp :: proxy aop -> Value' instr n -> Value' instr (UnaryArithRes aop n) Source #

Instances

Instances details
UnaryArithOp Abs 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Abs 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Abs -> Value' instr 'TInt -> Value' instr (UnaryArithRes Abs 'TInt) Source #

UnaryArithOp Eq' 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Eq' 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Eq' -> Value' instr 'TInt -> Value' instr (UnaryArithRes Eq' 'TInt) Source #

UnaryArithOp Ge 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Ge 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Ge -> Value' instr 'TInt -> Value' instr (UnaryArithRes Ge 'TInt) Source #

UnaryArithOp Gt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Gt 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Gt -> Value' instr 'TInt -> Value' instr (UnaryArithRes Gt 'TInt) Source #

UnaryArithOp Le 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Le 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Le -> Value' instr 'TInt -> Value' instr (UnaryArithRes Le 'TInt) Source #

UnaryArithOp Lt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Lt 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lt -> Value' instr 'TInt -> Value' instr (UnaryArithRes Lt 'TInt) Source #

UnaryArithOp Neg 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TBls12381Fr :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TBls12381Fr -> Value' instr (UnaryArithRes Neg 'TBls12381Fr) Source #

UnaryArithOp Neg 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TBls12381G1 :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TBls12381G1 -> Value' instr (UnaryArithRes Neg 'TBls12381G1) Source #

UnaryArithOp Neg 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TBls12381G2 :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TBls12381G2 -> Value' instr (UnaryArithRes Neg 'TBls12381G2) Source #

UnaryArithOp Neg 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TInt -> Value' instr (UnaryArithRes Neg 'TInt) Source #

UnaryArithOp Neg 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TNat :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TNat -> Value' instr (UnaryArithRes Neg 'TNat) Source #

UnaryArithOp Neq 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neq 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neq -> Value' instr 'TInt -> Value' instr (UnaryArithRes Neq 'TInt) Source #

UnaryArithOp Not 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TBool :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TBool -> Value' instr (UnaryArithRes Not 'TBool) Source #

UnaryArithOp Not 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TBytes :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TBytes -> Value' instr (UnaryArithRes Not 'TBytes) Source #

UnaryArithOp Not 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TInt -> Value' instr (UnaryArithRes Not 'TInt) Source #

UnaryArithOp Not 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TNat :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TNat -> Value' instr (UnaryArithRes Not 'TNat) Source #

class ToIntArithOp (n :: T) where Source #

Class for conversions to an integer value.

Methods

evalToIntOp :: Value' instr n -> Value' instr 'TInt Source #

Instances

Instances details
ToIntArithOp 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

evalToIntOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TBls12381Fr -> Value' instr 'TInt Source #

ToIntArithOp 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

evalToIntOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TBytes -> Value' instr 'TInt Source #

ToIntArithOp 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

evalToIntOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TNat -> Value' instr 'TInt Source #

class ToBytesArithOp (n :: T) where Source #

Class for conversions to bytes.

Methods

evalToBytesOp :: Value' instr n -> Value' instr 'TBytes Source #

Instances

Instances details
ToBytesArithOp 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

evalToBytesOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TInt -> Value' instr 'TBytes Source #

ToBytesArithOp 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

evalToBytesOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TNat -> Value' instr 'TBytes Source #

data ArithError n m Source #

Represents an arithmetic error of the operation.

Instances

Instances details
Generic (ArithError n m) Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type Rep (ArithError n m) :: Type -> Type #

Methods

from :: ArithError n m -> Rep (ArithError n m) x #

to :: Rep (ArithError n m) x -> ArithError n m #

(Show n, Show m) => Show (ArithError n m) Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

showsPrec :: Int -> ArithError n m -> ShowS #

show :: ArithError n m -> String #

showList :: [ArithError n m] -> ShowS #

(NFData n, NFData m) => NFData (ArithError n m) Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

rnf :: ArithError n m -> () #

(Eq n, Eq m) => Eq (ArithError n m) Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

(==) :: ArithError n m -> ArithError n m -> Bool #

(/=) :: ArithError n m -> ArithError n m -> Bool #

(Ord n, Ord m) => Ord (ArithError n m) Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

compare :: ArithError n m -> ArithError n m -> Ordering #

(<) :: ArithError n m -> ArithError n m -> Bool #

(<=) :: ArithError n m -> ArithError n m -> Bool #

(>) :: ArithError n m -> ArithError n m -> Bool #

(>=) :: ArithError n m -> ArithError n m -> Bool #

max :: ArithError n m -> ArithError n m -> ArithError n m #

min :: ArithError n m -> ArithError n m -> ArithError n m #

(Buildable n, Buildable m) => Buildable (ArithError n m) Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

build :: ArithError n m -> Doc

buildList :: [ArithError n m] -> Doc

type Rep (ArithError n m) Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data ShiftArithErrorType Source #

Denotes the error type occurred in the arithmetic shift operation.

Constructors

LslOverflow 
LsrUnderflow 

Instances

Instances details
Generic ShiftArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type Rep ShiftArithErrorType :: Type -> Type #

Show ShiftArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

NFData ShiftArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

rnf :: ShiftArithErrorType -> () #

Eq ShiftArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Ord ShiftArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Buildable ShiftArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type Rep ShiftArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type Rep ShiftArithErrorType = D1 ('MetaData "ShiftArithErrorType" "Morley.Michelson.Typed.Arith" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "LslOverflow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LsrUnderflow" 'PrefixI 'False) (U1 :: Type -> Type))

data MutezArithErrorType Source #

Denotes the error type occurred in the arithmetic operation involving mutez.

Constructors

AddOverflow 
MulOverflow 

Instances

Instances details
Generic MutezArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type Rep MutezArithErrorType :: Type -> Type #

Show MutezArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

NFData MutezArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

rnf :: MutezArithErrorType -> () #

Eq MutezArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Ord MutezArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Buildable MutezArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type Rep MutezArithErrorType Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type Rep MutezArithErrorType = D1 ('MetaData "MutezArithErrorType" "Morley.Michelson.Typed.Arith" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "AddOverflow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MulOverflow" 'PrefixI 'False) (U1 :: Type -> Type))

data Add Source #

Instances

Instances details
ArithOp Add 'TBls12381Fr 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TBls12381Fr 'TBls12381Fr :: T Source #

ArithOp Add 'TBls12381G1 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TBls12381G1 'TBls12381G1 :: T Source #

ArithOp Add 'TBls12381G2 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TBls12381G2 'TBls12381G2 :: T Source #

ArithOp Add 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes Add 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TInt 'TInt ~ ArithRes Add 'TInt 'TInt, ArithOp Add 'TInt 'TInt) Source #

ArithOp Add 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes Add 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TInt 'TNat ~ ArithRes Add 'TNat 'TInt, ArithOp Add 'TNat 'TInt) Source #

ArithOp Add 'TInt 'TTimestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TInt 'TTimestamp :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TInt -> Value' instr 'TTimestamp -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TTimestamp)) (Value' instr (ArithRes Add 'TInt 'TTimestamp)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TInt 'TTimestamp ~ ArithRes Add 'TTimestamp 'TInt, ArithOp Add 'TTimestamp 'TInt) Source #

ArithOp Add 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TMutez 'TMutez :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TMutez -> Value' instr 'TMutez -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TMutez)) (Value' instr (ArithRes Add 'TMutez 'TMutez)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TMutez 'TMutez ~ ArithRes Add 'TMutez 'TMutez, ArithOp Add 'TMutez 'TMutez) Source #

ArithOp Add 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes Add 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TNat 'TInt ~ ArithRes Add 'TInt 'TNat, ArithOp Add 'TInt 'TNat) Source #

ArithOp Add 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Add 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TNat 'TNat ~ ArithRes Add 'TNat 'TNat, ArithOp Add 'TNat 'TNat) Source #

ArithOp Add 'TTimestamp 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Add 'TTimestamp 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Add -> Value' instr 'TTimestamp -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TTimestamp) (Value' instr 'TInt)) (Value' instr (ArithRes Add 'TTimestamp 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Add 'TTimestamp 'TInt ~ ArithRes Add 'TInt 'TTimestamp, ArithOp Add 'TInt 'TTimestamp) Source #

type ArithRes Add 'TBls12381Fr 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TBls12381G1 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TBls12381G2 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TInt 'TTimestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Add 'TTimestamp 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Sub Source #

Instances

Instances details
ArithOp Sub 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes Sub 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TInt 'TInt ~ ArithRes Sub 'TInt 'TInt, ArithOp Sub 'TInt 'TInt) Source #

ArithOp Sub 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes Sub 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TInt 'TNat ~ ArithRes Sub 'TNat 'TInt, ArithOp Sub 'TNat 'TInt) Source #

ArithOp Sub 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes Sub 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TNat 'TInt ~ ArithRes Sub 'TInt 'TNat, ArithOp Sub 'TInt 'TNat) Source #

ArithOp Sub 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Sub 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TNat 'TNat ~ ArithRes Sub 'TNat 'TNat, ArithOp Sub 'TNat 'TNat) Source #

ArithOp Sub 'TTimestamp 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TTimestamp 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Sub -> Value' instr 'TTimestamp -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TTimestamp) (Value' instr 'TInt)) (Value' instr (ArithRes Sub 'TTimestamp 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Sub 'TTimestamp 'TInt ~ ArithRes Sub 'TInt 'TTimestamp, ArithOp Sub 'TInt 'TTimestamp) Source #

ArithOp Sub 'TTimestamp 'TTimestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Sub 'TTimestamp 'TTimestamp :: T Source #

type ArithRes Sub 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Sub 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Sub 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Sub 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Sub 'TTimestamp 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Sub 'TTimestamp 'TTimestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data SubMutez Source #

Instances

Instances details
ArithOp SubMutez 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes SubMutez 'TMutez 'TMutez :: T Source #

type ArithRes SubMutez 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Mul Source #

Instances

Instances details
ArithOp Mul 'TBls12381Fr 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TBls12381Fr :: T Source #

(Bottom, Bls12381MulBadOrder Bls12381Fr Bls12381G1 :: Constraint) => ArithOp Mul 'TBls12381Fr 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TBls12381G1 :: T Source #

(Bottom, Bls12381MulBadOrder Bls12381Fr Bls12381G2 :: Constraint) => ArithOp Mul 'TBls12381Fr 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TBls12381G2 :: T Source #

ArithOp Mul 'TBls12381Fr 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TInt :: T Source #

ArithOp Mul 'TBls12381Fr 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381Fr 'TNat :: T Source #

ArithOp Mul 'TBls12381G1 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381G1 'TBls12381Fr :: T Source #

ArithOp Mul 'TBls12381G2 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TBls12381G2 'TBls12381Fr :: T Source #

ArithOp Mul 'TInt 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TInt 'TBls12381Fr :: T Source #

ArithOp Mul 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes Mul 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TInt 'TInt ~ ArithRes Mul 'TInt 'TInt, ArithOp Mul 'TInt 'TInt) Source #

ArithOp Mul 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes Mul 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TInt 'TNat ~ ArithRes Mul 'TNat 'TInt, ArithOp Mul 'TNat 'TInt) Source #

ArithOp Mul 'TMutez 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TMutez 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TMutez -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TNat)) (Value' instr (ArithRes Mul 'TMutez 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TMutez 'TNat ~ ArithRes Mul 'TNat 'TMutez, ArithOp Mul 'TNat 'TMutez) Source #

ArithOp Mul 'TNat 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TBls12381Fr :: T Source #

ArithOp Mul 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes Mul 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TNat 'TInt ~ ArithRes Mul 'TInt 'TNat, ArithOp Mul 'TInt 'TNat) Source #

ArithOp Mul 'TNat 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TMutez :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TNat -> Value' instr 'TMutez -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TMutez)) (Value' instr (ArithRes Mul 'TNat 'TMutez)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TNat 'TMutez ~ ArithRes Mul 'TMutez 'TNat, ArithOp Mul 'TMutez 'TNat) Source #

ArithOp Mul 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Mul 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Mul -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Mul 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Mul 'TNat 'TNat ~ ArithRes Mul 'TNat 'TNat, ArithOp Mul 'TNat 'TNat) Source #

type ArithRes Mul 'TBls12381Fr 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TBls12381Fr 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TBls12381Fr 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TBls12381Fr 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TBls12381Fr 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TBls12381G1 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TBls12381G2 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TInt 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TMutez 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TNat 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TNat 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Mul 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data EDiv Source #

Instances

Instances details
ArithOp EDiv 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TInt 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TInt -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TInt)) (Value' instr (ArithRes EDiv 'TInt 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TInt 'TInt ~ ArithRes EDiv 'TInt 'TInt, ArithOp EDiv 'TInt 'TInt) Source #

ArithOp EDiv 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes EDiv 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TInt 'TNat ~ ArithRes EDiv 'TNat 'TInt, ArithOp EDiv 'TNat 'TInt) Source #

ArithOp EDiv 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TMutez 'TMutez :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TMutez -> Value' instr 'TMutez -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TMutez)) (Value' instr (ArithRes EDiv 'TMutez 'TMutez)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TMutez 'TMutez ~ ArithRes EDiv 'TMutez 'TMutez, ArithOp EDiv 'TMutez 'TMutez) Source #

ArithOp EDiv 'TMutez 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TMutez 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TMutez -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TMutez) (Value' instr 'TNat)) (Value' instr (ArithRes EDiv 'TMutez 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TMutez 'TNat ~ ArithRes EDiv 'TNat 'TMutez, ArithOp EDiv 'TNat 'TMutez) Source #

ArithOp EDiv 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TNat 'TInt :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TNat -> Value' instr 'TInt -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TInt)) (Value' instr (ArithRes EDiv 'TNat 'TInt)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TNat 'TInt ~ ArithRes EDiv 'TInt 'TNat, ArithOp EDiv 'TInt 'TNat) Source #

ArithOp EDiv 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes EDiv 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy EDiv -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes EDiv 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes EDiv 'TNat 'TNat ~ ArithRes EDiv 'TNat 'TNat, ArithOp EDiv 'TNat 'TNat) Source #

type ArithRes EDiv 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes EDiv 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes EDiv 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes EDiv 'TMutez 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes EDiv 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes EDiv 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Abs Source #

Instances

Instances details
UnaryArithOp Abs 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Abs 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Abs -> Value' instr 'TInt -> Value' instr (UnaryArithRes Abs 'TInt) Source #

type UnaryArithRes Abs 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Neg Source #

Instances

Instances details
UnaryArithOp Neg 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TBls12381Fr :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TBls12381Fr -> Value' instr (UnaryArithRes Neg 'TBls12381Fr) Source #

UnaryArithOp Neg 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TBls12381G1 :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TBls12381G1 -> Value' instr (UnaryArithRes Neg 'TBls12381G1) Source #

UnaryArithOp Neg 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TBls12381G2 :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TBls12381G2 -> Value' instr (UnaryArithRes Neg 'TBls12381G2) Source #

UnaryArithOp Neg 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TInt -> Value' instr (UnaryArithRes Neg 'TInt) Source #

UnaryArithOp Neg 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg 'TNat :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neg -> Value' instr 'TNat -> Value' instr (UnaryArithRes Neg 'TNat) Source #

type UnaryArithRes Neg 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type UnaryArithRes Neg 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type UnaryArithRes Neg 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type UnaryArithRes Neg 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type UnaryArithRes Neg 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Or Source #

Instances

Instances details
ArithOp Or 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Or 'TBool 'TBool :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Or -> Value' instr 'TBool -> Value' instr 'TBool -> Either (ArithError (Value' instr 'TBool) (Value' instr 'TBool)) (Value' instr (ArithRes Or 'TBool 'TBool)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Or 'TBool 'TBool ~ ArithRes Or 'TBool 'TBool, ArithOp Or 'TBool 'TBool) Source #

ArithOp Or 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Or 'TBytes 'TBytes :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Or -> Value' instr 'TBytes -> Value' instr 'TBytes -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TBytes)) (Value' instr (ArithRes Or 'TBytes 'TBytes)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Or 'TBytes 'TBytes ~ ArithRes Or 'TBytes 'TBytes, ArithOp Or 'TBytes 'TBytes) Source #

ArithOp Or 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Or 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Or -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Or 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Or 'TNat 'TNat ~ ArithRes Or 'TNat 'TNat, ArithOp Or 'TNat 'TNat) Source #

type ArithRes Or 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Or 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Or 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data And Source #

Instances

Instances details
ArithOp And 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TBool 'TBool :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TBool -> Value' instr 'TBool -> Either (ArithError (Value' instr 'TBool) (Value' instr 'TBool)) (Value' instr (ArithRes And 'TBool 'TBool)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TBool 'TBool ~ ArithRes And 'TBool 'TBool, ArithOp And 'TBool 'TBool) Source #

ArithOp And 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TBytes 'TBytes :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TBytes -> Value' instr 'TBytes -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TBytes)) (Value' instr (ArithRes And 'TBytes 'TBytes)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TBytes 'TBytes ~ ArithRes And 'TBytes 'TBytes, ArithOp And 'TBytes 'TBytes) Source #

ArithOp And 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TInt 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TInt -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TInt) (Value' instr 'TNat)) (Value' instr (ArithRes And 'TInt 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TInt 'TNat ~ ArithRes And 'TNat 'TInt, ArithOp And 'TNat 'TInt) Source #

ArithOp And 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes And 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy And -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes And 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes And 'TNat 'TNat ~ ArithRes And 'TNat 'TNat, ArithOp And 'TNat 'TNat) Source #

type ArithRes And 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes And 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes And 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes And 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Xor Source #

Instances

Instances details
ArithOp Xor 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Xor 'TBool 'TBool :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Xor -> Value' instr 'TBool -> Value' instr 'TBool -> Either (ArithError (Value' instr 'TBool) (Value' instr 'TBool)) (Value' instr (ArithRes Xor 'TBool 'TBool)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Xor 'TBool 'TBool ~ ArithRes Xor 'TBool 'TBool, ArithOp Xor 'TBool 'TBool) Source #

ArithOp Xor 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Xor 'TBytes 'TBytes :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Xor -> Value' instr 'TBytes -> Value' instr 'TBytes -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TBytes)) (Value' instr (ArithRes Xor 'TBytes 'TBytes)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Xor 'TBytes 'TBytes ~ ArithRes Xor 'TBytes 'TBytes, ArithOp Xor 'TBytes 'TBytes) Source #

ArithOp Xor 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Xor 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Xor -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Xor 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Xor 'TNat 'TNat ~ ArithRes Xor 'TNat 'TNat, ArithOp Xor 'TNat 'TNat) Source #

type ArithRes Xor 'TBool 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Xor 'TBytes 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Xor 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Not Source #

Instances

Instances details
UnaryArithOp Not 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TBool :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TBool -> Value' instr (UnaryArithRes Not 'TBool) Source #

UnaryArithOp Not 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TBytes :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TBytes -> Value' instr (UnaryArithRes Not 'TBytes) Source #

UnaryArithOp Not 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TInt -> Value' instr (UnaryArithRes Not 'TInt) Source #

UnaryArithOp Not 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not 'TNat :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Not -> Value' instr 'TNat -> Value' instr (UnaryArithRes Not 'TNat) Source #

type UnaryArithRes Not 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type UnaryArithRes Not 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type UnaryArithRes Not 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type UnaryArithRes Not 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Lsl Source #

Instances

Instances details
ArithOp Lsl 'TBytes 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsl 'TBytes 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsl -> Value' instr 'TBytes -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TNat)) (Value' instr (ArithRes Lsl 'TBytes 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsl 'TBytes 'TNat ~ ArithRes Lsl 'TNat 'TBytes, ArithOp Lsl 'TNat 'TBytes) Source #

ArithOp Lsl 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsl 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsl -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Lsl 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsl 'TNat 'TNat ~ ArithRes Lsl 'TNat 'TNat, ArithOp Lsl 'TNat 'TNat) Source #

type ArithRes Lsl 'TBytes 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Lsl 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Lsr Source #

Instances

Instances details
ArithOp Lsr 'TBytes 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsr 'TBytes 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsr -> Value' instr 'TBytes -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TBytes) (Value' instr 'TNat)) (Value' instr (ArithRes Lsr 'TBytes 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsr 'TBytes 'TNat ~ ArithRes Lsr 'TNat 'TBytes, ArithOp Lsr 'TNat 'TBytes) Source #

ArithOp Lsr 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type ArithRes Lsr 'TNat 'TNat :: T Source #

Methods

evalOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lsr -> Value' instr 'TNat -> Value' instr 'TNat -> Either (ArithError (Value' instr 'TNat) (Value' instr 'TNat)) (Value' instr (ArithRes Lsr 'TNat 'TNat)) Source #

commutativityProof :: Maybe $ Dict (ArithRes Lsr 'TNat 'TNat ~ ArithRes Lsr 'TNat 'TNat, ArithOp Lsr 'TNat 'TNat) Source #

type ArithRes Lsr 'TBytes 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

type ArithRes Lsr 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Eq' Source #

Instances

Instances details
UnaryArithOp Eq' 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Eq' 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Eq' -> Value' instr 'TInt -> Value' instr (UnaryArithRes Eq' 'TInt) Source #

type UnaryArithRes Eq' 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Neq Source #

Instances

Instances details
UnaryArithOp Neq 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neq 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Neq -> Value' instr 'TInt -> Value' instr (UnaryArithRes Neq 'TInt) Source #

type UnaryArithRes Neq 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Lt Source #

Instances

Instances details
UnaryArithOp Lt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Lt 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Lt -> Value' instr 'TInt -> Value' instr (UnaryArithRes Lt 'TInt) Source #

type UnaryArithRes Lt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Gt Source #

Instances

Instances details
UnaryArithOp Gt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Gt 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Gt -> Value' instr 'TInt -> Value' instr (UnaryArithRes Gt 'TInt) Source #

type UnaryArithRes Gt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Le Source #

Instances

Instances details
UnaryArithOp Le 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Le 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Le -> Value' instr 'TInt -> Value' instr (UnaryArithRes Le 'TInt) Source #

type UnaryArithRes Le 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

data Ge Source #

Instances

Instances details
UnaryArithOp Ge 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

Associated Types

type UnaryArithRes Ge 'TInt :: T Source #

Methods

evalUnaryArithOp :: forall proxy (instr :: [T] -> [T] -> Type). proxy Ge -> Value' instr 'TInt -> Value' instr (UnaryArithRes Ge 'TInt) Source #

type UnaryArithRes Ge 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Arith

compareOp :: Comparable t => Value' i t -> Value' i t -> Integer Source #

Implementation for COMPARE instruction.

Misc

type Bls12381MulBadOrder a1 a2 = DelayError (((('Text "Multiplication of " ':<>: 'ShowType a2) ':<>: 'Text " and ") ':<>: 'ShowType a1) ':<>: 'Text " works only other way around") Source #