{-# LANGUAGE CPP #-}
module Effectful.FileSystem.IO.ByteString
#if MIN_VERSION_bytestring(0,11,2)
(
fromFilePath
, toFilePath
, readFile
#else
(
readFile
#endif
, writeFile
, appendFile
, hGetLine
, hGetContents
, hGet
, hGetSome
, hGetNonBlocking
, hPut
, hPutNonBlocking
, hPutStr
, hPutStrLn
) where
import Prelude hiding
( appendFile
, readFile
, writeFile
)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS8
import System.IO (Handle)
import Effectful
import Effectful.Dispatch.Static
import Effectful.FileSystem
#if MIN_VERSION_bytestring(0,11,2)
fromFilePath :: FileSystem :> es => FilePath -> Eff es ByteString
fromFilePath :: forall (es :: [Effect]).
(FileSystem :> es) =>
FilePath -> Eff es ByteString
fromFilePath = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ByteString
BS.fromFilePath
toFilePath :: FileSystem :> es => ByteString -> Eff es FilePath
toFilePath :: forall (es :: [Effect]).
(FileSystem :> es) =>
ByteString -> Eff es FilePath
toFilePath = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> IO FilePath
BS.toFilePath
#endif
readFile :: FileSystem :> es => FilePath -> Eff es ByteString
readFile :: forall (es :: [Effect]).
(FileSystem :> es) =>
FilePath -> Eff es ByteString
readFile = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO ByteString
BS8.readFile
writeFile :: FileSystem :> es => FilePath -> ByteString -> Eff es ()
writeFile :: forall (es :: [Effect]).
(FileSystem :> es) =>
FilePath -> ByteString -> Eff es ()
writeFile FilePath
fp = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString -> IO ()
BS8.writeFile FilePath
fp
appendFile :: FileSystem :> es => FilePath -> ByteString -> Eff es ()
appendFile :: forall (es :: [Effect]).
(FileSystem :> es) =>
FilePath -> ByteString -> Eff es ()
appendFile FilePath
fp = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString -> IO ()
BS8.appendFile FilePath
fp
hGetLine :: FileSystem :> es => Handle -> Eff es ByteString
hGetLine :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> Eff es ByteString
hGetLine = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO ByteString
BS8.hGetLine
hGetContents :: FileSystem :> es => Handle -> Eff es ByteString
hGetContents :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> Eff es ByteString
hGetContents = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO ByteString
BS8.hGetContents
hGet :: FileSystem :> es => Handle -> Int -> Eff es ByteString
hGet :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> Int -> Eff es ByteString
hGet Handle
h = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> IO ByteString
BS8.hGet Handle
h
hGetSome :: FileSystem :> es => Handle -> Int -> Eff es ByteString
hGetSome :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> Int -> Eff es ByteString
hGetSome Handle
h = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> IO ByteString
BS8.hGetSome Handle
h
hGetNonBlocking :: FileSystem :> es => Handle -> Int -> Eff es ByteString
hGetNonBlocking :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> Int -> Eff es ByteString
hGetNonBlocking Handle
h = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Int -> IO ByteString
BS8.hGetNonBlocking Handle
h
hPut :: FileSystem :> es => Handle -> ByteString -> Eff es ()
hPut :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> ByteString -> Eff es ()
hPut Handle
h = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> ByteString -> IO ()
BS8.hPut Handle
h
hPutNonBlocking :: FileSystem :> es => Handle -> ByteString -> Eff es ByteString
hPutNonBlocking :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> ByteString -> Eff es ByteString
hPutNonBlocking Handle
h = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> ByteString -> IO ByteString
BS8.hPutNonBlocking Handle
h
hPutStr :: FileSystem :> es => Handle -> ByteString -> Eff es ()
hPutStr :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> ByteString -> Eff es ()
hPutStr Handle
h = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> ByteString -> IO ()
BS8.hPutStr Handle
h
hPutStrLn :: FileSystem :> es => Handle -> ByteString -> Eff es ()
hPutStrLn :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> ByteString -> Eff es ()
hPutStrLn Handle
h = forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> ByteString -> IO ()
BS8.hPutStrLn Handle
h