{----------------------------------------------------------------- (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 parser module contains functions that allow to parse -- and compare ebuild version numbers module Parsers.Version ( split_version , test_NumCharTok , test_Revision , remove_trailing_zeros , VersionTok(NumTok,Suffix,Revision) , SuffixChoice(Alpha,Beta,Pre,Rc,P) ) where -- imports import qualified Data.ByteString as B(ByteString, split, splitAt, takeWhile) import qualified Data.ByteString.Char8 as BC(pack) import Prelude import Text.Regex.PCRE((=~)) import Word(Word8) -- local imports import Helpers.ByteString(colonW, dashW, glob, globW, periodW, underscoreW) -- | keeps track of the type of version suffix data SuffixChoice = Alpha | Beta | Pre | Rc | P deriving(Enum,Eq,Ord,Show) -- | keeps track of the token type in a version string data VersionTok = NumTok B.ByteString | Suffix SuffixChoice | Revision deriving(Eq,Show) -- | default instance of versionTok instance Ord VersionTok where (NumTok a) <= (NumTok b) = a <= b Revision <= _ = True (Suffix _) <= _ = True _ <= Revision = False _ <= (Suffix _) = False -- | simple function to test if an VersionTok data element -- is of type NumTok or CharTok test_NumCharTok :: VersionTok -> Bool test_NumCharTok x = case x of NumTok _ -> True _ -> False -- | simple function to test if an VersionTok data element -- is of type Revision test_Revision :: VersionTok -> Bool test_Revision x = case x of Revision -> True _ -> False -- | parses the tokenized version information from a list -- of ByteString into a list of VersionTok so we can -- compare it more efficiently parse_into_VersionTok :: [B.ByteString] -> [VersionTok] parse_into_VersionTok list = parse [] (reverse list) where parse :: [VersionTok] -> [B.ByteString] -> [VersionTok] parse acc [] = acc parse acc (x:xs) | x =~ "[:][0-9]+" = parse (NumTok preEAPI1:acc) xs | x =~ "[*]$" = parse (NumTok preGlob:NumTok glob:acc) xs | x =~ "alpha" = parse (Suffix Alpha:acc) xs | x =~ "beta" = parse (Suffix Beta:acc) xs | x =~ "pre" = parse (Suffix Pre:acc) xs | x =~ "rc" = parse (Suffix Rc:acc) xs | x =~ "p" = parse (Suffix P:acc) xs | x =~ "r" = parse (Revision:acc) xs | x =~ "^[a-z]$" = parse (NumTok x:acc) xs | otherwise = parse (NumTok x:acc) xs where preGlob = B.takeWhile (\z -> z /= globW) x preEAPI1 = B.takeWhile (\z -> z /= colonW) x -- | split a version number into tokens split_version :: B.ByteString -> [VersionTok] split_version = parse_into_VersionTok . separate_number_suffix . separate_final_char . initial_parse -- | function separating a version string at instances -- of ".", "-", and "_" initial_parse :: B.ByteString -> [B.ByteString] initial_parse string = let stage1 = parse_sep periodW string stage2 = flatten $ map (parse_sep underscoreW) stage1 in flatten $ map (parse_sep dashW) stage2 -- | function separating off the optional characted after -- the intial numbers separate_final_char :: [B.ByteString] -> [B.ByteString] separate_final_char = flatten . map num_match where num_match :: B.ByteString -> [B.ByteString] num_match string = let (a,b) = string =~ "([0-9]+)[a-z]$" :: (Int,Int) (num,letter) = B.splitAt (b-1) string in if a == -1 then [string] else [num,letter] -- | function splitting the optional alpha, beta, pre, rc, p, -- and r suffices and the optional integer following them separate_number_suffix :: [B.ByteString] -> [B.ByteString] separate_number_suffix = flatten . map suffix_match where suffix_match :: B.ByteString -> [B.ByteString] suffix_match string = let (a,b) = string =~ "^(alpha|beta|pre|rc|p|r)" :: (Int,Int) (name,num) = B.splitAt b string in if a == -1 then [string] else [name,num] -- | parse a version string with a certain separator parse_sep :: Word8 -> B.ByteString -> [B.ByteString] parse_sep sep string = B.split sep string -- | flatten a list flatten :: [[a]] -> [a] flatten = foldl (++) [] -- | NumTok zero zeroTok :: VersionTok zeroTok = NumTok $ BC.pack "0" -- | remove trailing zeros from a list of NumToks remove_trailing_zeros :: [VersionTok] -> [VersionTok] remove_trailing_zeros = reverse . dropWhile ( \x -> x == zeroTok ) . reverse