{----------------------------------------------------------------- (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 the functionality needed for searching -- for packages module Drivers.SearchPackage ( search_for_packages_short , search_for_packages_detailed ) where -- imports import Control.Monad(foldM) import qualified Data.ByteString as B(append, ByteString, intercalate, putStr, splitWith) import qualified Data.ByteString.Char8 as BC(pack) import Data.List(sort) import Prelude import System.Directory(getDirectoryContents) import System.FilePath.Posix(()) import Text.Regex.PCRE((=~)) -- local imports import Helpers.FileIO(get_file_date) import Helpers.ByteString(char_to_Word8, dash, spaceChar, tilde) import Parsers.Chost(get_chost) import Parsers.Keywords(get_keywords) import Parsers.Repository(get_repository) -- import Debug.Trace -- | Simply retrieve matches and print them out search_for_packages_short :: B.ByteString -> [FilePath] -> IO () search_for_packages_short name paths = search_for_packages name paths >>= mapM_ putStrLn -- | Retrieve detailed information for all matched packages search_for_packages_detailed :: B.ByteString -> [FilePath] -> IO () search_for_packages_detailed name paths = search_for_packages name paths >>= mapM_ generate_pkg_info_string -- | retrieve all info for a particular package and then -- assemble a IO action for printing it all generate_pkg_info_string :: FilePath -> IO () generate_pkg_info_string pkgName = get_chost pkgName >>= \host -> get_repository pkgName >>= \repo -> get_file_date pkgName >>= \date -> get_keywords pkgName >>= \keywds -> putStr "[" >> (B.putStr $ create_keyword_string host keywds) >> (putStr $ " | " ++ create_repo_string repo) >> (putStr $ " | " ++ date) >> putStr "] : " >> putStrLn pkgName where create_keyword_string h kwd = let dashedHost = B.append dash h tildedHost = B.append tilde h in if any ( h == ) kwd then B.append spaceChar h else if any ( tildedHost == ) kwd then tildedHost else dashedHost create_repo_string rep = if (rep == BC.pack "gentoo") then "g" else "o" -- | Search for packages in complete data base based on pattern search_for_packages :: B.ByteString -> [FilePath] -> IO [FilePath] search_for_packages _ [] = return [] search_for_packages packageName paths = foldM (\acc p -> process_category p >>= \x -> return (acc ++ x) ) [] paths where process_category path = getDirectoryContents path >>= \packages -> let matches = sort $ filter (\x -> x =~ escape_regex_chars packageName :: Bool) packages categoryMatches = map ( path ) matches in return categoryMatches -- | this function looks for regexp characters in the search -- string an "escapes" them inside a character class. -- So far we're only looking for * and +, the latter being -- crucial to get search for gtk+ correct. escape_regex_chars :: B.ByteString -> B.ByteString escape_regex_chars = escape '+' . escape '*' where escape :: Char -> B.ByteString -> B.ByteString escape c = B.intercalate (BC.pack $ "[" ++ c:"]") . B.splitWith ( == char_to_Word8 c)