{----------------------------------------------------------------- this module contains the functionality to search for packages that have been emerged with a particular USE flag (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. --------------------------------------------------------------------} module Drivers.Use ( search_for_use_all , search_for_use_used ) where -- imports import Control.Monad(foldM) import qualified Data.ByteString as B(ByteString) import Prelude import System.FilePath.Posix(()) -- local imports import Helpers.FileIO(retrieve_directory_contents) import Parsers.Use(try_get_IUSE_flags, try_get_USE_flags) -- | read each packages IUSE flags and match against the -- user search request search_for_use_all :: [FilePath] -> B.ByteString -> IO () search_for_use_all categories useFlag = foldM (examine_category match_use_all) [] categories >>= print_useflag_pkgs where match_use_all :: [FilePath] -> FilePath -> IO [FilePath] match_use_all acc path = try_get_IUSE_flags path >>= \content -> case content of Nothing -> return acc Just c -> let result = filter ( useFlag == ) c in if null result then return acc else return (path:acc) -- | retrieve all packages within a category and apply a -- function to each entry examine_category :: ([FilePath] -> FilePath -> IO [FilePath]) -> [FilePath] -> FilePath -> IO [FilePath] examine_category f acc cat = retrieve_directory_contents cat >>= foldM (\a b -> f a (cat b)) acc -- | read each packages IUSE flags, match against the user -- request and finally check if the flag was actually present -- during the emerge search_for_use_used :: [FilePath] -> B.ByteString -> IO () search_for_use_used categories useFlag = foldM (examine_category match_use_used) [] categories >>= print_useflag_pkgs where -- check if a user requested USE flag -- is present in IUSE match_use_used acc path = try_get_IUSE_flags path >>= \content -> case content of Nothing -> return acc Just c -> let result = filter ( useFlag == ) c in if null result then return acc else match_use_active acc path -- check if use flag present in IUSE was actually active -- during the emerge match_use_active acc path = try_get_USE_flags path >>= \content -> case content of Nothing -> return acc Just c -> let result = filter ( useFlag == ) c in if null result then return acc else return (path:acc) -- | small helper function for printing the packages that depend -- on a particular use flag print_useflag_pkgs :: [FilePath] -> IO () print_useflag_pkgs = mapM_ putStrLn . reverse