{-# LANGUAGE CPP #-}
module Effectful.FileSystem.IO.ByteString.Builder
(
hPutBuilder
#if MIN_VERSION_bytestring(0,11,2)
, writeFile
#endif
) where
import Data.ByteString.Builder (Builder)
import Data.ByteString.Builder qualified as BSB
import Prelude hiding (writeFile)
import System.IO (Handle)
import Effectful
import Effectful.Dispatch.Static
import Effectful.FileSystem
hPutBuilder :: FileSystem :> es => Handle -> Builder -> Eff es ()
hPutBuilder :: forall (es :: [Effect]).
(FileSystem :> es) =>
Handle -> Builder -> Eff es ()
hPutBuilder Handle
h = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (Builder -> IO ()) -> Builder -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> Builder -> IO ()
BSB.hPutBuilder Handle
h
#if MIN_VERSION_bytestring(0,11,2)
writeFile :: FileSystem :> es => FilePath -> Builder -> Eff es ()
writeFile :: forall (es :: [Effect]).
(FileSystem :> es) =>
FilePath -> Builder -> Eff es ()
writeFile FilePath
fp = IO () -> Eff es ()
forall a (es :: [Effect]). IO a -> Eff es a
unsafeEff_ (IO () -> Eff es ()) -> (Builder -> IO ()) -> Builder -> Eff es ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Builder -> IO ()
BSB.writeFile FilePath
fp
#endif