module Darcs.Patch.Info ( PatchInfo(..), patchinfo, invertName,
idpatchinfo, addJunk,
makeFilename, makeAltFilename, readPatchInfo,
justName, justAuthor, justLog, repopatchinfo,
RepoPatchInfo, humanFriendly, toXml, piDate,
setPiDate, piDateString, piDateBytestring,
piName, piRename, piAuthor, piTag, piLog,
showPatchInfo, isTag
) where
import Text.Html hiding (name, text)
import System.Random ( randomRIO )
import Numeric ( showHex )
import Control.Monad ( when )
import ByteStringUtils
import qualified Data.ByteString as B (length, splitAt, null, drop
,isPrefixOf, tail, concat
,empty, head, cons, append
,ByteString )
import qualified Data.ByteString.Char8 as BC (index, head, unpack, pack, break)
import Data.List( isPrefixOf )
import Printer ( renderString, Doc, packedString,
empty, ($$), (<>), (<+>), vcat, text, blueText, prefix )
import Darcs.Patch.OldDate ( readUTCDate, showIsoDateTime )
import System.Time ( CalendarTime(ctTZ), calendarTimeToString, toClockTime,
toCalendarTime )
import System.IO.Unsafe ( unsafePerformIO )
import SHA1 ( sha1PS )
import Darcs.Utils ( promptYorn )
import Prelude hiding (pi, log)
data RepoPatchInfo = RPI String PatchInfo
repopatchinfo :: String -> PatchInfo -> RepoPatchInfo
repopatchinfo r pi = RPI r pi
data PatchInfo = PatchInfo { _piDate :: !B.ByteString
, _piName :: !B.ByteString
, _piAuthor :: !B.ByteString
, _piLog :: ![B.ByteString]
, isInverted :: !Bool
}
deriving (Eq,Ord)
idpatchinfo :: PatchInfo
idpatchinfo = PatchInfo myid myid myid [] False
where myid = BC.pack "identity"
patchinfo :: String -> String -> String -> [String] -> IO PatchInfo
patchinfo date name author log =
addJunk $ PatchInfo { _piDate = BC.pack date
, _piName = packStringToUTF8 name
, _piAuthor = packStringToUTF8 author
, _piLog = map packStringToUTF8 log
, isInverted = False }
addJunk :: PatchInfo -> IO PatchInfo
addJunk pinf =
do x <- randomRIO (0,2^(128 ::Integer) :: Integer)
when (_piLog pinf /= ignoreJunk (_piLog pinf)) $
do putStrLn "Lines beginning with 'Ignore-this: ' will be ignored."
yorn <- promptYorn "Proceed? "
when (yorn == 'n') $ fail "User cancelled because of Ignore-this."
return $ pinf { _piLog = BC.pack (head ignored++showHex x ""):
_piLog pinf }
ignored :: [String]
ignored = ["Ignore-this: "]
ignoreJunk :: [B.ByteString] -> [B.ByteString]
ignoreJunk = filter isnt_ignored
where isnt_ignored x = doesnt_start_with x (map BC.pack ignored)
doesnt_start_with x ys = not $ any (`B.isPrefixOf` x) ys
invertName :: PatchInfo -> PatchInfo
invertName pi = pi { isInverted = not (isInverted pi) }
justName :: PatchInfo -> String
justName pinf = if isInverted pinf then "UNDO: " ++ nameString
else nameString
where nameString = metadataToString (_piName pinf)
justAuthor :: PatchInfo -> String
justAuthor = metadataToString . _piAuthor
justLog :: PatchInfo -> String
justLog = unlines . map BC.unpack . _piLog
humanFriendly :: PatchInfo -> Doc
humanFriendly pi =
text (friendlyD $ _piDate pi) <> text " " <> text (piAuthor pi)
$$ hfn (piName pi)
$$ vcat (map ((text " " <>) . text) (piLog pi))
where hfn x = case piTag pi of
Nothing -> inverted <+> text x
Just t -> text " tagged" <+> text t
inverted = if isInverted pi then text " UNDO:" else text " *"
piName :: PatchInfo -> String
piName = metadataToString . _piName
piRename :: PatchInfo -> String -> PatchInfo
piRename x n = x { _piName = packStringToUTF8 n }
piAuthor :: PatchInfo -> String
piAuthor = metadataToString . _piAuthor
isTag :: PatchInfo -> Bool
isTag pinfo = "TAG " `isPrefixOf` justName pinfo
readPatchDate :: B.ByteString -> CalendarTime
readPatchDate = ignoreTz . readUTCDate . BC.unpack
where ignoreTz ct = ct { ctTZ = 0 }
piDate :: PatchInfo -> CalendarTime
piDate = readPatchDate . _piDate
piDateString :: PatchInfo -> String
piDateString = BC.unpack . _piDate
piDateBytestring :: PatchInfo -> B.ByteString
piDateBytestring = _piDate
setPiDate :: String -> PatchInfo -> PatchInfo
setPiDate date pi = pi { _piDate = BC.pack date }
piLog :: PatchInfo -> [String]
piLog = map metadataToString . ignoreJunk . _piLog
piTag :: PatchInfo -> Maybe String
piTag pinf =
if l == t
then Just $ metadataToString r
else Nothing
where (l, r) = B.splitAt (B.length t) (_piName pinf)
t = BC.pack "TAG "
metadataToString :: B.ByteString -> String
metadataToString bs | not ('\xfffd' `elem` bsUtf8) = bsUtf8
| otherwise = decodeLocale bs
where bsUtf8 = unpackPSFromUTF8 bs
friendlyD :: B.ByteString -> String
friendlyD d = unsafePerformIO $ do
ct <- toCalendarTime $ toClockTime $ readPatchDate d
return $ calendarTimeToString ct
toXml :: PatchInfo -> Doc
toXml pi =
text "<patch"
<+> text "author='" <> escapeXMLByteString (_piAuthor pi) <> text "'"
<+> text "date='" <> escapeXMLByteString (_piDate pi) <> text "'"
<+> text "local_date='" <> escapeXML (friendlyD $ _piDate pi) <> text "'"
<+> text "inverted='" <> text (show $ isInverted pi) <> text "'"
<+> text "hash='" <> text (makeFilename pi) <> text "'>"
$$ prefix "\t" (
text "<name>" <> escapeXMLByteString (_piName pi) <> text "</name>"
$$ commentsAsXml (_piLog pi))
$$ text "</patch>"
commentsAsXml :: [B.ByteString] -> Doc
commentsAsXml comments
| B.length comments' > 0 = text "<comment>"
<> escapeXMLByteString comments'
<> text "</comment>"
| otherwise = empty
where comments' = unlinesPS comments
escapeXML :: String -> Doc
escapeXML = text . strReplace '\'' "'" . strReplace '"' """ .
strReplace '>' ">" . strReplace '<' "<" . strReplace '&' "&"
escapeXMLByteString :: B.ByteString -> Doc
escapeXMLByteString = packedString . bstrReplace '\'' "'"
. bstrReplace '"' """
. bstrReplace '>' ">"
. bstrReplace '<' "<"
. bstrReplace '&' "&"
strReplace :: Char -> String -> String -> String
strReplace _ _ [] = []
strReplace x y (z:zs)
| x == z = y ++ (strReplace x y zs)
| otherwise = z : (strReplace x y zs)
bstrReplace :: Char -> String -> B.ByteString -> B.ByteString
bstrReplace c s bs | B.null bs = B.empty
| otherwise = if BC.head bs == c
then B.append (BC.pack s)
(bstrReplace c s (B.tail bs))
else B.cons (B.head bs)
(bstrReplace c s (B.tail bs))
makeAltFilename :: PatchInfo -> String
makeAltFilename pi@(PatchInfo { isInverted = False }) =
fixUpFname (midtrunc (piName pi)++"-"++justAuthor pi++"-"++BC.unpack (_piDate pi))
makeAltFilename pi@(PatchInfo { isInverted = True}) =
makeAltFilename (pi { isInverted = False }) ++ "-inverted"
makeFilename :: PatchInfo -> String
makeFilename pi =
showIsoDateTime d++"-"++sha1_a++"-"++sha1PS sha1_me++".gz"
where b2ps True = BC.pack "t"
b2ps False = BC.pack "f"
sha1_me = B.concat [_piName pi,
_piAuthor pi,
_piDate pi,
B.concat $ _piLog pi,
b2ps $ isInverted pi]
d = readPatchDate $ _piDate pi
sha1_a = take 5 $ sha1PS $ _piAuthor pi
midtrunc :: String -> String
midtrunc s
| length s < 73 = s
| otherwise = (take 40 s)++"..."++(reverse $ take 30 $ reverse s)
fixUpFname :: String -> String
fixUpFname = map mungeChar
mungeChar :: Char -> Char
mungeChar '*' = '+'
mungeChar '?' = '2'
mungeChar '>' = '7'
mungeChar '<' = '2'
mungeChar ' ' = '_'
mungeChar '"' = '~'
mungeChar '`' = '.'
mungeChar '\'' = '.'
mungeChar '/' = '1'
mungeChar '\\' = '1'
mungeChar '!' = '1'
mungeChar ':' = '.'
mungeChar ';' = ','
mungeChar '{' = '~'
mungeChar '}' = '~'
mungeChar '(' = '~'
mungeChar ')' = '~'
mungeChar '[' = '~'
mungeChar ']' = '~'
mungeChar '=' = '+'
mungeChar '#' = '+'
mungeChar '%' = '8'
mungeChar '&' = '6'
mungeChar '@' = '9'
mungeChar '|' = '1'
mungeChar c = c
instance HTML RepoPatchInfo where
toHtml = htmlPatchInfo
instance Show PatchInfo where
show pi = renderString (showPatchInfo pi)
showPatchInfo :: PatchInfo -> Doc
showPatchInfo pi =
blueText "[" <> packedString (_piName pi)
$$ packedString (_piAuthor pi) <> text inverted <> packedString (_piDate pi)
<> myunlines (_piLog pi) <> blueText "] "
where inverted = if isInverted pi then "*-" else "**"
myunlines [] = empty
myunlines xs = mul xs
where mul [] = text "\n"
mul (s:ss) = text "\n " <> packedString s <> mul ss
readPatchInfo :: B.ByteString -> Maybe (PatchInfo, B.ByteString)
readPatchInfo s | B.null (dropSpace s) = Nothing
readPatchInfo s =
if BC.head (dropSpace s) /= '['
then Nothing
else case BC.break ((==) '\n') $ B.tail $ dropSpace s of
(name,s') ->
case BC.break ((==) '*') $ B.tail s' of
(author,s2) ->
case BC.break (\c->c==']'||c=='\n') $ B.drop 2 s2 of
(ct,s''') ->
do (log, s4) <- linesStartingWithEndingWith ' ' ']' $ dn s'''
return $ (PatchInfo { _piDate = ct
, _piName = name
, _piAuthor = author
, _piLog = log
, isInverted = BC.index s2 1 /= '*'
}, s4)
where dn x = if B.null x || BC.head x /= '\n' then x else B.tail x
linesStartingWithEndingWith :: Char -> Char -> B.ByteString
-> Maybe ([B.ByteString],B.ByteString)
linesStartingWithEndingWith st en s = lswew s
where
lswew x | B.null x = Nothing
lswew x =
if BC.head x == en
then Just ([], B.tail x)
else if BC.head x /= st
then Nothing
else case BC.break ((==) '\n') $ B.tail x of
(l,r) -> case lswew $ B.tail r of
Just (ls,r') -> Just (l:ls,r')
Nothing ->
case breakLastPS en l of
Just (l2,_) ->
Just ([l2], B.drop (B.length l2+2) x)
Nothing -> Nothing
htmlPatchInfo :: RepoPatchInfo -> Html
htmlPatchInfo (RPI r pi) =
toHtml $ (td << patchLink r pi) `above`
((td ! [align "right"] << mailLink (justAuthor pi)) `beside`
(td << (friendlyD $ _piDate pi)))
patchLink :: String -> PatchInfo -> Html
patchLink r pi =
toHtml $ hotlink
("darcs?"++r++"**"++makeFilename pi)
[toHtml $ piName pi]
mailLink :: String -> Html
mailLink email = toHtml $ hotlink ("mailto:"++email) [toHtml email]