{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module System.IO.Interact
(
Repl,
repl,
repl',
pRepl,
pRepl',
ReplState,
replState,
replState',
pReplState,
pReplState',
replFold,
replFold',
pReplFold,
pReplFold',
)
where
import Control.Exception (bracket)
import Control.Monad.State
import Data.Maybe
import System.IO
import Text.Read (readMaybe)
class Repl a b where
repl :: (a -> b) -> IO ()
repl = pRepl ""
pRepl :: String -> (a -> b) -> IO ()
instance {-# OVERLAPPING #-} Repl [String] [String] where
pRepl :: String -> ([String] -> [String]) -> IO ()
pRepl "" f = interact $ unlines . f . lines
pRepl p f =
noBuffering . interact $
(p ++) . concatMap (++ '\n' : p) . f . lines
noBuffering :: IO a -> IO a
noBuffering = withBufferMode NoBuffering stdout
withBufferMode :: BufferMode -> Handle -> IO a -> IO a
withBufferMode mode h act =
bracket
(hGetBuffering h <* hSetBuffering h mode)
(hSetBuffering h)
(const act)
instance {-# OVERLAPPING #-} (Read a, Show b) => Repl [a] [b] where
pRepl :: String -> ([a] -> [b]) -> IO ()
pRepl p f = pRepl p $ map show . f . mapMaybe readMaybe
instance (Read a, Show b) => Repl a b where
pRepl :: String -> (a -> b) -> IO ()
pRepl p = pRepl p . readShow
readShowFunc ::
(Read a, Show b) =>
(String -> fs) ->
((b -> String) -> fb -> fs) ->
(a -> fb) ->
(String -> fs)
readShowFunc pr fm f = maybe (pr invalid) (fm show) . fmap f . readMaybe
readShow ::
(Read a, Show b) => (a -> b) -> (String -> String)
readShow = readShowFunc id id
readShowA ::
(Applicative f, Read a, Show b) => (a -> f b) -> (String -> f String)
readShowA = readShowFunc pure fmap
readShowAA ::
(Applicative g, Applicative f, Read a, Show b) =>
(a -> g (f b)) ->
(String -> g (f String))
readShowAA = readShowFunc (pure . pure) (fmap . fmap)
invalid :: String
invalid = "Invalid input"
instance {-# OVERLAPPING #-} Repl String String where
pRepl :: String -> (String -> String) -> IO ()
pRepl p = pRepl p . map
instance {-# OVERLAPPING #-} Repl String (Maybe String) where
pRepl :: String -> (String -> Maybe String) -> IO ()
pRepl p f = pRepl p $ whileJust . map f
whileJust :: [Maybe String] -> [String]
whileJust = map fromJust . takeWhile isJust
instance {-# OVERLAPPING #-} Repl String (Either String String) where
pRepl :: String -> (String -> Either String String) -> IO ()
pRepl p f = pRepl p $ whileRight . map f
whileRight :: [Either String String] -> [String]
whileRight (Right x : xs) = x : whileRight xs
whileRight (Left x : _) = [x]
whileRight [] = []
instance {-# OVERLAPPING #-} (Read a, Show b) => Repl a (Maybe b) where
pRepl :: String -> (a -> Maybe b) -> IO ()
pRepl p = pRepl p . readShowA
instance {-# OVERLAPPING #-} (Read a, Show b) => Repl a (Either String b) where
pRepl :: String -> (a -> Either String b) -> IO ()
pRepl p = pRepl p . readShowA
repl' :: (Eq a, Read a, Show b) => a -> (a -> b) -> IO ()
repl' = pRepl' ""
pRepl' ::
forall a b.
(Eq a, Read a, Show b) =>
String ->
a ->
(a -> b) ->
IO ()
pRepl' p stop = pRepl p . readShowA . checkEq stop
checkEq :: Eq a => a -> (a -> b) -> a -> Maybe b
checkEq stop f x
| x == stop = Nothing
| otherwise = Just $ f x
class ReplState a b s | b -> s where
replState ::
(a -> b) ->
s ->
IO ()
replState = pReplState ""
pReplState :: String -> (a -> b) -> s -> IO ()
instance {-# OVERLAPPING #-} ReplState String (s -> (String, s)) s where
pReplState :: String -> (String -> s -> (String, s)) -> s -> IO ()
pReplState p = pReplState p . toState
instance (Read a, Show b) => ReplState a (s -> (b, s)) s where
pReplState :: String -> (a -> s -> (b, s)) -> s -> IO ()
pReplState p = pReplState p . toState
toState :: (a -> s -> (b, s)) -> (a -> State s b)
toState f = state . f
instance {-# OVERLAPPING #-} ReplState [String] (State s [String]) s where
pReplState :: String -> ([String] -> State s [String]) -> s -> IO ()
pReplState p f s0 = pRepl p $ (`evalState` s0) . f
instance (Read a, Show b) => ReplState a (State s b) s where
pReplState :: String -> (a -> State s b) -> s -> IO ()
pReplState p = pReplState p . readShowA
instance {-# OVERLAPPING #-} ReplState String (State s String) s where
pReplState :: String -> (String -> State s String) -> s -> IO ()
pReplState p = pReplState @[String] p . mapM
instance {-# OVERLAPPING #-} ReplState String (State s (Maybe String)) s where
pReplState ::
String -> (String -> State s (Maybe String)) -> s -> IO ()
pReplState p f = pReplState p $ fmap whileJust . mapM f
instance {-# OVERLAPPING #-} ReplState String (State s (Either String String)) s where
pReplState ::
String -> (String -> State s (Either String String)) -> s -> IO ()
pReplState p f = pReplState p $ fmap whileRight . mapM f
instance {-# OVERLAPPING #-} (Read a, Show b) => ReplState a (State s (Maybe b)) s where
pReplState :: String -> (a -> State s (Maybe b)) -> s -> IO ()
pReplState p = pReplState p . readShowAA
instance {-# OVERLAPPING #-} (Read a, Show b) => ReplState a (State s (Either String b)) s where
pReplState :: String -> (a -> State s (Either String b)) -> s -> IO ()
pReplState p = pReplState p . readShowAA
replState' ::
(Eq a, Read a, Show b) => a -> (a -> State s b) -> s -> IO ()
replState' = pReplState' ""
pReplState' ::
forall a b s.
(Eq a, Read a, Show b) =>
String ->
a ->
(a -> State s b) ->
s ->
IO ()
pReplState' p stop f =
pReplState p . readShowAA $
sequence . checkEq stop f
replFold ::
(Read a, Show b) => (b -> a -> b) -> b -> IO ()
replFold = pReplFold ""
pReplFold :: (Read a, Show b) => String -> (b -> a -> b) -> b -> IO ()
pReplFold p = pReplState p . readShowA . foldState
foldState :: (b -> a -> b) -> a -> State b b
foldState f x = modify (`f` x) >> get
replFold' ::
(Eq a, Read a, Show b) => a -> (b -> a -> b) -> b -> IO ()
replFold' = pReplFold' ""
pReplFold' ::
(Eq a, Read a, Show b) =>
String ->
a ->
(b -> a -> b) ->
b ->
IO ()
pReplFold' p stop = pReplState' p stop . foldState