Skip to content

Commit

Permalink
adds new utf-8 test and test the merge padding algorithm
Browse files Browse the repository at this point in the history
  • Loading branch information
cpichard committed Jul 14, 2015
1 parent 9f34d3b commit 143abd6
Showing 1 changed file with 55 additions and 35 deletions.
90 changes: 55 additions & 35 deletions tests/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,21 +4,10 @@
module Main where
import System.FileSequence
import System.FileSequence.SparseFrameList
import Data.List (nub, sort)
import Data.List (nub, sort, permutations)
import Test.Framework

-- | Check that the padding is not less than the max number of digits in all frames
--paddingIsCoherent :: FileSequence -> Bool
--paddingIsCoherent fs =
-- case paddingLength fs of
-- Nothing -> True -- differs countDigits
-- Just p -> True -- maximum countDigits >= p
-- where countDigits = map (length.show.abs) (frameRange fs)
-- differs (x:xs) = not $ all (==x) xs
-- differs [] = False


-- | Negative frames quick test
-- |Negative frames quick test
test_negativeFrames :: IO ()
test_negativeFrames = assertEqual a b
where b = fileSequencesFromList ["test.-0004.dpx", "test.-0003.dpx"]
Expand All @@ -31,7 +20,7 @@ test_negativeFrames = assertEqual a b
, frameSep = "."
, extSep = "."}]

-- | Sequence with no name, only numbers
-- |Sequence with no name, only numbers, is valid
test_sequenceWithoutName :: IO ()
test_sequenceWithoutName = assertEqual a b
where b = fileSequenceFromName "0005.dpx"
Expand All @@ -44,9 +33,9 @@ test_sequenceWithoutName = assertEqual a b
, frameSep = ""
, extSep = "."}

-- | Test utf8 characters
test_utf8 :: IO ()
test_utf8 = assertEqual a b
-- |Test utf8 characters
test_utf8FromName :: IO ()
test_utf8FromName = assertEqual a b
where b = fileSequenceFromName "fffèè.0003.fg"
a = Just FileSequence
{ frames = [(3,3)]
Expand All @@ -57,36 +46,48 @@ test_utf8 = assertEqual a b
, frameSep = "."
, extSep = "."}

-- | Test minus zero ex: myfile.-0.tmp

-- |Minus zero frame (ex: myfile.-0.tmp) is invalid
test_minusZero :: IO ()
test_minusZero = assertEqual a b
where b = fileSequenceFromName "test-0.0a1"
a = Nothing

-- | Series of tests with the following case
-- | "a sequence can't have the same frame twice"
-- |Series of tests with the following case
-- "a sequence can't have the same frame twice"
sameFrameTwice :: [PathString]
sameFrameTwice = ["b.01.tmp", "b.10.tmp", "b.010.tmp"]

-- | If there is the same frame twice in a list, it is sure that the padding is
-- different so we should find two distinct sequences
-- |If there is the same frame twice in a list, then the padding is
-- different and we should find two distinct sequences
test_sameFrameTwice :: IO ()
test_sameFrameTwice = do assertBool $ length b == 2
assertEqual c d
test_sameFrameTwice = do
assertBool $ length b == 2
assertEqual c d
where b = fileSequencesFromList sameFrameTwice
c = isElementOf 10 $ frames (head b)
d = isElementOf 10 $ frames (last b)
c = isElementOf 10 $ frames (head b)
d = isElementOf 10 $ frames (last b)

-- |Same test as above, but we test that all permutations of the input frames
-- gives the same 2 result sequences
test_extendPaddingOrder :: IO ()
test_extendPaddingOrder = do assertBool $ all (a ==) b
where a = fileSequencesFromList sameFrameTwice
b = map fileSequencesFromList (permutations sameFrameTwice)

-- |
test_frameRestitution :: IO ()
test_frameRestitution = do assertEqual a b
where a = sort sameFrameTwice
b = sort $ concatMap frameList $ fileSequencesFromList a
b = sort $ concatMap frameList $ fileSequencesFromList a

-- |Padding extension
extendPaddingSample :: [PathString]
extendPaddingSample = ["b.01.tmp", "b.10.tmp", "b.100.tmp"]

-- | Extended padding
test_extendedPadding :: IO ()
test_extendedPadding = assertEqual a b
where a = fileSequencesFromList ["b.01.tmp", "b.10.tmp", "b.100.tmp"]
where a = fileSequencesFromList extendPaddingSample
b = [FileSequence
{ frames = [(1,1),(10,10),(100,100)]
, padding = PaddingFixed 2
Expand All @@ -96,40 +97,59 @@ test_extendedPadding = assertEqual a b
, frameSep = "."
, extSep = "."}]

-- | Frames are restitued correctly in a sparse frame sequence
-- |Frames are restitued correctly in a sparse frame sequence
prop_sparseFrameList :: [Int] -> Bool
prop_sparseFrameList frm =
let sfl = foldl addFrame [] frm in
sort (toList sfl) == sort (nub frm)

-- | SparseFrameSequence test - first element of a frame range is
-- |SparseFrameSequence test - first element of a frame range is
-- less or equal than the second one
prop_FrameRange :: FileSequence -> Bool
prop_FrameRange fs = all sup sfl
where sup (a,b) = a <= b
sfl = frames fs

-- | Property:
-- |Property:
-- list of files A -> FileSequence -> list of files B
-- => A == B
-- Also enforce that the list of file is not empty
prop_frameConsistency :: FileSequence -> Bool
prop_frameConsistency fs = sort (frameList fs) == sort (frameList newfss)
prop_frameConsistency fs = sort (frameList fs) == sort (frameList newfss)
where newfss = head $ fileSequencesFromList (frameList fs)

-- | FIXME Test filesequence equality here
-- |FIXME Test filesequence equality here instead of the list of files
prop_bijectiveFunc :: FileSequence -> Bool
prop_bijectiveFunc fs = sort (frameList fs1) == sort (frameList fs2)
where fs1 = head $ fileSequencesFromList (frameList fs)
fs2 = head $ fileSequencesFromList (frameList fs1)

-- |TODO: write a reducePadding function that reduce the padding to the lowest common padding possible
-- for a particular set of frames
prop_orderDoesNotMatter :: FileSequence -> Bool
prop_orderDoesNotMatter fs = all (fs==) permuts
where permuts = map head $ map fileSequencesFromList $ permutations (frameList fs)

-- |Number of missing frames max-min - nbframes
prop_holeSize :: SparseFrameList -> Bool
prop_holeSize [] = nbMissing [] == nbFrames [] -- no frames at all
prop_holeSize fs = nbMissing fs == lastFrame fs - firstFrame fs + 1 - nbFrames fs


-- |Test utf8
test_utf8FromList :: IO ()
test_utf8FromList = do
assertBool $ length b == 1
assertEqual a (head b)
where b = fileSequencesFromList ["ffᄅᄅΠ.001.f", "ffᄅᄅΠ.002.f", "ffᄅᄅΠ.003.f"]
a = FileSequence
{ frames = [(1,3)]
, padding = PaddingFixed 3
, path = ""
, name = "ffᄅᄅΠ"
, ext = "f"
, frameSep = "."
, extSep = "."
}

main ::IO ()
main = htfMain htf_thisModulesTests

0 comments on commit 143abd6

Please sign in to comment.