{-# LANGUAGE Trustworthy #-}
module System.IO.Utils(
hCopy, hCopyProgress, hLineCopy, lineCopy,
copyFileLinesToFile,
hPutStrLns, hGetLines,
hInteract,
hLineInteract, lineInteract,
lazyMapM,
optimizeForBatch, optimizeForInteraction
) where
import Data.List (genericLength)
import System.IO (BufferMode (BlockBuffering, LineBuffering),
IOMode (ReadMode, WriteMode), hClose,
hSetBuffering, openFile, stdin, stdout)
import System.IO.HVIO (HVIO (vGetContents, vGetLine, vIsEOF, vPutStr, vPutStrLn))
import System.IO.Unsafe (unsafeInterleaveIO)
hPutStrLns :: HVIO a => a -> [String] -> IO ()
hPutStrLns :: a -> [String] -> IO ()
hPutStrLns a
h = (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ ((String -> IO ()) -> [String] -> IO ())
-> (String -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$ a -> String -> IO ()
forall a. HVIO a => a -> String -> IO ()
vPutStrLn a
h
hGetLines :: HVIO a => a -> IO [String]
hGetLines :: a -> IO [String]
hGetLines a
h = IO [String] -> IO [String]
forall a. IO a -> IO a
unsafeInterleaveIO (do
Bool
ieof <- a -> IO Bool
forall a. HVIO a => a -> IO Bool
vIsEOF a
h
if (Bool
ieof)
then [String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return []
else do
String
line <- a -> IO String
forall a. HVIO a => a -> IO String
vGetLine a
h
[String]
remainder <- a -> IO [String]
forall a. HVIO a => a -> IO [String]
hGetLines a
h
[String] -> IO [String]
forall (m :: * -> *) a. Monad m => a -> m a
return (String
line String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
remainder))
hInteract :: (HVIO a, HVIO b) => a -> b -> (String -> String) -> IO ()
hInteract :: a -> b -> (String -> String) -> IO ()
hInteract a
finput b
foutput String -> String
func = do
String
content <- a -> IO String
forall a. HVIO a => a -> IO String
vGetContents a
finput
b -> String -> IO ()
forall a. HVIO a => a -> String -> IO ()
vPutStr b
foutput (String -> String
func String
content)
lineInteract :: ([String] -> [String]) -> IO ()
lineInteract :: ([String] -> [String]) -> IO ()
lineInteract = Handle -> Handle -> ([String] -> [String]) -> IO ()
forall a b.
(HVIO a, HVIO b) =>
a -> b -> ([String] -> [String]) -> IO ()
hLineInteract Handle
stdin Handle
stdout
hLineInteract :: (HVIO a, HVIO b) => a -> b -> ([String] -> [String]) -> IO ()
hLineInteract :: a -> b -> ([String] -> [String]) -> IO ()
hLineInteract a
finput b
foutput [String] -> [String]
func =
do
[String]
ls <- a -> IO [String]
forall a. HVIO a => a -> IO [String]
hGetLines a
finput
b -> [String] -> IO ()
forall a. HVIO a => a -> [String] -> IO ()
hPutStrLns b
foutput ([String] -> [String]
func [String]
ls)
hCopy :: (HVIO a, HVIO b) => a -> b -> IO ()
hCopy :: a -> b -> IO ()
hCopy a
hin b
hout = do
String
c <- a -> IO String
forall a. HVIO a => a -> IO String
vGetContents a
hin
b -> String -> IO ()
forall a. HVIO a => a -> String -> IO ()
vPutStr b
hout String
c
hCopyProgress :: (HVIO b, HVIO c, Integral a) =>
b
-> c
-> (Maybe a -> Integer -> Bool -> IO ())
-> Int
-> Maybe a
-> IO Integer
hCopyProgress :: b
-> c
-> (Maybe a -> Integer -> Bool -> IO ())
-> Int
-> Maybe a
-> IO Integer
hCopyProgress b
hin c
hout Maybe a -> Integer -> Bool -> IO ()
func Int
bsize Maybe a
estsize =
let copyFunc :: String -> Integer -> IO Integer
copyFunc :: String -> Integer -> IO Integer
copyFunc [] Integer
count = Integer -> IO Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
count
copyFunc String
indata Integer
count =
let block :: String
block = Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
bsize String
indata
remainder :: String
remainder = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
bsize String
indata
newcount :: Integer
newcount = Integer
count Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ (String -> Integer
forall i a. Num i => [a] -> i
genericLength String
block)
in
do
c -> String -> IO ()
forall a. HVIO a => a -> String -> IO ()
vPutStr c
hout String
block
Maybe a -> Integer -> Bool -> IO ()
func Maybe a
estsize Integer
count Bool
False
String -> Integer -> IO Integer
copyFunc String
remainder Integer
newcount
in
do
String
c <- b -> IO String
forall a. HVIO a => a -> IO String
vGetContents b
hin
Integer
bytes <- String -> Integer -> IO Integer
copyFunc String
c Integer
0
Maybe a -> Integer -> Bool -> IO ()
func Maybe a
estsize Integer
bytes Bool
True
Integer -> IO Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
bytes
hLineCopy :: (HVIO a, HVIO b) => a -> b -> IO()
hLineCopy :: a -> b -> IO ()
hLineCopy a
hin b
hout = a -> b -> ([String] -> [String]) -> IO ()
forall a b.
(HVIO a, HVIO b) =>
a -> b -> ([String] -> [String]) -> IO ()
hLineInteract a
hin b
hout [String] -> [String]
forall a. a -> a
id
lineCopy :: IO ()
lineCopy :: IO ()
lineCopy = Handle -> Handle -> IO ()
forall a b. (HVIO a, HVIO b) => a -> b -> IO ()
hLineCopy Handle
stdin Handle
stdout
copyFileLinesToFile :: FilePath -> FilePath -> IO ()
copyFileLinesToFile :: String -> String -> IO ()
copyFileLinesToFile String
infn String
outfn = do
Handle
hin <- String -> IOMode -> IO Handle
openFile String
infn IOMode
ReadMode
Handle
hout <- String -> IOMode -> IO Handle
openFile String
outfn IOMode
WriteMode
Handle -> Handle -> IO ()
forall a b. (HVIO a, HVIO b) => a -> b -> IO ()
hLineCopy Handle
hin Handle
hout
Handle -> IO ()
hClose Handle
hin
Handle -> IO ()
hClose Handle
hout
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
optimizeForBatch :: IO ()
optimizeForBatch :: IO ()
optimizeForBatch = do
Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdin (Maybe Int -> BufferMode
BlockBuffering (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4096))
Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdout (Maybe Int -> BufferMode
BlockBuffering (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4096))
optimizeForInteraction :: IO ()
optimizeForInteraction :: IO ()
optimizeForInteraction = do
Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdin BufferMode
LineBuffering
Handle -> BufferMode -> IO ()
hSetBuffering Handle
stdout BufferMode
LineBuffering
lazyMapM :: (a -> IO b) -> [a] -> IO [b]
lazyMapM :: (a -> IO b) -> [a] -> IO [b]
lazyMapM a -> IO b
_ [] = [b] -> IO [b]
forall (m :: * -> *) a. Monad m => a -> m a
return []
lazyMapM a -> IO b
conv (a
x:[a]
xs) =
do b
this <- a -> IO b
conv a
x
[b]
next <- IO [b] -> IO [b]
forall a. IO a -> IO a
unsafeInterleaveIO (IO [b] -> IO [b]) -> IO [b] -> IO [b]
forall a b. (a -> b) -> a -> b
$ (a -> IO b) -> [a] -> IO [b]
forall a b. (a -> IO b) -> [a] -> IO [b]
lazyMapM a -> IO b
conv [a]
xs
[b] -> IO [b]
forall (m :: * -> *) a. Monad m => a -> m a
return (b
thisb -> [b] -> [b]
forall a. a -> [a] -> [a]
:[b]
next)