Skip to content

Commit e8aec6a

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

File tree

9 files changed

+649
-70
lines changed

9 files changed

+649
-70
lines changed
Lines changed: 82 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,14 @@
11
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
23

34
-- |
45
-- Bindings into the @plt-scheduler@ Rust library exposing safe wrappers.
56
--
67
-- Each foreign imported function must match the signature of functions found in @plt-scheduler/src/ffi.rs@.
78
module Concordium.PLTScheduler (
8-
PLTBlockState,
9-
initialPLTBlockState,
109
executeTransaction,
10+
ExecutionOutcome (..),
11+
ExecutionAccepts (..),
1112
) where
1213

1314
import qualified Data.ByteString as BS
@@ -16,55 +17,100 @@ import qualified Data.Word as Word
1617
import qualified Foreign as FFI
1718
import qualified Foreign.C.Types as FFI
1819

20+
import qualified Concordium.PLTScheduler.PLTBlockState as PLTBlockState
21+
import qualified Concordium.Types as Types
22+
import qualified Data.FixedByteString as FixedByteString
23+
1924
-- | 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.
2125
--
2226
-- See @execute_transaction@ in @plt-scheduler@ rust crate for details.
2327
executeTransaction ::
2428
-- | Block state to mutate.
25-
PLTBlockState ->
29+
PLTBlockState.PLTBlockState ->
2630
-- | Transaction payload byte string.
2731
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'"
32+
-- | The account index of the account which signed as the sender of the transaction.
33+
Types.AccountIndex ->
34+
-- | The account address of the account which signed as the sender of the transaction.
35+
Types.AccountAddress ->
36+
-- | Remaining energy.
37+
Types.Energy ->
38+
-- | Outcome of the execution
39+
IO ExecutionOutcome
40+
executeTransaction
41+
blockState
42+
transactionPayload
43+
senderAccountIndex
44+
(Types.AccountAddress senderAccountAddress)
45+
remainingEnergy =
46+
FFI.alloca $ \remainingEnergyOut ->
47+
FFI.alloca $ \updatedBlockStatePtrOut -> do
48+
-- Invoke the ffi call
49+
statusCode <- PLTBlockState.withPLTBlockState blockState $ \blockStatePtr ->
50+
FixedByteString.withPtrReadOnly senderAccountAddress $ \senderAccountAddressPtr ->
51+
BS.unsafeUseAsCStringLen transactionPayload $
52+
\(transactionPayloadPtr, transactionPayloadLen) ->
53+
ffiExecuteTransaction
54+
blockStatePtr
55+
(FFI.castPtr transactionPayloadPtr)
56+
(fromIntegral transactionPayloadLen)
57+
(fromIntegral senderAccountIndex)
58+
senderAccountAddressPtr
59+
(fromIntegral remainingEnergy)
60+
updatedBlockStatePtrOut
61+
remainingEnergyOut
62+
-- Process the and construct the outcome
63+
newRemainingEnergy :: Types.Energy <- fromIntegral <$> FFI.peek remainingEnergyOut
64+
status <- case statusCode of
65+
0 -> do
66+
updatedBlockState <- FFI.peek updatedBlockStatePtrOut >>= PLTBlockState.wrapFFIPtr
67+
return $
68+
Right
69+
ExecutionAccepts
70+
{ eaUpdatedPLTBlockState = updatedBlockState,
71+
eaEvents = ()
72+
}
73+
1 -> return $ Left ()
74+
_ -> error "Unexpected status code from calling 'ffiExecuteTransaction'"
75+
return
76+
ExecutionOutcome
77+
{ erRemainingEnergy = newRemainingEnergy,
78+
erStatus = status
79+
}
3880

3981
foreign import ccall "ffi_execute_transaction"
4082
ffiExecuteTransaction ::
41-
FFI.Ptr PLTBlockState ->
83+
FFI.Ptr PLTBlockState.PLTBlockState ->
4284
-- | Pointer to transaction payload bytes.
4385
FFI.Ptr Word.Word8 ->
4486
-- | Byte length of transaction payload.
4587
FFI.CSize ->
88+
-- | The account index of the account which signed as the sender of the transaction.
89+
Word.Word64 ->
90+
-- | Pointer to 32 bytes representing the account address of the account which signed as the
91+
-- sender of the transaction.
92+
FFI.Ptr Word.Word8 ->
93+
-- | Remaining energy
94+
Word.Word64 ->
95+
-- | Output location for the updated block state.
96+
FFI.Ptr (FFI.Ptr PLTBlockState.PLTBlockState) ->
97+
-- | Output location for the remaining energy after execution.
98+
FFI.Ptr Word.Word64 ->
4699
-- | Status code
47100
IO Word.Word8
48101

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)
102+
-- | The outcome of executing a transaction using the PLT scheduler.
103+
data ExecutionOutcome = ExecutionOutcome
104+
{ -- | The amount of energy remaining after the execution.
105+
erRemainingEnergy :: Types.Energy,
106+
-- | The resulting execution status.
107+
erStatus :: Either () ExecutionAccepts
108+
}
55109

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