Skip to content

Commit

Permalink
Add documentation.
Browse files Browse the repository at this point in the history
  • Loading branch information
abizjak committed Dec 23, 2021
1 parent cdd07b9 commit eefe1d6
Show file tree
Hide file tree
Showing 9 changed files with 150 additions and 98 deletions.
2 changes: 1 addition & 1 deletion concordium-consensus/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ default-extensions:
flags:
dynamic:
manual: True
default: False
default: True

library:
source-dirs: src
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -81,10 +81,10 @@ putInstancesV0 (Instances (Tree _ t)) = do
case inst of
InstanceV0 i -> do
putWord8 2
putInstanceV0 i
putV0InstanceV0 i
InstanceV1 i -> do
putWord8 3
putInstanceV1 i
putV1InstanceV0 i

-- |Deserialize 'Instances' in V0 format.
getInstancesV0
Expand All @@ -95,6 +95,6 @@ getInstancesV0 resolve = Instances <$> constructM buildInstance
buildInstance idx = getWord8 >>= \case
0 -> return Nothing
1 -> Just . Left <$> get
2 -> Just . Right . InstanceV0 <$> getInstanceV0 resolve idx
3 -> Just . Right . InstanceV1 <$> getInstanceV1 resolve idx
2 -> Just . Right . InstanceV0 <$> getV0InstanceV0 resolve idx
3 -> Just . Right . InstanceV1 <$> getV1InstanceV0 resolve idx
_ -> fail "Bad instance list"
Original file line number Diff line number Diff line change
Expand Up @@ -42,27 +42,34 @@ type ModuleIndex = Word64
--------------------------------------------------------------------------------

-- |A module contains both the module interface and the raw source code of the
-- module.
-- module. The module is parameterized by the wasm version, which determines the shape
-- of the module interface.
data ModuleV v = ModuleV {
-- | The instrumented module, ready to be instantiated.
moduleVInterface :: !(GSWasm.ModuleInterfaceV v),
-- | The raw module binary source.
moduleVSource :: !WasmModule
} deriving (Show)

-- Create the class HasSource a with a function
-- source :: Lens a WasmModule
-- Create the class HasSource a with functions
-- source :: Lens a WasmModule and interface :: Lens (ModuleV v) (GSWasm.ModuleInterfaceV v)
makeFields ''ModuleV

-- |A module, either of version 0 or 1. This is only used when storing a module
-- independently, e.g., in the module table. When a module is referenced from a
-- contract instance we use the ModuleV type directly so we may tie the version
-- of the module to the version of the instance.
data Module where
ModuleV0 :: ModuleV GSWasm.V0 -> Module
ModuleV1 :: ModuleV GSWasm.V1 -> Module
deriving(Show)

-- |Helper (internal to the module) to convert from a module to an interface.
fromModule :: Module -> GSWasm.ModuleInterface
fromModule (ModuleV0 v) = GSWasm.ModuleInterfaceV0 (moduleVInterface v)
fromModule (ModuleV1 v) = GSWasm.ModuleInterfaceV1 (moduleVInterface v)

-- |Helper to convert from an interface to a module.
toModule :: GSWasm.ModuleInterface -> WasmModule -> Module
toModule (GSWasm.ModuleInterfaceV0 moduleVInterface) moduleVSource = ModuleV0 ModuleV{..}
toModule (GSWasm.ModuleInterfaceV1 moduleVInterface) moduleVSource = ModuleV1 ModuleV{..}
Expand Down
23 changes: 12 additions & 11 deletions concordium-consensus/src/Concordium/GlobalState/Instance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -219,9 +219,9 @@ updateInstance' amnt val (InstanceV0 i) = InstanceV0 $ updateInstanceV' amnt val
updateInstance' amnt val (InstanceV1 i) = InstanceV1 $ updateInstanceV' amnt val i


-- |Serialize a smart contract instance in V0 format.
putInstanceV0 :: Putter (InstanceV GSWasm.V0)
putInstanceV0 InstanceV{ _instanceVParameters = InstanceParameters{..}, ..} = do
-- |Serialize a V0 smart contract instance in V0 format.
putV0InstanceV0 :: Putter (InstanceV GSWasm.V0)
putV0InstanceV0 InstanceV{ _instanceVParameters = InstanceParameters{..}, ..} = do
-- InstanceParameters
-- Only put the Subindex part of the address
put (contractSubindex _instanceAddress)
Expand All @@ -233,8 +233,9 @@ putInstanceV0 InstanceV{ _instanceVParameters = InstanceParameters{..}, ..} = do
put _instanceVModel
put _instanceVAmount

putInstanceV1 :: Putter (InstanceV GSWasm.V1)
putInstanceV1 InstanceV{ _instanceVParameters = InstanceParameters{..}, ..} = do
-- |Serialize a V1 smart contract instance in V0 format.
putV1InstanceV0 :: Putter (InstanceV GSWasm.V1)
putV1InstanceV0 InstanceV{ _instanceVParameters = InstanceParameters{..}, ..} = do
-- InstanceParameters
-- Only put the Subindex part of the address
put (contractSubindex _instanceAddress)
Expand All @@ -247,14 +248,14 @@ putInstanceV1 InstanceV{ _instanceVParameters = InstanceParameters{..}, ..} = do
put _instanceVAmount


-- |Deserialize a smart contract instance in V0 format.
getInstanceV0
-- |Deserialize a V0 smart contract instance in V0 format.
getV0InstanceV0
:: (ModuleRef -> Wasm.InitName -> Maybe (Set.Set Wasm.ReceiveName, GSWasm.ModuleInterface))
-- ^Function for resolving the receive functions and module interface.
-> ContractIndex
-- ^Index of the contract
-> Get (InstanceV GSWasm.V0)
getInstanceV0 resolve idx = do
getV0InstanceV0 resolve idx = do
-- InstanceParameters
subindex <- get
let _instanceAddress = ContractAddress idx subindex
Expand All @@ -270,14 +271,14 @@ getInstanceV0 resolve idx = do
_instanceVAmount <- get
return $ makeInstanceV instanceInitName instanceReceiveFuns instanceModuleInterface _instanceVModel _instanceVAmount instanceOwner _instanceAddress

-- |Deserialize a smart contract instance in V0 format.
getInstanceV1
-- |Deserialize a V1 smart contract instance in V0 format.
getV1InstanceV0
:: (ModuleRef -> Wasm.InitName -> Maybe (Set.Set Wasm.ReceiveName, GSWasm.ModuleInterface))
-- ^Function for resolving the receive functions and module interface.
-> ContractIndex
-- ^Index of the contract
-> Get (InstanceV GSWasm.V1)
getInstanceV1 resolve idx = do
getV1InstanceV0 resolve idx = do
-- InstanceParameters
subindex <- get
let _instanceAddress = ContractAddress idx subindex
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -45,30 +45,33 @@ type ModuleIndex = Word64

--------------------------------------------------------------------------------

-- |A module contains both the module interface and a plain reference to where
-- the raw source code of the module is stored in the blobstore.
-- |A module contains both the module interface and the raw source code of the
-- module. The module is parameterized by the wasm version, which determines the shape
-- of the module interface.
data ModuleV v = ModuleV {
-- | The instrumented module, ready to be instantiated.
moduleVInterface :: !(GSWasm.ModuleInterfaceV v),
-- | A plain reference to the raw module binary source.
-- | A plain reference to the raw module binary source. This is generally not needed by consensus, so
-- it is almost always simply kept on disk.
moduleVSource :: !(BlobRef WasmModule)
}
deriving(Show)

-- Create two typeclasses HasInterface a _ and HasSource a _
-- with methods source :: Lens' a (BlobRef WasmModule) and
-- interface :: Lens' a (GSWasm.ModuleInterfaceV v)
-- interface :: Lens' (ModuleV v) (GSWasm.ModuleInterfaceV v)
makeFields ''ModuleV

fromModule :: Module -> GSWasm.ModuleInterface
fromModule (ModuleV0 v) = GSWasm.ModuleInterfaceV0 (moduleVInterface v)
fromModule (ModuleV1 v) = GSWasm.ModuleInterfaceV1 (moduleVInterface v)

-- |Helper to convert from an interface to a module.
toModule :: GSWasm.ModuleInterface -> BlobRef WasmModule -> Module
toModule (GSWasm.ModuleInterfaceV0 moduleVInterface) moduleVSource = ModuleV0 ModuleV{..}
toModule (GSWasm.ModuleInterfaceV1 moduleVInterface) moduleVSource = ModuleV1 ModuleV{..}


-- |A module, either of version 0 or 1. This is only used when storing a module
-- independently, e.g., in the module table. When a module is referenced from a
-- contract instance we use the ModuleV type directly so we may tie the version
-- of the module to the version of the instance.
data Module where
ModuleV0 :: ModuleV GSWasm.V0 -> Module
ModuleV1 :: ModuleV GSWasm.V1 -> Module
Expand All @@ -87,7 +90,7 @@ instance GSWasm.HasModuleRef Module where
moduleReference (ModuleV0 m) = GSWasm.moduleReference (moduleVInterface m)
moduleReference (ModuleV1 m) = GSWasm.moduleReference (moduleVInterface m)

-- FIXME: This should probably take host versioning into account since that is not part of the reference
-- The module reference already takes versioning into account, so this instance is reasonable.
instance HashableTo Hash Module where
getHash = coerce . GSWasm.moduleReference

Expand All @@ -102,7 +105,7 @@ instance Serialize Module where
moduleVSource <- get
return $! toModule moduleVInterface moduleVSource
put m = do
put (fromModule m)
put (getModuleInterface m)
put (m ^. source)

-- |This serialization is used for storing the module in the BlobStore.
Expand Down Expand Up @@ -213,7 +216,7 @@ unsafeGetModuleReferenceV0 :: MonadBlobStore m => ModuleRef -> Modules -> m (May
unsafeGetModuleReferenceV0 ref mods = fmap (unsafeCoerceBufferedRef extract) <$> getModuleReference ref mods
where extract (ModuleV0 m) = m
extract _ = error "Precondition violation."
-- |Gets the buffered reference to a module as stored in the module table assuming it is version 0.
-- |Gets the buffered reference to a module as stored in the module table assuming it is version 1.
unsafeGetModuleReferenceV1 :: MonadBlobStore m => ModuleRef -> Modules -> m (Maybe (BufferedRef (ModuleV GSWasm.V1)))
unsafeGetModuleReferenceV1 ref mods = fmap (unsafeCoerceBufferedRef extract) <$> getModuleReference ref mods
where extract (ModuleV1 m) = m
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -76,9 +76,12 @@ instance Applicative m => Cacheable m PersistentInstanceParameters

----------------------------------------------------------------------------------------------------

-- |An instance of a smart contract.
-- |An instance of a smart contract. This is parametrized by the Wasm version
-- `v` that is used to tie the instance version to the module version. At
-- present the version only appears in the module, but with the state changes it
-- will also appear in the contract state.
data PersistentInstanceV v = PersistentInstanceV {
-- |The fixed parameters of the instance
-- |The fixed parameters of the instance.
pinstanceParameters :: !(BufferedRef PersistentInstanceParameters),
-- |The interface of 'pinstanceContractModule'. Note this is a BufferedRef to a Module as this
-- is how the data is stored in the Modules table. A 'Module' carries a BlobRef to the source
Expand Down Expand Up @@ -236,9 +239,9 @@ fromPersistentInstance pinst = do
_instanceVParameters = mkParams iface
})

-- |Serialize a smart contract instance in V0 format.
putInstanceV0 :: (MonadBlobStore m, MonadPut m) => PersistentInstanceV GSWasm.V0 -> m ()
putInstanceV0 PersistentInstanceV {..} = do
-- |Serialize a V0 smart contract instance in V0 format.
putV0InstanceV0 :: (MonadBlobStore m, MonadPut m) => PersistentInstanceV GSWasm.V0 -> m ()
putV0InstanceV0 PersistentInstanceV {..} = do
-- Instance parameters
PersistentInstanceParameters{..} <- refLoad pinstanceParameters
liftPut $ do
Expand All @@ -250,10 +253,9 @@ putInstanceV0 PersistentInstanceV {..} = do
put pinstanceModel
put pinstanceAmount

-- |Serialize a smart contract instance in V0 format.
-- FIXME: Add versioning
putInstanceV1 :: (MonadBlobStore m, MonadPut m) => PersistentInstanceV GSWasm.V1 -> m ()
putInstanceV1 PersistentInstanceV {..} = do
-- |Serialize a V1 smart contract instance in V0 format.
putV1InstanceV0 :: (MonadBlobStore m, MonadPut m) => PersistentInstanceV GSWasm.V1 -> m ()
putV1InstanceV0 PersistentInstanceV {..} = do
-- Instance parameters
PersistentInstanceParameters{..} <- refLoad pinstanceParameters
liftPut $ do
Expand Down Expand Up @@ -616,7 +618,7 @@ putInstancesV0 (InstancesTree _ it) = do
put (contractSubindex ca)
putOptInstance (Right (PersistentInstanceV0 inst)) = do
liftPut $ putWord8 2
putInstanceV0 inst
putV0InstanceV0 inst
putOptInstance (Right (PersistentInstanceV1 inst)) = do
liftPut $ putWord8 3
putInstanceV1 inst
putV1InstanceV0 inst
54 changes: 28 additions & 26 deletions concordium-consensus/src/Concordium/GlobalState/Wasm.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
Expand Down Expand Up @@ -50,11 +51,26 @@ foreign import ccall unsafe "artifact_v1_from_bytes" fromBytesArtifactV1 :: Ptr

-- | A processed module artifact ready for execution. The actual module is
-- allocated and stored on the Rust heap, in a reference counted pointer.
newtype ModuleArtifact v = ModuleArtifact { maArtifact :: ForeignPtr (ModuleArtifact v) }
newtype ModuleArtifact (v :: WasmVersion) = ModuleArtifact { maArtifact :: ForeignPtr (ModuleArtifact v) }
deriving(Eq, Show) -- the Eq and Show instances are only for debugging and compare and show pointers.

data V0
data V1
-- |Supported versions of Wasm modules. This version defines available host
-- functions, their semantics, and limitations of contracts.
data WasmVersion = V0 | V1

instance Serialize WasmVersion where
put V0 = putWord32be 0
put V1 = putWord32be 1

get = getWord32be >>= \case
0 -> return V0
1 -> return V1
n -> fail $ "Unrecognized Wasm version " ++ show n

-- These type aliases are provided for convenience to avoid having to enable
-- DataKinds everywhere we need wasm version.
type V0 = 'V0
type V1 = 'V1

type ModuleArtifactV0 = ModuleArtifact V0
type ModuleArtifactV1 = ModuleArtifact V1
Expand Down Expand Up @@ -114,24 +130,6 @@ data InstrumentedModuleV v where
deriving instance Eq (InstrumentedModuleV v)
deriving instance Show (InstrumentedModuleV v)

-- This is just an internal helper
data InstrumentedModule where
IWMV0 :: { imwArtifactV0 :: ModuleArtifact V0 } -> InstrumentedModule
IWMV1 :: { imwArtifactV1 :: ModuleArtifact V1 } -> InstrumentedModule

instance Serialize InstrumentedModule where
put IWMV0{..} = do
putWord32be 0
put imwArtifactV0
put IWMV1{..} = do
putWord32be 1
put imwArtifactV1

get = getWord32be >>= \case
0 -> IWMV0 <$> get
1 -> IWMV1 <$> get
_ -> fail "Unsupported Wasm module version."

imWasmVersion :: InstrumentedModuleV v -> Word32
imWasmVersion (InstrumentedWasmModuleV0 _) = 0
imWasmVersion (InstrumentedWasmModuleV1 _) = 1
Expand Down Expand Up @@ -226,11 +224,15 @@ instance Serialize ModuleInterface where
miModuleRef <- get
miExposedInit <- getSafeSetOf get
miExposedReceive <- getSafeMapOf get (getSafeSetOf get)
miModuleV <- get
miModuleSize <- getWord64be
case miModuleV of
IWMV0 imWasmArtifactV0 -> return (ModuleInterfaceV0 ModuleInterface{miModule = InstrumentedWasmModuleV0 {..},..})
IWMV1 imWasmArtifactV1 -> return (ModuleInterfaceV1 ModuleInterface{miModule = InstrumentedWasmModuleV1 {..},..})
get >>= \case
V0 -> do
miModule <- InstrumentedWasmModuleV0 <$> get
miModuleSize <- getWord64be
return (ModuleInterfaceV0 ModuleInterface{..})
V1 -> do
miModule <- InstrumentedWasmModuleV1 <$> get
miModuleSize <- getWord64be
return (ModuleInterfaceV1 ModuleInterface{..})
put (ModuleInterfaceV0 ModuleInterface{..}) = do
put miModuleRef
putSafeSetOf put miExposedInit
Expand Down
11 changes: 6 additions & 5 deletions concordium-consensus/src/Concordium/Scheduler/Environment.hs
Original file line number Diff line number Diff line change
Expand Up @@ -392,15 +392,16 @@ class (StaticInformation m, IsProtocolVersion pv) => TransactionMonad pv m | m -
-- entire computation is aborted.
orElse :: m a -> m a -> m a

-- |Try to run the first computation. If it leads to `reject` for a logic reason then
-- try the second computation. If the left computation fails with out of energy then the
-- entire computation is aborted.
-- |Try to run the first computation. If it leads to `reject` for a logic
-- reason then try the second computation. If the left computation fails with
-- out of energy then the entire computation is aborted. Compared to 'orElse'
-- above, here the right computation gets access to the rejection reason of the left one.
orElseWith :: m a -> (RejectReason -> m a) -> m a

-- |Try to run the first computation. If it leads to `Left err` then abort and revert all the changes.
-- |Try to run the first computation. If it leads to `Left err` then abort and revert all the changes
-- apart from consumed energy.
withRollback :: m (Either a b) -> m (Either a b)


-- |Fail transaction processing because we would have exceeded maximum block energy limit.
outOfBlockEnergy :: m a

Expand Down
Loading

0 comments on commit eefe1d6

Please sign in to comment.