{-# language LambdaCase #-} module Text.ParseSR.IO ( withInput, withOutput ) where import Control.Monad ( unless, forM_ ) import System.IO import qualified Data.ByteString.Char8 as B import Data.SRTree import Text.ParseSR ( SRAlgs, Output, parseSR, showOutput ) withInput :: String -> SRAlgs -> String -> Bool -> IO [Either String (SRTree Int Double)] withInput :: String -> SRAlgs -> String -> Bool -> IO [Either String (SRTree Int Double)] withInput String fname SRAlgs sr String hd Bool param = do Handle h <- if forall (t :: * -> *) a. Foldable t => t a -> Bool null String fname then forall (f :: * -> *) a. Applicative f => a -> f a pure Handle stdin else String -> IOMode -> IO Handle openFile String fname IOMode ReadMode [String] contents <- Handle -> IO [String] hGetLines Handle h let myParser :: String -> Either String (SRTree Int Double) myParser = SRAlgs -> ByteString -> Bool -> ByteString -> Either String (SRTree Int Double) parseSR SRAlgs sr (String -> ByteString B.pack String hd) Bool param forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ByteString B.pack es :: [Either String (SRTree Int Double)] es = forall a b. (a -> b) -> [a] -> [b] map String -> Either String (SRTree Int Double) myParser [String] contents forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (forall (t :: * -> *) a. Foldable t => t a -> Bool null String fname) forall a b. (a -> b) -> a -> b $ Handle -> IO () hClose Handle h forall (f :: * -> *) a. Applicative f => a -> f a pure [Either String (SRTree Int Double)] es withOutput :: String -> Output -> [Either String (SRTree Int Double)] -> IO () withOutput :: String -> Output -> [Either String (SRTree Int Double)] -> IO () withOutput String fname Output output [Either String (SRTree Int Double)] exprs = do Handle h <- if forall (t :: * -> *) a. Foldable t => t a -> Bool null String fname then forall (f :: * -> *) a. Applicative f => a -> f a pure Handle stdout else String -> IOMode -> IO Handle openFile String fname IOMode WriteMode forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, Monad m) => t a -> (a -> m b) -> m () forM_ [Either String (SRTree Int Double)] exprs forall a b. (a -> b) -> a -> b $ \case Left String err -> Handle -> String -> IO () hPutStrLn Handle h forall a b. (a -> b) -> a -> b $ String "invalid expression: " forall a. Semigroup a => a -> a -> a <> String err Right SRTree Int Double ex -> Handle -> String -> IO () hPutStrLn Handle h (Output -> SRTree Int Double -> String showOutput Output output SRTree Int Double ex) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (forall (t :: * -> *) a. Foldable t => t a -> Bool null String fname) forall a b. (a -> b) -> a -> b $ Handle -> IO () hClose Handle h hGetLines :: Handle -> IO [String] hGetLines :: Handle -> IO [String] hGetLines Handle h = do Bool done <- Handle -> IO Bool hIsEOF Handle h if Bool done then forall (m :: * -> *) a. Monad m => a -> m a return [] else do String line <- Handle -> IO String hGetLine Handle h (String line forall a. a -> [a] -> [a] :) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Handle -> IO [String] hGetLines Handle h