morley-0.3.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 Compare CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CInt CInt :: CT Source #

ArithOp Compare CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CNat CNat :: CT Source #

ArithOp Compare CString CString Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CString CString :: CT Source #

ArithOp Compare CBytes CBytes Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CBytes CBytes :: CT Source #

ArithOp Compare CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CMutez CMutez :: CT Source #

ArithOp Compare CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CBool CBool :: CT Source #

ArithOp Compare CKeyHash CKeyHash Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CKeyHash CKeyHash :: CT Source #

ArithOp Compare CTimestamp CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CTimestamp CTimestamp :: CT Source #

ArithOp Compare CAddress CAddress Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CAddress CAddress :: CT Source #

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
ArithOpHs Add Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Integer :: Type Source #

ArithOpHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Natural :: Type Source #

ArithOpHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Timestamp :: Type Source #

ArithOpHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Integer :: Type Source #

ArithOpHs Add Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Natural :: Type Source #

ArithOpHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Timestamp Integer :: Type Source #

ArithOpHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Mutez Mutez :: Type 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 #

type ArithResHs Add Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

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
ArithOpHs Sub Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Integer :: Type Source #

ArithOpHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Natural :: Type Source #

ArithOpHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Integer :: Type Source #

ArithOpHs Sub Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Natural :: Type Source #

ArithOpHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Integer :: Type Source #

ArithOpHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Timestamp :: Type Source #

ArithOpHs Sub Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Mutez Mutez :: Type 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 #

type ArithResHs Sub Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

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
ArithOpHs Mul Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Integer :: Type Source #

ArithOpHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Natural :: Type Source #

ArithOpHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Integer :: Type Source #

ArithOpHs Mul Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Natural :: Type Source #

ArithOpHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Mutez :: Type Source #

ArithOpHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Mutez Natural :: Type 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 #

type ArithResHs Mul Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

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
UnaryArithOpHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Abs Integer :: Type Source #

UnaryArithOp Abs CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Abs CInt :: CT Source #

type UnaryArithResHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithRes Abs CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Neg Source #

Instances
UnaryArithOpHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Integer :: Type Source #

UnaryArithOpHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Natural :: Type 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 #

type UnaryArithResHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

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
ArithOpHs Or Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Bool Bool :: Type Source #

ArithOpHs Or Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Natural Natural :: Type 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 #

type ArithResHs Or Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Or Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

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
ArithOpHs And Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Bool Bool :: Type Source #

ArithOpHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Integer Natural :: Type Source #

ArithOpHs And Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Natural Natural :: Type 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 #

type ArithResHs And Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs And Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

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
ArithOpHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Bool Bool :: Type Source #

ArithOpHs Xor Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Natural Natural :: Type 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 #

type ArithResHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Xor Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

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
UnaryArithOpHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Bool :: Type Source #

UnaryArithOpHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Integer :: Type Source #

UnaryArithOpHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Natural :: Type 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 #

type UnaryArithResHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

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
ArithOpHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsl Natural Natural :: Type Source #

ArithOp Lsl CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Lsl CNat CNat :: CT Source #

type ArithResHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithRes Lsl CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

data Lsr Source #

Instances
ArithOpHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsr Natural Natural :: Type Source #

ArithOp Lsr CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Lsr CNat CNat :: CT Source #

type ArithResHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithRes Lsr CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

data Compare Source #

Instances
ArithOpHs Compare Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Bool Bool :: Type Source #

ArithOpHs Compare Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Integer Integer :: Type Source #

ArithOpHs Compare Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Natural Natural :: Type Source #

ArithOpHs Compare ByteString ByteString Source # 
Instance details

Defined in Lorentz.Arith

ArithOpHs Compare MText MText Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare MText MText :: Type Source #

ArithOpHs Compare Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

ArithOpHs Compare Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Mutez Mutez :: Type Source #

ArithOpHs Compare KeyHash KeyHash Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare KeyHash KeyHash :: Type Source #

ArithOpHs Compare Address Address Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Address Address :: Type Source #

ArithOp Compare CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CInt CInt :: CT Source #

ArithOp Compare CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CNat CNat :: CT Source #

ArithOp Compare CString CString Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CString CString :: CT Source #

ArithOp Compare CBytes CBytes Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CBytes CBytes :: CT Source #

ArithOp Compare CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CMutez CMutez :: CT Source #

ArithOp Compare CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CBool CBool :: CT Source #

ArithOp Compare CKeyHash CKeyHash Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CKeyHash CKeyHash :: CT Source #

ArithOp Compare CTimestamp CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CTimestamp CTimestamp :: CT Source #

ArithOp Compare CAddress CAddress Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type ArithRes Compare CAddress CAddress :: CT Source #

type ArithResHs Compare Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare ByteString ByteString Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare MText MText Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare KeyHash KeyHash Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Compare Address Address Source # 
Instance details

Defined in Lorentz.Arith

type ArithRes Compare CInt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CNat CNat Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CString CString Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CBytes CBytes Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CMutez CMutez Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CBool CBool Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CKeyHash CKeyHash Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CTimestamp CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Arith

type ArithRes Compare CAddress CAddress Source # 
Instance details

Defined in Michelson.Typed.Arith

data Eq' Source #

Instances
UnaryArithOpHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Integer :: Type Source #

UnaryArithOp Eq' CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Eq' CInt :: CT Source #

type UnaryArithResHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithRes Eq' CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Neq Source #

Instances
UnaryArithOpHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Integer :: Type Source #

UnaryArithOp Neq CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Neq CInt :: CT Source #

type UnaryArithResHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithRes Neq CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Lt Source #

Instances
UnaryArithOpHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Integer :: Type Source #

UnaryArithOp Lt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Lt CInt :: CT Source #

type UnaryArithResHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithRes Lt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Gt Source #

Instances
UnaryArithOpHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Integer :: Type Source #

UnaryArithOp Gt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Gt CInt :: CT Source #

type UnaryArithResHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithRes Gt CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Le Source #

Instances
UnaryArithOpHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Integer :: Type Source #

UnaryArithOp Le CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Le CInt :: CT Source #

type UnaryArithResHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithRes Le CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

data Ge Source #

Instances
UnaryArithOpHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Integer :: Type Source #

UnaryArithOp Ge CInt Source # 
Instance details

Defined in Michelson.Typed.Arith

Associated Types

type UnaryArithRes Ge CInt :: CT Source #

type UnaryArithResHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithRes Ge CInt Source # 
Instance details

Defined in Michelson.Typed.Arith