Begin tests for Haskell File module
Cameron sent over some property tests for his File.split function, which is a part of a larger effort to port f.el, a nice library for working with file paths, over to Haskell.
This commit is contained in:
parent
34dc3e05c8
commit
bb0de3dec2
2 changed files with 56 additions and 0 deletions
|
@ -1,7 +1,14 @@
|
|||
module F
|
||||
( join
|
||||
, split
|
||||
) where
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Dependencies
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
import Data.List (span)
|
||||
import System.FilePath (FilePath, pathSeparator)
|
||||
import System.FilePath.Posix (FilePath)
|
||||
import qualified System.FilePath.Posix as F
|
||||
|
||||
|
@ -25,6 +32,16 @@ simpleAssert x y =
|
|||
join :: [FilePath] -> FilePath
|
||||
join = F.joinPath
|
||||
|
||||
-- | Split path and return list containing parts.
|
||||
split :: FilePath -> [String]
|
||||
split = splitJoin . span (/= pathSeparator)
|
||||
where
|
||||
splitJoin :: (String, String) -> [String]
|
||||
splitJoin ([], []) = []
|
||||
splitJoin (a, []) = [a]
|
||||
splitJoin (a, [_]) = [a]
|
||||
splitJoin (a, _:b) = a : split b
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Tests
|
||||
--------------------------------------------------------------------------------
|
||||
|
|
39
haskell-file/tests.hs
Normal file
39
haskell-file/tests.hs
Normal file
|
@ -0,0 +1,39 @@
|
|||
module FTest where
|
||||
--------------------------------------------------------------------------------
|
||||
import Test.Tasty
|
||||
import Test.Tasty.Hedgehog
|
||||
import Hedgehog
|
||||
--------------------------------------------------------------------------------
|
||||
import qualified Hedgehog as H
|
||||
import qualified Hedgehog.Gen as Gen
|
||||
import qualified Hedgehog.Range as Range
|
||||
--------------------------------------------------------------------------------
|
||||
import Data.List (intercalate)
|
||||
import System.FilePath (pathSeparator)
|
||||
--------------------------------------------------------------------------------
|
||||
import F
|
||||
--------------------------------------------------------------------------------
|
||||
main :: IO ()
|
||||
main
|
||||
= defaultMain
|
||||
. localOption (HedgehogTestLimit $ Just 50)
|
||||
$ testGroup "f functions"
|
||||
[ test_split
|
||||
]
|
||||
--------------------------------------------------------------------------------
|
||||
test_split :: TestTree
|
||||
test_split
|
||||
= testGroup "split function"
|
||||
[ testProperty "splits parts properly" splitSuccess
|
||||
]
|
||||
splitSuccess :: Property
|
||||
splitSuccess = property $ do
|
||||
-- separator
|
||||
-- <- H.forAll
|
||||
-- $ Gen.element ['/', '\\']
|
||||
parts
|
||||
<- H.forAll
|
||||
. Gen.list (Range.linear 0 10)
|
||||
$ Gen.list (Range.linear 1 10) Gen.alphaNum
|
||||
let path = intercalate [pathSeparator] parts
|
||||
F.split path === parts
|
Loading…
Reference in a new issue