| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Michelson.Typed.Arith
Description
Module, containing some boilerplate for support of arithmetic operations in Michelson language.
Synopsis
- class ArithOp aop (n :: T) (m :: T) where
- class UnaryArithOp aop (n :: T) where
- type UnaryArithRes aop n :: T
- evalUnaryArithOp :: proxy aop -> Value' instr n -> Value' instr (UnaryArithRes aop n)
- data ArithError n m
- data ArithErrorType
- data Add
- data Sub
- data Mul
- data Abs
- data Neg
- data Or
- data And
- data Xor
- data Not
- data Lsl
- data Lsr
- data Compare
- data Eq'
- data Neq
- data Lt
- data Gt
- data Le
- data Ge
- compareOp :: forall t i. (Comparable t, SingI t) => Value' i t -> Value' i t -> Integer
Documentation
class 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.
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.
Instances
class UnaryArithOp aop (n :: T) where Source #
Marker data type for add operation.
Associated Types
type UnaryArithRes aop n :: T Source #
Methods
evalUnaryArithOp :: proxy aop -> Value' instr n -> Value' instr (UnaryArithRes aop n) Source #
Instances
| UnaryArithOp Ge 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Le 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Gt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Lt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Neq 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Eq' 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Not 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Not 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Not 'TBool Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Neg 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Neg 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Abs 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
data ArithError n m Source #
Represents an arithmetic error of the operation.
Constructors
| MutezArithError ArithErrorType n m | |
| ShiftArithError ArithErrorType n m |
Instances
data ArithErrorType Source #
Denotes the error type occured in the arithmetic operation.
Constructors
| AddOverflow | |
| MulOverflow | |
| SubUnderflow | |
| LslOverflow | |
| LsrUnderflow |
Instances
Instances
| ArithOp Add 'TInt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Add 'TInt 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Add 'TInt 'TTimestamp Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Add 'TNat 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Add 'TNat 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Add 'TMutez 'TMutez Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Add 'TTimestamp 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type ArithRes Add 'TInt 'TInt Source # | |
| type ArithRes Add 'TInt 'TNat Source # | |
| type ArithRes Add 'TInt 'TTimestamp Source # | |
Defined in Michelson.Typed.Arith | |
| type ArithRes Add 'TNat 'TInt Source # | |
| type ArithRes Add 'TNat 'TNat Source # | |
| type ArithRes Add 'TMutez 'TMutez Source # | |
| type ArithRes Add 'TTimestamp 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
Instances
| ArithOp Mul 'TInt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Mul 'TInt 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Mul 'TNat 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Mul 'TNat 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Mul 'TNat 'TMutez Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp Mul 'TMutez 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| type ArithRes Mul 'TInt 'TInt Source # | |
| type ArithRes Mul 'TInt 'TNat Source # | |
| type ArithRes Mul 'TNat 'TInt Source # | |
| type ArithRes Mul 'TNat 'TNat Source # | |
| type ArithRes Mul 'TNat 'TMutez Source # | |
| type ArithRes Mul 'TMutez 'TNat Source # | |
Instances
| UnaryArithOp Abs 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Abs 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Neg 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Neg 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Neg 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Neg 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| ArithOp And 'TInt 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp And 'TNat 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| ArithOp And 'TBool 'TBool Source # | |
Defined in Michelson.Typed.Arith | |
| type ArithRes And 'TInt 'TNat Source # | |
| type ArithRes And 'TNat 'TNat Source # | |
| type ArithRes And 'TBool 'TBool Source # | |
Instances
| UnaryArithOp Not 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Not 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| UnaryArithOp Not 'TBool Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Not 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Not 'TNat Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Not 'TBool Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Eq' 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Eq' 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Neq 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Neq 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Lt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Lt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Gt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Gt 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Le 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Le 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Ge 'TInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Ge 'TInt Source # | |
Defined in Michelson.Typed.Arith | |