{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}
module Universum.Lifted.File
( appendFile
, getLine
, readFile
, writeFile
, withFile
, openFile
, hClose
) where
import Control.Exception.Safe (MonadMask, bracket)
import Control.Monad.Trans (MonadIO, liftIO)
import Data.Function ((.))
import Data.Text (Text)
import Prelude (FilePath)
import System.IO (Handle, IOMode)
import qualified Data.Text.IO as XIO
import qualified System.IO as XIO (openFile, hClose, IO)
appendFile :: MonadIO m => FilePath -> Text -> m ()
appendFile a b = liftIO (XIO.appendFile a b)
{-# INLINE appendFile #-}
getLine :: MonadIO m => m Text
getLine = liftIO XIO.getLine
{-# INLINE getLine #-}
readFile :: MonadIO m => FilePath -> m Text
readFile a = liftIO (XIO.readFile a)
{-# INLINE readFile #-}
writeFile :: MonadIO m => FilePath -> Text -> m ()
writeFile a b = liftIO (XIO.writeFile a b)
{-# INLINE writeFile #-}
openFile :: MonadIO m => FilePath -> IOMode -> m Handle
openFile a b = liftIO (XIO.openFile a b)
{-# INLINE openFile #-}
hClose :: MonadIO m => Handle -> m ()
hClose = liftIO . XIO.hClose
{-# INLINE hClose #-}
withFile :: (MonadIO m, MonadMask m) => FilePath -> IOMode -> (Handle -> m a) -> m a
withFile filePath mode f = bracket (openFile filePath mode) hClose f
{-# SPECIALIZE appendFile :: FilePath -> Text -> XIO.IO () #-}
{-# SPECIALIZE getLine :: XIO.IO Text #-}
{-# SPECIALIZE readFile :: FilePath -> XIO.IO Text #-}
{-# SPECIALIZE writeFile :: FilePath -> Text -> XIO.IO () #-}
{-# SPECIALIZE openFile :: FilePath -> IOMode -> XIO.IO Handle #-}
{-# SPECIALIZE hClose :: Handle -> XIO.IO () #-}
{-# SPECIALIZE withFile :: FilePath -> IOMode -> (Handle -> XIO.IO a) -> XIO.IO a #-}