Skip to content

Commit

Permalink
Add rm test cases
Browse files Browse the repository at this point in the history
  • Loading branch information
rnjtranjan committed Jul 27, 2022
1 parent c2f8138 commit 92f593d
Show file tree
Hide file tree
Showing 4 changed files with 117 additions and 89 deletions.
2 changes: 2 additions & 0 deletions hie.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@ cradle:
cabal:
- path: "./src"
component: "lib:streamly-coreutils"
- path: "./test"
component: "test:coreutils-test"
dependencies:
- streamly-coreutils.cabal
- hie.yaml
8 changes: 4 additions & 4 deletions src/Streamly/Coreutils/StringQ.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Control.Applicative (Alternative(..))
import Control.Monad.Catch (MonadCatch)
import Control.Monad.IO.Class (liftIO, MonadIO)
import Data.Char (chr)
import Data.Data (Data, Typeable)
import Data.Data (Data)
import Data.Default.Class (Default(..))
import Language.Haskell.TH (Exp, Q, Pat)
import Language.Haskell.TH.Quote (QuasiQuoter(..), dataToExpQ, dataToPatQ)
Expand Down Expand Up @@ -61,20 +61,20 @@ data Permissions = Permissions
{ readable :: Bool
, writable :: Bool
, executable :: Bool
} deriving (Eq, Ord, Read, Show, Typeable, Data)
} deriving (Eq, Ord, Read, Show, Data)

data UserType =
Owner
| Group
| Others
| All
deriving (Eq, Ord, Read, Show, Typeable, Data)
deriving (Eq, Ord, Read, Show, Data)

data UserTypePerm =
UserTypePerm
{ utype :: UserType
, permssions :: Permissions
} deriving (Eq, Ord, Read, Show, Typeable, Data)
} deriving (Eq, Ord, Read, Show, Data)

instance Default Permissions where
def = Permissions
Expand Down
22 changes: 8 additions & 14 deletions test/Common.hs
Original file line number Diff line number Diff line change
@@ -1,22 +1,16 @@
module Common
( createParent
, createDirWithParent
, createDir
, createFileWithParent
, createFile
)
where

import Control.Monad (unless)
import System.Directory
( createDirectory
, createDirectoryIfMissing
, createDirectoryLink
, removeFile
, removePathForcibly
, renameDirectory
, renamePath
)
import System.Directory (createDirectory, createDirectoryIfMissing)
import System.FilePath ((</>), takeDirectory)
import System.IO
( BufferMode(..), hSetBuffering, stdout, IOMode (WriteMode), openFile
, hClose)
import System.IO.Temp (withSystemTempDirectory)

import System.IO ( IOMode (WriteMode), openFile, hClose)

createParent :: FilePath -> FilePath -> IO ()
createParent file parent = do
Expand Down
174 changes: 103 additions & 71 deletions test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,13 +7,12 @@ where
import qualified Streamly.Prelude as S
import qualified Streamly.Internal.Data.Fold as FL

import Data.List (stripPrefix)
import Streamly.Coreutils.Common (Switch(..))
import Streamly.Coreutils.Uniq
import Streamly.Coreutils.Rm
import Streamly.Coreutils.FileTest
import Streamly.Coreutils.Chmod
import System.FilePath ((</>))
import System.IO.Temp (withSystemTempDirectory)

import Control.Exception (try, SomeException)
import Control.Monad.IO.Class (MonadIO)
Expand Down Expand Up @@ -59,8 +58,8 @@ gen c n = S.unfoldr step (0, True)
-- * File parent dirs not having permissions
-- * File owned by someone else

cleanup :: String -> IO ()
cleanup = rm (force Nuke . recursive On)
rmDir :: FilePath
rmDir = "rmDir"

processResult :: Either SomeException s -> IO String
processResult res = return $
Expand All @@ -69,80 +68,109 @@ processResult res = return $
Right _ -> "Passed"

testRmDefault :: IO String
testRmDefault = do
let dir = "testDir1"
file = "file.txt"
path = dir </> file
cleanup dir
createFileWithParent file dir
exist <- test path isExisting
rm id path
failed <- test path isExisting
if exist && not failed
then return "Passed"
else return "Failed"
testRmDefault =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "file.txt"
path = dir </> file
createFileWithParent file dir
try (rm id path) >>= processResult

testRmDefaultFail :: IO String
testRmDefaultFail =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRO.txt"
path = dir </> file
createFileWithParent file dir
chmod [perm|u=r|] path
try (rm id path) >>= processResult

testRmNonExist :: IO String
testRmNonExist = do
let dir = "testDir2"
file = "file.txt"
fileNE = "fileNE.txt"
pathNE = dir </> fileNE
cleanup dir
createFileWithParent file dir
try (rm id pathNE) >>= processResult
testRmNonExist =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
fileNE = "fileNE.txt"
pathNE = dir </> fileNE
try (rm id pathNE) >>= processResult

--chmod [perm|a=rwx|] "path"
-- make path read-only
-- chmod [perm|u=r|] "path"

testRmROFile :: IO String
testRmROFile = do
let dir = "testDir3"
file = "fileRO.txt"
path = dir </> file
cleanup dir
createFileWithParent file dir
chmod [perm|u=r|] path
try (rm id path) >>= processResult
testRmROFile =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRO.txt"
path = dir </> file
createFileWithParent file dir
chmod [perm|u=r|] path
try (rm id path) >>= processResult

testRmForceFile :: IO String
testRmForceFile = do
let dir = "testDir4"
file = "fileRO.txt"
path = dir </> file
cleanup dir
createFileWithParent file dir
chmod [perm|u=r|] path
try (rm (force Force) path) >>= processResult

testRmForceFail :: IO String
testRmForceFail = do
let dir = "testDirRO1"
file = "fileRW.txt"
path = dir </> file
cleanup dir
createFileWithParent file dir
chmod [perm|u=r|] dir
try (rm (force Force) path) >>= processResult
testRmForceFile =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRO.txt"
path = dir </> file
createFileWithParent file dir
chmod [perm|u=r|] path
try (rm (force Force) path) >>= processResult

testRmForceFailRO :: IO String
testRmForceFailRO =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRW.txt"
path = dir </> file
createFileWithParent file dir
chmod [perm|u=r|] dir
try (rm (force Force) path) >>= processResult

testRmForceFailNP :: IO String
testRmForceFailNP =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRW.txt"
path = dir </> file
createFileWithParent file dir
chmod [perm|a=|] dir
try (rm (force Force) path) >>= processResult

testRmNuke :: IO String
testRmNuke = do
let dir = "testDirNuke"
file = "fileRW.txt"
path = dir </> file
cleanup dir
createFileWithParent file dir
chmod [perm|u=r|] dir
try (rm (force Nuke . recursive On) dir) >>= processResult

testRmNuke =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRW.txt"
createFileWithParent file dir
chmod [perm|u=r|] dir
try (rm (force Nuke . recursive On) dir) >>= processResult

testRmNukeNoPerm :: IO String
testRmNukeNoPerm =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRW.txt"
createFileWithParent file dir
chmod [perm|a=|] dir
try (rm (force Nuke . recursive On) dir) >>= processResult

testRmNukeRecOff :: IO String
testRmNukeRecOff =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir"
file = "fileRW.txt"
createFileWithParent file dir
chmod [perm|a=|] dir
try (rm (force Nuke . recursive Off) dir) >>= processResult

testRmRecursive ::(Rm -> Rm) -> IO String
testRmRecursive f = do
let dir = "testDirRec"
file = "fileRW.txt"
path = dir </> file
cleanup dir
createFileWithParent file dir
try (rm f dir) >>= processResult
testRmRecursive f =
withSystemTempDirectory rmDir $ \fp -> do
let dir = fp </> "testDir" </> "testDir"
file = "fileRW.txt"
createFileWithParent file dir
try (rm f dir) >>= processResult

testRmRecursiveOn :: IO String
testRmRecursiveOn = testRmRecursive (recursive On)
Expand All @@ -151,22 +179,26 @@ testRmRecursiveOff :: IO String
testRmRecursiveOff = testRmRecursive (recursive Off)

printResult :: String -> String -> IO String -> IO ()
printResult tc exp m = do
printResult tc expec m = do
res <- m
if res == exp
if res == expec
then print $ tc ++ "->" ++ "PASS"
else print $ tc ++ "->" ++ "FAILED"

testRm :: IO ()
testRm = do
printResult "default" "Passed" testRmDefault
printResult "defaultFail" "Failed" testRmDefaultFail
printResult "nonExistant" "Failed" testRmNonExist
printResult "readOnly" "Failed" testRmROFile
printResult "forcePass" "Passed" testRmForceFile
printResult "forceFail" "Failed" testRmForceFail
printResult "nuke" "Passed" testRmNuke
printResult "forceFail ReadOnly" "Failed" testRmForceFailRO
printResult "forceFail None Permission" "Failed" testRmForceFailNP
printResult "recursiveOn" "Passed" testRmRecursiveOn
printResult "recursiveOff" "Failed" testRmRecursiveOff
printResult "nuke" "Passed" testRmNuke
printResult "nuke None Permission" "Passed" testRmNukeNoPerm
printResult "nuke Recursive Off" "Passed" testRmNukeRecOff

main :: IO ()
main = do
Expand Down

0 comments on commit 92f593d

Please sign in to comment.