module Plutarch.Extra.FixedDecimal (
FixedDecimal (..),
fixedNumerator,
fixedDenominator,
emul,
ediv,
toFixedZero,
fromFixedZero,
convertExp,
PFixedDecimal (..),
pfixedNumerator,
pfixedDenominator,
pemul,
pediv,
ptoFixedZero,
pfromFixedZero,
pconvertExp,
pfromFixedDecimal,
ptoFixedDecimal,
ptoRational,
punsafeMkFixedDecimal,
) where
import Control.Monad (unless)
import Data.Aeson ((.:), (.=), (<?>))
import Data.Aeson qualified as Aeson
import Data.Aeson.Types (JSONPathElement (Key), Parser)
import Data.Proxy (Proxy (Proxy))
import Data.Ratio ((%))
import GHC.Real (Ratio ((:%)))
import GHC.TypeLits (KnownNat, Natural, natVal, type (+), type (-))
import Plutarch.Extra.Rational ((#%))
import Plutarch.Lift (
PConstantDecl (PConstantRepr, PConstanted, pconstantFromRepr, pconstantToRepr),
PUnsafeLiftDecl (PLifted),
)
import Plutarch.Num (
PNum,
pabs,
pfromInteger,
(#*),
(#-),
)
import Plutarch.Rational (PFractional (pfromRational, precip, (#/)))
import Plutarch.Show (pshow')
import Plutarch.Unsafe (punsafeCoerce)
import PlutusLedgerApi.V1 qualified as PlutusTx
newtype FixedDecimal (exp :: Natural) = FixedDecimal {forall (exp :: Natural). FixedDecimal exp -> Integer
numerator :: Integer}
deriving stock (forall (exp :: Natural) x.
Rep (FixedDecimal exp) x -> FixedDecimal exp
forall (exp :: Natural) x.
FixedDecimal exp -> Rep (FixedDecimal exp) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (exp :: Natural) x.
Rep (FixedDecimal exp) x -> FixedDecimal exp
$cfrom :: forall (exp :: Natural) x.
FixedDecimal exp -> Rep (FixedDecimal exp) x
Generic, FixedDecimal exp -> FixedDecimal exp -> Bool
forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FixedDecimal exp -> FixedDecimal exp -> Bool
$c/= :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
== :: FixedDecimal exp -> FixedDecimal exp -> Bool
$c== :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
Eq, FixedDecimal exp -> FixedDecimal exp -> Bool
FixedDecimal exp -> FixedDecimal exp -> Ordering
forall (exp :: Natural). Eq (FixedDecimal exp)
forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Ordering
forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
$cmin :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
max :: FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
$cmax :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
>= :: FixedDecimal exp -> FixedDecimal exp -> Bool
$c>= :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
> :: FixedDecimal exp -> FixedDecimal exp -> Bool
$c> :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
<= :: FixedDecimal exp -> FixedDecimal exp -> Bool
$c<= :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
< :: FixedDecimal exp -> FixedDecimal exp -> Bool
$c< :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Bool
compare :: FixedDecimal exp -> FixedDecimal exp -> Ordering
$ccompare :: forall (exp :: Natural).
FixedDecimal exp -> FixedDecimal exp -> Ordering
Ord, Int -> FixedDecimal exp -> ShowS
forall (exp :: Natural). Int -> FixedDecimal exp -> ShowS
forall (exp :: Natural). [FixedDecimal exp] -> ShowS
forall (exp :: Natural). FixedDecimal exp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FixedDecimal exp] -> ShowS
$cshowList :: forall (exp :: Natural). [FixedDecimal exp] -> ShowS
show :: FixedDecimal exp -> String
$cshow :: forall (exp :: Natural). FixedDecimal exp -> String
showsPrec :: Int -> FixedDecimal exp -> ShowS
$cshowsPrec :: forall (exp :: Natural). Int -> FixedDecimal exp -> ShowS
Show)
instance
forall (exp :: Natural).
(KnownNat exp) =>
Aeson.ToJSON (FixedDecimal exp)
where
toJSON :: FixedDecimal exp -> Value
toJSON (FixedDecimal Integer
num) =
[Pair] -> Value
Aeson.object
[ Key
"numerator" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Integer
num
, Key
"exponent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp)
]
toEncoding :: FixedDecimal exp -> Encoding
toEncoding (FixedDecimal Integer
num) =
Series -> Encoding
Aeson.pairs (Key
"numerator" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Integer
num forall a. Semigroup a => a -> a -> a
<> Key
"exponent" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))
instance
forall (exp :: Natural).
(KnownNat exp) =>
Aeson.FromJSON (FixedDecimal exp)
where
parseJSON :: Value -> Parser (FixedDecimal exp)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"FixedDecimal" forall a b. (a -> b) -> a -> b
$ \Object
v -> do
Integer
num <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"numerator" forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
"numerator"
()
_ <-
((Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"exponent") forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= Integer -> Parser ()
checkExponent)
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
"exponent"
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal Integer
num
where
expectedExponent :: Integer
expectedExponent :: Integer
expectedExponent = forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp)
checkExponent :: Integer -> Parser ()
checkExponent :: Integer -> Parser ()
checkExponent Integer
e =
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
unless (Integer
e forall a. Eq a => a -> a -> Bool
== Integer
expectedExponent) forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$
String
"expected: "
forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Integer
expectedExponent
forall a. Semigroup a => a -> a -> a
<> String
", but encountered "
forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Integer
e
fixedNumerator :: forall (exp :: Natural). FixedDecimal exp -> Integer
fixedNumerator :: forall (exp :: Natural). FixedDecimal exp -> Integer
fixedNumerator (FixedDecimal Integer
num) = Integer
num
fixedDenominator :: forall (exp :: Natural). (KnownNat exp) => FixedDecimal exp -> Integer
fixedDenominator :: forall (exp :: Natural).
KnownNat exp =>
FixedDecimal exp -> Integer
fixedDenominator FixedDecimal exp
_ = Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp)
emul ::
forall (expA :: Natural) (expB :: Natural).
FixedDecimal expA ->
FixedDecimal expB ->
FixedDecimal (expA + expB)
emul :: forall (expA :: Natural) (expB :: Natural).
FixedDecimal expA
-> FixedDecimal expB -> FixedDecimal (expA + expB)
emul (FixedDecimal Integer
a) (FixedDecimal Integer
b) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall a b. (a -> b) -> a -> b
$ Integer
a forall a. Num a => a -> a -> a
* Integer
b
ediv ::
forall (expA :: Natural) (expB :: Natural).
FixedDecimal expA ->
FixedDecimal expB ->
FixedDecimal (expA - expB)
ediv :: forall (expA :: Natural) (expB :: Natural).
FixedDecimal expA
-> FixedDecimal expB -> FixedDecimal (expA - expB)
ediv (FixedDecimal Integer
a) (FixedDecimal Integer
b) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall a b. (a -> b) -> a -> b
$ Integer
a forall a. Integral a => a -> a -> a
`div` Integer
b
toFixedZero :: Integer -> FixedDecimal 0
toFixedZero :: Integer -> FixedDecimal 0
toFixedZero = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal
fromFixedZero :: FixedDecimal 0 -> Integer
fromFixedZero :: FixedDecimal 0 -> Integer
fromFixedZero (FixedDecimal Integer
n) = Integer
n
convertExp ::
forall (expA :: Natural) (expB :: Natural).
(KnownNat expA, KnownNat expB) =>
FixedDecimal expA ->
FixedDecimal expB
convertExp :: forall (expA :: Natural) (expB :: Natural).
(KnownNat expA, KnownNat expB) =>
FixedDecimal expA -> FixedDecimal expB
convertExp (FixedDecimal Integer
a) =
let ediff :: Integer
ediff = forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @expB) forall a. Num a => a -> a -> a
- forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @expA)
in forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall a b. (a -> b) -> a -> b
$
if Integer
ediff forall a. Ord a => a -> a -> Bool
>= Integer
0
then Integer
a forall a. Num a => a -> a -> a
* Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
ediff
else Integer
a forall a. Integral a => a -> a -> a
`div` Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (-Integer
ediff)
instance (KnownNat exp) => Num (FixedDecimal exp) where
(FixedDecimal Integer
a) + :: FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
+ (FixedDecimal Integer
b) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal (Integer
a forall a. Num a => a -> a -> a
+ Integer
b)
fa :: FixedDecimal exp
fa@(FixedDecimal Integer
a) * :: FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
* (FixedDecimal Integer
b) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal (Integer
a forall a. Num a => a -> a -> a
* Integer
b forall a. Integral a => a -> a -> a
`div` forall (exp :: Natural).
KnownNat exp =>
FixedDecimal exp -> Integer
fixedDenominator FixedDecimal exp
fa)
abs :: FixedDecimal exp -> FixedDecimal exp
abs (FixedDecimal Integer
a) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
abs Integer
a
signum :: FixedDecimal exp -> FixedDecimal exp
signum fa :: FixedDecimal exp
fa@(FixedDecimal Integer
a) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
signum Integer
a forall a. Num a => a -> a -> a
* forall (exp :: Natural).
KnownNat exp =>
FixedDecimal exp -> Integer
fixedDenominator FixedDecimal exp
fa
negate :: FixedDecimal exp -> FixedDecimal exp
negate (FixedDecimal Integer
a) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal (forall a. Num a => a -> a
negate Integer
a)
fromInteger :: Integer -> FixedDecimal exp
fromInteger Integer
i = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal (Integer
i forall a. Num a => a -> a -> a
* Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))
instance (KnownNat exp) => Fractional (FixedDecimal exp) where
fromRational :: Rational -> FixedDecimal exp
fromRational (Integer
a :% Integer
b) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall a b. (a -> b) -> a -> b
$ Integer
a forall a. Num a => a -> a -> a
* Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp) forall a. Integral a => a -> a -> a
`div` Integer
b
(FixedDecimal Integer
a) / :: FixedDecimal exp -> FixedDecimal exp -> FixedDecimal exp
/ (FixedDecimal Integer
b) = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall a b. (a -> b) -> a -> b
$ Integer
a forall a. Num a => a -> a -> a
* Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp) forall a. Integral a => a -> a -> a
`div` Integer
b
instance KnownNat n => Real (FixedDecimal n) where
toRational :: FixedDecimal n -> Rational
toRational FixedDecimal n
f = forall (exp :: Natural). FixedDecimal exp -> Integer
fixedNumerator FixedDecimal n
f forall a. Integral a => a -> a -> Ratio a
% forall (exp :: Natural).
KnownNat exp =>
FixedDecimal exp -> Integer
fixedDenominator FixedDecimal n
f
newtype PFixedDecimal (exp :: Natural) (s :: S)
= PFixedDecimal (Term s PInteger)
deriving stock
(
forall (exp :: Natural) (s :: S) x.
Rep (PFixedDecimal exp s) x -> PFixedDecimal exp s
forall (exp :: Natural) (s :: S) x.
PFixedDecimal exp s -> Rep (PFixedDecimal exp s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (exp :: Natural) (s :: S) x.
Rep (PFixedDecimal exp s) x -> PFixedDecimal exp s
$cfrom :: forall (exp :: Natural) (s :: S) x.
PFixedDecimal exp s -> Rep (PFixedDecimal exp s) x
Generic
)
deriving anyclass
(
forall (exp :: Natural) (s :: S).
PFixedDecimal exp s -> Term s (PInner (PFixedDecimal exp))
forall (exp :: Natural) (s :: S) (b :: PType).
Term s (PInner (PFixedDecimal exp))
-> (PFixedDecimal exp s -> Term s b) -> Term s b
forall (a :: PType).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: PType).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
pmatch' :: forall (s :: S) (b :: PType).
Term s (PInner (PFixedDecimal exp))
-> (PFixedDecimal exp s -> Term s b) -> Term s b
$cpmatch' :: forall (exp :: Natural) (s :: S) (b :: PType).
Term s (PInner (PFixedDecimal exp))
-> (PFixedDecimal exp s -> Term s b) -> Term s b
pcon' :: forall (s :: S).
PFixedDecimal exp s -> Term s (PInner (PFixedDecimal exp))
$cpcon' :: forall (exp :: Natural) (s :: S).
PFixedDecimal exp s -> Term s (PInner (PFixedDecimal exp))
PlutusType
,
forall (exp :: Natural) (s :: S).
Term s (PAsData (PFixedDecimal exp)) -> Term s (PFixedDecimal exp)
forall (exp :: Natural) (s :: S).
Term s (PFixedDecimal exp) -> Term s PData
forall (a :: PType).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
pdataImpl :: forall (s :: S). Term s (PFixedDecimal exp) -> Term s PData
$cpdataImpl :: forall (exp :: Natural) (s :: S).
Term s (PFixedDecimal exp) -> Term s PData
pfromDataImpl :: forall (s :: S).
Term s (PAsData (PFixedDecimal exp)) -> Term s (PFixedDecimal exp)
$cpfromDataImpl :: forall (exp :: Natural) (s :: S).
Term s (PAsData (PFixedDecimal exp)) -> Term s (PFixedDecimal exp)
PIsData
,
forall (exp :: Natural) (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
forall (t :: PType).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
#== :: forall (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
$c#== :: forall (exp :: Natural) (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
PEq
,
forall (exp :: Natural). PEq (PFixedDecimal exp)
forall (exp :: Natural) (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
forall (t :: PType).
PEq t
-> (forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> (forall (s :: S). Term s t -> Term s t -> Term s PBool)
-> PPartialOrd t
#< :: forall (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
$c#< :: forall (exp :: Natural) (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
#<= :: forall (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
$c#<= :: forall (exp :: Natural) (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s PBool
PPartialOrd
,
forall (exp :: Natural). PPartialOrd (PFixedDecimal exp)
forall (t :: PType). PPartialOrd t -> POrd t
POrd
)
instance forall (exp :: Natural). DerivePlutusType (PFixedDecimal exp) where
type DPTStrat _ = PlutusTypeNewtype
instance PUnsafeLiftDecl (PFixedDecimal unit) where
type PLifted (PFixedDecimal unit) = FixedDecimal unit
instance PConstantDecl (FixedDecimal unit) where
type PConstantRepr (FixedDecimal unit) = PConstantRepr Integer
type PConstanted (FixedDecimal unit) = PFixedDecimal unit
pconstantToRepr :: FixedDecimal unit -> PConstantRepr (FixedDecimal unit)
pconstantToRepr (FixedDecimal Integer
x) = forall h. PConstantDecl h => h -> PConstantRepr h
pconstantToRepr Integer
x
pconstantFromRepr :: PConstantRepr (FixedDecimal unit) -> Maybe (FixedDecimal unit)
pconstantFromRepr PConstantRepr (FixedDecimal unit)
x = forall (exp :: Natural). Integer -> FixedDecimal exp
FixedDecimal forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall h. PConstantDecl h => PConstantRepr h -> Maybe h
pconstantFromRepr PConstantRepr (FixedDecimal unit)
x
deriving via
Integer
instance
PlutusTx.ToData (FixedDecimal unit)
deriving via
Integer
instance
PlutusTx.FromData (FixedDecimal unit)
deriving via
Integer
instance
PlutusTx.UnsafeFromData (FixedDecimal unit)
instance forall (exp :: Natural). KnownNat exp => PShow (PFixedDecimal exp) where
pshow' :: forall (s :: S).
Bool -> Term s (PFixedDecimal exp) -> Term s PString
pshow' Bool
wrap Term s (PFixedDecimal exp)
z =
Term s PString -> Term s PString
wrap' forall a b. (a -> b) -> a -> b
$
Term s PString
"PFixedDecimal "
forall a. Semigroup a => a -> a -> a
<> forall (a :: PType) (s :: S). PShow a => Term s a -> Term s PString
pshow (forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pquot forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
z forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
base)
forall a. Semigroup a => a -> a -> a
<> Term s PString
"."
forall a. Semigroup a => a -> a -> a
<> (forall (s :: S). Term s (PInteger :--> (PString :--> PString))
replicateStr forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant Integer
baseExp forall (a :: PType) (s :: S).
PNum a =>
Term s a -> Term s a -> Term s a
#- (forall {s :: S}. Term s (PInteger :--> PInteger)
places forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
decimal)) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PString
"0")
forall a. Semigroup a => a -> a -> a
<> forall (a :: PType) (s :: S). PShow a => Term s a -> Term s PString
pshow Term s PInteger
decimal
where
baseExp :: Integer
baseExp = forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp)
base :: Term s PInteger
base = forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant forall a b. (a -> b) -> a -> b
$ PLifted PInteger
10 forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
baseExp
decimal :: Term s PInteger
decimal = forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
prem forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (forall (a :: PType) (s :: S). PNum a => Term s (a :--> a)
pabs forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
z) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
base
wrap' :: Term s PString -> Term s PString
wrap' Term s PString
x = if Bool
wrap then Term s PString
"(" forall a. Semigroup a => a -> a -> a
<> Term s PString
x forall a. Semigroup a => a -> a -> a
<> Term s PString
")" else Term s PString
x
places :: Term s (PInteger :--> PInteger)
places =
forall (s :: S) (a :: PType) (b :: PType).
Term s (((a :--> b) :--> (a :--> b)) :--> (a :--> b))
pfix forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
#$ forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PInteger :--> PInteger)
self Term s PInteger
x ->
forall (s :: S) (a :: PType) (b :: PType).
Term s a -> (Term s a -> Term s b) -> Term s b
plet (forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pquot forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
x forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
10) forall a b. (a -> b) -> a -> b
$ \Term s PInteger
q ->
forall (s :: S) (a :: PType).
Term s PBool -> Term s a -> Term s a -> Term s a
pif (Term s PInteger
q forall (t :: PType) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s PInteger
0) Term s PInteger
1 (Term s PInteger
1 forall a. Num a => a -> a -> a
+ Term s (PInteger :--> PInteger)
self forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PInteger
q)
replicateStr :: Term s (PInteger :--> PString :--> PString)
replicateStr :: forall (s :: S). Term s (PInteger :--> (PString :--> PString))
replicateStr =
forall (s :: S) (a :: PType) (b :: PType).
Term s (((a :--> b) :--> (a :--> b)) :--> (a :--> b))
pfix forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
#$ forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PInteger :--> (PString :--> PString))
self Term s PInteger
x Term s PString
str ->
forall (s :: S) (a :: PType).
Term s PBool -> Term s a -> Term s a -> Term s a
pif (Term s PInteger
0 forall (t :: PType) (s :: S).
PPartialOrd t =>
Term s t -> Term s t -> Term s PBool
#< Term s PInteger
x) (Term s PString
str forall a. Semigroup a => a -> a -> a
<> (Term s (PInteger :--> (PString :--> PString))
self forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger
x forall (a :: PType) (s :: S).
PNum a =>
Term s a -> Term s a -> Term s a
#- Term s PInteger
1) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s PString
str)) Term s PString
""
instance forall (exp :: Natural). KnownNat exp => PNum (PFixedDecimal exp) where
Term s (PFixedDecimal exp)
a' #* :: forall (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp)
#* Term s (PFixedDecimal exp)
b' =
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic
( forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
a Term s (PFixedDecimal exp)
b ->
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$
forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
a forall a. Num a => a -> a -> a
* forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
b) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))
)
# a'
# b'
pfromInteger :: forall (s :: S). Integer -> Term s (PFixedDecimal exp)
pfromInteger =
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Num a => a -> a -> a
* (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp)))
instance forall (exp :: Natural). KnownNat exp => PIntegral (PFixedDecimal exp) where
pdiv :: forall (s :: S).
Term
s
(PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp))
pdiv =
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
x Term s (PFixedDecimal exp)
y ->
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$
forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
x forall a. Num a => a -> a -> a
* forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
y
pmod :: forall (s :: S).
Term
s
(PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp))
pmod = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$ forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
x Term s (PFixedDecimal exp)
y -> forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pmod forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
x forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
y
pquot :: forall (s :: S).
Term
s
(PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp))
pquot =
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
x Term s (PFixedDecimal exp)
y ->
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$
forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pquot forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
x forall a. Num a => a -> a -> a
* forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
y
prem :: forall (s :: S).
Term
s
(PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp))
prem =
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$ forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
x Term s (PFixedDecimal exp)
y -> forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
prem forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
x forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
y
instance (KnownNat exp) => PFractional (PFixedDecimal exp) where
pfromRational ::
forall (s :: S).
Term s (PRational :--> PFixedDecimal exp)
pfromRational :: forall (s :: S). Term s (PRational :--> PFixedDecimal exp)
pfromRational = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch forall a b. (a -> b) -> a -> b
$ \(PRational Term s PInteger
num Term s PPositive
denom) ->
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (Term s PInteger
num forall a. Num a => a -> a -> a
* forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s PPositive
denom
Term s (PFixedDecimal exp)
a' #/ :: forall (s :: S).
Term s (PFixedDecimal exp)
-> Term s (PFixedDecimal exp) -> Term s (PFixedDecimal exp)
#/ Term s (PFixedDecimal exp)
b' = Term
s
(PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp))
go forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PFixedDecimal exp)
a' forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PFixedDecimal exp)
b'
where
go :: Term
s
(PFixedDecimal exp :--> (PFixedDecimal exp :--> PFixedDecimal exp))
go = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
a Term s (PFixedDecimal exp)
b ->
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# (forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
a forall a. Num a => a -> a -> a
* forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
b
precip :: forall (s :: S). Term s (PFixedDecimal exp :--> PFixedDecimal exp)
precip =
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
x ->
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (Integer
2 forall a. Num a => a -> a -> a
* forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))) forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
x
pfixedNumerator ::
forall (s :: S) (unit :: Natural).
Term s (PFixedDecimal unit) ->
Term s PInteger
pfixedNumerator :: forall (s :: S) (unit :: Natural).
Term s (PFixedDecimal unit) -> Term s PInteger
pfixedNumerator = forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto
pfixedDenominator ::
forall (s :: S) (unit :: Natural).
(KnownNat unit) =>
Term s (PFixedDecimal unit) ->
Term s PInteger
pfixedDenominator :: forall (s :: S) (unit :: Natural).
KnownNat unit =>
Term s (PFixedDecimal unit) -> Term s PInteger
pfixedDenominator Term s (PFixedDecimal unit)
_ = forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant forall a b. (a -> b) -> a -> b
$ Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @unit)
pemul ::
forall (s :: S) (expA :: Natural) (expB :: Natural).
Term s (PFixedDecimal expA) ->
Term s (PFixedDecimal expB) ->
Term s (PFixedDecimal (expA + expB))
pemul :: forall (s :: S) (expA :: Natural) (expB :: Natural).
Term s (PFixedDecimal expA)
-> Term s (PFixedDecimal expB)
-> Term s (PFixedDecimal (expA + expB))
pemul Term s (PFixedDecimal expA)
a Term s (PFixedDecimal expB)
b = forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$ forall (s :: S) (unit :: Natural).
Term s (PFixedDecimal unit) -> Term s PInteger
pfixedNumerator Term s (PFixedDecimal expA)
a forall a. Num a => a -> a -> a
* forall (s :: S) (unit :: Natural).
Term s (PFixedDecimal unit) -> Term s PInteger
pfixedNumerator Term s (PFixedDecimal expB)
b
pediv ::
forall (s :: S) (expA :: Natural) (expB :: Natural).
Term s (PFixedDecimal expA) ->
Term s (PFixedDecimal expB) ->
Term s (PFixedDecimal (expA - expB))
pediv :: forall (s :: S) (expA :: Natural) (expB :: Natural).
Term s (PFixedDecimal expA)
-> Term s (PFixedDecimal expB)
-> Term s (PFixedDecimal (expA - expB))
pediv Term s (PFixedDecimal expA)
a Term s (PFixedDecimal expB)
b = forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$ forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (unit :: Natural).
Term s (PFixedDecimal unit) -> Term s PInteger
pfixedNumerator Term s (PFixedDecimal expA)
a forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (unit :: Natural).
Term s (PFixedDecimal unit) -> Term s PInteger
pfixedNumerator Term s (PFixedDecimal expB)
b
ptoFixedZero ::
forall (s :: S).
Term s PInteger ->
Term s (PFixedDecimal 0)
ptoFixedZero :: forall (s :: S). Term s PInteger -> Term s (PFixedDecimal 0)
ptoFixedZero = forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal
pfromFixedZero ::
forall (s :: S).
Term s (PFixedDecimal 0) ->
Term s PInteger
pfromFixedZero :: forall (s :: S). Term s (PFixedDecimal 0) -> Term s PInteger
pfromFixedZero = forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto
pconvertExp ::
forall (exp2 :: Natural) (exp1 :: Natural) (s :: S).
(KnownNat exp1, KnownNat exp2) =>
Term s (PFixedDecimal exp1 :--> PFixedDecimal exp2)
pconvertExp :: forall (exp2 :: Natural) (exp1 :: Natural) (s :: S).
(KnownNat exp1, KnownNat exp2) =>
Term s (PFixedDecimal exp1 :--> PFixedDecimal exp2)
pconvertExp = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp1)
z ->
let ediff :: Integer
ediff = (forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp2) forall a. Num a => a -> a -> a
- forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp1))
in forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal forall a b. (a -> b) -> a -> b
$
case forall a. Ord a => a -> a -> Ordering
compare Integer
ediff Integer
0 of
Ordering
GT -> forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp1)
z forall a. Num a => a -> a -> a
* forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall a. Num a => a -> a
abs Integer
ediff)
Ordering
EQ -> forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp1)
z
Ordering
LT -> forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp1)
z forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ (-Integer
ediff))
pfromFixedDecimal ::
forall (exp :: Natural) (s :: S).
KnownNat exp =>
Term s (PFixedDecimal exp :--> PInteger)
pfromFixedDecimal :: forall (exp :: Natural) (s :: S).
KnownNat exp =>
Term s (PFixedDecimal exp :--> PInteger)
pfromFixedDecimal = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s (PFixedDecimal exp)
z ->
if Integer
expVal forall a. Eq a => a -> a -> Bool
== Integer
0
then forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
z
else forall (a :: PType) (s :: S).
PIntegral a =>
Term s (a :--> (a :--> a))
pdiv forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
# forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
z forall (s :: S) (a :: PType) (b :: PType).
HasCallStack =>
Term s (a :--> b) -> Term s a -> Term s b
#$ forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
expVal)
where
expVal :: Integer
expVal = forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp)
ptoFixedDecimal ::
forall (exp :: Natural) (s :: S).
KnownNat exp =>
Term s (PInteger :--> PFixedDecimal exp)
ptoFixedDecimal :: forall (exp :: Natural) (s :: S).
KnownNat exp =>
Term s (PInteger :--> PFixedDecimal exp)
ptoFixedDecimal = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$ \Term s PInteger
z ->
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (exp :: Natural) (s :: S).
Term s PInteger -> PFixedDecimal exp s
PFixedDecimal
forall a b. (a -> b) -> a -> b
$ if Integer
expVal forall a. Eq a => a -> a -> Bool
== Integer
0
then Term s PInteger
z
else Term s PInteger
z forall a. Num a => a -> a -> a
* forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))
where
expVal :: Integer
expVal = forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp)
ptoRational ::
forall (exp :: Natural) (s :: S).
KnownNat exp =>
Term s (PFixedDecimal exp :--> PRational)
ptoRational :: forall (exp :: Natural) (s :: S).
KnownNat exp =>
Term s (PFixedDecimal exp :--> PRational)
ptoRational = forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic forall a b. (a -> b) -> a -> b
$
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall a b. (a -> b) -> a -> b
$
\Term s (PFixedDecimal exp)
z -> forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s (PFixedDecimal exp)
z forall (s :: S).
Term s PInteger -> Term s PInteger -> Term s PRational
#% forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant (Integer
10 forall a b. (Num a, Integral b) => a -> b -> a
^ forall (n :: Natural) (proxy :: Natural -> Type).
KnownNat n =>
proxy n -> Integer
natVal (forall {k} (t :: k). Proxy t
Proxy @exp))
punsafeMkFixedDecimal ::
forall (exp :: Natural) (s :: S).
Term s (PInteger :--> PFixedDecimal exp)
punsafeMkFixedDecimal :: forall (exp :: Natural) (s :: S).
Term s (PInteger :--> PFixedDecimal exp)
punsafeMkFixedDecimal = forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam forall (s :: S) (a :: PType) (b :: PType). Term s a -> Term s b
punsafeCoerce