{- 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 file-related type-synonyms, and associated operations. -} module Squeeze.File ( -- * Types -- ** Type-synonyms FilePathList, FileSize, FileSizeAndPath, -- * Functions aggregateSize, -- findSize, findSizes, getPath, getSize, hasSize, order ) where import Control.Applicative((<$>)) import System.FilePath(()) import qualified Control.Exception --import qualified Data.Int import qualified Data.List import qualified Data.Ord import qualified System.IO import qualified System.Directory import qualified System.IO.Error import qualified System.Posix.Files -- | A type suitable for containing an arbitrary set of file-paths. type FilePathList = [System.IO.FilePath] -- | A type-synonym specifically to hold file-sizes (in bytes); 'Integer' matches the return-type of 'IO.hFileSize', but 'Data.Int.Int64' is about 4% faster. --type FileSize = Data.Int.Int64 type FileSize = Integer -- | A type suitable for containing a file-path, qualified by the corresponding 'FileSize'. type FileSizeAndPath = (FileSize, System.IO.FilePath) -- | Accessor. getSize :: FileSizeAndPath -> FileSize getSize = fst -- | Accessor. getPath :: FileSizeAndPath -> System.IO.FilePath getPath = snd -- | Sum the 'FileSize's contained in the specified list. aggregateSize :: [FileSizeAndPath] -> FileSize aggregateSize = Data.List.foldl' (\accumulator -> (accumulator +) . getSize) 0 --Three times faster than 'sum' & marginally faster than 'foldr'. -- | Get the size of a file, treating a directory as an atomic unit. findSize :: System.IO.FilePath -> IO FileSize findSize f = do stat <- System.Posix.Files.getFileStatus f --CAVEAT: throws if user unauthorised, or file non-existent. if System.Posix.Files.isRegularFile stat then Control.Exception.bracket (System.IO.openFile f System.IO.ReadMode) System.IO.hClose $ \handle -> fromInteger <$> System.IO.hFileSize handle else {-not a regular file-} if System.Posix.Files.isDirectory stat then System.Directory.getDirectoryContents f >>= fmap {-into IO-monad-} aggregateSize . findSizes . map (f ) . filter (`notElem` [".", ".."]) --Treat any directory as an atomic unit. else {-non-directory-} Control.Exception.throw $ System.IO.Error.mkIOError System.IO.Error.illegalOperationErrorType ("file='" ++ f ++ "' has unexpected type") Nothing (Just f) -- | Finds file-sizes. findSizes :: FilePathList -> IO [FileSizeAndPath] findSizes filePathList = (`zip` filePathList) <$> {-lift into IO-monad-} mapM findSize filePathList -- | Sorts list of 'FileSizeAndPath' by size, largest first. order :: [FileSizeAndPath] -> [FileSizeAndPath] order = Data.List.sortBy (flip $ Data.Ord.comparing getSize) -- | 'True' if the specified file has the required size according to the specified predicate. hasSize :: (FileSize -> Bool) -- ^ The predicate. -> FileSizeAndPath -- ^ The file parameters to be tested. -> Bool hasSize f = f . getSize