{----------------------------------------------------------------- (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 parses the USE info of a package module Parsers.Use ( get_USE_flags , get_IUSE_flags , try_get_USE_flags , try_get_IUSE_flags ) where -- imports import qualified Data.ByteString as B(ByteString, head, tail) import Prelude import System.FilePath.Posix(()) -- local imports import Helpers.ByteString(tokenize_BS, plusW, dashW) import Helpers.FileIO(read_file, try_read_file) -- | parses the USE flags active during the emerge of the current -- package and returns them as a raw ByteString get_IUSE_flags :: FilePath -> IO [B.ByteString] get_IUSE_flags path = (get_USE_flags_generic "IUSE" path) >>= \flags -> let filteredFlags = filter_prefix flags in return filteredFlags -- | parses the USE flags active during the emerge of the current -- package and returns the content in tokenized form. get_USE_flags :: FilePath -> IO [B.ByteString] get_USE_flags = get_USE_flags_generic "USE" -- | same as get_useFlags_raw but uses try_read so we can handle -- failure in opening a USE file during execution try_get_IUSE_flags :: FilePath -> IO (Maybe [B.ByteString]) try_get_IUSE_flags path = (try_get_USE_flags_generic "IUSE" path) >>= \flags -> case flags of Nothing -> return Nothing Just f -> let filteredFlags = filter_prefix f in return $ Just filteredFlags -- | same as get_useFlags but uses try_read so we can handle -- failure in opening a USE file during execution try_get_USE_flags :: FilePath -> IO (Maybe [B.ByteString]) try_get_USE_flags = try_get_USE_flags_generic "USE" -- | generic function to parse USE/IUSE flags active during the -- emerge of the current package and returns them as a -- tokenized ByteString get_USE_flags_generic :: String -> FilePath -> IO [B.ByteString] get_USE_flags_generic name path = (read_file $ path name) >>= return . tokenize_BS -- | same as get_USE_flags_generic but uses try_read so we can handle -- failure in opening a USE/IUSE file during execution try_get_USE_flags_generic :: String -> FilePath -> IO (Maybe [B.ByteString]) try_get_USE_flags_generic name path = try_read_file (path name) >>= \useContent -> case useContent of Just v -> return . Just $ tokenize_BS v _ -> return Nothing -- | according to EAPI=1 use flags in IUSE can have a prefix -- of +/- that we throw out for the moment in order to be able -- to match it against plain use flag requests. -- NOTE: We might be able to use these prefixes for more detailed -- queries in the future filter_prefix :: [B.ByteString] -> [B.ByteString] filter_prefix foo = map remove_prefix foo where remove_prefix x = if ( (B.head x) == plusW || (B.head x) == dashW) then B.tail x else x