Skip to content

Commit

Permalink
Add test cases
Browse files Browse the repository at this point in the history
  • Loading branch information
rnjtranjan committed Jul 26, 2022
1 parent 3496908 commit 937e707
Show file tree
Hide file tree
Showing 2 changed files with 99 additions and 11 deletions.
1 change: 1 addition & 0 deletions src/Streamly/Coreutils/Chmod.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@

module Streamly.Coreutils.Chmod
( chmod
, perm
)
where

Expand Down
109 changes: 98 additions & 11 deletions test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,18 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE QuasiQuotes #-}
module Main
(main)
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 Control.Exception (try, SomeException)
Expand Down Expand Up @@ -55,31 +59,114 @@ gen c n = S.unfoldr step (0, True)
-- * File parent dirs not having permissions
-- * File owned by someone else

testRm :: IO ()
testRm = do
let dir = "testDir"
cleanup :: String -> IO ()
cleanup = rm (force Nuke . recursive On)

processResult :: Either SomeException s -> IO String
processResult res = return $
case res of
Left _ -> "Failed"
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 print "Test Rm PASS"
else print "Test Rm Failed"
then return "Passed"
else return "Failed"

testRmNonExist :: IO ()
testRmNonExist :: IO String
testRmNonExist = do
let dir = "testDir"
let dir = "testDir2"
file = "file.txt"
fileNE = "fileNE.txt"
pathNE = dir </> fileNE
cleanup dir
createFileWithParent file dir
res <- try (rm id pathNE)
case res of
Left (_e :: SomeException) -> print "Test RmNE Passed"
Right _ -> print "Test RmNE Failed"
try (rm id pathNE) >>= processResult

--chmod [perm|a=rwx|] "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

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

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


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

testRmRecursiveOn :: IO String
testRmRecursiveOn = testRmRecursive (recursive On)

testRmRecursiveOff :: IO String
testRmRecursiveOff = testRmRecursive (recursive Off)

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

testRm :: IO ()
testRm = do
printResult "default" "Passed" testRmDefault
printResult "nonExistant" "Failed" testRmNonExist
printResult "readOnly" "Failed" testRmROFile
printResult "forcePass" "Passed" testRmForceFile
printResult "forceFail" "Failed" testRmForceFail
printResult "nuke" "Passed" testRmNuke
printResult "recursiveOn" "Passed" testRmRecursiveOn
printResult "recursiveOff" "Failed" testRmRecursiveOff

main :: IO ()
main = do
Expand Down

0 comments on commit 937e707

Please sign in to comment.