{-# OPTIONS_GHC -fno-warn-orphans #-} {- 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.QC( -- * Types -- ** Type-synonyms -- Testable, -- * Functions quickChecks ) where import qualified Control.Arrow import qualified Data.List import qualified Test.QuickCheck import qualified Squeeze.File as File import qualified Squeeze.FileSizeBounds as FileSizeBounds import qualified Squeeze.Squeeze as Squeeze type Testable = [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 :: [File.FileSizeAndPath] -> [File.FileSizeAndPath] translate = Data.List.nub . map (Control.Arrow.first abs) prop_bisectionRatio, prop_totalCombinations, prop_bounds, prop_all :: Testable prop_bisectionRatio fileSizeAndPathList = Test.QuickCheck.label "prop_bisectionRatio" $ (== 1) . length . Data.List.nub . map ( \bisectionRatio -> Data.List.sort . Squeeze.distribute bisectionRatio fileSizeBounds $ File.order l ) . take 8 {-arbitrarily-} $ map ((1.0 /) . fromInteger) [1 ..] where l :: [File.FileSizeAndPath] l = take 10 {-arbitrarily-} $ translate fileSizeAndPathList --CAVEAT: may be shorter than requested. fileSizeBounds :: FileSizeBounds.FileSizeBounds fileSizeBounds = (minimumBytes, maximumBytes) where maximumBytes, minimumBytes :: File.FileSize maximumBytes = round $ fromIntegral (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)) $ File.order l) == 2 ^ length l where l :: [File.FileSizeAndPath] l = take 10 {-arbitrarily-} $ translate fileSizeAndPathList --CAVEAT: may be shorter than requested. prop_bounds fileSizeAndPathList = Test.QuickCheck.label "prop_bounds" $ all (FileSizeBounds.inside fileSizeBounds) . map fst . Squeeze.findCombinations fileSizeBounds $ File.order l where l :: [File.FileSizeAndPath] l = take 16 {-arbitrarily-} $ translate fileSizeAndPathList --CAVEAT: may be shorter than requested. fileSizeBounds :: FileSizeBounds.FileSizeBounds fileSizeBounds = (minimumBytes, maximumBytes) where maximumBytes, minimumBytes :: File.FileSize maximumBytes = round $ fromIntegral (File.aggregateSize l) / (4.0 :: Double) --Arbitrarily. minimumBytes = maximumBytes `div` 2 --Arbitrarily. prop_all fileSizeAndPathList = Test.QuickCheck.label "prop_all" $ (== bytes) . last . map fst $ Squeeze.findBestFit 0.5 (FileSizeBounds.precisely bytes) l where l :: [File.FileSizeAndPath] l = take 16 {-arbitrarily-} . translate $ fileSizeAndPathList --CAVEAT: may be shorter than requested. bytes :: File.FileSize bytes = File.aggregateSize l