Skip to content

Commit c519b09

Browse files
committed
Add FFI for block state managed by rust
1 parent 9b1274a commit c519b09

File tree

9 files changed

+646
-72
lines changed

9 files changed

+646
-72
lines changed
Lines changed: 81 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,11 @@
1-
{-# LANGUAGE OverloadedStrings #-}
2-
31
-- |
42
-- Bindings into the @plt-scheduler@ Rust library exposing safe wrappers.
53
--
64
-- Each foreign imported function must match the signature of functions found in @plt-scheduler/src/ffi.rs@.
75
module Concordium.PLTScheduler (
8-
PLTBlockState,
9-
initialPLTBlockState,
106
executeTransaction,
7+
ExecutionOutcome (..),
8+
ExecutionAccepts (..),
119
) where
1210

1311
import qualified Data.ByteString as BS
@@ -16,55 +14,100 @@ import qualified Data.Word as Word
1614
import qualified Foreign as FFI
1715
import qualified Foreign.C.Types as FFI
1816

17+
import qualified Concordium.PLTScheduler.PLTBlockState as PLTBlockState
18+
import qualified Concordium.Types as Types
19+
import qualified Data.FixedByteString as FixedByteString
20+
1921
-- | Execute a transaction payload modifying the `block_state` accordingly.
20-
-- The caller must ensure to rollback state changes in case of the transaction being rejected.
2122
--
2223
-- See @execute_transaction@ in @plt-scheduler@ rust crate for details.
2324
executeTransaction ::
2425
-- | Block state to mutate.
25-
PLTBlockState ->
26+
PLTBlockState.PLTBlockState ->
2627
-- | Transaction payload byte string.
2728
BS.ByteString ->
28-
-- | The events produced or the reject reason.
29-
IO (Either () ())
30-
executeTransaction blockState transactionPayload = do
31-
statusCode <- withPLTBlockState blockState $ \blockStatePtr ->
32-
BS.unsafeUseAsCStringLen transactionPayload $ \(transactionPayloadPtr, transactionPayloadLen) -> do
33-
ffiExecuteTransaction blockStatePtr (FFI.castPtr transactionPayloadPtr) (fromIntegral transactionPayloadLen)
34-
case statusCode of
35-
0 -> return $ Right ()
36-
1 -> return $ Left ()
37-
_ -> error "Unexpected status code from calling 'ffiExecuteTransaction'"
29+
-- | The account index of the account which signed as the sender of the transaction.
30+
Types.AccountIndex ->
31+
-- | The account address of the account which signed as the sender of the transaction.
32+
Types.AccountAddress ->
33+
-- | Remaining energy.
34+
Types.Energy ->
35+
-- | Outcome of the execution
36+
IO ExecutionOutcome
37+
executeTransaction
38+
blockState
39+
transactionPayload
40+
senderAccountIndex
41+
(Types.AccountAddress senderAccountAddress)
42+
remainingEnergy =
43+
FFI.alloca $ \remainingEnergyOut ->
44+
FFI.alloca $ \updatedBlockStatePtrOut -> do
45+
-- Invoke the ffi call
46+
statusCode <- PLTBlockState.withPLTBlockState blockState $ \blockStatePtr ->
47+
FixedByteString.withPtrReadOnly senderAccountAddress $ \senderAccountAddressPtr ->
48+
BS.unsafeUseAsCStringLen transactionPayload $
49+
\(transactionPayloadPtr, transactionPayloadLen) ->
50+
ffiExecuteTransaction
51+
blockStatePtr
52+
(FFI.castPtr transactionPayloadPtr)
53+
(fromIntegral transactionPayloadLen)
54+
(fromIntegral senderAccountIndex)
55+
senderAccountAddressPtr
56+
(fromIntegral remainingEnergy)
57+
updatedBlockStatePtrOut
58+
remainingEnergyOut
59+
-- Process the and construct the outcome
60+
newRemainingEnergy <- fromIntegral <$> FFI.peek remainingEnergyOut
61+
status <- case statusCode of
62+
0 -> do
63+
updatedBlockState <- FFI.peek updatedBlockStatePtrOut >>= PLTBlockState.wrapFFIPtr
64+
return $
65+
Right
66+
ExecutionAccepts
67+
{ eaUpdatedPLTBlockState = updatedBlockState,
68+
eaEvents = ()
69+
}
70+
1 -> return $ Left ()
71+
_ -> error "Unexpected status code from calling 'ffiExecuteTransaction'"
72+
return
73+
ExecutionOutcome
74+
{ erRemainingEnergy = newRemainingEnergy,
75+
erStatus = status
76+
}
3877

3978
foreign import ccall "ffi_execute_transaction"
4079
ffiExecuteTransaction ::
41-
FFI.Ptr PLTBlockState ->
80+
FFI.Ptr PLTBlockState.PLTBlockState ->
4281
-- | Pointer to transaction payload bytes.
4382
FFI.Ptr Word.Word8 ->
4483
-- | Byte length of transaction payload.
4584
FFI.CSize ->
85+
-- | The account index of the account which signed as the sender of the transaction.
86+
Word.Word64 ->
87+
-- | Pointer to 32 bytes representing the account address of the account which signed as the
88+
-- sender of the transaction.
89+
FFI.Ptr Word.Word8 ->
90+
-- | Remaining energy
91+
Word.Word64 ->
92+
-- | Output location for the updated block state.
93+
FFI.Ptr (FFI.Ptr PLTBlockState.PLTBlockState) ->
94+
-- | Output location for the remaining energy after execution.
95+
FFI.Ptr Word.Word64 ->
4696
-- | Status code
4797
IO Word.Word8
4898

49-
-- Block state FFI
50-
51-
-- | Opaque pointer to the PLT block state managed by the rust library.
52-
--
53-
-- Memory is deallocated using a finalizer.
54-
newtype PLTBlockState = PLTBlockState (FFI.ForeignPtr PLTBlockState)
55-
56-
-- | Allocate new initial block state
57-
initialPLTBlockState :: IO PLTBlockState
58-
initialPLTBlockState = do
59-
state <- ffiInitialPLTBlockState
60-
PLTBlockState <$> FFI.newForeignPtr ffiFreePLTBlockState state
99+
-- | The outcome of executing a transaction using the PLT scheduler.
100+
data ExecutionOutcome = ExecutionOutcome
101+
{ -- | The amount of energy remaining after the execution.
102+
erRemainingEnergy :: Types.Energy,
103+
-- | The resulting execution status.
104+
erStatus :: Either () ExecutionAccepts
105+
}
61106

62-
foreign import ccall "ffi_initial_plt_block_state" ffiInitialPLTBlockState :: IO (FFI.Ptr PLTBlockState)
63-
foreign import ccall unsafe "&ffi_free_plt_block_state" ffiFreePLTBlockState :: FFI.FinalizerPtr PLTBlockState
64-
65-
-- | Get temporary access to the block state pointer. The pointer should not be
66-
-- leaked from the computation.
67-
--
68-
-- This ensures the finalizer is not called until the computation is over.
69-
withPLTBlockState :: PLTBlockState -> (FFI.Ptr PLTBlockState -> IO a) -> IO a
70-
withPLTBlockState (PLTBlockState foreignPtr) = FFI.withForeignPtr foreignPtr
107+
-- | Additional execution outcome when the transaction gets accepted by the PLT scheduler.
108+
data ExecutionAccepts = ExecutionAccepts
109+
{ -- | The updated PLT block state after the execution
110+
eaUpdatedPLTBlockState :: PLTBlockState.PLTBlockState,
111+
-- | Events produced during the execution
112+
eaEvents :: ()
113+
}
Lines changed: 149 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,149 @@
1+
{-# LANGUAGE DerivingVia #-}
2+
3+
-- | Bindings to the PLT block state implementation found in @plt-scheduler/block_state.rs@.
4+
module Concordium.PLTScheduler.PLTBlockState (
5+
PLTBlockState,
6+
empty,
7+
wrapFFIPtr,
8+
withPLTBlockState,
9+
migrate,
10+
Hash,
11+
-- | Get the inner @SHA256.Hash@.
12+
innerSha256Hash,
13+
) where
14+
15+
import qualified Data.Serialize as Serialize
16+
import qualified Foreign as FFI
17+
18+
import qualified Concordium.Crypto.SHA256 as SHA256
19+
import qualified Concordium.GlobalState.ContractStateFFIHelpers as FFI
20+
import qualified Concordium.GlobalState.Persistent.BlobStore as BlobStore
21+
import qualified Concordium.Types.HashableTo as Hashable
22+
import Control.Monad.Trans (lift, liftIO)
23+
import qualified Data.FixedByteString as FixedByteString
24+
25+
-- | Opaque pointer to a immutable PLT block state save-point managed by the rust library.
26+
--
27+
-- Memory is deallocated using a finalizer.
28+
newtype PLTBlockState = PLTBlockState (FFI.ForeignPtr PLTBlockState)
29+
30+
-- | Helper function to convert a raw pointer passed by the Rust library into a `PLTBlockState` object.
31+
wrapFFIPtr :: FFI.Ptr PLTBlockState -> IO PLTBlockState
32+
wrapFFIPtr blockStatePtr = PLTBlockState <$> FFI.newForeignPtr ffiFreePLTBlockState blockStatePtr
33+
34+
-- | Deallocate a pointer to `PLTBlockState`.
35+
foreign import ccall unsafe "&ffi_free_plt_block_state"
36+
ffiFreePLTBlockState :: FFI.FinalizerPtr PLTBlockState
37+
38+
-- | Allocate new empty block state
39+
empty :: (BlobStore.MonadBlobStore m) => m PLTBlockState
40+
empty = liftIO $ do
41+
state <- ffiEmptyPLTBlockState
42+
wrapFFIPtr state
43+
44+
foreign import ccall "ffi_empty_plt_block_state"
45+
ffiEmptyPLTBlockState :: IO (FFI.Ptr PLTBlockState)
46+
47+
instance (BlobStore.MonadBlobStore m) => BlobStore.BlobStorable m PLTBlockState where
48+
load = do
49+
blobRef <- Serialize.get
50+
pure $! do
51+
loadCallback <- fst <$> BlobStore.getCallbacks
52+
liftIO $! do
53+
blockState <- ffiLoadPLTBlockState loadCallback blobRef
54+
wrapFFIPtr blockState
55+
storeUpdate pltBlockState = do
56+
storeCallback <- snd <$> BlobStore.getCallbacks
57+
blobRef <- liftIO $ withPLTBlockState pltBlockState $ ffiStorePLTBlockState storeCallback
58+
return (Serialize.put blobRef, pltBlockState)
59+
60+
-- | Load PLT block state from the given disk reference.
61+
foreign import ccall "ffi_load_plt_block_state"
62+
ffiLoadPLTBlockState ::
63+
-- | Called to read data from blob store.
64+
FFI.LoadCallback ->
65+
-- | Reference in the blob store.
66+
BlobStore.BlobRef PLTBlockState ->
67+
-- | Pointer to the loaded block state.
68+
IO (FFI.Ptr PLTBlockState)
69+
70+
-- | Write out the block state using the provided callback, and return a `BlobRef`.
71+
foreign import ccall "ffi_store_plt_block_state"
72+
ffiStorePLTBlockState ::
73+
-- | The provided closure is called to write data to blob store.
74+
FFI.StoreCallback ->
75+
-- | Pointer to the block state to write.
76+
FFI.Ptr PLTBlockState ->
77+
-- | New reference in the blob store.
78+
IO (BlobStore.BlobRef PLTBlockState)
79+
80+
instance (BlobStore.MonadBlobStore m) => BlobStore.Cacheable m PLTBlockState where
81+
cache blockState = do
82+
loadCallback <- fst <$> BlobStore.getCallbacks
83+
liftIO $! withPLTBlockState blockState (ffiCachePLTBlockState loadCallback)
84+
return blockState
85+
86+
-- | Cache block state into memory.
87+
foreign import ccall "ffi_cache_plt_block_state"
88+
ffiCachePLTBlockState ::
89+
-- | Called to read data from blob store.
90+
FFI.LoadCallback ->
91+
-- | Pointer to the block state to cache into memory.
92+
FFI.Ptr PLTBlockState ->
93+
IO ()
94+
95+
-- | The hash of some `PLTBlockState`.
96+
newtype Hash = Hash {innerSha256Hash :: SHA256.Hash}
97+
deriving newtype (Eq, Ord, Show, Serialize.Serialize)
98+
99+
instance (BlobStore.MonadBlobStore m) => Hashable.MHashableTo m Hash PLTBlockState where
100+
getHashM blockState = do
101+
loadCallback <- fst <$> BlobStore.getCallbacks
102+
((), hash) <-
103+
liftIO $
104+
withPLTBlockState blockState $
105+
FixedByteString.createWith . ffiHashPLTBlockState loadCallback
106+
return $ Hash (SHA256.Hash hash)
107+
108+
-- | Compute the hash of the block state.
109+
foreign import ccall "ffi_hash_plt_block_state"
110+
ffiHashPLTBlockState ::
111+
-- | Called to read data from blob store.
112+
FFI.LoadCallback ->
113+
-- | Pointer to the block state to write.
114+
FFI.Ptr PLTBlockState ->
115+
-- | Pointer to write destination of the hash
116+
FFI.Ptr FFI.Word8 ->
117+
IO ()
118+
119+
-- | Get temporary access to the block state pointer. The pointer should not be
120+
-- leaked from the computation.
121+
--
122+
-- This ensures the finalizer is not called until the computation is over.
123+
withPLTBlockState :: PLTBlockState -> (FFI.Ptr PLTBlockState -> IO a) -> IO a
124+
withPLTBlockState (PLTBlockState foreignPtr) = FFI.withForeignPtr foreignPtr
125+
126+
-- | Run migration during a protocol update.
127+
migrate ::
128+
(BlobStore.SupportMigration m t) =>
129+
-- | Current block state
130+
PLTBlockState ->
131+
-- | New migrated block state
132+
t m PLTBlockState
133+
migrate currentState = do
134+
loadCallback <- fst <$> lift BlobStore.getCallbacks
135+
storeCallback <- snd <$> BlobStore.getCallbacks
136+
newState <- liftIO $ withPLTBlockState currentState $ ffiMigratePLTBlockState loadCallback storeCallback
137+
liftIO $ PLTBlockState <$> FFI.newForeignPtr ffiFreePLTBlockState newState
138+
139+
-- | Migrate PLT block state from one blob store to another.
140+
foreign import ccall "ffi_migrate_plt_block_state"
141+
ffiMigratePLTBlockState ::
142+
-- | Called to read data from the old blob store.
143+
FFI.LoadCallback ->
144+
-- | Called to write data to the new blob store.
145+
FFI.StoreCallback ->
146+
-- | Pointer to the old block state.
147+
FFI.Ptr PLTBlockState ->
148+
-- | Pointer to the new block state.
149+
IO (FFI.Ptr PLTBlockState)

plt-scheduler/Cargo.lock

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

plt-scheduler/Cargo.toml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,3 +14,4 @@ concordium_base = {path = "../concordium-base/rust-src/concordium_base"}
1414
plt-deployment-unit = {path = "../plt-deployment-unit"}
1515
derive_more = { version = "2.1.0", features = ["into", "from"] }
1616
libc = { version = "0.2", optional = true }
17+
thiserror = "2.0.17"

0 commit comments

Comments
 (0)