{- |
Copyright:  (c) 2018-2019 Kowainik
SPDX-License-Identifier: MIT
Maintainer: Kowainik <xrom.xkov@gmail.com>

Lifted to 'MonadIO' families of file processing functions for 'Text', 'LText',
'ByteString' and 'LByteString' types.

These functions are lifted which means that you can also use them inside
various Monad Transformers without adding 'liftIO' call explicitly.

__NOTE:__ These functions are for working with textual data. Functions that work
with 'Text' or 'LText' types are system and locale-sensitive (encoding,
line-endings). If you want binary data, use 'ByteString' functions (they are
also faster since they don't check encoding). However, you can then decode that
data with the help of functions from the @"Relude.String.Conversion"@ module, e. g.
'Relude.String.Conversion.decodeUtf8'.
-}

module Relude.File
       ( -- * Text
         readFileText
       , writeFileText
       , appendFileText

         -- * Lazy Text
       , readFileLText
       , writeFileLText
       , appendFileLText

         -- * ByteString
       , readFileBS
       , writeFileBS
       , appendFileBS

         -- * Lazy ByteString
       , 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

----------------------------------------------------------------------------
-- Text
----------------------------------------------------------------------------

-- | Lifted version of 'T.readFile'.
readFileText :: MonadIO m => FilePath -> m Text
readFileText :: FilePath -> m Text
readFileText = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> (FilePath -> IO Text) -> FilePath -> m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Text
T.readFile
{-# SPECIALIZE readFileText :: FilePath -> IO Text #-}
{-# INLINE     readFileText #-}

-- | Lifted version of 'T.writeFile'.
writeFileText :: MonadIO m => FilePath -> Text -> m ()
writeFileText :: FilePath -> Text -> m ()
writeFileText p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (Text -> IO ()) -> Text -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text -> IO ()
T.writeFile FilePath
p
{-# SPECIALIZE writeFileText :: FilePath -> Text -> IO () #-}
{-# INLINE     writeFileText #-}

-- | Lifted version of 'T.appendFile'.
appendFileText :: MonadIO m => FilePath -> Text -> m ()
appendFileText :: FilePath -> Text -> m ()
appendFileText p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (Text -> IO ()) -> Text -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text -> IO ()
T.appendFile FilePath
p
{-# SPECIALIZE appendFileText :: FilePath -> Text -> IO () #-}
{-# INLINE     appendFileText #-}

----------------------------------------------------------------------------
-- Lazy Text
----------------------------------------------------------------------------

-- | Lifted version of 'LT.readFile'.
readFileLText :: MonadIO m => FilePath -> m LText
readFileLText :: FilePath -> m LText
readFileLText = IO LText -> m LText
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LText -> m LText)
-> (FilePath -> IO LText) -> FilePath -> m LText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO LText
LT.readFile
{-# SPECIALIZE readFileLText :: FilePath -> IO LText #-}
{-# INLINE     readFileLText #-}

-- | Lifted version of 'LT.writeFile'.
writeFileLText :: MonadIO m => FilePath -> LText -> m ()
writeFileLText :: FilePath -> LText -> m ()
writeFileLText p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LText -> IO ()) -> LText -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LText -> IO ()
LT.writeFile FilePath
p
{-# SPECIALIZE writeFileLText :: FilePath -> LText -> IO () #-}
{-# INLINE     writeFileLText #-}

-- | Lifted version of 'LT.appendFile'.
appendFileLText :: MonadIO m => FilePath -> LText -> m ()
appendFileLText :: FilePath -> LText -> m ()
appendFileLText p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LText -> IO ()) -> LText -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LText -> IO ()
LT.appendFile FilePath
p
{-# SPECIALIZE appendFileLText :: FilePath -> LText -> IO () #-}
{-# INLINE     appendFileLText #-}

----------------------------------------------------------------------------
-- ByteString
----------------------------------------------------------------------------

-- | Lifted version of 'BS.readFile'.
readFileBS :: MonadIO m => FilePath -> m ByteString
readFileBS :: FilePath -> m ByteString
readFileBS = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString)
-> (FilePath -> IO ByteString) -> FilePath -> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ByteString
BS.readFile
{-# SPECIALIZE readFileBS :: FilePath -> IO ByteString #-}
{-# INLINE     readFileBS #-}

-- | Lifted version of 'BS.writeFile'.
writeFileBS :: MonadIO m => FilePath -> ByteString -> m ()
writeFileBS :: FilePath -> ByteString -> m ()
writeFileBS p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (ByteString -> IO ()) -> ByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString -> IO ()
BS.writeFile FilePath
p
{-# SPECIALIZE writeFileBS :: FilePath -> ByteString -> IO () #-}
{-# INLINE     writeFileBS #-}

-- | Lifted version of 'BS.appendFile'.
appendFileBS :: MonadIO m => FilePath -> ByteString -> m ()
appendFileBS :: FilePath -> ByteString -> m ()
appendFileBS p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (ByteString -> IO ()) -> ByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString -> IO ()
BS.appendFile FilePath
p
{-# SPECIALIZE appendFileBS :: FilePath -> ByteString -> IO () #-}
{-# INLINE     appendFileBS #-}

----------------------------------------------------------------------------
-- Lazy ByteString
----------------------------------------------------------------------------

-- | Lifted version of 'LBS.readFile'.
readFileLBS :: MonadIO m => FilePath -> m LByteString
readFileLBS :: FilePath -> m LByteString
readFileLBS = IO LByteString -> m LByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LByteString -> m LByteString)
-> (FilePath -> IO LByteString) -> FilePath -> m LByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO LByteString
LBS.readFile
{-# SPECIALIZE readFileLBS :: FilePath -> IO LByteString #-}
{-# INLINE     readFileLBS #-}

-- | Lifted version of 'LBS.writeFile'.
writeFileLBS :: MonadIO m => FilePath -> LByteString -> m ()
writeFileLBS :: FilePath -> LByteString -> m ()
writeFileLBS p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LByteString -> IO ()) -> LByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LByteString -> IO ()
LBS.writeFile FilePath
p
{-# SPECIALIZE writeFileLBS :: FilePath -> LByteString -> IO () #-}
{-# INLINE     writeFileLBS #-}

-- | Lifted version of 'LBS.appendFile'.
appendFileLBS :: MonadIO m => FilePath -> LByteString -> m ()
appendFileLBS :: FilePath -> LByteString -> m ()
appendFileLBS p :: FilePath
p = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (LByteString -> IO ()) -> LByteString -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> LByteString -> IO ()
LBS.appendFile FilePath
p
{-# SPECIALIZE appendFileLBS :: FilePath -> LByteString -> IO () #-}
{-# INLINE     appendFileLBS #-}