{-# LANGUAGE CPP, NoImplicitPrelude #-}
module System.IO.Compat (
module Base
, getContents'
, hGetContents'
, readFile'
) where
import System.IO as Base
#if !(MIN_VERSION_base(4,15,0))
import Prelude.Compat
getContents' :: IO String
getContents' :: IO String
getContents' = Handle -> IO String
hGetContents' Handle
stdin
readFile' :: FilePath -> IO String
readFile' :: String -> IO String
readFile' String
name = String -> IOMode -> IO Handle
openFile String
name IOMode
ReadMode IO Handle -> (Handle -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Handle -> IO String
hGetContents'
hGetContents' :: Handle -> IO String
hGetContents' :: Handle -> IO String
hGetContents' Handle
h = Handle -> IO String
hGetContents Handle
h IO String -> (String -> IO String) -> IO String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
s -> String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s Int -> IO String -> IO String
`seq` String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
s
#endif