mirror of https://github.com/voidlizard/hbs2
optional-rpc-parameter
This commit is contained in:
parent
961ee4d370
commit
3b569777bc
|
@ -216,3 +216,5 @@ fixme-set "workflow" "wip" "BhME2nDpbd"
|
||||||
fixme-set "assigned" "voidlizard" "BhME2nDpbd"
|
fixme-set "assigned" "voidlizard" "BhME2nDpbd"
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
fixme-set "workflow" "test" "BhME2nDpbd"
|
|
@ -11,7 +11,7 @@ module HBS2.System.Logger.Simple
|
||||||
, warn
|
, warn
|
||||||
, notice
|
, notice
|
||||||
, info
|
, info
|
||||||
, setLogging
|
, setLogging, setLoggingOff
|
||||||
, defLog
|
, defLog
|
||||||
, loggerTr
|
, loggerTr
|
||||||
, module HBS2.System.Logger.Simple.Class
|
, module HBS2.System.Logger.Simple.Class
|
||||||
|
@ -63,6 +63,12 @@ setLogging f = do
|
||||||
let key = logKey @a
|
let key = logKey @a
|
||||||
void $ liftIO $ atomicModifyIORef' loggers (\x -> (IntMap.insert key def x, ()))
|
void $ liftIO $ atomicModifyIORef' loggers (\x -> (IntMap.insert key def x, ()))
|
||||||
|
|
||||||
|
|
||||||
|
setLoggingOff :: forall a m . (MonadIO m, HasLogLevel a) => m ()
|
||||||
|
setLoggingOff = do
|
||||||
|
let key = logKey @a
|
||||||
|
void $ liftIO $ atomicModifyIORef' loggers (\x -> (IntMap.delete key x, IntMap.lookup key x))
|
||||||
|
|
||||||
withLogger :: forall a m . (HasLogLevel a, MonadIO m) => (LoggerEntry -> m ()) -> m ()
|
withLogger :: forall a m . (HasLogLevel a, MonadIO m) => (LoggerEntry -> m ()) -> m ()
|
||||||
withLogger f = do
|
withLogger f = do
|
||||||
lo <- liftIO $ readIORef loggers <&> IntMap.lookup (logKey @a)
|
lo <- liftIO $ readIORef loggers <&> IntMap.lookup (logKey @a)
|
||||||
|
|
|
@ -47,7 +47,7 @@ cfgName = "config"
|
||||||
|
|
||||||
newtype PeerConfig =
|
newtype PeerConfig =
|
||||||
PeerConfig [Syntax C]
|
PeerConfig [Syntax C]
|
||||||
deriving newtype (Monoid, Semigroup)
|
deriving newtype (Monoid, Semigroup, Pretty)
|
||||||
|
|
||||||
|
|
||||||
peerConfigDefault :: MonadIO m => m FilePath
|
peerConfigDefault :: MonadIO m => m FilePath
|
||||||
|
@ -126,7 +126,7 @@ peerConfigRead mbfp = do
|
||||||
|
|
||||||
let confData = confData' <> either mempty id (parseTop peerConfDef)
|
let confData = confData' <> either mempty id (parseTop peerConfDef)
|
||||||
|
|
||||||
debug $ pretty confData
|
-- debug $ pretty confData
|
||||||
|
|
||||||
config <- flip transformBiM confData $ \case
|
config <- flip transformBiM confData $ \case
|
||||||
List co (Key "key" [LitStrVal p]) -> do
|
List co (Key "key" [LitStrVal p]) -> do
|
||||||
|
|
|
@ -119,6 +119,14 @@ instance HasCfgValue PeerAcceptAnnounceKey AcceptAnnounce where
|
||||||
kk = key @PeerAcceptAnnounceKey @AcceptAnnounce
|
kk = key @PeerAcceptAnnounceKey @AcceptAnnounce
|
||||||
|
|
||||||
|
|
||||||
|
data RPCOpt =
|
||||||
|
RPCOpt
|
||||||
|
{ _rpcOptConf :: Maybe FilePath
|
||||||
|
, _rpcOptAddr :: Maybe String
|
||||||
|
}
|
||||||
|
|
||||||
|
makeLenses 'RPCOpt
|
||||||
|
|
||||||
data RPCCommand =
|
data RPCCommand =
|
||||||
POKE
|
POKE
|
||||||
| ANNOUNCE (Hash HbSync)
|
| ANNOUNCE (Hash HbSync)
|
||||||
|
@ -171,6 +179,12 @@ runCLI = join . customExecParser (prefs showHelpOnError) $
|
||||||
<> command "peers" (info pPeers (progDesc "show known peers"))
|
<> command "peers" (info pPeers (progDesc "show known peers"))
|
||||||
)
|
)
|
||||||
|
|
||||||
|
confOpt = strOption ( long "config" <> short 'c' <> help "config" )
|
||||||
|
|
||||||
|
rpcOpt = strOption ( short 'r' <> long "rpc"
|
||||||
|
<> help "addr:port" )
|
||||||
|
|
||||||
|
|
||||||
common = do
|
common = do
|
||||||
pref <- optional $ strOption ( short 'p' <> long "prefix"
|
pref <- optional $ strOption ( short 'p' <> long "prefix"
|
||||||
<> help "storage prefix" )
|
<> help "storage prefix" )
|
||||||
|
@ -178,13 +192,12 @@ runCLI = join . customExecParser (prefs showHelpOnError) $
|
||||||
l <- optional $ strOption ( short 'l' <> long "listen"
|
l <- optional $ strOption ( short 'l' <> long "listen"
|
||||||
<> help "addr:port" )
|
<> help "addr:port" )
|
||||||
|
|
||||||
r <- optional $ strOption ( short 'r' <> long "rpc"
|
r <- optional rpcOpt
|
||||||
<> help "addr:port" )
|
|
||||||
|
|
||||||
k <- optional $ strOption ( short 'k' <> long "key"
|
k <- optional $ strOption ( short 'k' <> long "key"
|
||||||
<> help "peer keys file" )
|
<> help "peer keys file" )
|
||||||
|
|
||||||
c <- optional $ strOption ( long "config" <> short 'c' <> help "config" )
|
c <- optional confOpt
|
||||||
|
|
||||||
pure $ PeerOpts pref l r k c
|
pure $ PeerOpts pref l r k c
|
||||||
|
|
||||||
|
@ -192,10 +205,8 @@ runCLI = join . customExecParser (prefs showHelpOnError) $
|
||||||
runPeer <$> common
|
runPeer <$> common
|
||||||
|
|
||||||
pRpcCommon = do
|
pRpcCommon = do
|
||||||
strOption ( short 'r' <> long "rpc"
|
RPCOpt <$> optional confOpt
|
||||||
<> help "addr:port"
|
<*> optional rpcOpt
|
||||||
<> value defRpcUDP
|
|
||||||
)
|
|
||||||
|
|
||||||
pPoke = do
|
pPoke = do
|
||||||
rpc <- pRpcCommon
|
rpc <- pRpcCommon
|
||||||
|
@ -303,7 +314,7 @@ runPeer opts = Exception.handle myException $ do
|
||||||
conf <- peerConfigRead (view peerConfig opts)
|
conf <- peerConfigRead (view peerConfig opts)
|
||||||
|
|
||||||
-- let (PeerConfig syn) = conf
|
-- let (PeerConfig syn) = conf
|
||||||
-- print $ pretty syn
|
print $ pretty conf
|
||||||
|
|
||||||
let listenConf = cfgValue @PeerListenKey conf
|
let listenConf = cfgValue @PeerListenKey conf
|
||||||
let rpcConf = cfgValue @PeerRpcKey conf
|
let rpcConf = cfgValue @PeerRpcKey conf
|
||||||
|
@ -650,8 +661,16 @@ emitToPeer :: ( MonadIO m
|
||||||
|
|
||||||
emitToPeer env k e = liftIO $ withPeerM env (emit k e)
|
emitToPeer env k e = liftIO $ withPeerM env (emit k e)
|
||||||
|
|
||||||
withRPC :: String -> RPC UDP -> IO ()
|
withRPC :: RPCOpt -> RPC UDP -> IO ()
|
||||||
withRPC saddr cmd = do
|
withRPC o cmd = do
|
||||||
|
|
||||||
|
setLoggingOff @DEBUG
|
||||||
|
|
||||||
|
conf <- peerConfigRead (view rpcOptConf o)
|
||||||
|
|
||||||
|
let rpcConf = cfgValue @PeerRpcKey conf :: Maybe String
|
||||||
|
|
||||||
|
saddr <- pure (view rpcOptAddr o <|> rpcConf) `orDie` "RPC endpoint not set"
|
||||||
|
|
||||||
as <- parseAddr (fromString saddr) <&> fmap (PeerUDP . addrAddress)
|
as <- parseAddr (fromString saddr) <&> fmap (PeerUDP . addrAddress)
|
||||||
let rpc' = headMay $ L.sortBy (compare `on` addrPriority) as
|
let rpc' = headMay $ L.sortBy (compare `on` addrPriority) as
|
||||||
|
@ -719,13 +738,13 @@ withRPC saddr cmd = do
|
||||||
(\(pa, k) -> Log.info $ pretty (AsBase58 k) <+> pretty pa
|
(\(pa, k) -> Log.info $ pretty (AsBase58 k) <+> pretty pa
|
||||||
)
|
)
|
||||||
|
|
||||||
runRpcCommand :: String -> RPCCommand -> IO ()
|
runRpcCommand :: RPCOpt -> RPCCommand -> IO ()
|
||||||
runRpcCommand saddr = \case
|
runRpcCommand opt = \case
|
||||||
POKE -> withRPC saddr RPCPoke
|
POKE -> withRPC opt RPCPoke
|
||||||
PING s _ -> withRPC saddr (RPCPing s)
|
PING s _ -> withRPC opt (RPCPing s)
|
||||||
ANNOUNCE h -> withRPC saddr (RPCAnnounce h)
|
ANNOUNCE h -> withRPC opt (RPCAnnounce h)
|
||||||
FETCH h -> withRPC saddr (RPCFetch h)
|
FETCH h -> withRPC opt (RPCFetch h)
|
||||||
PEERS -> withRPC saddr RPCPeers
|
PEERS -> withRPC opt RPCPeers
|
||||||
|
|
||||||
_ -> pure ()
|
_ -> pure ()
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue