Add various new functions to HPath.IO
This commit is contained in:
69
hpath-io/test/HPath/IO/CreateDirIfMissingSpec.hs
Normal file
69
hpath-io/test/HPath/IO/CreateDirIfMissingSpec.hs
Normal file
@@ -0,0 +1,69 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module HPath.IO.CreateDirIfMissingSpec where
|
||||
|
||||
|
||||
import Test.Hspec
|
||||
import System.IO.Error
|
||||
(
|
||||
ioeGetErrorType
|
||||
)
|
||||
import GHC.IO.Exception
|
||||
(
|
||||
IOErrorType(..)
|
||||
)
|
||||
import Utils
|
||||
|
||||
|
||||
|
||||
upTmpDir :: IO ()
|
||||
upTmpDir = do
|
||||
setTmpDir "CreateDirIfMissingSpec"
|
||||
createTmpDir
|
||||
|
||||
setupFiles :: IO ()
|
||||
setupFiles = do
|
||||
createDir' "alreadyExists"
|
||||
createDir' "noPerms"
|
||||
createDir' "noWritePerms"
|
||||
noPerms "noPerms"
|
||||
noWritableDirPerms "noWritePerms"
|
||||
|
||||
|
||||
|
||||
cleanupFiles :: IO ()
|
||||
cleanupFiles = do
|
||||
normalDirPerms "noPerms"
|
||||
normalDirPerms "noWritePerms"
|
||||
deleteDir' "alreadyExists"
|
||||
deleteDir' "noPerms"
|
||||
deleteDir' "noWritePerms"
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = beforeAll_ (upTmpDir >> setupFiles) $ afterAll_ cleanupFiles $
|
||||
describe "HPath.IO.CreateDirIfMissing" $ do
|
||||
|
||||
-- successes --
|
||||
it "createDirIfMissing, all fine" $ do
|
||||
createDirIfMissing' "newDir"
|
||||
removeDirIfExists "newDir"
|
||||
|
||||
it "createDirIfMissing, destination directory already exists" $
|
||||
createDirIfMissing' "alreadyExists"
|
||||
|
||||
-- posix failures --
|
||||
it "createDirIfMissing, parent directories do not exist" $
|
||||
createDirIfMissing' "some/thing/dada"
|
||||
`shouldThrow`
|
||||
(\e -> ioeGetErrorType e == NoSuchThing)
|
||||
|
||||
it "createDirIfMissing, can't write to output directory" $
|
||||
createDirIfMissing' "noWritePerms/newDir"
|
||||
`shouldThrow`
|
||||
(\e -> ioeGetErrorType e == PermissionDenied)
|
||||
|
||||
it "createDirIfMissing, can't open output directory" $
|
||||
createDirIfMissing' "noPerms/newDir"
|
||||
`shouldThrow`
|
||||
(\e -> ioeGetErrorType e == PermissionDenied)
|
||||
@@ -8,7 +8,7 @@ import Data.List
|
||||
sort
|
||||
)
|
||||
import qualified HPath as P
|
||||
import HPath.IO
|
||||
import HPath.IO hiding (getDirsFiles')
|
||||
import Test.Hspec
|
||||
import System.IO.Error
|
||||
(
|
||||
|
||||
108
hpath-io/test/HPath/IO/WriteFileLSpec.hs
Normal file
108
hpath-io/test/HPath/IO/WriteFileLSpec.hs
Normal file
@@ -0,0 +1,108 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
|
||||
module HPath.IO.WriteFileLSpec where
|
||||
|
||||
|
||||
import Test.Hspec
|
||||
import System.IO.Error
|
||||
(
|
||||
ioeGetErrorType
|
||||
)
|
||||
import GHC.IO.Exception
|
||||
(
|
||||
IOErrorType(..)
|
||||
)
|
||||
import Utils
|
||||
|
||||
|
||||
|
||||
upTmpDir :: IO ()
|
||||
upTmpDir = do
|
||||
setTmpDir "WriteFileLSpec"
|
||||
createTmpDir
|
||||
|
||||
setupFiles :: IO ()
|
||||
setupFiles = do
|
||||
createRegularFile' "fileWithContent"
|
||||
createRegularFile' "fileWithoutContent"
|
||||
createSymlink' "inputFileSymL" "fileWithContent"
|
||||
createDir' "alreadyExistsD"
|
||||
createRegularFile' "noPerms"
|
||||
noPerms "noPerms"
|
||||
createDir' "noPermsD"
|
||||
createRegularFile' "noPermsD/inputFile"
|
||||
noPerms "noPermsD"
|
||||
writeFile' "fileWithContent" "BLKASL"
|
||||
|
||||
|
||||
cleanupFiles :: IO ()
|
||||
cleanupFiles = do
|
||||
deleteFile' "fileWithContent"
|
||||
deleteFile' "fileWithoutContent"
|
||||
deleteFile' "inputFileSymL"
|
||||
deleteDir' "alreadyExistsD"
|
||||
normalFilePerms "noPerms"
|
||||
deleteFile' "noPerms"
|
||||
normalDirPerms "noPermsD"
|
||||
deleteFile' "noPermsD/inputFile"
|
||||
deleteDir' "noPermsD"
|
||||
|
||||
|
||||
spec :: Spec
|
||||
spec = beforeAll_ (upTmpDir >> setupFiles) $ afterAll_ cleanupFiles $
|
||||
describe "HPath.IO.WriteFileL" $ do
|
||||
|
||||
-- successes --
|
||||
it "WriteFileL file with content, everything clear" $ do
|
||||
writeFileL' "fileWithContent" "blahfaselllll"
|
||||
out <- readFile' "fileWithContent"
|
||||
out `shouldBe` "blahfaselllll"
|
||||
|
||||
it "WriteFileL file with content, everything clear" $ do
|
||||
writeFileL' "fileWithContent" "gagagaga"
|
||||
out <- readFile' "fileWithContent"
|
||||
out `shouldBe` "gagagaga"
|
||||
|
||||
it "WriteFileL file with content, everything clear" $ do
|
||||
writeFileL' "fileWithContent" ""
|
||||
out <- readFile' "fileWithContent"
|
||||
out `shouldBe` ""
|
||||
|
||||
it "WriteFileL file without content, everything clear" $ do
|
||||
writeFileL' "fileWithoutContent" "blahfaselllll"
|
||||
out <- readFile' "fileWithoutContent"
|
||||
out `shouldBe` "blahfaselllll"
|
||||
|
||||
it "WriteFileL, everything clear" $ do
|
||||
writeFileL' "fileWithoutContent" "gagagaga"
|
||||
out <- readFile' "fileWithoutContent"
|
||||
out `shouldBe` "gagagaga"
|
||||
|
||||
it "WriteFileL symlink, everything clear" $ do
|
||||
writeFileL' "inputFileSymL" "blahfaselllll"
|
||||
out <- readFile' "inputFileSymL"
|
||||
out `shouldBe` "blahfaselllll"
|
||||
|
||||
it "WriteFileL symlink, everything clear" $ do
|
||||
writeFileL' "inputFileSymL" "gagagaga"
|
||||
out <- readFile' "inputFileSymL"
|
||||
out `shouldBe` "gagagaga"
|
||||
|
||||
|
||||
-- posix failures --
|
||||
it "WriteFileL to dir, inappropriate type" $ do
|
||||
writeFileL' "alreadyExistsD" ""
|
||||
`shouldThrow` (\e -> ioeGetErrorType e == InappropriateType)
|
||||
|
||||
it "WriteFileL, no permissions to file" $ do
|
||||
writeFileL' "noPerms" ""
|
||||
`shouldThrow` (\e -> ioeGetErrorType e == PermissionDenied)
|
||||
|
||||
it "WriteFileL, no permissions to file" $ do
|
||||
writeFileL' "noPermsD/inputFile" ""
|
||||
`shouldThrow` (\e -> ioeGetErrorType e == PermissionDenied)
|
||||
|
||||
it "WriteFileL, file does not exist" $ do
|
||||
writeFileL' "gaga" ""
|
||||
`shouldThrow` (\e -> ioeGetErrorType e == NoSuchThing)
|
||||
@@ -19,6 +19,7 @@ import Control.Monad.IfElse
|
||||
whenM
|
||||
)
|
||||
import qualified Data.ByteString as BS
|
||||
import qualified Data.ByteString.Lazy as BSL
|
||||
import Data.IORef
|
||||
(
|
||||
newIORef
|
||||
@@ -163,6 +164,10 @@ createDir' :: ByteString -> IO ()
|
||||
{-# NOINLINE createDir' #-}
|
||||
createDir' dest = withTmpDir dest (createDir newDirPerms)
|
||||
|
||||
createDirIfMissing' :: ByteString -> IO ()
|
||||
{-# NOINLINE createDirIfMissing' #-}
|
||||
createDirIfMissing' dest = withTmpDir dest (createDirIfMissing newDirPerms)
|
||||
|
||||
createDirRecursive' :: ByteString -> IO ()
|
||||
{-# NOINLINE createDirRecursive' #-}
|
||||
createDirRecursive' dest = withTmpDir dest (createDirRecursive newDirPerms)
|
||||
@@ -262,8 +267,13 @@ canonicalizePath' p = withTmpDir p canonicalizePath
|
||||
|
||||
writeFile' :: ByteString -> ByteString -> IO ()
|
||||
{-# NOINLINE writeFile' #-}
|
||||
writeFile' ip bs =
|
||||
withTmpDir ip $ \p -> writeFile p bs
|
||||
writeFile' ip bs =
|
||||
withTmpDir ip $ \p -> writeFile p Nothing bs
|
||||
|
||||
writeFileL' :: ByteString -> BSL.ByteString -> IO ()
|
||||
{-# NOINLINE writeFileL' #-}
|
||||
writeFileL' ip bs =
|
||||
withTmpDir ip $ \p -> writeFileL p Nothing bs
|
||||
|
||||
|
||||
appendFile' :: ByteString -> ByteString -> IO ()
|
||||
|
||||
Reference in New Issue
Block a user