{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Plutarch.Integer (PInteger, PIntegral (..)) where
import GHC.Generics (Generic)
import Plutarch.Bool (PEq, POrd, PPartialOrd, pif, (#<), (#<=), (#==))
import Plutarch.Internal (
Term,
phoistAcyclic,
(#),
(:-->),
)
import Plutarch.Internal.Newtype (PlutusTypeNewtype)
import Plutarch.Internal.Other (POpaque, pto)
import Plutarch.Internal.PLam (plam)
import Plutarch.Internal.PlutusType (DPTStrat, DerivePlutusType, PInner, PlutusType)
import Plutarch.Lift (
DerivePConstantDirect (DerivePConstantDirect),
PConstantDecl,
PLifted,
PUnsafeLiftDecl,
pconstant,
)
import Plutarch.Num (PNum, pabs, pfromInteger, pnegate, psignum, (#*), (#+), (#-))
import Plutarch.Unsafe (punsafeBuiltin, punsafeDowncast)
import PlutusCore qualified as PLC
newtype PInteger s = PInteger (Term s POpaque)
deriving stock (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PInteger s) x -> PInteger s
forall (s :: S) x. PInteger s -> Rep (PInteger s) x
$cto :: forall (s :: S) x. Rep (PInteger s) x -> PInteger s
$cfrom :: forall (s :: S) x. PInteger s -> Rep (PInteger s) x
Generic)
deriving anyclass (forall (s :: S). PInteger s -> Term s (PInner PInteger)
forall (s :: S) (b :: PType).
Term s (PInner PInteger) -> (PInteger 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 PInteger) -> (PInteger s -> Term s b) -> Term s b
$cpmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PInteger) -> (PInteger s -> Term s b) -> Term s b
pcon' :: forall (s :: S). PInteger s -> Term s (PInner PInteger)
$cpcon' :: forall (s :: S). PInteger s -> Term s (PInner PInteger)
PlutusType)
instance DerivePlutusType PInteger where type DPTStrat _ = PlutusTypeNewtype
instance PUnsafeLiftDecl PInteger where type PLifted PInteger = Integer
deriving via (DerivePConstantDirect Integer PInteger) instance PConstantDecl Integer
class PIntegral a where
pdiv :: Term s (a :--> a :--> a)
default pdiv :: PIntegral (PInner a) => Term s (a :--> a :--> a)
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 a
x Term s a
y -> forall (s :: S) (a :: PType). Term s (PInner a) -> Term s a
punsafeDowncast 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 a
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 a
y
pmod :: Term s (a :--> a :--> a)
default pmod :: PIntegral (PInner a) => Term s (a :--> a :--> a)
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 a
x Term s a
y -> forall (s :: S) (a :: PType). Term s (PInner a) -> Term s a
punsafeDowncast 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 a
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 a
y
pquot :: Term s (a :--> a :--> a)
default pquot :: PIntegral (PInner a) => Term s (a :--> a :--> a)
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 a
x Term s a
y -> forall (s :: S) (a :: PType). Term s (PInner a) -> Term s a
punsafeDowncast 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 a
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 a
y
prem :: Term s (a :--> a :--> a)
default prem :: PIntegral (PInner a) => Term s (a :--> a :--> a)
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 a
x Term s a
y -> forall (s :: S) (a :: PType). Term s (PInner a) -> Term s a
punsafeDowncast 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 a
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 a
y
instance PIntegral PInteger where
pdiv :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger))
pdiv = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.DivideInteger
pmod :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger))
pmod = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.ModInteger
pquot :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger))
pquot = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.QuotientInteger
prem :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger))
prem = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.RemainderInteger
instance PEq PInteger where
Term s PInteger
x #== :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool
#== Term s PInteger
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.EqualsInteger 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
y
instance PPartialOrd PInteger where
Term s PInteger
x #<= :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool
#<= Term s PInteger
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.LessThanEqualsInteger 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
y
Term s PInteger
x #< :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool
#< Term s PInteger
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.LessThanInteger 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
y
instance POrd PInteger
instance PNum PInteger where
Term s PInteger
x #+ :: forall (s :: S).
Term s PInteger -> Term s PInteger -> Term s PInteger
#+ Term s PInteger
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.AddInteger 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
y
Term s PInteger
x #- :: forall (s :: S).
Term s PInteger -> Term s PInteger -> Term s PInteger
#- Term s PInteger
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.SubtractInteger 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
y
Term s PInteger
x #* :: forall (s :: S).
Term s PInteger -> Term s PInteger -> Term s PInteger
#* Term s PInteger
y = forall (s :: S) (a :: PType). DefaultFun -> Term s a
punsafeBuiltin DefaultFun
PLC.MultiplyInteger 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
y
pabs :: forall (s :: S). Term s (PInteger :--> PInteger)
pabs = 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 \Term s PInteger
x -> forall (s :: S) (a :: PType).
Term s PBool -> Term s a -> Term s a -> Term s a
pif (Term s PInteger
x forall (t :: PType) (s :: S).
PPartialOrd t =>
Term s t -> Term s t -> Term s PBool
#<= Term s PInteger
-1) (forall a. Num a => a -> a
negate Term s PInteger
x) Term s PInteger
x
pnegate :: forall (s :: S). Term s (PInteger :--> PInteger)
pnegate = 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 (Term s PInteger
0 #-)
psignum :: forall (s :: S). Term s (PInteger :--> PInteger)
psignum = forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
plam \Term s PInteger
x ->
forall (s :: S) (a :: PType).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
(Term s PInteger
x forall (t :: PType) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== Term s PInteger
0)
Term s PInteger
0
forall a b. (a -> b) -> a -> b
$ forall (s :: S) (a :: PType).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
(Term s PInteger
x forall (t :: PType) (s :: S).
PPartialOrd t =>
Term s t -> Term s t -> Term s PBool
#<= Term s PInteger
0)
(Term s PInteger
-1)
Term s PInteger
1
pfromInteger :: forall (s :: S). Integer -> Term s PInteger
pfromInteger = forall (p :: PType) (s :: S). PLift p => PLifted p -> Term s p
pconstant