morley-1.0.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Typed.Arith

Description

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

Synopsis

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
ArithOp Lsr CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Lsr CNat CNat :: CT Source #

ArithOp Lsl CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Lsl CNat CNat :: CT Source #

ArithOp Xor CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Xor CNat CNat :: CT Source #

ArithOp Xor CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Xor CBool CBool :: CT Source #

ArithOp And CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes And CInt CNat :: CT Source #

ArithOp And CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes And CNat CNat :: CT Source #

ArithOp And CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes And CBool CBool :: CT Source #

ArithOp Or CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Or CNat CNat :: CT Source #

ArithOp Or CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Or CBool CBool :: CT Source #

ArithOp Mul CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CInt CInt :: CT Source #

ArithOp Mul CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CInt CNat :: CT Source #

ArithOp Mul CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CNat CInt :: CT Source #

ArithOp Mul CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CNat CNat :: CT Source #

ArithOp Mul CNat CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CNat CMutez :: CT Source #

ArithOp Mul CMutez CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CMutez CNat :: CT Source #

ArithOp Sub CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CInt CInt :: CT Source #

ArithOp Sub CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CInt CNat :: CT Source #

ArithOp Sub CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CNat CInt :: CT Source #

ArithOp Sub CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CNat CNat :: CT Source #

ArithOp Sub CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CMutez CMutez :: CT Source #

ArithOp Sub CTimestamp CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CTimestamp CInt :: CT Source #

ArithOp Sub CTimestamp CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CTimestamp CTimestamp :: CT Source #

ArithOp Add CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CInt CInt :: CT Source #

ArithOp Add CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CInt CNat :: CT Source #

ArithOp Add CInt CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CInt CTimestamp :: CT Source #

ArithOp Add CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CNat CInt :: CT Source #

ArithOp Add CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CNat CNat :: CT Source #

ArithOp Add CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CMutez CMutez :: CT Source #

ArithOp Add CTimestamp CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CTimestamp CInt :: CT Source #

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
UnaryArithOp Ge CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Ge CInt :: CT Source #

UnaryArithOp Le CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Le CInt :: CT Source #

UnaryArithOp Gt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Gt CInt :: CT Source #

UnaryArithOp Lt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Lt CInt :: CT Source #

UnaryArithOp Neq CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neq CInt :: CT Source #

UnaryArithOp Eq' CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Eq' CInt :: CT Source #

UnaryArithOp Not CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not CInt :: CT Source #

UnaryArithOp Not CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not CNat :: CT Source #

UnaryArithOp Not CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not CBool :: CT Source #

UnaryArithOp Neg CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg CInt :: CT Source #

UnaryArithOp Neg CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg CNat :: CT Source #

UnaryArithOp Abs CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Abs CInt :: CT Source #

data ArithError n m Source #

Represents an arithmetic error of the operation.

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

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Michelson.Typed.Arith

Methods

build :: ArithError n m -> Builder #

data Add Source #

Instances
ArithOp Add CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CInt CInt :: CT Source #

ArithOp Add CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CInt CNat :: CT Source #

ArithOp Add CInt CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CInt CTimestamp :: CT Source #

ArithOp Add CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CNat CInt :: CT Source #

ArithOp Add CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CNat CNat :: CT Source #

ArithOp Add CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CMutez CMutez :: CT Source #

ArithOp Add CTimestamp CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Add CTimestamp CInt :: CT Source #

type ArithRes Add CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Add CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Add CInt CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Add CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Add CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Add CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Add CTimestamp CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Sub Source #

Instances
ArithOp Sub CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CInt CInt :: CT Source #

ArithOp Sub CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CInt CNat :: CT Source #

ArithOp Sub CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CNat CInt :: CT Source #

ArithOp Sub CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CNat CNat :: CT Source #

ArithOp Sub CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CMutez CMutez :: CT Source #

ArithOp Sub CTimestamp CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CTimestamp CInt :: CT Source #

ArithOp Sub CTimestamp CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Sub CTimestamp CTimestamp :: CT Source #

type ArithRes Sub CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Sub CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Sub CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Sub CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Sub CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Sub CTimestamp CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Sub CTimestamp CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

data Mul Source #

Instances
ArithOp Mul CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CInt CInt :: CT Source #

ArithOp Mul CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CInt CNat :: CT Source #

ArithOp Mul CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CNat CInt :: CT Source #

ArithOp Mul CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CNat CNat :: CT Source #

ArithOp Mul CNat CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CNat CMutez :: CT Source #

ArithOp Mul CMutez CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Mul CMutez CNat :: CT Source #

type ArithRes Mul CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Mul CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Mul CNat CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Mul CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Mul CNat CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Mul CMutez CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

data Abs Source #

Instances
UnaryArithOp Abs CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Abs CInt :: CT Source #

type UnaryArithRes Abs CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Neg Source #

Instances
UnaryArithOp Neg CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg CInt :: CT Source #

UnaryArithOp Neg CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neg CNat :: CT Source #

type UnaryArithRes Neg CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type UnaryArithRes Neg CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

data Or Source #

Instances
ArithOp Or CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Or CNat CNat :: CT Source #

ArithOp Or CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Or CBool CBool :: CT Source #

type ArithRes Or CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Or CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

data And Source #

Instances
ArithOp And CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes And CInt CNat :: CT Source #

ArithOp And CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes And CNat CNat :: CT Source #

ArithOp And CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes And CBool CBool :: CT Source #

type ArithRes And CInt CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes And CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes And CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

data Xor Source #

Instances
ArithOp Xor CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Xor CNat CNat :: CT Source #

ArithOp Xor CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Xor CBool CBool :: CT Source #

type ArithRes Xor CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Xor CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

data Not Source #

Instances
UnaryArithOp Not CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not CInt :: CT Source #

UnaryArithOp Not CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not CNat :: CT Source #

UnaryArithOp Not CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Not CBool :: CT Source #

type UnaryArithRes Not CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type UnaryArithRes Not CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type UnaryArithRes Not CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

data Lsl Source #

Instances
ArithOp Lsl CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Lsl CNat CNat :: CT Source #

type ArithRes Lsl CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

data Lsr Source #

Instances
ArithOp Lsr CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Lsr CNat CNat :: CT Source #

type ArithRes Lsr CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

data Eq' Source #

Instances
UnaryArithOp Eq' CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Eq' CInt :: CT Source #

type UnaryArithRes Eq' CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Neq Source #

Instances
UnaryArithOp Neq CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neq CInt :: CT Source #

type UnaryArithRes Neq CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Lt Source #

Instances
UnaryArithOp Lt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Lt CInt :: CT Source #

type UnaryArithRes Lt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Gt Source #

Instances
UnaryArithOp Gt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Gt CInt :: CT Source #

type UnaryArithRes Gt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Le Source #

Instances
UnaryArithOp Le CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Le CInt :: CT Source #

type UnaryArithRes Le CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Ge Source #

Instances
UnaryArithOp Ge CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Ge CInt :: CT Source #

type UnaryArithRes Ge CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

compareOp :: forall t i. (Comparable t, SingI t) => Value' i t -> Value' i t -> Integer Source #