module Ssb.Aux where import Protolude import Data.Aeson as Aeson import Data.ByteString.Lazy as BS (toStrict) import Data.ByteString.Char8 as BS (pack, unpack) import Data.Default import Data.Serialize as Serialize import Data.Either.Combinators ( mapLeft , mapRight ) import Control.Concurrent.STM import System.IO ( hFlush , hGetLine , hSetBinaryMode ) import System.Process -- | Convertible describes instances where types can be easily converted. class Convertible a b where convert :: a -> b -- | decodeJSON deserializes the JSON bytestring. -- It is a reimplementation Aeson's eitherDecodeStrict which returns Text -- instead of String. decodeJSON :: (FromJSON a) => ByteString -> Either Text a decodeJSON = mapLeft toS . Aeson.eitherDecodeStrict encodeJSON :: (ToJSON a) => a -> ByteString encodeJSON = BS.toStrict . Aeson.encode encodeByteString :: Serialize.Serialize a => a -> ByteString encodeByteString = Serialize.encode decodeByteString :: Serialize.Serialize a => ByteString -> Either Text a decodeByteString a = mapLeft toS $ Serialize.decode a withErr :: Text -> Maybe a -> Either Text a withErr = maybeToRight error :: Text -> Either Text a error = Left maybeWord8 :: Int -> Either Text Word8 maybeWord8 arg = if arg >= min && arg <= max then return $ fromIntegral arg else Left "out of bounds" where min = fromIntegral (minBound :: Word8) max = fromIntegral (maxBound :: Word8) -- | TODO: kill command forked by forkCommand command :: Text -> TMVar ByteString -> TMVar ByteString -> IO () command cmd input output = do (hIn, hOut, hErr, hProc) <- runInteractiveCommand (toS cmd) hSetBinaryMode hIn False hSetBinaryMode hOut False hSetBinaryMode hErr False let loop = do v <- atomically $ takeTMVar input hPutStr hIn (BS.unpack v :: [Char]) hFlush hIn v' <- hGetLine hOut atomically $ putTMVar output (BS.pack v') loop loop