module Effectful.Temporary
(
Temporary
, runTemporary
, withSystemTempFile
, withSystemTempDirectory
, withTempFile
, withTempDirectory
) where
import System.IO
import UnliftIO.Temporary qualified as T
import Effectful
import Effectful.Dispatch.Static
data Temporary :: Effect
type instance DispatchOf Temporary = Static WithSideEffects
data instance StaticRep Temporary = Temporary
runTemporary :: IOE :> es => Eff (Temporary : es) a -> Eff es a
runTemporary :: forall (es :: [Effect]) a.
(IOE :> es) =>
Eff (Temporary : es) a -> Eff es a
runTemporary = StaticRep Temporary -> Eff (Temporary : es) a -> Eff es a
forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect])
a.
(DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) =>
StaticRep e -> Eff (e : es) a -> Eff es a
evalStaticRep StaticRep Temporary
Temporary
withSystemTempFile
:: Temporary :> es
=> String
-> (FilePath -> Handle -> Eff es a)
-> Eff es a
withSystemTempFile :: forall (es :: [Effect]) a.
(Temporary :> es) =>
String -> (String -> Handle -> Eff es a) -> Eff es a
withSystemTempFile String
template String -> Handle -> Eff es a
action = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
String -> (String -> Handle -> IO a) -> IO a
forall (m :: Type -> Type) a.
MonadUnliftIO m =>
String -> (String -> Handle -> m a) -> m a
T.withSystemTempFile String
template ((String -> Handle -> IO a) -> IO a)
-> (String -> Handle -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \String
fp Handle
handle -> Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> Eff es a -> IO a
forall a b. (a -> b) -> a -> b
$ String -> Handle -> Eff es a
action String
fp Handle
handle
withSystemTempDirectory
:: Temporary :> es
=> String
-> (FilePath -> Eff es a)
-> Eff es a
withSystemTempDirectory :: forall (es :: [Effect]) a.
(Temporary :> es) =>
String -> (String -> Eff es a) -> Eff es a
withSystemTempDirectory String
template String -> Eff es a
action = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
String -> (String -> IO a) -> IO a
forall (m :: Type -> Type) a.
MonadUnliftIO m =>
String -> (String -> m a) -> m a
T.withSystemTempDirectory String
template ((String -> IO a) -> IO a) -> (String -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \String
fp -> Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> Eff es a -> IO a
forall a b. (a -> b) -> a -> b
$ String -> Eff es a
action String
fp
withTempFile
:: Temporary :> es
=> FilePath
-> String
-> (FilePath -> Handle -> Eff es a)
-> Eff es a
withTempFile :: forall (es :: [Effect]) a.
(Temporary :> es) =>
String -> String -> (String -> Handle -> Eff es a) -> Eff es a
withTempFile String
tmpDir String
template String -> Handle -> Eff es a
action = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
String -> String -> (String -> Handle -> IO a) -> IO a
forall (m :: Type -> Type) a.
MonadUnliftIO m =>
String -> String -> (String -> Handle -> m a) -> m a
T.withTempFile String
tmpDir String
template ((String -> Handle -> IO a) -> IO a)
-> (String -> Handle -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \String
fp Handle
handle -> Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> Eff es a -> IO a
forall a b. (a -> b) -> a -> b
$ String -> Handle -> Eff es a
action String
fp Handle
handle
withTempDirectory
:: Temporary :> es
=> FilePath
-> String
-> (FilePath -> Eff es a)
-> Eff es a
withTempDirectory :: forall (es :: [Effect]) a.
(Temporary :> es) =>
String -> String -> (String -> Eff es a) -> Eff es a
withTempDirectory String
tmpDir String
template String -> Eff es a
action = ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall (es :: [Effect]) a.
HasCallStack =>
((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeSeqUnliftIO (((forall r. Eff es r -> IO r) -> IO a) -> Eff es a)
-> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
forall a b. (a -> b) -> a -> b
$ \forall r. Eff es r -> IO r
unlift -> do
String -> String -> (String -> IO a) -> IO a
forall (m :: Type -> Type) a.
MonadUnliftIO m =>
String -> String -> (String -> m a) -> m a
T.withTempDirectory String
tmpDir String
template ((String -> IO a) -> IO a) -> (String -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \String
fp -> Eff es a -> IO a
forall r. Eff es r -> IO r
unlift (Eff es a -> IO a) -> Eff es a -> IO a
forall a b. (a -> b) -> a -> b
$ String -> Eff es a
action String
fp