{- DisTract ------------------------------------------------------\ | | | Copyright (c) 2007, Matthew Sackman (matthew@wellquite.org) | | | | DisTract is freely distributable under the terms of a 3-Clause | | BSD-style license. For details, see the DisTract web site: | | http://distract.wellquite.org/ | | | \-----------------------------------------------------------------} module DisTract.Parsers (findBugId) where import DisTract.Types import DisTract.Utils import Text.ParserCombinators.Parsec import Data.Either import Data.Time import Data.Fixed import System.Locale import Control.Monad findBugId :: String -> Either ParseError BugId findBugId = runParser parseBugId () "DisTract.Utils findBugId" parseBugId :: Parser BugId parseBugId = do { string "bug-" ; timeStr <- count bugIdDateFormatLength anyChar ; let timeM = parseTime defaultTimeLocale bugIdDateFormat timeStr ; when (timeM == Nothing) $ fail $ "Unable to parse time: '" ++ timeStr ++ "'" ; let (Just time) = timeM ; char 'S' ; millis <- sequence $ replicate 3 digit ; char '-' ; author <- manyTill anyChar (eof <|> try (space >> return ())) ; let time' = setMillis millis time ; return $ BugId time' author } where setMillis :: String -> UTCTime -> UTCTime setMillis millisStr t@(UTCTime { utctDayTime = fromMidnight }) = t { utctDayTime = (fromMidnight - badPicos + goodPicos) } where badPicos = fromMidnight `mod'` 0.001 millis = read millisStr goodPicos = picosecondsToDiffTime ( millis * 1000000000 )