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

Lorentz.CustomArith.RationalArith

Synopsis

Documentation

data Rational Source #

Instances

Instances details
Show Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Eq Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

HasAnnotation Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

LorentzRational Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

numerator :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (Rational ': s) :-> (a ': s) Source #

denominator :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (Rational ': s) :-> (Natural ': s) Source #

deconstructRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (Rational ': s) :-> (a ': (Natural ': s)) Source #

constructRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (a ': (Natural ': s)) :-> (Rational ': s) Source #

unsafePairToRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => ((a, Natural) ': s) :-> (Rational ': s) Source #

uncheckedPairToRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => ((a, Natural) ': s) :-> (Rational ': s) Source #

pairToRational :: forall a (s :: [Type]). (Unwrappabled Rational ~ (a, Natural), KnownValue Rational) => ((a, Natural) ': s) :-> (Maybe Rational ': s) Source #

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

reduce :: forall (s :: [Type]). (KnownList s, KnownList (ToTs s)) => (Rational ': s) :-> (Rational ': s) Source #

Unwrappable Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type Unwrappabled Rational Source #

IsoValue Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type ToT Rational :: T #

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 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 Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Rational ': 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 #

r ~ Rational => ArithOpHs Add 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 Add 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 Add 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 Add 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 Add 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 Add Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

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

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

Defined in Lorentz.CustomArith.RationalArith

Methods

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

r ~ Rational => ArithOpHs Mul 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 Mul 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 Mul 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 Mul 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 Mul 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 Mul Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

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

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

Defined in Lorentz.CustomArith.RationalArith

Methods

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

r ~ Rational => ArithOpHs Sub 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 Sub 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 Sub 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 Sub 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 Sub 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 Sub Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

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

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

Defined in Lorentz.CustomArith.RationalArith

Methods

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

type Unwrappabled Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

type ToT Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

type ToT Rational = 'TPair 'TInt 'TNat

data NRational Source #

Instances

Instances details
Show NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Eq NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

HasAnnotation NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

LorentzRational NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

numerator :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (NRational ': s) :-> (a ': s) Source #

denominator :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (NRational ': s) :-> (Natural ': s) Source #

deconstructRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (NRational ': s) :-> (a ': (Natural ': s)) Source #

constructRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (a ': (Natural ': s)) :-> (NRational ': s) Source #

unsafePairToRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => ((a, Natural) ': s) :-> (NRational ': s) Source #

uncheckedPairToRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => ((a, Natural) ': s) :-> (NRational ': s) Source #

pairToRational :: forall a (s :: [Type]). (Unwrappabled NRational ~ (a, Natural), KnownValue NRational) => ((a, Natural) ': s) :-> (Maybe NRational ': s) Source #

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

reduce :: forall (s :: [Type]). (KnownList s, KnownList (ToTs s)) => (NRational ': s) :-> (NRational ': s) Source #

Unwrappable NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type Unwrappabled NRational Source #

IsoValue NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type ToT NRational :: T #

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 Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NRational ': 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 ~ NRational => ArithOpHs Add 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 Add 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 Add 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 Add 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 Add 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 Add Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

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

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

Defined in Lorentz.CustomArith.RationalArith

Methods

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

r ~ NRational => ArithOpHs Mul 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 Mul 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 Mul 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 Mul 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 Mul 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 Mul Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

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

r ~ NRational => ArithOpHs Mul 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 Sub 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 Sub 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 Sub NRational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

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

r ~ Rational => ArithOpHs Sub 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 Sub 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 Sub 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 Sub Natural NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

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

type Unwrappabled NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

type ToT NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

type ToT NRational = 'TPair 'TNat 'TNat

Common functions

oppositeRational :: LorentzRational r => (r ': s) :-> (r ': s) Source #

gcdEuclid :: (Natural ': (Natural ': s)) :-> (Natural ': s) Source #

For a given Natural values, calculates their gcd, using Euclid algorithm.

euclidExtendedNormalization :: forall s. (Rational ': s) :-> (Rational ': s) Source #

Reduce Rational value, using extended Euclid algorithm. Consumes slightly more gas, than reduce, but contract with it is cheaper in terms of origination.

reduce :: (LorentzRational r, KnownList s, KnownList (ToTs s)) => (r ': s) :-> (r ': s) Source #

tripleMul :: forall r a s. (ArithOpHs Mul a a a, Unwrappabled r ~ (a, Natural), LorentzRational r) => (r ': (r ': (r ': s))) :-> (r ': s) Source #

Special multiplication helper, in case you want to multiply three 'Rational values' given values (a b) * (c d) * (e / f) performs (a * c * e) / (b * d * f).

Constructor functions for Rational

(%!) :: Integer -> Natural -> Rational infixl 7 Source #

Constructor functions for NRational

Rational specific typeclasses

class Unwrappable r => LorentzRational r Source #

Minimal complete definition

oppositeRational, reduce

Instances

Instances details
LorentzRational NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

numerator :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (NRational ': s) :-> (a ': s) Source #

denominator :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (NRational ': s) :-> (Natural ': s) Source #

deconstructRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (NRational ': s) :-> (a ': (Natural ': s)) Source #

constructRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => (a ': (Natural ': s)) :-> (NRational ': s) Source #

unsafePairToRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => ((a, Natural) ': s) :-> (NRational ': s) Source #

uncheckedPairToRational :: forall a (s :: [Type]). Unwrappabled NRational ~ (a, Natural) => ((a, Natural) ': s) :-> (NRational ': s) Source #

pairToRational :: forall a (s :: [Type]). (Unwrappabled NRational ~ (a, Natural), KnownValue NRational) => ((a, Natural) ': s) :-> (Maybe NRational ': s) Source #

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

reduce :: forall (s :: [Type]). (KnownList s, KnownList (ToTs s)) => (NRational ': s) :-> (NRational ': s) Source #

LorentzRational Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

numerator :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (Rational ': s) :-> (a ': s) Source #

denominator :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (Rational ': s) :-> (Natural ': s) Source #

deconstructRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (Rational ': s) :-> (a ': (Natural ': s)) Source #

constructRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => (a ': (Natural ': s)) :-> (Rational ': s) Source #

unsafePairToRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => ((a, Natural) ': s) :-> (Rational ': s) Source #

uncheckedPairToRational :: forall a (s :: [Type]). Unwrappabled Rational ~ (a, Natural) => ((a, Natural) ': s) :-> (Rational ': s) Source #

pairToRational :: forall a (s :: [Type]). (Unwrappabled Rational ~ (a, Natural), KnownValue Rational) => ((a, Natural) ': s) :-> (Maybe Rational ': s) Source #

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

reduce :: forall (s :: [Type]). (KnownList s, KnownList (ToTs s)) => (Rational ': s) :-> (Rational ': s) Source #

Constructors

mkRational_ :: (forall s0. ErrInstr (("numerator" :! Integer, "denominator" :! Natural) ': s0)) -> (Integer ': (Natural ': s)) :-> (Rational ': s) Source #

numerator :: (LorentzRational r, Unwrappabled r ~ (a, Natural)) => (r ': s) :-> (a ': s) Source #

denominator :: (LorentzRational r, Unwrappabled r ~ (a, Natural)) => (r ': s) :-> (Natural ': s) Source #

constructRational :: (LorentzRational r, Unwrappabled r ~ (a, Natural)) => (a ': (Natural ': s)) :-> (r ': s) Source #

deconstructRational :: (LorentzRational r, Unwrappabled r ~ (a, Natural)) => (r ': s) :-> (a ': (Natural ': s)) Source #

unsafePairToRational :: (LorentzRational r, Unwrappabled r ~ (a, Natural)) => ((a, Natural) ': s) :-> (r ': s) Source #

Orphan instances

CustomErrorHasDoc "zero_denominator" Source # 
Instance 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

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 #