{-# LANGUAGE MultiParamTypeClasses
,FunctionalDependencies #-}
module Data.ListLike.IO
( ListLikeIO(..)
)
where
import Prelude hiding (length, head, last, null, tail, map, filter, concat,
any, lookup, init, all, foldl, foldr, foldl1, foldr1,
maximum, minimum, iterate, span, break, takeWhile,
dropWhile, reverse, zip, zipWith, sequence,
sequence_, mapM, mapM_, concatMap, and, or, sum,
product, repeat, replicate, cycle, take, drop,
splitAt, elem, notElem, unzip, lines, words,
unlines, unwords, putStr, getContents)
import qualified System.IO as IO
import Data.ListLike.Base
class (ListLike full item) => ListLikeIO full item | full -> item where
hGetLine :: IO.Handle -> IO full
hGetContents :: IO.Handle -> IO full
hGet :: IO.Handle -> Int -> IO full
hGetNonBlocking :: IO.Handle -> Int -> IO full
hPutStr :: IO.Handle -> full -> IO ()
hPutStrLn :: IO.Handle -> full -> IO ()
hPutStrLn Handle
fp full
x =
do Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
fp full
x
Handle -> String -> IO ()
IO.hPutStrLn Handle
fp String
""
getLine :: IO full
getLine = Handle -> IO full
forall full item. ListLikeIO full item => Handle -> IO full
hGetLine Handle
IO.stdin
getContents :: IO full
getContents = Handle -> IO full
forall full item. ListLikeIO full item => Handle -> IO full
hGetContents Handle
IO.stdin
putStr :: full -> IO ()
putStr = Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
IO.stdout
putStrLn :: full -> IO ()
putStrLn = Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStrLn Handle
IO.stdout
interact :: (full -> full) -> IO ()
interact full -> full
func =
do full
c <- IO full
forall full item. ListLikeIO full item => IO full
getContents
full -> IO ()
forall full item. ListLikeIO full item => full -> IO ()
putStr (full -> full
func full
c)
readFile :: FilePath -> IO full
readFile String
fn =
do Handle
fp <- String -> IOMode -> IO Handle
IO.openFile String
fn IOMode
IO.ReadMode
Handle -> IO full
forall full item. ListLikeIO full item => Handle -> IO full
hGetContents Handle
fp
writeFile :: FilePath -> full -> IO ()
writeFile String
fn full
x =
do Handle
fp <- String -> IOMode -> IO Handle
IO.openFile String
fn IOMode
IO.WriteMode
Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
fp full
x
Handle -> IO ()
IO.hClose Handle
fp
appendFile :: FilePath -> full -> IO ()
appendFile String
fn full
x =
do Handle
fp <- String -> IOMode -> IO Handle
IO.openFile String
fn IOMode
IO.AppendMode
Handle -> full -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
fp full
x
Handle -> IO ()
IO.hClose Handle
fp