{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE StrictData #-}
module PlutusCore.Evaluation.Machine.ExBudget
( ExBudget(..)
, minusExBudget
, ExBudgetBuiltin(..)
, ExRestrictingBudget(..)
, LowerIntialCharacter
, enormousBudget
)
where
import PlutusCore.Evaluation.Machine.ExMemory
import PlutusPrelude hiding (toList)
import Data.Char (toLower)
import Data.Semigroup
import Deriving.Aeson
import Language.Haskell.TH.Lift (Lift)
import NoThunks.Class
import Prettyprinter
data LowerIntialCharacter
instance StringModifier LowerIntialCharacter where
getStringModifier :: String -> String
getStringModifier String
"" = String
""
getStringModifier (Char
c : String
xs) = Char -> Char
toLower Char
c Char -> String -> String
forall a. a -> [a] -> [a]
: String
xs
class ExBudgetBuiltin fun exBudgetCat where
exBudgetBuiltin :: fun -> exBudgetCat
instance ExBudgetBuiltin fun () where
exBudgetBuiltin :: fun -> ()
exBudgetBuiltin fun
_ = ()
data ExBudget = ExBudget { ExBudget -> ExCPU
exBudgetCPU :: ExCPU, ExBudget -> ExMemory
exBudgetMemory :: ExMemory }
deriving stock (ExBudget -> ExBudget -> Bool
(ExBudget -> ExBudget -> Bool)
-> (ExBudget -> ExBudget -> Bool) -> Eq ExBudget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExBudget -> ExBudget -> Bool
$c/= :: ExBudget -> ExBudget -> Bool
== :: ExBudget -> ExBudget -> Bool
$c== :: ExBudget -> ExBudget -> Bool
Eq, Int -> ExBudget -> String -> String
[ExBudget] -> String -> String
ExBudget -> String
(Int -> ExBudget -> String -> String)
-> (ExBudget -> String)
-> ([ExBudget] -> String -> String)
-> Show ExBudget
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExBudget] -> String -> String
$cshowList :: [ExBudget] -> String -> String
show :: ExBudget -> String
$cshow :: ExBudget -> String
showsPrec :: Int -> ExBudget -> String -> String
$cshowsPrec :: Int -> ExBudget -> String -> String
Show, (forall x. ExBudget -> Rep ExBudget x)
-> (forall x. Rep ExBudget x -> ExBudget) -> Generic ExBudget
forall x. Rep ExBudget x -> ExBudget
forall x. ExBudget -> Rep ExBudget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExBudget x -> ExBudget
$cfrom :: forall x. ExBudget -> Rep ExBudget x
Generic, ExBudget -> Q Exp
ExBudget -> Q (TExp ExBudget)
(ExBudget -> Q Exp)
-> (ExBudget -> Q (TExp ExBudget)) -> Lift ExBudget
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: ExBudget -> Q (TExp ExBudget)
$cliftTyped :: ExBudget -> Q (TExp ExBudget)
lift :: ExBudget -> Q Exp
$clift :: ExBudget -> Q Exp
Lift)
deriving anyclass (PrettyBy config, ExBudget -> ()
(ExBudget -> ()) -> NFData ExBudget
forall a. (a -> ()) -> NFData a
rnf :: ExBudget -> ()
$crnf :: ExBudget -> ()
NFData, Context -> ExBudget -> IO (Maybe ThunkInfo)
Proxy ExBudget -> String
(Context -> ExBudget -> IO (Maybe ThunkInfo))
-> (Context -> ExBudget -> IO (Maybe ThunkInfo))
-> (Proxy ExBudget -> String)
-> NoThunks ExBudget
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy ExBudget -> String
$cshowTypeOf :: Proxy ExBudget -> String
wNoThunks :: Context -> ExBudget -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> ExBudget -> IO (Maybe ThunkInfo)
noThunks :: Context -> ExBudget -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> ExBudget -> IO (Maybe ThunkInfo)
NoThunks)
deriving (Value -> Parser [ExBudget]
Value -> Parser ExBudget
(Value -> Parser ExBudget)
-> (Value -> Parser [ExBudget]) -> FromJSON ExBudget
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ExBudget]
$cparseJSONList :: Value -> Parser [ExBudget]
parseJSON :: Value -> Parser ExBudget
$cparseJSON :: Value -> Parser ExBudget
FromJSON, [ExBudget] -> Encoding
[ExBudget] -> Value
ExBudget -> Encoding
ExBudget -> Value
(ExBudget -> Value)
-> (ExBudget -> Encoding)
-> ([ExBudget] -> Value)
-> ([ExBudget] -> Encoding)
-> ToJSON ExBudget
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ExBudget] -> Encoding
$ctoEncodingList :: [ExBudget] -> Encoding
toJSONList :: [ExBudget] -> Value
$ctoJSONList :: [ExBudget] -> Value
toEncoding :: ExBudget -> Encoding
$ctoEncoding :: ExBudget -> Encoding
toJSON :: ExBudget -> Value
$ctoJSON :: ExBudget -> Value
ToJSON) via CustomJSON '[FieldLabelModifier LowerIntialCharacter] ExBudget
minusExBudget :: ExBudget -> ExBudget -> ExBudget
minusExBudget :: ExBudget -> ExBudget -> ExBudget
minusExBudget (ExBudget ExCPU
c1 ExMemory
m1) (ExBudget ExCPU
c2 ExMemory
m2) = ExCPU -> ExMemory -> ExBudget
ExBudget (ExCPU
c1ExCPU -> ExCPU -> ExCPU
forall a. Num a => a -> a -> a
-ExCPU
c2) (ExMemory
m1ExMemory -> ExMemory -> ExMemory
forall a. Num a => a -> a -> a
-ExMemory
m2)
instance Semigroup ExBudget where
{-# INLINE (<>) #-}
(ExBudget ExCPU
cpu1 ExMemory
mem1) <> :: ExBudget -> ExBudget -> ExBudget
<> (ExBudget ExCPU
cpu2 ExMemory
mem2) = ExCPU -> ExMemory -> ExBudget
ExBudget (ExCPU
cpu1 ExCPU -> ExCPU -> ExCPU
forall a. Semigroup a => a -> a -> a
<> ExCPU
cpu2) (ExMemory
mem1 ExMemory -> ExMemory -> ExMemory
forall a. Semigroup a => a -> a -> a
<> ExMemory
mem2)
{-# INLINE stimes #-}
stimes :: b -> ExBudget -> ExBudget
stimes b
r (ExBudget (ExCPU CostingInteger
cpu) (ExMemory CostingInteger
mem)) = ExCPU -> ExMemory -> ExBudget
ExBudget (CostingInteger -> ExCPU
ExCPU (b -> CostingInteger
forall a b. (Integral a, Num b) => a -> b
fromIntegral b
r CostingInteger -> CostingInteger -> CostingInteger
forall a. Num a => a -> a -> a
* CostingInteger
cpu)) (CostingInteger -> ExMemory
ExMemory (b -> CostingInteger
forall a b. (Integral a, Num b) => a -> b
fromIntegral b
r CostingInteger -> CostingInteger -> CostingInteger
forall a. Num a => a -> a -> a
* CostingInteger
mem))
instance Monoid ExBudget where
mempty :: ExBudget
mempty = ExCPU -> ExMemory -> ExBudget
ExBudget ExCPU
forall a. Monoid a => a
mempty ExMemory
forall a. Monoid a => a
mempty
instance Pretty ExBudget where
pretty :: ExBudget -> Doc ann
pretty (ExBudget ExCPU
cpu ExMemory
memory) = Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
parens (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold
[ Doc ann
"{ cpu: ", ExCPU -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ExCPU
cpu, Doc ann
forall ann. Doc ann
line
, Doc ann
"| mem: ", ExMemory -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ExMemory
memory, Doc ann
forall ann. Doc ann
line
, Doc ann
"}"
]
newtype ExRestrictingBudget = ExRestrictingBudget
{ ExRestrictingBudget -> ExBudget
unExRestrictingBudget :: ExBudget
} deriving stock (Int -> ExRestrictingBudget -> String -> String
[ExRestrictingBudget] -> String -> String
ExRestrictingBudget -> String
(Int -> ExRestrictingBudget -> String -> String)
-> (ExRestrictingBudget -> String)
-> ([ExRestrictingBudget] -> String -> String)
-> Show ExRestrictingBudget
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExRestrictingBudget] -> String -> String
$cshowList :: [ExRestrictingBudget] -> String -> String
show :: ExRestrictingBudget -> String
$cshow :: ExRestrictingBudget -> String
showsPrec :: Int -> ExRestrictingBudget -> String -> String
$cshowsPrec :: Int -> ExRestrictingBudget -> String -> String
Show, ExRestrictingBudget -> ExRestrictingBudget -> Bool
(ExRestrictingBudget -> ExRestrictingBudget -> Bool)
-> (ExRestrictingBudget -> ExRestrictingBudget -> Bool)
-> Eq ExRestrictingBudget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExRestrictingBudget -> ExRestrictingBudget -> Bool
$c/= :: ExRestrictingBudget -> ExRestrictingBudget -> Bool
== :: ExRestrictingBudget -> ExRestrictingBudget -> Bool
$c== :: ExRestrictingBudget -> ExRestrictingBudget -> Bool
Eq)
deriving newtype (b -> ExRestrictingBudget -> ExRestrictingBudget
NonEmpty ExRestrictingBudget -> ExRestrictingBudget
ExRestrictingBudget -> ExRestrictingBudget -> ExRestrictingBudget
(ExRestrictingBudget -> ExRestrictingBudget -> ExRestrictingBudget)
-> (NonEmpty ExRestrictingBudget -> ExRestrictingBudget)
-> (forall b.
Integral b =>
b -> ExRestrictingBudget -> ExRestrictingBudget)
-> Semigroup ExRestrictingBudget
forall b.
Integral b =>
b -> ExRestrictingBudget -> ExRestrictingBudget
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> ExRestrictingBudget -> ExRestrictingBudget
$cstimes :: forall b.
Integral b =>
b -> ExRestrictingBudget -> ExRestrictingBudget
sconcat :: NonEmpty ExRestrictingBudget -> ExRestrictingBudget
$csconcat :: NonEmpty ExRestrictingBudget -> ExRestrictingBudget
<> :: ExRestrictingBudget -> ExRestrictingBudget -> ExRestrictingBudget
$c<> :: ExRestrictingBudget -> ExRestrictingBudget -> ExRestrictingBudget
Semigroup, Semigroup ExRestrictingBudget
ExRestrictingBudget
Semigroup ExRestrictingBudget
-> ExRestrictingBudget
-> (ExRestrictingBudget
-> ExRestrictingBudget -> ExRestrictingBudget)
-> ([ExRestrictingBudget] -> ExRestrictingBudget)
-> Monoid ExRestrictingBudget
[ExRestrictingBudget] -> ExRestrictingBudget
ExRestrictingBudget -> ExRestrictingBudget -> ExRestrictingBudget
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [ExRestrictingBudget] -> ExRestrictingBudget
$cmconcat :: [ExRestrictingBudget] -> ExRestrictingBudget
mappend :: ExRestrictingBudget -> ExRestrictingBudget -> ExRestrictingBudget
$cmappend :: ExRestrictingBudget -> ExRestrictingBudget -> ExRestrictingBudget
mempty :: ExRestrictingBudget
$cmempty :: ExRestrictingBudget
$cp1Monoid :: Semigroup ExRestrictingBudget
Monoid)
deriving newtype ([ExRestrictingBudget] -> Doc ann
ExRestrictingBudget -> Doc ann
(forall ann. ExRestrictingBudget -> Doc ann)
-> (forall ann. [ExRestrictingBudget] -> Doc ann)
-> Pretty ExRestrictingBudget
forall ann. [ExRestrictingBudget] -> Doc ann
forall ann. ExRestrictingBudget -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: [ExRestrictingBudget] -> Doc ann
$cprettyList :: forall ann. [ExRestrictingBudget] -> Doc ann
pretty :: ExRestrictingBudget -> Doc ann
$cpretty :: forall ann. ExRestrictingBudget -> Doc ann
Pretty, PrettyBy config, ExRestrictingBudget -> ()
(ExRestrictingBudget -> ()) -> NFData ExRestrictingBudget
forall a. (a -> ()) -> NFData a
rnf :: ExRestrictingBudget -> ()
$crnf :: ExRestrictingBudget -> ()
NFData)
enormousBudget :: ExRestrictingBudget
enormousBudget :: ExRestrictingBudget
enormousBudget = ExBudget -> ExRestrictingBudget
ExRestrictingBudget (ExBudget -> ExRestrictingBudget)
-> ExBudget -> ExRestrictingBudget
forall a b. (a -> b) -> a -> b
$ ExCPU -> ExMemory -> ExBudget
ExBudget (CostingInteger -> ExCPU
ExCPU CostingInteger
maxInt) (CostingInteger -> ExMemory
ExMemory CostingInteger
maxInt)
where maxInt :: CostingInteger
maxInt = Int -> CostingInteger
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
forall a. Bounded a => a
maxBound ::Int)