module System.Console.Shell.ShellMonad (
Sh
, runSh
, shellPut
, shellPutStr, shellPutStrLn
, shellPutInfo, shellPutInfoLn
, shellPutErr, shellPutErrLn
, getShellSt, putShellSt
, modifyShellSt
, shellSpecial
, ShellContext
, extractContext, runWithContext, updateCommandResult
) where
import Control.Monad.Reader
import Control.Monad.State
import System.Console.Shell.Backend
import System.Console.Shell.Types
runSh :: st -> OutputCommand -> Sh st () -> IO (CommandResult st)
runSh st info = (flip runReaderT) info . (flip execStateT) (st,Nothing) . unSh
shellPut :: BackendOutput -> Sh st ()
shellPut out = Sh (lift ask >>= \f -> liftIO (f out))
shellPutStr :: String -> Sh st ()
shellPutStr = shellPut . RegularOutput
shellPutInfo :: String -> Sh st ()
shellPutInfo = shellPut . InfoOutput
shellPutErr :: String -> Sh st ()
shellPutErr = shellPut . ErrorOutput
shellPutStrLn :: String -> Sh st ()
shellPutStrLn = shellPutStr . (++"\n")
shellPutInfoLn :: String -> Sh st ()
shellPutInfoLn = shellPutInfo . (++"\n")
shellPutErrLn :: String -> Sh st ()
shellPutErrLn = shellPutErr . (++"\n")
getShellSt :: Sh st st
getShellSt = Sh (get >>= return . fst)
putShellSt :: st -> Sh st ()
putShellSt st = Sh (get >>= \ (_,spec) -> put (st,spec))
modifyShellSt :: (st -> st) -> Sh st ()
modifyShellSt f = getShellSt >>= putShellSt . f
shellSpecial :: ShellSpecial st -> Sh st ()
shellSpecial spec = Sh (get >>= \ (st,_) -> put (st,Just spec))
instance MonadState st (Sh st) where
get = getShellSt
put = putShellSt
type ShellContext st = (CommandResult st, OutputCommand)
extractContext :: Sh st (ShellContext st)
extractContext = (Sh . StateT) $ \s -> do
imC <- ask
return ((s, imC), s)
runWithContext :: ShellContext st -> Sh st a -> IO (a, CommandResult st)
runWithContext (mC, imC) = (flip runReaderT) imC . (flip runStateT) mC . unSh
updateCommandResult :: CommandResult st -> Sh st ()
updateCommandResult s = (Sh . StateT) $ \_ -> return (() , s)