mirror of
https://github.com/graninas/Hydra.git
synced 2024-11-28 04:35:18 +03:00
Cmd handlers from console reworked.
This commit is contained in:
parent
b22e71e34b
commit
4e3baff6f0
@ -113,6 +113,7 @@ dependencies:
|
|||||||
- warp
|
- warp
|
||||||
- http-client
|
- http-client
|
||||||
- http-client-tls
|
- http-client-tls
|
||||||
|
- data-default
|
||||||
|
|
||||||
library:
|
library:
|
||||||
source-dirs:
|
source-dirs:
|
||||||
|
@ -33,16 +33,6 @@ initKVDB' coreRt cfg@(D.RocksDBConfig _ _ _) dbName =
|
|||||||
initKVDB' coreRt cfg@(D.RedisConfig) dbName =
|
initKVDB' coreRt cfg@(D.RedisConfig) dbName =
|
||||||
R.initRedisDB' (coreRt ^. RLens.redisConns) cfg dbName
|
R.initRedisDB' (coreRt ^. RLens.redisConns) cfg dbName
|
||||||
|
|
||||||
-- TODO: rework
|
|
||||||
callHandler :: R.AppRuntime -> Map Text (String -> L.LangL Text) -> String -> IO Text
|
|
||||||
callHandler appRt methods msg = do
|
|
||||||
let tag = T.pack $ takeWhile (/= ' ') msg
|
|
||||||
let coreRt = appRt ^. RLens.coreRuntime
|
|
||||||
case methods ^. at tag of
|
|
||||||
Just method -> Impl.runLangL coreRt $ method msg
|
|
||||||
Nothing -> pure $ "The method " <> tag <> " isn't supported."
|
|
||||||
|
|
||||||
|
|
||||||
connect :: D.DBConfig beM -> IO (D.DBResult (D.SqlConn beM))
|
connect :: D.DBConfig beM -> IO (D.DBResult (D.SqlConn beM))
|
||||||
connect cfg = do
|
connect cfg = do
|
||||||
eConn <- try $ R.connect' cfg
|
eConn <- try $ R.connect' cfg
|
||||||
@ -85,22 +75,19 @@ interpretAppF appRt (L.InitSqlDB cfg next) = do
|
|||||||
pure $ next $ Left err
|
pure $ next $ Left err
|
||||||
|
|
||||||
|
|
||||||
interpretAppF appRt (L.StdF completeFunc handlers next) = do
|
interpretAppF appRt (L.StdF completeFunc stdDef next) = do
|
||||||
methodsMVar <- newMVar Map.empty
|
let coreRt = appRt ^. RLens.coreRuntime
|
||||||
_ <- Impl.runCmdHandlerL methodsMVar handlers
|
-- TODO: add history.
|
||||||
-- TODO: rework. Consider masking the exceptions.
|
void $ forkIO $ do
|
||||||
-- TODO: add history.
|
let loop = HS.getInputLine "> " >>= \case
|
||||||
void $ forkIO $ do
|
Nothing -> pure ()
|
||||||
methods <- readMVar methodsMVar
|
Just line -> do
|
||||||
let loop = HS.getInputLine "> " >>= \case
|
liftIO $ Impl.runCmdHandlerL coreRt (toText line) stdDef
|
||||||
Nothing -> pure ()
|
-- HS.outputStrLn $ T.unpack res
|
||||||
Just line -> do
|
loop
|
||||||
res <- liftIO $ callHandler appRt methods line
|
let cf = HS.completeWord Nothing " \t" $ pure . completeFunc
|
||||||
HS.outputStrLn $ T.unpack res
|
HS.runInputT (HS.setComplete cf HS.defaultSettings) loop
|
||||||
loop
|
pure $ next ()
|
||||||
let cf = HS.completeWord Nothing " \t" $ pure . completeFunc
|
|
||||||
HS.runInputT (HS.setComplete cf HS.defaultSettings) loop
|
|
||||||
pure $ next ()
|
|
||||||
|
|
||||||
runAppL :: R.AppRuntime -> L.AppL a -> IO a
|
runAppL :: R.AppRuntime -> L.AppL a -> IO a
|
||||||
runAppL appRt = foldFree (interpretAppF appRt)
|
runAppL appRt = foldFree (interpretAppF appRt)
|
||||||
|
@ -5,14 +5,15 @@ import Hydra.Prelude
|
|||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
|
||||||
import qualified Hydra.Framework.Cmd.Language as L
|
import qualified Hydra.Framework.Cmd.Language as L
|
||||||
|
import qualified Hydra.Core.Runtime as R
|
||||||
|
import qualified Hydra.Core.Interpreters as Impl
|
||||||
|
|
||||||
-- TODO: rework.
|
interpretCmdHandlerL :: R.CoreRuntime -> Text -> L.CmdHandlerF a -> IO a
|
||||||
|
|
||||||
interpretCmdHandlerL :: MVar (M.Map Text L.CmdHandler) -> L.CmdHandlerF a -> IO a
|
interpretCmdHandlerL coreRt line (L.UserCmd parser cont next) =
|
||||||
interpretCmdHandlerL methodsMVar (L.CmdHandler name method' next) = do
|
next <$> case parser line of
|
||||||
methods <- takeMVar methodsMVar
|
Nothing -> pure ()
|
||||||
putMVar methodsMVar $ M.insert name method' methods
|
Just a -> Impl.runLangL coreRt $ cont a
|
||||||
pure $ next ()
|
|
||||||
|
|
||||||
runCmdHandlerL :: MVar (Map Text L.CmdHandler) -> L.CmdHandlerL a -> IO a
|
runCmdHandlerL :: R.CoreRuntime -> Text -> L.CmdHandlerL a -> IO a
|
||||||
runCmdHandlerL m = foldFree (interpretCmdHandlerL m)
|
runCmdHandlerL coreRt line = foldFree (interpretCmdHandlerL coreRt line)
|
||||||
|
@ -1,37 +1,40 @@
|
|||||||
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE ConstraintKinds #-}
|
{-# LANGUAGE ConstraintKinds #-}
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
|
|
||||||
-- TODO: rework.
|
-- TODO: rework.
|
||||||
module Hydra.Framework.Cmd.Language
|
module Hydra.Framework.Cmd.Language
|
||||||
( CmdHandlerF (..)
|
( CmdHandlerF (..)
|
||||||
, CmdHandler
|
|
||||||
, CmdHandlerL
|
, CmdHandlerL
|
||||||
, stdHandler
|
, userCmd
|
||||||
, toTag
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Hydra.Prelude
|
import Hydra.Prelude
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Typeable
|
import Data.Typeable
|
||||||
|
import Data.Data
|
||||||
|
import Data.Default
|
||||||
|
|
||||||
import qualified Hydra.Core.Language as L
|
import qualified Hydra.Core.Language as L
|
||||||
|
|
||||||
toTag :: Typeable a => a -> Text
|
data CmdHandlerF next where
|
||||||
toTag = T.pack . takeWhile (/= ' ') . show . typeOf
|
UserCmd :: (Text -> Maybe a) -> (a -> L.LangL ()) -> (() -> next) -> CmdHandlerF next
|
||||||
|
|
||||||
data CmdHandlerF a where
|
|
||||||
CmdHandler :: Text -> CmdHandler -> (() -> a) -> CmdHandlerF a
|
|
||||||
|
|
||||||
instance Functor CmdHandlerF where
|
instance Functor CmdHandlerF where
|
||||||
fmap g (CmdHandler text f next) = CmdHandler text f (g . next)
|
fmap g (UserCmd parser cont next) = UserCmd parser cont (g . next)
|
||||||
|
|
||||||
type CmdHandler = String -> L.LangL Text
|
|
||||||
type CmdHandlerL a = Free CmdHandlerF a
|
type CmdHandlerL a = Free CmdHandlerF a
|
||||||
|
|
||||||
stdHandler :: (Typeable a, Read a) => (a -> L.LangL Text) -> CmdHandlerL ()
|
userCmd
|
||||||
stdHandler f = liftF $ CmdHandler (toTag f) (makeStdHandler f) id
|
:: forall a
|
||||||
|
. (Read a, Data a, Default a)
|
||||||
|
=> Text
|
||||||
|
-> (a -> L.LangL ())
|
||||||
|
-> CmdHandlerL ()
|
||||||
|
userCmd cmd handler = liftF $ UserCmd fParse handler id
|
||||||
where
|
where
|
||||||
makeStdHandler :: Read a => (a -> L.LangL Text) -> String -> L.LangL Text
|
cName = T.toLower $ toText $ show @String $ toConstr $ def @a
|
||||||
makeStdHandler f raw = case readMaybe raw of
|
fParse :: Text -> Maybe a
|
||||||
Just req -> f req
|
fParse line = do
|
||||||
Nothing -> pure "Error of request parsing"
|
t <- T.stripPrefix cmd $ T.stripStart line
|
||||||
|
readMaybe $ toString $ T.concat [toText cName, " ", t]
|
||||||
|
Loading…
Reference in New Issue
Block a user