{-# LANGUAGE Safe #-}
module Relude.File
(
readFileText
, writeFileText
, appendFileText
, readFileLText
, writeFileLText
, appendFileLText
, readFileBS
, writeFileBS
, appendFileBS
, readFileLBS
, writeFileLBS
, appendFileLBS
) where
import Relude.Base (FilePath, IO)
import Relude.Function ((.))
import Relude.Monad.Reexport (MonadIO (..))
import Relude.String (ByteString, LByteString, LText, Text)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy.IO as LT
readFileText :: MonadIO m => FilePath -> m Text
readFileText :: forall (m :: * -> *). MonadIO m => FilePath -> m Text
readFileText = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Text
T.readFile
{-# SPECIALIZE readFileText :: FilePath -> IO Text #-}
{-# INLINE readFileText #-}
{-# WARNING readFileText ["'readFileText' depends on the system's locale settings and can throw unexpected exceptions.", "Use 'readFileBS' instead."] #-}
writeFileText :: MonadIO m => FilePath -> Text -> m ()
writeFileText :: forall (m :: * -> *). MonadIO m => FilePath -> Text -> m ()
writeFileText FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text -> IO ()
T.writeFile FilePath
p
{-# SPECIALIZE writeFileText :: FilePath -> Text -> IO () #-}
{-# INLINE writeFileText #-}
appendFileText :: MonadIO m => FilePath -> Text -> m ()
appendFileText :: forall (m :: * -> *). MonadIO m => FilePath -> Text -> m ()
appendFileText FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text -> IO ()
T.appendFile FilePath
p
{-# SPECIALIZE appendFileText :: FilePath -> Text -> IO () #-}
{-# INLINE appendFileText #-}
readFileLText :: MonadIO m => FilePath -> m LText
readFileLText :: forall (m :: * -> *). MonadIO m => FilePath -> m LText
readFileLText = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO LText
LT.readFile
{-# SPECIALIZE readFileLText :: FilePath -> IO LText #-}
{-# INLINE readFileLText #-}
{-# WARNING readFileLText ["'readFileLText' depends on the system's locale settings and can throw unexpected exceptions.", "Use 'readFileLBS' instead."] #-}
writeFileLText :: MonadIO m => FilePath -> LText -> m ()
writeFileLText :: forall (m :: * -> *). MonadIO m => FilePath -> LText -> m ()
writeFileLText FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LText -> IO ()
LT.writeFile FilePath
p
{-# SPECIALIZE writeFileLText :: FilePath -> LText -> IO () #-}
{-# INLINE writeFileLText #-}
appendFileLText :: MonadIO m => FilePath -> LText -> m ()
appendFileLText :: forall (m :: * -> *). MonadIO m => FilePath -> LText -> m ()
appendFileLText FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LText -> IO ()
LT.appendFile FilePath
p
{-# SPECIALIZE appendFileLText :: FilePath -> LText -> IO () #-}
{-# INLINE appendFileLText #-}
readFileBS :: MonadIO m => FilePath -> m ByteString
readFileBS :: forall (m :: * -> *). MonadIO m => FilePath -> m ByteString
readFileBS = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ByteString
BS.readFile
{-# SPECIALIZE readFileBS :: FilePath -> IO ByteString #-}
{-# INLINE readFileBS #-}
writeFileBS :: MonadIO m => FilePath -> ByteString -> m ()
writeFileBS :: forall (m :: * -> *). MonadIO m => FilePath -> ByteString -> m ()
writeFileBS FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString -> IO ()
BS.writeFile FilePath
p
{-# SPECIALIZE writeFileBS :: FilePath -> ByteString -> IO () #-}
{-# INLINE writeFileBS #-}
appendFileBS :: MonadIO m => FilePath -> ByteString -> m ()
appendFileBS :: forall (m :: * -> *). MonadIO m => FilePath -> ByteString -> m ()
appendFileBS FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString -> IO ()
BS.appendFile FilePath
p
{-# SPECIALIZE appendFileBS :: FilePath -> ByteString -> IO () #-}
{-# INLINE appendFileBS #-}
readFileLBS :: MonadIO m => FilePath -> m LByteString
readFileLBS :: forall (m :: * -> *). MonadIO m => FilePath -> m LByteString
readFileLBS = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO LByteString
LBS.readFile
{-# SPECIALIZE readFileLBS :: FilePath -> IO LByteString #-}
{-# INLINE readFileLBS #-}
writeFileLBS :: MonadIO m => FilePath -> LByteString -> m ()
writeFileLBS :: forall (m :: * -> *). MonadIO m => FilePath -> LByteString -> m ()
writeFileLBS FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LByteString -> IO ()
LBS.writeFile FilePath
p
{-# SPECIALIZE writeFileLBS :: FilePath -> LByteString -> IO () #-}
{-# INLINE writeFileLBS #-}
appendFileLBS :: MonadIO m => FilePath -> LByteString -> m ()
appendFileLBS :: forall (m :: * -> *). MonadIO m => FilePath -> LByteString -> m ()
appendFileLBS FilePath
p = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LByteString -> IO ()
LBS.appendFile FilePath
p
{-# SPECIALIZE appendFileLBS :: FilePath -> LByteString -> IO () #-}
{-# INLINE appendFileLBS #-}