This commit is contained in:
Dmitry Zuikov 2024-03-12 12:45:37 +03:00
parent e71d5403fc
commit 14a3d23fcf
7 changed files with 123 additions and 20 deletions

View File

@ -1,24 +1,43 @@
module CLI.LWWRef where module CLI.LWWRef where
import HBS2.Prelude.Plated import HBS2.Prelude.Plated
import HBS2.Net.Proto.Service
import HBS2.Net.Auth.Schema
import HBS2.Peer.Proto.LWWRef import HBS2.Peer.Proto.LWWRef
import HBS2.Peer.RPC.API.LWWRef
import CLI.Common import CLI.Common
import RPC2() import RPC2()
import PeerLogger hiding (info) import PeerLogger hiding (info)
import System.Exit
import Options.Applicative import Options.Applicative
pLwwRef :: Parser (IO ()) pLwwRef :: Parser (IO ())
pLwwRef = hsubparser ( command "fetch" (info pLwwRefFetch (progDesc "fetch lwwref")) pLwwRef = hsubparser ( command "fetch" (info pLwwRefFetch (progDesc "fetch lwwref"))
<> command "get" (info pLwwRefGet (progDesc "get lwwref")) <> command "get" (info pLwwRefGet (progDesc "get lwwref"))
) )
pLwwRefFetch :: Parser (IO ()) pLwwRefFetch :: Parser (IO ())
pLwwRefFetch = pure do pLwwRefFetch = do
pure () rpc <- pRpcCommon
ref <- strArgument (metavar "LWWREF")
pure $ withMyRPC @LWWRefAPI rpc $ \caller -> do
callService @RpcLWWRefFetch caller ref >>= \case
Left e -> err (viaShow e) >> exitFailure
Right{} -> pure ()
lwwRef :: ReadM (LWWRefKey HBS2Basic)
lwwRef = maybeReader (fromStringMay @(LWWRefKey HBS2Basic))
pLwwRefGet :: Parser (IO ()) pLwwRefGet :: Parser (IO ())
pLwwRefGet = pure do pLwwRefGet = do
pure () rpc <- pRpcCommon
ref <- strArgument (metavar "LWWREF")
pure $ withMyRPC @LWWRefAPI rpc $ \caller -> do
callService @RpcLWWRefGet caller ref >>= \case
Left e -> err (viaShow e) >> exitFailure
Right r -> print $ pretty r

View File

@ -67,6 +67,7 @@ import HBS2.Peer.RPC.API.Storage
import HBS2.Peer.RPC.API.Peer import HBS2.Peer.RPC.API.Peer
import HBS2.Peer.RPC.API.RefLog import HBS2.Peer.RPC.API.RefLog
import HBS2.Peer.RPC.API.RefChan import HBS2.Peer.RPC.API.RefChan
import HBS2.Peer.RPC.API.LWWRef
import HBS2.Peer.Notify import HBS2.Peer.Notify
import HBS2.Peer.RPC.Client.StorageClient import HBS2.Peer.RPC.Client.StorageClient
@ -1160,6 +1161,7 @@ runPeer opts = Exception.handle (\e -> myException e
, makeResponse (makeServer @RefLogAPI) , makeResponse (makeServer @RefLogAPI)
, makeResponse (makeServer @RefChanAPI) , makeResponse (makeServer @RefChanAPI)
, makeResponse (makeServer @StorageAPI) , makeResponse (makeServer @StorageAPI)
, makeResponse (makeServer @LWWRefAPI)
, makeResponse (makeNotifyServer @(RefChanEvents L4Proto) env) , makeResponse (makeNotifyServer @(RefChanEvents L4Proto) env)
, makeResponse (makeNotifyServer @(RefLogEvents L4Proto) envrl) , makeResponse (makeNotifyServer @(RefLogEvents L4Proto) envrl)
] ]

View File

@ -2,10 +2,12 @@ module RPC2
( module RPC2.Peer ( module RPC2.Peer
, module RPC2.RefLog , module RPC2.RefLog
, module RPC2.RefChan , module RPC2.RefChan
, module RPC2.LWWRef
) where ) where
import RPC2.Peer import RPC2.Peer
import RPC2.RefLog import RPC2.RefLog
import RPC2.RefChan import RPC2.RefChan
import RPC2.LWWRef

View File

@ -1 +1,64 @@
module RPC2.LWWRef where {-# OPTIONS_GHC -fno-warn-orphans #-}
{-# Language UndecidableInstances #-}
module RPC2.LWWRef where
import HBS2.Peer.Prelude
import HBS2.Actors.Peer
import HBS2.Data.Types.SignedBox
import HBS2.Peer.Proto
import HBS2.Peer.Proto.LWWRef
import HBS2.Storage
import HBS2.Net.Messaging.Unix
import PeerTypes
import HBS2.Peer.RPC.Internal.Types
import HBS2.Peer.RPC.API.LWWRef
import Lens.Micro.Platform
import Control.Monad.Reader
import Control.Monad.Trans.Maybe
type LWWRefContext m = (MonadIO m, HasRpcContext LWWRefAPI RPC2Context m)
instance (Monad m)
=> HasRpcContext LWWRefAPI RPC2Context (ResponseM UNIX (ReaderT RPC2Context m)) where
getRpcContext = lift ask
instance (LWWRefContext m) => HandleMethod m RpcLWWRefGet where
handleMethod key = do
co <- getRpcContext @LWWRefAPI
debug "rpc.LWWRefContext"
let penv = rpcPeerEnv co
liftIO $ withPeerM penv $ do
sto <- getStorage
runMaybeT do
rv <- getRef sto key >>= toMPlus
val <- getBlock sto rv >>= toMPlus
<&> unboxSignedBox @(LWWRef L4Proto) @L4Proto
>>= toMPlus
pure $ snd val
instance LWWRefContext m => HandleMethod m RpcLWWRefFetch where
handleMethod key = do
co <- getRpcContext @LWWRefAPI
debug $ "rpc.LWWRefFetch" <+> pretty key
let penv = rpcPeerEnv co
liftIO $ withPeerM penv $ do
gossip (LWWRefProto1 @L4Proto (LWWProtoGet key))
instance LWWRefContext m => HandleMethod m RpcLWWRefUpdate where
handleMethod box = do
-- co <- getRpcContext @LWWRefAPI
debug "rpc.LWWRefUpdate"
pure ()

View File

@ -10,6 +10,7 @@ import HBS2.Data.Types.Refs
import HBS2.Net.Proto.Types import HBS2.Net.Proto.Types
import HBS2.Net.Auth.Schema() import HBS2.Net.Auth.Schema()
import Data.ByteString (ByteString)
import Data.Hashable hiding (Hashed) import Data.Hashable hiding (Hashed)
import Data.Maybe import Data.Maybe
import Data.Word import Data.Word
@ -26,9 +27,9 @@ data LWWRefProto e =
data LWWRef e = data LWWRef e =
LWWRef LWWRef
{ lwwSeq :: Word64 { lwwSeq :: Word64
, lwwProof :: Maybe HashRef , lwwProof :: Maybe HashRef
, lwwValue :: HashRef , lwwValue :: HashRef
} }
deriving stock (Generic) deriving stock (Generic)
@ -41,7 +42,7 @@ instance ForLWWRefProto e => Serialise (LWWRef e)
newtype LWWRefKey s = newtype LWWRefKey s =
LWWRefKey LWWRefKey
{ lwwRefKey :: PubKey 'Sign s { fromLwwRefKey :: PubKey 'Sign s
} }
deriving stock (Generic) deriving stock (Generic)
@ -70,3 +71,12 @@ instance Pretty (AsBase58 (PubKey 'Sign s )) => Pretty (AsBase58 (LWWRefKey s))
instance Pretty (AsBase58 (PubKey 'Sign s )) => Pretty (LWWRefKey s) where instance Pretty (AsBase58 (PubKey 'Sign s )) => Pretty (LWWRefKey s) where
pretty (LWWRefKey k) = pretty (AsBase58 k) pretty (LWWRefKey k) = pretty (AsBase58 k)
instance Pretty (LWWRef e) where
pretty (LWWRef{..}) = braces $ "lwwref" <> line
<> indent 2
( "seq" <+> pretty lwwSeq <> line
<> "val" <+> pretty lwwValue <> line
<> "proof" <+> pretty lwwProof <> line
)

View File

@ -63,7 +63,9 @@ lwwRefProto pkt@(LWWRefProto1 req) = do
LWWProtoSet key box -> void $ runMaybeT do LWWProtoSet key box -> void $ runMaybeT do
(_, lww) <- MaybeT $ pure $ unboxSignedBox0 box (puk, lww) <- MaybeT $ pure $ unboxSignedBox0 box
guard ( puk == fromLwwRefKey key )
deferred @proto do deferred @proto do

View File

@ -11,25 +11,30 @@ import HBS2.Peer.Proto.RefLog (RefLogUpdate)
import Data.ByteString.Lazy (ByteString) import Data.ByteString.Lazy (ByteString)
import Codec.Serialise import Codec.Serialise
data LWWRefGet data RpcLWWRefGet
data LWWRefUpdate data RpcLWWRefUpdate
data RpcLWWRefFetch
type LWWRefAPI = '[ LWWRefGet -- may be done via storage type LWWRefAPI = '[ RpcLWWRefGet -- may be done via storage
, LWWRefUpdate -- , RpcLWWRefUpdate --
, RpcLWWRefFetch --
] ]
instance HasProtocol UNIX (ServiceProto LWWRefAPI UNIX) where instance HasProtocol UNIX (ServiceProto LWWRefAPI UNIX) where
type instance ProtocolId (ServiceProto LWWRefAPI UNIX) = 16267229472009458342 type instance ProtocolId (ServiceProto LWWRefAPI UNIX) = 16267229472009458342
type instance Encoded UNIX = ByteString type instance Encoded UNIX = ByteString
decode = either (const Nothing) Just . deserialiseOrFail decode = either (const Nothing) Just . deserialiseOrFail
encode = serialise encode = serialise
type instance Input LWWRefGet = LWWRefKey HBS2Basic type instance Input RpcLWWRefGet = LWWRefKey HBS2Basic
type instance Output LWWRefGet = Maybe (LWWRef L4Proto) type instance Output RpcLWWRefGet = Maybe (LWWRef L4Proto)
type instance Input RpcLWWRefFetch = LWWRefKey HBS2Basic
type instance Output RpcLWWRefFetch = ()
type instance Input RpcLWWRefUpdate = SignedBox (LWWRef L4Proto) L4Proto
type instance Output RpcLWWRefUpdate = ()
type instance Input LWWRefUpdate = SignedBox (LWWRef L4Proto) L4Proto
type instance Output LWWRefUpdate = ()