{----------------------------------------------------------------- this module contains functions doing actual file IO (c) 2008-2009 Markus Dittrich This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License Version 3 as published by the Free Software Foundation. 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 Version 3 for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. --------------------------------------------------------------------} -- | this module contains file IO functionality module Helpers.FileIO ( dataBaseDir , filter_dot_dirs , get_file_date , read_file , retrieve_directory_contents , try_read_file ) where -- imports import qualified Data.ByteString as B(ByteString, readFile) import List(sort) import Prelude import System.Directory(getDirectoryContents, getModificationTime) import System.FilePath.Posix(()) import System.IO.Error(isPermissionError, isDoesNotExistError, try) import System.Locale(defaultTimeLocale) import System.Time(formatCalendarTime, toCalendarTime) -- local imports import Helpers.PrettyPrint(Color(..), putColorStrLn) -- location of database dataBaseDir :: FilePath --dataBaseDir = "/home/markus/programming/haskell/hark-data/db" dataBaseDir = "/var/db/pkg" -- | try to open the given file and return the content -- as a Just ByteString if it exists and Nothing otherwise try_read_file :: FilePath -> IO (Maybe B.ByteString) try_read_file path = try (B.readFile path) >>= \content -> case content of Right fileContent -> return (Just fileContent) Left _ -> return Nothing -- | open the given file. If things fail try to detect -- why and provide the user with some sort of useful error -- message (generic one otherwise); then quit read_file :: FilePath -> IO B.ByteString read_file path = try (B.readFile path) >>= \content -> case content of Right fileContent -> return fileContent Left e -> let reason = analyze_error e in (putColorStrLn Red $ "\n\nERROR: Cannot parse file\n") >> (putColorStrLn Yellow $ dataBaseDir path ++ "\n") >> (putColorStrLn Red $ "Reason: " ++ reason ++ "\n") >> (error "... aborting.") where analyze_error :: IOError -> String analyze_error err | isPermissionError err = "Permission denied." | isDoesNotExistError err = "File does not exist." | otherwise = "Unknown problem :(" -- | return the modification time of a file as a string of -- the form mm-dd-yy-hh-mm get_file_date :: FilePath -> IO String get_file_date path = getModificationTime path >>= toCalendarTime >>= \calTime -> return $ formatCalendarTime defaultTimeLocale "%m/%d/%y %H:%M" calTime -- | returns a list of the content of dir sans ".." and "." retrieve_directory_contents :: FilePath -> IO [FilePath] retrieve_directory_contents dir = getDirectoryContents dir >>= \rawPackages -> return (sort $ filter_dot_dirs rawPackages) -- | filter the .. and . directories from a list of paths filter_dot_dirs :: [FilePath] -> [FilePath] filter_dot_dirs = filter (`notElem` [".",".."])