module Effectful.FileSystem.IO.ByteString.Lazy
(
readFile
, writeFile
, appendFile
, hGetContents
, hGet
, hGetNonBlocking
, hPut
, hPutNonBlocking
, hPutStr
, hPutStrLn
) where
import Prelude hiding
( appendFile
, readFile
, writeFile
)
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy.Char8 as LBS8
import System.IO (Handle)
import Effectful
import Effectful.Dispatch.Static
import Effectful.FileSystem
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
LBS8.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 ()
LBS8.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 ()
LBS8.appendFile FilePath
fp
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
LBS8.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
LBS8.hGet 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
LBS8.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 ()
LBS8.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
LBS8.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 ()
LBS8.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 ()
LBS8.hPutStrLn Handle
h