{-# LANGUAGE NoImplicitPrelude #-} module Precursor.System.IO ( -- * The IO monad IO -- * IO class , MonadIO , liftIO -- * Files and handles , FilePath -- * File-at-a-time operations , readFile , writeFile , appendFile -- * Special cases for standard input and output , interact , getContents , getLine , putStr , putStrLn ) where import Control.Monad.IO.Class import Data.Text.Lazy import qualified Data.Text.Lazy.IO as Text import Precursor.Control.Category import Precursor.Function import System.IO (FilePath, IO) -- | Read a file and return its contents as a string. The file is -- read lazily, as with 'getContents'. readFile :: MonadIO m => FilePath -> m Text readFile = liftIO . Text.readFile -- | Write a string to a file. The file is truncated to zero length -- before writing begins. writeFile :: MonadIO m => FilePath -> Text -> m () writeFile = liftIO .: Text.writeFile -- | Write a string the end of a file. appendFile :: MonadIO m => FilePath -> Text -> m () appendFile = liftIO .: Text.appendFile -- | The 'interact' function takes a function of type @Text -> Text@ -- as its argument. The entire input from the standard input device is -- passed (lazily) to this function as its argument, and the resulting -- string is output on the standard output device. interact :: MonadIO m => (Text -> Text) -> m () interact = liftIO . Text.interact -- | Lazily read all user input on 'stdin' as a single string. getContents :: MonadIO m => m Text getContents = liftIO Text.getContents -- | Read a single line of user input from 'stdin'. getLine :: MonadIO m => m Text getLine = liftIO Text.getLine -- | Write a string to 'stdout'. putStr :: MonadIO m => Text -> m () putStr = liftIO . Text.putStr -- | Write a string to 'stdout', followed by a newline. putStrLn :: MonadIO m => Text -> m () putStrLn = liftIO . Text.putStrLn