module Test.Syd.Path where
import Data.ByteString (ByteString)
import qualified Data.ByteString as SB
import Path
import Path.IO
import System.IO
import Test.Syd.Def.SetupFunc
import Test.Syd.Def.TestDefM
tempDirSpec ::
  
  String ->
  TestDefM outers (Path Abs Dir) result ->
  TestDefM outers () result
tempDirSpec :: String
-> TestDefM outers (Path Abs Dir) result
-> TestDefM outers () result
tempDirSpec String
template = SetupFunc (Path Abs Dir)
-> TestDefM outers (Path Abs Dir) result
-> TestDefM outers () result
forall inner (outers :: [*]) result.
SetupFunc inner
-> TestDefM outers inner result -> TestDefM outers () result
setupAround (SetupFunc (Path Abs Dir)
 -> TestDefM outers (Path Abs Dir) result
 -> TestDefM outers () result)
-> SetupFunc (Path Abs Dir)
-> TestDefM outers (Path Abs Dir) result
-> TestDefM outers () result
forall a b. (a -> b) -> a -> b
$ String -> SetupFunc (Path Abs Dir)
tempDirSetupFunc String
template
tempDirSetupFunc ::
  
  String ->
  SetupFunc (Path Abs Dir)
tempDirSetupFunc :: String -> SetupFunc (Path Abs Dir)
tempDirSetupFunc String
template = (forall r. (Path Abs Dir -> IO r) -> IO r)
-> SetupFunc (Path Abs Dir)
forall resource.
(forall r. (resource -> IO r) -> IO r) -> SetupFunc resource
SetupFunc ((forall r. (Path Abs Dir -> IO r) -> IO r)
 -> SetupFunc (Path Abs Dir))
-> (forall r. (Path Abs Dir -> IO r) -> IO r)
-> SetupFunc (Path Abs Dir)
forall a b. (a -> b) -> a -> b
$ String -> (Path Abs Dir -> IO r) -> IO r
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (Path Abs Dir -> m a) -> m a
withSystemTempDir String
template
tempBinaryFileWithContentsSetupFunc ::
  
  String ->
  ByteString ->
  SetupFunc (Path Abs File)
tempBinaryFileWithContentsSetupFunc :: String -> ByteString -> SetupFunc (Path Abs File)
tempBinaryFileWithContentsSetupFunc String
template ByteString
contents = (forall r. (Path Abs File -> IO r) -> IO r)
-> SetupFunc (Path Abs File)
forall resource.
(forall r. (resource -> IO r) -> IO r) -> SetupFunc resource
SetupFunc ((forall r. (Path Abs File -> IO r) -> IO r)
 -> SetupFunc (Path Abs File))
-> (forall r. (Path Abs File -> IO r) -> IO r)
-> SetupFunc (Path Abs File)
forall a b. (a -> b) -> a -> b
$ \Path Abs File -> IO r
func ->
  String -> (Path Abs File -> Handle -> IO r) -> IO r
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (Path Abs File -> Handle -> m a) -> m a
withSystemTempFile
    String
template
    ( \Path Abs File
af Handle
h -> do
        Handle -> ByteString -> IO ()
SB.hPut Handle
h ByteString
contents
        Handle -> IO ()
hFlush Handle
h
        Handle -> IO ()
hClose Handle
h
        Path Abs File -> IO r
func Path Abs File
af
    )