module BuildBox.Command.Darcs (
EmailAddress, DarcsPath, DarcsPatch(..),
changes, changesN, changesAfter
) where
import Data.Time
import Data.Maybe
import System.Locale
import qualified Data.Sequence as Seq
import qualified Data.ByteString.Char8 as B
import BuildBox.Build
import BuildBox.Command.System
import qualified BuildBox.Data.Log as Log
type DarcsPath = String
type EmailAddress = String
data DarcsPatch = DarcsPatch
{
darcsTimestamp :: LocalTime
, darcsAuthor :: EmailAddress
, darcsComment :: Log.Log
}
instance Show DarcsPatch where
show (DarcsPatch time author desc) =
formatTime defaultTimeLocale "%a %b %e %H:%M:%S %Z %Y" time
++ " " ++ author
++ "\n" ++ Log.toString desc
changes :: Maybe DarcsPath -> Build [DarcsPatch]
changes = darcs . ("darcs changes --repo=" ++) . fromMaybe "."
changesN :: Maybe DarcsPath -> Int -> Build [DarcsPatch]
changesN repo n =
darcs $ "darcs changes --last=" ++ show n
++ " --repo=" ++ fromMaybe "." repo
changesAfter :: Maybe DarcsPath -> LocalTime -> Build [DarcsPatch]
changesAfter repo time =
darcs $ "darcs changes --matches='date \"after " ++ show time ++ "\"'"
++ " --repo=" ++ fromMaybe "." repo
darcs :: String -> Build [DarcsPatch]
darcs cmd = do
(status, logOut, logErr) <- systemTeeLog False cmd Log.empty
case status of
ExitSuccess -> return $ splitPatches logOut
_ -> throw $ ErrorSystemCmdFailed cmd status logOut logErr
splitPatches :: Log.Log -> [DarcsPatch]
splitPatches l
| Seq.null l = []
| otherwise = let (h,t) = Seq.breakl B.null l
in patch h : splitPatches (Seq.dropWhileL B.null t)
where
patch p =
let toks = words . B.unpack $ Seq.index p 0
(time,author) = splitAt 6 toks
in
DarcsPatch
{
darcsTimestamp = readTime defaultTimeLocale "%a %b %e %H:%M:%S %Z %Y" (unwords time)
, darcsAuthor = unwords author
, darcsComment = Seq.drop 1 p
}