lorentz-0.15.0: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lorentz.CustomArith.Common

Synopsis

Arithmetic operations

div :: forall r n m s. ArithOpHs Div n m r => (n ': (m ': s)) :-> (r ': s) Source #

Operation that represents division of two values with a given result

Lorentz casts

class LorentzRounding a b where Source #

Class that enables support of rounding operations for Lorentz non-integer values

Methods

round_ :: (a ': s) :-> (b ': s) Source #

ceil_ :: (a ': s) :-> (b ': s) Source #

floor_ :: (a ': s) :-> (b ': s) Source #

Instances

Instances details
(LorentzRational r, Unwrappabled r ~ (a, Natural), ArithOpHs EDiv a Natural (Maybe (a, Natural)), ArithOpHs Add a Natural a, ArithOpHs Add Natural a a) => LorentzRounding r a Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

round_ :: forall (s :: [Type]). (r ': s) :-> (a ': s) Source #

ceil_ :: forall (s :: [Type]). (r ': s) :-> (a ': s) Source #

floor_ :: forall (s :: [Type]). (r ': s) :-> (a ': s) Source #

(KnownNat a, KnownNat b) => LorentzRounding (Fixed (BinBase a)) (Fixed (BinBase b)) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

round_ :: forall (s :: [Type]). (Fixed (BinBase a) ': s) :-> (Fixed (BinBase b) ': s) Source #

ceil_ :: forall (s :: [Type]). (Fixed (BinBase a) ': s) :-> (Fixed (BinBase b) ': s) Source #

floor_ :: forall (s :: [Type]). (Fixed (BinBase a) ': s) :-> (Fixed (BinBase b) ': s) Source #

(KnownNat a, KnownNat b) => LorentzRounding (Fixed (DecBase a)) (Fixed (DecBase b)) Source #

Round is implemented using "banker's rounding" strategy, rounding half-way values towards nearest even value

Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

round_ :: forall (s :: [Type]). (Fixed (DecBase a) ': s) :-> (Fixed (DecBase b) ': s) Source #

ceil_ :: forall (s :: [Type]). (Fixed (DecBase a) ': s) :-> (Fixed (DecBase b) ': s) Source #

floor_ :: forall (s :: [Type]). (Fixed (DecBase a) ': s) :-> (Fixed (DecBase b) ': s) Source #

(KnownNat a, KnownNat b) => LorentzRounding (NFixed (BinBase a)) (NFixed (BinBase b)) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

round_ :: forall (s :: [Type]). (NFixed (BinBase a) ': s) :-> (NFixed (BinBase b) ': s) Source #

ceil_ :: forall (s :: [Type]). (NFixed (BinBase a) ': s) :-> (NFixed (BinBase b) ': s) Source #

floor_ :: forall (s :: [Type]). (NFixed (BinBase a) ': s) :-> (NFixed (BinBase b) ': s) Source #

LorentzRounding (Fixed (DecBase a)) (Fixed (DecBase b)) => LorentzRounding (NFixed (DecBase a)) (NFixed (DecBase b)) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

round_ :: forall (s :: [Type]). (NFixed (DecBase a) ': s) :-> (NFixed (DecBase b) ': s) Source #

ceil_ :: forall (s :: [Type]). (NFixed (DecBase a) ': s) :-> (NFixed (DecBase b) ': s) Source #

floor_ :: forall (s :: [Type]). (NFixed (DecBase a) ': s) :-> (NFixed (DecBase b) ': s) Source #

Additional Arithmetic operations

data Div Source #

Since Michelson doesn't support divide operation, we will use our own to represent divison of Fixed and Rational values

Instances

Instances details
r ~ NRational => ArithOpHs Div NRational NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div NRational Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Rational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div NRational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Integer ': s)) :-> (r ': s) Source #

r ~ NRational => ArithOpHs Div NRational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Rational NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Rational Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Rational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Rational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Rational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Rational ': s)) :-> (r ': s) Source #

r ~ NRational => ArithOpHs Div Natural NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Natural Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Rational ': s)) :-> (r ': s) Source #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (Fixed (BinBase a)) (Fixed (BinBase b)) (Maybe (Fixed (BinBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (Fixed (BinBase b) ': s)) :-> (Maybe (Fixed (BinBase r)) ': s) Source #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (Fixed (DecBase a)) (Fixed (DecBase b)) (Maybe (Fixed (DecBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (Fixed (DecBase b) ': s)) :-> (Maybe (Fixed (DecBase r)) ': s) Source #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (NFixed (BinBase a)) (NFixed (BinBase b)) (Maybe (NFixed (BinBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (NFixed (BinBase b) ': s)) :-> (Maybe (NFixed (BinBase r)) ': s) Source #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (NFixed (DecBase a)) (NFixed (DecBase b)) (Maybe (NFixed (DecBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (NFixed (DecBase b) ': s)) :-> (Maybe (NFixed (DecBase r)) ': s) Source #