diff options
Diffstat (limited to 'hsm-command')
-rw-r--r-- | hsm-command/Hsm/Command/Command.hs | 52 | ||||
-rw-r--r-- | hsm-command/Hsm/Command/Readline.hs | 51 | ||||
-rw-r--r-- | hsm-command/Main.hs | 33 | ||||
-rw-r--r-- | hsm-command/hsm-command.cabal | 48 |
4 files changed, 184 insertions, 0 deletions
diff --git a/hsm-command/Hsm/Command/Command.hs b/hsm-command/Hsm/Command/Command.hs new file mode 100644 index 0000000..3b53287 --- /dev/null +++ b/hsm-command/Hsm/Command/Command.hs @@ -0,0 +1,52 @@ +{-# LANGUAGE DeriveAnyClass #-} + +module Hsm.Command.Command + ( Direction(X, Z) + , Angle(CW, CCW) + , Speed(Slow, Mid, Fast) + , Command(Move, Rotate) + , commandStream + ) where + +import Data.Binary (Binary) +import Data.Maybe (fromJust, isJust) +import Data.Text (pack) +import Effectful (Eff, (:>)) +import Effectful.Log (Log, logAttention_) +import GHC.Generics (Generic) +import Hsm.Command.Readline (Readline, readline) +import Streamly.Data.Stream qualified as S +import Text.Read (readEither) + +data Direction + = X + | Z + deriving (Binary, Generic, Read, Show) + +data Angle + = CW + | CCW + deriving (Binary, Generic, Read, Show) + +data Speed + = Slow + | Mid + | Fast + deriving (Binary, Generic, Read, Show) + +data Command + = Move Direction Speed Int + | Rotate Angle Speed Int + deriving (Binary, Generic, Read, Show) + +commandStream :: + forall es. (Log :> es, Readline :> es) + => S.Stream (Eff es) Command +commandStream = + S.mapMaybeM (parse . fromJust) $ S.takeWhile isJust $ S.repeatM readline + where + parse :: String -> Eff es (Maybe Command) + parse string = + case readEither string of + Left err -> logAttention_ (pack err) >> return Nothing + Right command -> return $ Just command diff --git a/hsm-command/Hsm/Command/Readline.hs b/hsm-command/Hsm/Command/Readline.hs new file mode 100644 index 0000000..3c56453 --- /dev/null +++ b/hsm-command/Hsm/Command/Readline.hs @@ -0,0 +1,51 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} + +module Hsm.Command.Readline + ( Readline + , readline + , runReadline + ) where + +import Effectful (Dispatch(Static), DispatchOf, Eff, IOE, (:>)) +import Effectful.Dispatch.Static qualified as S +import Effectful.Log (Log, getLoggerEnv, leLogger, waitForLogger) +import Effectful.Resource (Resource, allocate) +import System.Console.Haskeline qualified as H +import System.Console.Haskeline.IO qualified as H + +data Readline a b + +type instance DispatchOf Readline = Static S.WithSideEffects + +newtype instance S.StaticRep Readline = + Readline H.InputState + +readline :: + forall es. (Log :> es, Readline :> es) + => Eff es (Maybe String) +readline = do + flushLogger + Readline hdl <- S.getStaticRep + S.unsafeEff_ $ nextLine hdl + where + flushLogger :: Eff es () + flushLogger = getLoggerEnv >>= S.unsafeEff_ . waitForLogger . leLogger + -- + nextLine :: H.InputState -> IO (Maybe String) + nextLine hdl = + H.queryInput hdl + $ H.handleInterrupt (return Nothing) + $ H.withInterrupt + $ H.getInputLine "% " + +runReadline :: (IOE :> es, Resource :> es) => Eff (Readline : es) a -> Eff es a +runReadline action = do + handle <- snd <$> allocate istate H.cancelInput + S.evalStaticRep (Readline handle) action + where + settings :: H.Settings IO + settings = H.defaultSettings {H.historyFile = Just ".hsm_command_history"} + -- + istate :: IO H.InputState + istate = H.initializeInput settings diff --git a/hsm-command/Main.hs b/hsm-command/Main.hs new file mode 100644 index 0000000..0b24719 --- /dev/null +++ b/hsm-command/Main.hs @@ -0,0 +1,33 @@ +{-# LANGUAGE OverloadedRecordDot #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TemplateHaskell #-} + +import Data.Function ((&)) +import Data.Text (Text) +import Effectful (runEff) +import Effectful.Log (runLog) +import Effectful.Reader.Static (runReader) +import Effectful.Resource (runResource) +import Hsm.Command.Command (commandStream) +import Hsm.Command.Readline (runReadline) +import Hsm.Core.App (launch) +import Hsm.Core.Env (deriveFromYaml) +import Hsm.Core.Zmq.Server (runServer, send) + +data Env = Env + { name :: Text + , pubEp :: Text + } + +$(deriveFromYaml ''Env) + +main :: IO () +main = + launch @Env "command" id $ \env logger level -> + (commandStream & send @Env) + & runServer @Env + & runLog env.name logger level + & runReader env + & runReadline + & runResource + & runEff diff --git a/hsm-command/hsm-command.cabal b/hsm-command/hsm-command.cabal new file mode 100644 index 0000000..766f372 --- /dev/null +++ b/hsm-command/hsm-command.cabal @@ -0,0 +1,48 @@ +cabal-version: 3.4 +author: Paul Oliver +build-type: Simple +maintainer: contact@pauloliver.dev +name: hsm-command +version: 0.1.0.0 + +library + build-depends: + , base + , binary + , effectful-core + , haskeline + , log-effectful + , resourcet-effectful + , streamly-core + , text + + exposed-modules: + Hsm.Command.Command + Hsm.Command.Readline + + ghc-options: -Wall -Wunused-packages + default-language: GHC2021 + +executable command + build-depends: + , base + , binary + , effectful-core + , haskeline + , hsm-core + , log-effectful + , resourcet-effectful + , streamly-core + , text + + main-is: Main.hs + other-modules: + Hsm.Command.Command + Hsm.Command.Readline + + ghc-options: -Wall -Wunused-packages + + if !arch(x86_64) + ghc-options: -optl=-mno-fix-cortex-a53-835769 + + default-language: GHC2021 |