Skip to content

Commit

Permalink
More GasM updates
Browse files Browse the repository at this point in the history
  • Loading branch information
imalsogreg committed May 16, 2024
1 parent ba619bf commit 5e73901
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 12 deletions.
20 changes: 10 additions & 10 deletions gasmodel/Pact/Core/GasModel/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,9 @@ module Pact.Core.GasModel.Utils where

import Control.Lens
import Control.Monad.Except
import Control.Monad.IO.Class
import Control.DeepSeq
import Data.Default
import Data.Text (Text)
import Data.Map.Strict(Map)
import qualified Criterion as C
Expand All @@ -20,6 +22,7 @@ import qualified Database.SQLite3 as SQL
import Pact.Core.Builtin
import Pact.Core.Environment
import Pact.Core.Errors
import Pact.Core.Gas
import Pact.Core.Names
import Pact.Core.Literal
import Pact.Core.Type
Expand Down Expand Up @@ -233,20 +236,17 @@ gmLoaded = Loaded
, _loModules=M.singleton gmModuleName gmModuleData
, _loAllLoaded=gmFqMap}

prepopulateDb :: PactDb CoreBuiltin i -> IO ()
prepopulateDb :: Default i => PactDb CoreBuiltin i -> GasM (PactError i) ()
prepopulateDb pdb = do
_ <- _pdbBeginTx pdb Transactional
_ <- liftIO $ _pdbBeginTx pdb Transactional
_pdbCreateUserTable pdb def gasModelTable
_pdbWrite pdb expectNoGas Write (DUserTables gasModelTable) gmTableK1 gmTableV1
_pdbWrite pdb expectNoGas Write (DUserTables gasModelTable) gmTableK1 gmTableV1
_pdbWrite pdb expectNoGas Write DNamespaces gmNamespaceName gmNamespace
_pdbWrite pdb expectNoGas Write DKeySets gmKeysetName gmKeyset
_ <- _pdbCommitTx pdb
_pdbWrite pdb def Write (DUserTables gasModelTable) gmTableK1 gmTableV1
_pdbWrite pdb def Write (DUserTables gasModelTable) gmTableK1 gmTableV1
_pdbWrite pdb def Write DNamespaces gmNamespaceName gmNamespace
_pdbWrite pdb def Write DKeySets gmKeysetName gmKeyset
_ <- liftIO $ _pdbCommitTx pdb
pure ()

where
expectNoGas = \_ -> error "Expected no gas use (even charges of 0 gas)"

evaluateN
:: EvalEnv CoreBuiltin ()
-> EvalState CoreBuiltin ()
Expand Down
3 changes: 1 addition & 2 deletions pact/Pact/Core/Environment/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -185,13 +185,12 @@ data EvalState b i
, _esDefPactExec :: !(Maybe DefPactExec)
, _esGasLog :: !(Maybe [GasLogEntry b])
-- ^ Sequence of gas expendature events.
, _countBytesCounter :: Int
} deriving (Show, Generic)

instance (NFData b, NFData i) => NFData (EvalState b i)

instance Default (EvalState b i) where
def = EvalState def [] [] mempty Nothing Nothing 0
def = EvalState def [] [] mempty Nothing Nothing

makeClassy ''EvalState

Expand Down

0 comments on commit 5e73901

Please sign in to comment.