| 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 :: CT) (m :: CT) where
- class UnaryArithOp aop (n :: CT) where
- type UnaryArithRes aop n :: CT
- evalUnaryArithOp :: proxy aop -> CValue n -> CValue (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 :: CT) (m :: CT) 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 :: CT 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 -> CValue n -> CValue m -> Either (ArithError (CValue n) (CValue m)) (CValue (ArithRes aop n m)) Source #
Evaluate arithmetic operation on given operands.
Instances
class UnaryArithOp aop (n :: CT) where Source #
Marker data type for add operation.
Associated Types
type UnaryArithRes aop n :: CT Source #
Methods
evalUnaryArithOp :: proxy aop -> CValue n -> CValue (UnaryArithRes aop n) Source #
Instances
data ArithError n m Source #
Represents an arithmetic error of the operation.
Constructors
| MutezArithError ArithErrorType n m | |
| ShiftArithError ArithErrorType n m |
Instances
| (Eq n, Eq m) => Eq (ArithError n m) Source # | |
Defined in 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 # | |
Defined in 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 # | |
| (Show n, Show m) => Show (ArithError n m) Source # | |
Defined in Michelson.Typed.Arith Methods showsPrec :: Int -> ArithError n m -> ShowS # show :: ArithError n m -> String # showList :: [ArithError n m] -> ShowS # | |
| (Show n, Show m) => Buildable (ArithError n m) Source # | |
Defined in Michelson.Typed.Arith Methods build :: ArithError n m -> Builder # | |
data ArithErrorType Source #
Denotes the error type occured in the arithmetic operation.
Constructors
| AddOverflow | |
| MulOverflow | |
| SubUnderflow | |
| LslOverflow | |
| LsrUnderflow |
Instances
| Eq ArithErrorType Source # | |
Defined in Michelson.Typed.Arith Methods (==) :: ArithErrorType -> ArithErrorType -> Bool # (/=) :: ArithErrorType -> ArithErrorType -> Bool # | |
| Ord ArithErrorType Source # | |
Defined in Michelson.Typed.Arith Methods compare :: ArithErrorType -> ArithErrorType -> Ordering # (<) :: ArithErrorType -> ArithErrorType -> Bool # (<=) :: ArithErrorType -> ArithErrorType -> Bool # (>) :: ArithErrorType -> ArithErrorType -> Bool # (>=) :: ArithErrorType -> ArithErrorType -> Bool # max :: ArithErrorType -> ArithErrorType -> ArithErrorType # min :: ArithErrorType -> ArithErrorType -> ArithErrorType # | |
| Show ArithErrorType Source # | |
Defined in Michelson.Typed.Arith Methods showsPrec :: Int -> ArithErrorType -> ShowS # show :: ArithErrorType -> String # showList :: [ArithErrorType] -> ShowS # | |
| Buildable ArithErrorType Source # | |
Defined in Michelson.Typed.Arith Methods build :: ArithErrorType -> Builder # | |
Instances
| ArithOp Add CInt CInt Source # | |
| ArithOp Add CInt CNat Source # | |
| ArithOp Add CInt CTimestamp Source # | |
Defined in Michelson.Typed.Arith Methods evalOp :: proxy Add -> CValue CInt -> CValue CTimestamp -> Either (ArithError (CValue CInt) (CValue CTimestamp)) (CValue (ArithRes Add CInt CTimestamp)) Source # | |
| ArithOp Add CNat CInt Source # | |
| ArithOp Add CNat CNat Source # | |
| ArithOp Add CMutez CMutez Source # | |
| ArithOp Add CTimestamp CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalOp :: proxy Add -> CValue CTimestamp -> CValue CInt -> Either (ArithError (CValue CTimestamp) (CValue CInt)) (CValue (ArithRes Add CTimestamp CInt)) Source # | |
| type ArithRes Add CInt CInt Source # | |
| type ArithRes Add CInt CNat Source # | |
| type ArithRes Add CInt CTimestamp Source # | |
Defined in Michelson.Typed.Arith | |
| type ArithRes Add CNat CInt Source # | |
| type ArithRes Add CNat CNat Source # | |
| type ArithRes Add CMutez CMutez Source # | |
| type ArithRes Add CTimestamp CInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
Instances
| ArithOp Mul CInt CInt Source # | |
| ArithOp Mul CInt CNat Source # | |
| ArithOp Mul CNat CInt Source # | |
| ArithOp Mul CNat CNat Source # | |
| ArithOp Mul CNat CMutez Source # | |
| ArithOp Mul CMutez CNat Source # | |
| type ArithRes Mul CInt CInt Source # | |
| type ArithRes Mul CInt CNat Source # | |
| type ArithRes Mul CNat CInt Source # | |
| type ArithRes Mul CNat CNat Source # | |
| type ArithRes Mul CNat CMutez Source # | |
| type ArithRes Mul CMutez CNat Source # | |
Instances
| UnaryArithOp Abs CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Abs -> CValue CInt -> CValue (UnaryArithRes Abs CInt) Source # | |
| type UnaryArithRes Abs CInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Neg CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Neg -> CValue CInt -> CValue (UnaryArithRes Neg CInt) Source # | |
| UnaryArithOp Neg CNat Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Neg -> CValue CNat -> CValue (UnaryArithRes Neg CNat) Source # | |
| type UnaryArithRes Neg CInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Neg CNat Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Not CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Not -> CValue CInt -> CValue (UnaryArithRes Not CInt) Source # | |
| UnaryArithOp Not CNat Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Not -> CValue CNat -> CValue (UnaryArithRes Not CNat) Source # | |
| UnaryArithOp Not CBool Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Not -> CValue CBool -> CValue (UnaryArithRes Not CBool) Source # | |
| type UnaryArithRes Not CInt Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Not CNat Source # | |
Defined in Michelson.Typed.Arith | |
| type UnaryArithRes Not CBool Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Eq' CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Eq' -> CValue CInt -> CValue (UnaryArithRes Eq' CInt) Source # | |
| type UnaryArithRes Eq' CInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Neq CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Neq -> CValue CInt -> CValue (UnaryArithRes Neq CInt) Source # | |
| type UnaryArithRes Neq CInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Lt CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Lt -> CValue CInt -> CValue (UnaryArithRes Lt CInt) Source # | |
| type UnaryArithRes Lt CInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Gt CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Gt -> CValue CInt -> CValue (UnaryArithRes Gt CInt) Source # | |
| type UnaryArithRes Gt CInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Le CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Le -> CValue CInt -> CValue (UnaryArithRes Le CInt) Source # | |
| type UnaryArithRes Le CInt Source # | |
Defined in Michelson.Typed.Arith | |
Instances
| UnaryArithOp Ge CInt Source # | |
Defined in Michelson.Typed.Arith Methods evalUnaryArithOp :: proxy Ge -> CValue CInt -> CValue (UnaryArithRes Ge CInt) Source # | |
| type UnaryArithRes Ge CInt Source # | |
Defined in Michelson.Typed.Arith | |