{- 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@] A data-type which references a set of files by their paths, and qualifies them with their aggregate size. -} module Squeeze.Data.FileCombination( -- * Types -- ** Data-types FileCombination( -- MkFileCombination, getAggregateFileSize -- getFilePathList ), -- * Constants nullFileCombination, -- * Functions prepend, risingFilter, risingMerge, -- ** Constructors singleton, -- ** Predicates hasSizeBy ) where import qualified Data.List import qualified Squeeze.Data.File as Data.File -- | Declare a list of files qualified by its aggregate size. data FileCombination = MkFileCombination { getAggregateFileSize :: !Data.File.FileSize, -- ^ The aggregate size of the files referenced by 'getFilePathList'. getFilePathList :: Data.File.FilePathList -- ^ A list of paths, defining a set of files. } deriving Eq instance Show FileCombination where showsPrec _ fileCombination = shows (getAggregateFileSize fileCombination) . showChar '\t' . shows (Data.List.sort $ getFilePathList fileCombination) -- | A constant empty instance. nullFileCombination :: FileCombination nullFileCombination = MkFileCombination 0 [] -- | Construct a 'FileCombination' from a single 'Data.File.FileSizeAndPath'. singleton :: Data.File.FileSizeAndPath -> FileCombination singleton (fileSize, filePath) = MkFileCombination fileSize [filePath] {- | * Prepend a 'Data.File.FileSizeAndPath' to an existing 'FileCombination'. * CAVEAT: performance hot-spot. -} {-# INLINE prepend #-} prepend :: Data.File.FileSizeAndPath -- ^ The new path to prepend to the incumbent file-combination. -> FileCombination -- ^ The incumbent combination of files. -> FileCombination prepend (fileSize, filePath) fileCombination = MkFileCombination { getAggregateFileSize = fileSize + getAggregateFileSize fileCombination, getFilePathList = filePath : getFilePathList fileCombination } -- | Predicate used to determine whether a specific file-combination matches a size-related requirement. {-# INLINE hasSizeBy #-} hasSizeBy :: (Data.File.FileSize -> Bool) -- ^ The predicate. -> FileCombination -- ^ The input datum to be tested. -> Bool hasSizeBy predicate = predicate . getAggregateFileSize -- | Progressively raises the selection-criterion as each match is found, to produce monotonically increasing file-combinations. risingFilter :: Data.File.FileSize -- ^ The initial minimum byte-size of file to accept. -> [FileCombination] -- ^ The input list of files to filter. -> [FileCombination] -- ^ The resulting list of files, which have met rising criterion. risingFilter _ [] = [] risingFilter minimumSize (x : xs) | aggregateFileSize >= minimumSize = x : risingFilter aggregateFileSize xs | otherwise = risingFilter minimumSize xs where aggregateFileSize = getAggregateFileSize x {- | * Merges two lists of monotonically increasing values, into a single monotonically increasing list, by dropping values which compare less than results already found. * CAVEAT: both lists must produce an element, in order to determine which is selected. As a result, if one list produces a value, it can't be returned until the other does (which make take a long time), even if ultimately the first is then selected. -} risingMerge :: (FileCombination -> FileCombination -> Ordering) -- ^ Comparator used to select the best file-combination from the heads of the two list supplied. -> [FileCombination] -- ^ A list of monotonically increasing file-combinations. -> [FileCombination] -- ^ A list of monotonically increasing file-combinations. -> [FileCombination] risingMerge cmp = slave nullFileCombination where slave bar [] r = dropWhile ((== LT) . (`cmp` bar)) r slave bar l [] = dropWhile ((== LT) . (`cmp` bar)) l slave _ (x : xs) (y : ys) | o == GT = x : slave x xs ys | o == LT = y : slave y xs ys | otherwise = x : y : slave x xs ys where o = x `cmp` y