liqwid-plutarch-extra-3.21.1: A collection of Plutarch extras from Liqwid Labs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Plutarch.Extra.FixedDecimal

Synopsis

Documentation

newtype FixedDecimal (exp :: Natural) Source #

Fixed precision number. It behaves like scientific notation: exp shows to what power of base 10 an integer is multiplied.

For example, Underlying value of 123456 with type `FixedDecimal 3` is `123.456 (123456 * 10 ^ -3)`. If it's coerced into `FixedDecimal 5`, it will be `1.23456 (123456 * 10 ^ -5)`. `FixedDecimal 0` will be identical to Integer.

Note, exp is the negative exponent to base 10.

Compared to Rational, Fixed gives addition and subtraction as fast as regular PInteger, allows negative values, and does not require simplifications.

Performance note: Prefer emul, ediv, toFixedZero, and fromFixedZero. Then group calculations in a way that requires the least amount of convertExp calls.

Since: 3.12.0

Constructors

FixedDecimal 

Fields

Instances

Instances details
KnownNat exp => FromJSON (FixedDecimal exp) Source #

Since: 3.16.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

KnownNat exp => ToJSON (FixedDecimal exp) Source #

Since: 3.16.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Generic (FixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Associated Types

type Rep (FixedDecimal exp) :: Type -> Type Source #

Methods

from :: FixedDecimal exp -> Rep (FixedDecimal exp) x Source #

to :: Rep (FixedDecimal exp) x -> FixedDecimal exp Source #

KnownNat exp => Num (FixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

KnownNat exp => Fractional (FixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

KnownNat n => Real (FixedDecimal n) Source #

Since: 3.14.4

Instance details

Defined in Plutarch.Extra.FixedDecimal

Show (FixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Eq (FixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Ord (FixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

PConstantDecl (FixedDecimal unit) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Associated Types

type PConstantRepr (FixedDecimal unit) Source #

type PConstanted (FixedDecimal unit) :: PType Source #

FromData (FixedDecimal unit) Source #

Since: 3.16.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

ToData (FixedDecimal unit) Source #

Since: 3.16.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

UnsafeFromData (FixedDecimal unit) Source #

Since: 3.16.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

type Rep (FixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

type Rep (FixedDecimal exp) = D1 ('MetaData "FixedDecimal" "Plutarch.Extra.FixedDecimal" "liqwid-plutarch-extra-3.21.1-KPadsMN5oqEA2Ctxwq6qig" 'True) (C1 ('MetaCons "FixedDecimal" 'PrefixI 'True) (S1 ('MetaSel ('Just "numerator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))
type PConstantRepr (FixedDecimal unit) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

type PConstanted (FixedDecimal unit) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

fixedNumerator :: forall (exp :: Natural). FixedDecimal exp -> Integer Source #

Integer numerator of FixedDecimal

Since: 3.12.0

fixedDenominator :: forall (exp :: Natural). KnownNat exp => FixedDecimal exp -> Integer Source #

Integer denominator of FixedDecimal

Since: 3.12.0

emul :: forall (expA :: Natural) (expB :: Natural). FixedDecimal expA -> FixedDecimal expB -> FixedDecimal (expA + expB) Source #

Exponent-changing multiplication (implemented with a single integer multiplication)

Since: 3.12.0

ediv :: forall (expA :: Natural) (expB :: Natural). FixedDecimal expA -> FixedDecimal expB -> FixedDecimal (expA - expB) Source #

Exponent-changing division (implemented with a single integer division)

Since: 3.12.0

toFixedZero :: Integer -> FixedDecimal 0 Source #

Zero-cost transformation from Integer to 'FixedDecimal 0'.

For use together with emul and ediv.

Since: 3.12.1

fromFixedZero :: FixedDecimal 0 -> Integer Source #

Zero-cost transformation from 'FixedDecimal 0' to Integer.

For use together with emul and ediv.

Since: 3.12.1

convertExp :: forall (expA :: Natural) (expB :: Natural). (KnownNat expA, KnownNat expB) => FixedDecimal expA -> FixedDecimal expB Source #

Convert to a different type-level exponent.

Since: 3.12.0

newtype PFixedDecimal (exp :: Natural) (s :: S) Source #

Fixed precision number. It behaves like scientific notation: exp shows to what power of base 10 an integer is multiplied.

For example, Underlying value of 123456 with type `PFixedDecimal 3` is `123.456 (123456 * 10 ^ -3)`. If it's coerced into `PFixedDecimal 5`, it will be `1.23456 (123456 * 10 ^ -5)`. `PFixedDecimal 0` will be identical to PInteger.

Note, exp is the negative exponent to base 10. PFixed does not support positive exponent.

Compared to PRational, PFixed gives addition and subtraction as fast as regular PInteger, allows negative values, and does not require simplifications.

Performance note: Prefer pemul, pediv, ptoFixedZero, and pfromFixedZero. Then group calculations in a way that requires the least amount of convertExp calls.

Since: 3.12.0

Constructors

PFixedDecimal (Term s PInteger) 

Instances

Instances details
PEq (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

(#==) :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) -> Term s PBool Source #

POrd (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

PPartialOrd (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

(#<=) :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) -> Term s PBool Source #

PIsData (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PFixedDecimal exp)) -> Term s (PFixedDecimal exp) Source #

pdataImpl :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s PData Source #

KnownNat exp => PIntegral (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

pdiv :: forall (s :: S). Term s (PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp)) Source #

pmod :: forall (s :: S). Term s (PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp)) Source #

pquot :: forall (s :: S). Term s (PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp)) Source #

prem :: forall (s :: S). Term s (PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp)) Source #

DerivePlutusType (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Associated Types

type DPTStrat (PFixedDecimal exp) Source #

PlutusType (PFixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

pcon' :: forall (s :: S). PFixedDecimal exp s -> Term s (PInner (PFixedDecimal exp)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PFixedDecimal exp)) -> (PFixedDecimal exp s -> Term s b) -> Term s b Source #

PUnsafeLiftDecl (PFixedDecimal unit) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Associated Types

type PLifted (PFixedDecimal unit) = (r :: Type) Source #

KnownNat exp => PNum (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

(#+) :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) Source #

(#-) :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) Source #

(#*) :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) Source #

pnegate :: forall (s :: S). Term s (PFixedDecimal exp :--> PFixedDecimal exp) Source #

pabs :: forall (s :: S). Term s (PFixedDecimal exp :--> PFixedDecimal exp) Source #

psignum :: forall (s :: S). Term s (PFixedDecimal exp :--> PFixedDecimal exp) Source #

pfromInteger :: forall (s :: S). Integer -> Term s (PFixedDecimal exp) Source #

KnownNat exp => PFractional (PFixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

(#/) :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp) Source #

precip :: forall (s :: S). Term s (PFixedDecimal exp :--> PFixedDecimal exp) Source #

pfromRational :: forall (s :: S). Term s (PRational :--> PFixedDecimal exp) Source #

KnownNat exp => PShow (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PFixedDecimal exp) -> Term s PString Source #

Generic (PFixedDecimal exp s) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

Associated Types

type Rep (PFixedDecimal exp s) :: Type -> Type Source #

Methods

from :: PFixedDecimal exp s -> Rep (PFixedDecimal exp s) x Source #

to :: Rep (PFixedDecimal exp s) x -> PFixedDecimal exp s Source #

type DPTStrat (PFixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

type PContravariant' (PFixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

type PContravariant' (PFixedDecimal exp) = All2 PContravariant'' (PCode (PFixedDecimal exp))
type PCovariant' (PFixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

type PCovariant' (PFixedDecimal exp) = All2 PCovariant'' (PCode (PFixedDecimal exp))
type PInner (PFixedDecimal exp) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

type PVariant' (PFixedDecimal exp) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

type PVariant' (PFixedDecimal exp) = All2 PVariant'' (PCode (PFixedDecimal exp))
type PLifted (PFixedDecimal unit) Source # 
Instance details

Defined in Plutarch.Extra.FixedDecimal

type Rep (PFixedDecimal exp s) Source #

Since: 3.12.0

Instance details

Defined in Plutarch.Extra.FixedDecimal

type Rep (PFixedDecimal exp s) = D1 ('MetaData "PFixedDecimal" "Plutarch.Extra.FixedDecimal" "liqwid-plutarch-extra-3.21.1-KPadsMN5oqEA2Ctxwq6qig" 'True) (C1 ('MetaCons "PFixedDecimal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PInteger))))

pfixedNumerator :: forall (s :: S) (unit :: Natural). Term s (PFixedDecimal unit) -> Term s PInteger Source #

Integer numerator of PFixedDecimal

Since: 3.12.0

pfixedDenominator :: forall (s :: S) (unit :: Natural). KnownNat unit => Term s (PFixedDecimal unit) -> Term s PInteger Source #

Integer denominator of PFixedDecimal

Since: 3.12.0

pemul :: forall (s :: S) (expA :: Natural) (expB :: Natural). Term s (PFixedDecimal expA) -> Term s (PFixedDecimal expB) -> Term s (PFixedDecimal (expA + expB)) Source #

Exponent-changing multiplication (implemented with a single integer multiplication)

Since: 3.12.0

pediv :: forall (s :: S) (expA :: Natural) (expB :: Natural). Term s (PFixedDecimal expA) -> Term s (PFixedDecimal expB) -> Term s (PFixedDecimal (expA - expB)) Source #

Exponent-changing division (implemented with a single integer division)

Since: 3.12.0

ptoFixedZero :: forall (s :: S). Term s PInteger -> Term s (PFixedDecimal 0) Source #

Zero-cost transformation from PInteger to 'PFixedDecimal 0'.

For use together with pemul and pediv.

Since: 3.12.1

pfromFixedZero :: forall (s :: S). Term s (PFixedDecimal 0) -> Term s PInteger Source #

Zero-cost transformation from 'PFixedDecimal 0' to PInteger.

For use together with pemul and pediv.

Since: 3.12.1

pconvertExp :: forall (exp2 :: Natural) (exp1 :: Natural) (s :: S). (KnownNat exp1, KnownNat exp2) => Term s (PFixedDecimal exp1 :--> PFixedDecimal exp2) Source #

Change decimal point.

  • Caution* This function will drop precision when converting from more decimal points to less decimal points.

For example, converting `1.234 :: Fixed 3` into `Fixed 1` will drop hundredth and thousandth place value and will give `1.2 :: Fixed 1`.

There is not data loss going from small decimal points to big decimal points, but they will take up more memory.

Since: 3.12.0

pfromFixedDecimal :: forall (exp :: Natural) (s :: S). KnownNat exp => Term s (PFixedDecimal exp :--> PInteger) Source #

Convert PFixed into PInteger.

  • Caution* This will drop all decimal point values. For example, converting `12.345 :: Fixed 3` will give `12 :: Integer`. Pay close attention using this function.

If one needs to retrive all decimal point values, use pto instead.

Since: 3.12.0

ptoFixedDecimal :: forall (exp :: Natural) (s :: S). KnownNat exp => Term s (PInteger :--> PFixedDecimal exp) Source #

Convert PInteger into PFixed.

There is no dataloss, but takes more memory.

Since: 3.12.0

ptoRational :: forall (exp :: Natural) (s :: S). KnownNat exp => Term s (PFixedDecimal exp :--> PRational) Source #

Convert PFixed into PRational.

Note, it will *not* simplify. There is no data loss.

Since: 3.12.0

punsafeMkFixedDecimal :: forall (exp :: Natural) (s :: S). Term s (PInteger :--> PFixedDecimal exp) Source #

Make PFixed from PInteger.

  • Caution* PInteger given will not be equal to returned PFixed. Input ignores decimal point: `1234 :: Integer` will return `12.34 :: Fixed 2`.

Since: 3.12.0