{- Copyright (C) 2010 Dr. Alistair Ward This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | [@AUTHOR@] Dr. Alistair Ward [@DESCRIPTION@] Defines tests to dynamically verify the module "Squeeze.Squeeze" against arbitrary data. -} module Squeeze.Test.QC( -- * Types -- ** Type-synonyms -- Testable, -- * Functions quickChecks ) where import qualified Control.Arrow import qualified Data.List import qualified Factory.Data.Interval import qualified Squeeze.Data.File as Data.File import qualified Squeeze.Data.FileCombination as Data.FileCombination import qualified Squeeze.Squeeze as Squeeze import qualified Test.QuickCheck import Test.QuickCheck((==>)) type Testable = [Data.File.FileSizeAndPath] -> Test.QuickCheck.Property -- | Defines invariant properties, which must hold for any 'FileSizeAndPath'. quickChecks :: (Testable -> IO ()) -> IO () quickChecks = (`mapM_` [prop_bisectionRatio, prop_totalCombinations, prop_bounds, prop_all]) where translate :: [Data.File.FileSizeAndPath] -> [Data.File.FileSizeAndPath] translate = Data.List.nub . map (Control.Arrow.first abs) prop_bisectionRatio, prop_totalCombinations, prop_bounds, prop_all :: Testable prop_bisectionRatio fileSizeAndPathList = not (null l) ==> Test.QuickCheck.label "prop_bisectionRatio" $ (== 1) . length . Data.List.nub . map ( \bisectionRatio -> Data.List.sort . Squeeze.distribute bisectionRatio fileSizeBounds $ Data.File.orderBySize l ) . take (length l) $ map recip [1 :: Double ..] where l :: [Data.File.FileSizeAndPath] l = take 14 {-arbitrarily-} $ translate fileSizeAndPathList --CAVEAT: may be shorter than requested. fileSizeBounds :: Factory.Data.Interval.Interval Data.File.FileSize fileSizeBounds = (minimumBytes, maximumBytes) where maximumBytes, minimumBytes :: Data.File.FileSize maximumBytes = round $ fromIntegral (Data.File.aggregateSize l) / (4.0 :: Double) --Arbitrarily. minimumBytes = maximumBytes `div` 2 --Arbitrarily. prop_totalCombinations fileSizeAndPathList = Test.QuickCheck.label "prop_totalCombinations" $ (length . Data.List.nub . Squeeze.findCombinations (0, fromIntegral (maxBound :: Int)) $ Data.File.orderBySize l) == 2 ^ length l where l :: [Data.File.FileSizeAndPath] l = take 10 {-arbitrarily-} $ translate fileSizeAndPathList --CAVEAT: may be shorter than requested. prop_bounds fileSizeAndPathList = Test.QuickCheck.label "prop_bounds" . all ((`Factory.Data.Interval.elem'` fileSizeBounds) . Data.FileCombination.getAggregateFileSize) . Squeeze.findCombinations fileSizeBounds $ Data.File.orderBySize l where l :: [Data.File.FileSizeAndPath] l = take 16 {-arbitrarily-} $ translate fileSizeAndPathList --CAVEAT: may be shorter than requested. fileSizeBounds :: Factory.Data.Interval.Interval Data.File.FileSize fileSizeBounds = (minimumBytes, maximumBytes) where maximumBytes, minimumBytes :: Data.File.FileSize maximumBytes = round $ fromIntegral (Data.File.aggregateSize l) / (4.0 :: Double) --Arbitrarily. minimumBytes = maximumBytes `div` 2 --Arbitrarily. prop_all fileSizeAndPathList = Test.QuickCheck.label "prop_all" . (== bytes) . last . map Data.FileCombination.getAggregateFileSize $ Squeeze.findBestFit (recip 2 :: Double) (Factory.Data.Interval.precisely bytes) l where l :: [Data.File.FileSizeAndPath] l = take 16 {-arbitrarily-} $ translate fileSizeAndPathList --CAVEAT: may be shorter than requested. bytes :: Data.File.FileSize bytes = Data.File.aggregateSize l