mirror of https://github.com/voidlizard/hbs2
done expose-all-new-rpc
This commit is contained in:
parent
f8421015ac
commit
850354c529
|
@ -1,5 +1,3 @@
|
|||
(fixme-set "assigned" "voidlizard" "CmfGGmDAuC")
|
||||
(fixme-set "assigned" "voidlizard" "4Bm5kS8t54" )
|
||||
(fixme-set "assigned" "voidlizard" "8i2gUFTTnH" )
|
||||
(fixme-set "assigned" "voidlizard" "CPhvijEXN2" )
|
||||
|
||||
(fixme-set "assigned" "voidlizard" "DGW8fuaufG" )
|
||||
(fixme-set "workflow" "test" "DGW8fuaufG")
|
||||
|
|
|
@ -4,4 +4,7 @@ hbs2.prof
|
|||
.fixme/state.db
|
||||
result
|
||||
# VS Code
|
||||
settings.json
|
||||
settings.json
|
||||
|
||||
cabal.project.local
|
||||
|
||||
|
|
|
@ -11,8 +11,10 @@ import HBS2.Net.Proto.Service
|
|||
|
||||
import HBS2.OrDie
|
||||
|
||||
import HBS2.Peer.RPC.API.RefChan
|
||||
|
||||
import CLI.Common
|
||||
import RPC2.RefChan
|
||||
import RPC2()
|
||||
|
||||
import Options.Applicative
|
||||
import Data.ByteString qualified as BS
|
||||
|
|
|
@ -68,11 +68,13 @@ import Log
|
|||
|
||||
import HBS2.Peer.RPC.Internal.Types()
|
||||
import HBS2.Peer.RPC.Internal.Storage()
|
||||
import HBS2.Peer.RPC.API.Storage
|
||||
|
||||
import RPC2.Peer
|
||||
import RPC2.RefLog
|
||||
import RPC2.RefChan
|
||||
import HBS2.Peer.RPC.API.Storage
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
import HBS2.Peer.RPC.API.RefLog
|
||||
import HBS2.Peer.RPC.API.RefChan
|
||||
|
||||
import RPC2(RPC2Context(..))
|
||||
|
||||
import Codec.Serialise as Serialise
|
||||
import Control.Concurrent.STM
|
||||
|
|
|
@ -1,4 +1,11 @@
|
|||
module RPC2 where
|
||||
module RPC2
|
||||
( module RPC2.Peer
|
||||
, module RPC2.RefLog
|
||||
, module RPC2.RefChan
|
||||
) where
|
||||
|
||||
import Data.Config.Suckless.KeyValue()
|
||||
|
||||
import RPC2.Peer
|
||||
import RPC2.RefLog
|
||||
import RPC2.RefChan
|
||||
|
||||
|
|
|
@ -11,7 +11,7 @@ import HBS2.System.Logger.Simple
|
|||
import SendBlockAnnounce
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
|
||||
instance (MonadIO m,HasRpcContext PeerAPI RPC2Context m) => HandleMethod m RpcAnnounce where
|
||||
|
|
|
@ -8,7 +8,7 @@ import HBS2.System.Logger.Simple
|
|||
import Data.Config.Suckless.KeyValue
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
import System.Exit qualified as Exit
|
||||
import Control.Concurrent.Async
|
||||
|
|
|
@ -9,7 +9,7 @@ import HBS2.Net.Proto.Service
|
|||
import HBS2.System.Logger.Simple
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
instance (MonadIO m, HasRpcContext PeerAPI RPC2Context m) => HandleMethod m RpcFetch where
|
||||
type instance Input RpcFetch = HashRef
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
module RPC2.LogLevel where
|
||||
|
||||
import HBS2.Prelude.Plated
|
||||
|
@ -5,16 +6,11 @@ import HBS2.Net.Proto.Service
|
|||
|
||||
import Log
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
import HBS2.System.Logger.Simple
|
||||
import Codec.Serialise
|
||||
|
||||
data SetLogging =
|
||||
DebugOn Bool
|
||||
| TraceOn Bool
|
||||
deriving (Generic,Eq,Show)
|
||||
|
||||
instance Serialise SetLogging
|
||||
|
||||
|
|
|
@ -1,17 +1,17 @@
|
|||
module RPC2.Peer
|
||||
( module RPC2.Peer
|
||||
, module RPC2.Peer.API
|
||||
, module HBS2.Peer.RPC.API.Peer
|
||||
, module RPC2.LogLevel
|
||||
-- , SetLogging(..)
|
||||
) where
|
||||
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
import RPC2.Announce()
|
||||
import RPC2.Fetch()
|
||||
import RPC2.Peers()
|
||||
import RPC2.PexInfo()
|
||||
import RPC2.Ping()
|
||||
import RPC2.Poke
|
||||
import RPC2.Poke()
|
||||
import RPC2.RefLog()
|
||||
import RPC2.RefChan()
|
||||
import RPC2.Die()
|
||||
|
|
|
@ -15,7 +15,7 @@ import HBS2.Net.Proto.Definition()
|
|||
import PeerTypes
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
import Control.Monad
|
||||
import Lens.Micro.Platform
|
||||
|
|
|
@ -11,7 +11,7 @@ import HBS2.Net.Proto.Definition()
|
|||
import HBS2.Net.Proto.PeerExchange
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
instance ( MonadIO m
|
||||
, HasRpcContext PeerAPI RPC2Context m
|
||||
|
|
|
@ -13,7 +13,7 @@ import HBS2.System.Logger.Simple
|
|||
import HBS2.Peer.RPC.Internal.Types
|
||||
|
||||
import PeerTypes
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
|
||||
instance (MonadIO m, HasRpcContext PeerAPI RPC2Context m) => HandleMethod m RpcPing where
|
||||
|
|
|
@ -8,7 +8,7 @@ import HBS2.Net.Proto.Service
|
|||
import HBS2.System.Logger.Simple
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import RPC2.Peer.API
|
||||
import HBS2.Peer.RPC.API.Peer
|
||||
|
||||
|
||||
instance ( MonadIO m
|
||||
|
|
|
@ -12,54 +12,21 @@ import HBS2.Base58
|
|||
import HBS2.Data.Types.Refs (HashRef(..))
|
||||
import HBS2.Net.Proto.Definition()
|
||||
import HBS2.Net.Proto.Service
|
||||
import HBS2.Net.Proto.Types
|
||||
import HBS2.Data.Types.SignedBox
|
||||
import HBS2.Net.Proto.RefChan
|
||||
import HBS2.Net.Messaging.Unix
|
||||
import HBS2.Storage
|
||||
|
||||
import HBS2.Peer.RPC.API.RefChan
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
|
||||
import HBS2.System.Logger.Simple
|
||||
import PeerTypes
|
||||
|
||||
import Data.ByteString.Lazy (ByteString)
|
||||
import Data.ByteString qualified as BS
|
||||
import Data.Functor
|
||||
import Codec.Serialise
|
||||
import Control.Monad.Reader
|
||||
|
||||
-- NOTE: refchan-head-endpoints
|
||||
data RpcRefChanHeadGet
|
||||
data RpcRefChanHeadFetch
|
||||
data RpcRefChanHeadPost
|
||||
|
||||
-- NOTE: refchan-endpoints
|
||||
data RpcRefChanFetch
|
||||
data RpcRefChanGet
|
||||
data RpcRefChanPropose
|
||||
|
||||
data RpcRefChanNotify
|
||||
|
||||
type RefChanAPI = '[ RpcRefChanHeadGet
|
||||
, RpcRefChanHeadFetch
|
||||
, RpcRefChanHeadPost
|
||||
, RpcRefChanGet
|
||||
, RpcRefChanFetch
|
||||
, RpcRefChanPropose
|
||||
, RpcRefChanNotify
|
||||
]
|
||||
|
||||
|
||||
type RefChanAPIProto = 0xDA2374630001
|
||||
|
||||
-- FIXME: hbs2-peer-protocols-to-
|
||||
instance HasProtocol UNIX (ServiceProto RefChanAPI UNIX) where
|
||||
type instance ProtocolId (ServiceProto RefChanAPI UNIX) = RefChanAPIProto
|
||||
type instance Encoded UNIX = ByteString
|
||||
decode = either (const Nothing) Just . deserialiseOrFail
|
||||
encode = serialise
|
||||
|
||||
type RefChanContext m = (MonadIO m, HasRpcContext RefChanAPI RPC2Context m)
|
||||
|
||||
instance (Monad m)
|
||||
|
|
|
@ -15,7 +15,6 @@ import HBS2.Events
|
|||
import HBS2.Net.Proto.Definition()
|
||||
import HBS2.Net.Proto.RefLog
|
||||
import HBS2.Net.Proto.Service
|
||||
import HBS2.Net.Proto.Types
|
||||
import HBS2.Storage
|
||||
import HBS2.Net.Messaging.Unix
|
||||
|
||||
|
@ -24,32 +23,14 @@ import PeerTypes
|
|||
import RefLog (doRefLogBroadCast)
|
||||
|
||||
import HBS2.Peer.RPC.Internal.Types
|
||||
import HBS2.Peer.RPC.API.RefLog
|
||||
|
||||
import Data.Functor
|
||||
import Lens.Micro.Platform
|
||||
import Data.ByteString.Lazy ( ByteString )
|
||||
import Codec.Serialise
|
||||
import Control.Monad.Reader
|
||||
|
||||
data RpcRefLogGet
|
||||
data RpcRefLogFetch
|
||||
data RpcRefLogPost
|
||||
|
||||
type RefLogAPI = '[ RpcRefLogGet
|
||||
, RpcRefLogFetch
|
||||
, RpcRefLogPost
|
||||
]
|
||||
|
||||
|
||||
type RefLogContext m = (MonadIO m, HasRpcContext RefLogAPI RPC2Context m)
|
||||
|
||||
instance HasProtocol UNIX (ServiceProto RefLogAPI UNIX) where
|
||||
type instance ProtocolId (ServiceProto RefLogAPI UNIX) = 0xDA2371620001
|
||||
type instance Encoded UNIX = ByteString
|
||||
decode = either (const Nothing) Just . deserialiseOrFail
|
||||
encode = serialise
|
||||
|
||||
|
||||
instance (Monad m)
|
||||
=> HasRpcContext RefLogAPI RPC2Context (ResponseM UNIX (ReaderT RPC2Context m)) where
|
||||
-- type instance RpcContext RefLogAPI = RPC2Context
|
||||
|
|
|
@ -133,7 +133,9 @@ library
|
|||
|
||||
exposed-modules:
|
||||
HBS2.Peer.RPC.Class
|
||||
HBS2.Peer.RPC.API
|
||||
HBS2.Peer.RPC.API.Peer
|
||||
HBS2.Peer.RPC.API.RefLog
|
||||
HBS2.Peer.RPC.API.RefChan
|
||||
HBS2.Peer.RPC.API.Storage
|
||||
HBS2.Peer.RPC.Client.Unix
|
||||
HBS2.Peer.RPC.Client.StorageClient
|
||||
|
@ -165,7 +167,6 @@ executable hbs2-peer
|
|||
, Fetch
|
||||
, Log
|
||||
, RPC2
|
||||
, RPC2.Peer.API
|
||||
, RPC2.Peer
|
||||
, RPC2.Poke
|
||||
, RPC2.Announce
|
||||
|
|
|
@ -1,3 +0,0 @@
|
|||
module HBS2.Peer.RPC.API where
|
||||
|
||||
|
|
@ -1,5 +1,6 @@
|
|||
module RPC2.Peer.API where
|
||||
module HBS2.Peer.RPC.API.Peer where
|
||||
|
||||
import HBS2.Prelude.Plated
|
||||
import HBS2.Net.Messaging.Unix
|
||||
import HBS2.Net.Proto.Service
|
||||
import HBS2.Actors.Peer
|
||||
|
@ -40,3 +41,9 @@ instance (Monad m)
|
|||
-- type instance RpcContext PeerAPI = RPC2Context
|
||||
getRpcContext = lift ask
|
||||
|
||||
|
||||
data SetLogging =
|
||||
DebugOn Bool
|
||||
| TraceOn Bool
|
||||
deriving (Generic,Eq,Show)
|
||||
|
|
@ -0,0 +1,40 @@
|
|||
module HBS2.Peer.RPC.API.RefChan where
|
||||
|
||||
import HBS2.Net.Proto.Service
|
||||
import HBS2.Net.Messaging.Unix (UNIX)
|
||||
|
||||
import Data.ByteString.Lazy ( ByteString )
|
||||
import Codec.Serialise
|
||||
|
||||
-- NOTE: refchan-head-endpoints
|
||||
data RpcRefChanHeadGet
|
||||
data RpcRefChanHeadFetch
|
||||
data RpcRefChanHeadPost
|
||||
|
||||
-- NOTE: refchan-endpoints
|
||||
data RpcRefChanFetch
|
||||
data RpcRefChanGet
|
||||
data RpcRefChanPropose
|
||||
|
||||
data RpcRefChanNotify
|
||||
|
||||
type RefChanAPI = '[ RpcRefChanHeadGet
|
||||
, RpcRefChanHeadFetch
|
||||
, RpcRefChanHeadPost
|
||||
, RpcRefChanGet
|
||||
, RpcRefChanFetch
|
||||
, RpcRefChanPropose
|
||||
, RpcRefChanNotify
|
||||
]
|
||||
|
||||
|
||||
type RefChanAPIProto = 0xDA2374630001
|
||||
|
||||
-- FIXME: hbs2-peer-protocols-to-
|
||||
instance HasProtocol UNIX (ServiceProto RefChanAPI UNIX) where
|
||||
type instance ProtocolId (ServiceProto RefChanAPI UNIX) = RefChanAPIProto
|
||||
type instance Encoded UNIX = ByteString
|
||||
decode = either (const Nothing) Just . deserialiseOrFail
|
||||
encode = serialise
|
||||
|
||||
|
|
@ -0,0 +1,25 @@
|
|||
module HBS2.Peer.RPC.API.RefLog where
|
||||
|
||||
import HBS2.Net.Messaging.Unix
|
||||
import HBS2.Net.Proto.Service
|
||||
|
||||
import Data.ByteString.Lazy (ByteString)
|
||||
import Codec.Serialise
|
||||
|
||||
data RpcRefLogGet
|
||||
data RpcRefLogFetch
|
||||
data RpcRefLogPost
|
||||
|
||||
type RefLogAPI = '[ RpcRefLogGet
|
||||
, RpcRefLogFetch
|
||||
, RpcRefLogPost
|
||||
]
|
||||
|
||||
|
||||
|
||||
instance HasProtocol UNIX (ServiceProto RefLogAPI UNIX) where
|
||||
type instance ProtocolId (ServiceProto RefLogAPI UNIX) = 0xDA2371620001
|
||||
type instance Encoded UNIX = ByteString
|
||||
decode = either (const Nothing) Just . deserialiseOrFail
|
||||
encode = serialise
|
||||
|
Loading…
Reference in New Issue