% Copyright (C) 2002-2003 David Roundy
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU General Public License as published by
% the Free Software Foundation; either version 2, or (at your option)
% any later version.
%
% 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 for more details.
%
% You should have received a copy of the GNU General Public License
% along with this program; see the file COPYING. If not, write to
% the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
% Boston, MA 02110-1301, USA.
\begin{code}
module PatchInfo ( PatchInfo(..), patchinfo, invert_name, is_inverted,
make_filename, make_alt_filename, readPatchInfo,
just_name, just_author, repopatchinfo, RepoPatchInfo,
human_friendly, to_xml, pi_date, set_pi_date,
pi_author, pi_tag, showPatchInfo,
) where
import Text.Html hiding (name, text)
import FastPackedString
import Printer ( renderString, Doc, packedString,
empty, ($$), (<>), (<+>), vcat, text, blueText, prefix )
import IsoDate ( cleanDate, readDate )
import System.Time ( CalendarTime, calendarTimeToString, toClockTime,
toCalendarTime )
import System.IO.Unsafe ( unsafePerformIO )
import SHA1 ( sha1PS )
import PatchReadMonads
import Prelude hiding (pi, log)
data RepoPatchInfo = RPI String PatchInfo
repopatchinfo :: String -> PatchInfo -> RepoPatchInfo
repopatchinfo r pi = RPI r pi
data PatchInfo = PatchInfo !PackedString !PackedString
!PackedString ![PackedString] !Bool
deriving (Eq,Ord)
patchinfo :: String -> String -> String -> [String] -> PatchInfo
patchinfo date name author log =
PatchInfo (packString date) (packString name) (packString author)
(map packString log) False
\end{code}
\section{Patch info formatting}
\begin{code}
invert_name :: PatchInfo -> PatchInfo
invert_name (PatchInfo d n a l inv) = PatchInfo d n a l (not inv)
is_inverted :: PatchInfo -> Bool
is_inverted (PatchInfo _ _ _ _ inv) = inv
\end{code}
\begin{code}
just_name :: PatchInfo -> String
just_name (PatchInfo _ n _ _ False) = unpackPS n
just_name (PatchInfo _ n _ _ True) = "UNDO: " ++ unpackPS n
just_author :: PatchInfo -> String
just_author (PatchInfo _ _ a _ _) = unpackPS a
human_friendly :: PatchInfo -> Doc
human_friendly pinfo@(PatchInfo d n a l inv) =
text (friendly_d d) <> text " " <> packedString a
$$ hfn n
$$ vcat (map ((text " " <>) . packedString) l)
where hfn x = case pi_tag pinfo of
Nothing -> inverted <+> packedString x
Just t -> text " tagged" <+> text t
inverted = if inv then text " UNDO:" else text " *"
pi_author :: PatchInfo -> String
pi_author (PatchInfo _ _ a _ _) = unpackPS a
pi_date :: PatchInfo -> CalendarTime
pi_date (PatchInfo d _ _ _ _) = readDate $ unpackPS d
set_pi_date :: String -> PatchInfo -> PatchInfo
set_pi_date date (PatchInfo _ a b c d)
= PatchInfo (packString date) a b c d
pi_tag :: PatchInfo -> Maybe String
pi_tag (PatchInfo _ n _ _ _) =
if l == t
then Just $ unpackPS r
else Nothing
where (l, r) = splitAtPS (lengthPS t) n
t = packString "TAG "
friendly_d :: PackedString -> String
--friendly_d d = calendarTimeToString . readDate . unpackPS . d
friendly_d d = unsafePerformIO $ do
ct <- toCalendarTime $ toClockTime $ readDate $ unpackPS d
return $ calendarTimeToString ct
\end{code}
\begin{code}
to_xml :: PatchInfo -> Doc
to_xml pi@(PatchInfo date patch_name author comments inverted) =
text " text "author='" <> escapeXML (unpackPS author) <> text "'"
<+> text "date='" <> escapeXML (unpackPS date) <> text "'"
<+> text "local_date='" <> escapeXML (friendly_d date) <> text "'"
<+> text "inverted='" <> text (show inverted) <> text "'"
<+> text "hash='" <> text (make_filename pi) <> text "'>"
$$ prefix "\t" (
text "" <> escapeXML (unpackPS patch_name) <> text ""
$$ comments_as_xml comments)
$$ text ""
comments_as_xml :: [PackedString] -> Doc
comments_as_xml comments
| lengthPS comments' > 0 = text ""
<> escapeXML (unpackPS comments')
<> text ""
| otherwise = empty
where comments' = unlinesPS comments
-- escapeXML is duplicated in Patch.lhs and Annotate.lhs
-- It should probably be refactored to exist in one place.
escapeXML :: String -> Doc
escapeXML = text . strReplace '\'' "'" . strReplace '"' """ .
strReplace '>' ">" . strReplace '<' "<" . strReplace '&' "&"
strReplace :: Char -> String -> String -> String
strReplace _ _ [] = []
strReplace x y (z:zs)
| x == z = y ++ (strReplace x y zs)
| otherwise = z : (strReplace x y zs)
\end{code}
\begin{code}
make_alt_filename :: PatchInfo -> String
make_alt_filename (PatchInfo d n a _ False) =
fix_up_fname (midtrunc (unpackPS n)++"-"++unpackPS a++"-"++unpackPS d)
make_alt_filename (PatchInfo d n a l True) =
make_alt_filename (PatchInfo d n a l False) ++ "-inverted"
make_filename :: PatchInfo -> String
make_filename (PatchInfo dps nps aps lps inv) =
cleanDate d++"-"++sha1_a++"-"++sha1PS sha1_me++".gz"
where b2ps True = packString "t"
b2ps False = packString "f"
sha1_me = concatPS [nps, aps, dps, concatPS lps, b2ps inv]
d = unpackPS dps
sha1_a = take 5 $ sha1PS aps
midtrunc :: String -> String
midtrunc s
| length s < 73 = s
| otherwise = (take 40 s)++"..."++(reverse $ take 30 $ reverse s)
fix_up_fname :: String -> String
fix_up_fname = map munge_char
munge_char :: Char -> Char
munge_char '*' = '+'
munge_char '?' = '2'
munge_char '>' = '7'
munge_char '<' = '2'
munge_char ' ' = '_'
munge_char '"' = '~'
munge_char '`' = '.'
munge_char '\'' = '.'
munge_char '/' = '1'
munge_char '\\' = '1'
munge_char '!' = '1'
munge_char ':' = '.'
munge_char ';' = ','
munge_char '{' = '~'
munge_char '}' = '~'
munge_char '(' = '~'
munge_char ')' = '~'
munge_char '[' = '~'
munge_char ']' = '~'
munge_char '=' = '+'
munge_char '#' = '+'
munge_char '%' = '8'
munge_char '&' = '6'
munge_char '@' = '9'
munge_char '|' = '1'
munge_char c = c
\end{code}
\begin{code}
instance HTML RepoPatchInfo where
toHtml = htmlPatchInfo
instance Show PatchInfo where
show pi = renderString (showPatchInfo pi)
\end{code}
\paragraph{Patch info}
Patch is stored between square brackets.
\begin{verbatim}
[
*
(indented one)
]
\end{verbatim}
\begin{code}
-- note that below I assume the name has no newline in it.
showPatchInfo :: PatchInfo -> Doc
showPatchInfo (PatchInfo ct name author log inv) =
blueText "[" <> packedString name
$$ packedString author <> text inverted <> packedString ct
<> myunlines log <> blueText "] "
where inverted = if inv then "*-" else "**"
myunlines [] = empty
myunlines xs = mul xs
where mul [] = text "\n"
mul (s:ss) = text "\n " <> packedString s <> mul ss
readPatchInfo :: Stringalike s => s -> Maybe (PatchInfo, s)
readPatchInfo s | sal_null (sal_dropWhite s) = Nothing
readPatchInfo s =
if sal_head (sal_dropWhite s) /= '[' -- ]
then Nothing
else case sal_breakOn '\n' $ sal_tail $ sal_dropWhite s of
(name,s') ->
case sal_breakOn '*' $ sal_tail s' of
(author,s2) ->
case sal_break (\c->c==']'||c=='\n') $ sal_drop 2 s2 of
(ct,s''') ->
case lines_starting_with_ending_with ' ' ']' $ dn s''' of
Just (log, s4) ->
let not_star = sal_index s2 1 /= '*'
in Just (PatchInfo (sal_to_PS ct)
(sal_to_PS name)
(sal_to_PS author)
(map sal_to_PS log)
not_star,
s4)
Nothing -> error $ "Error parsing patchinfo:\n"++
unlines (map show $ lines $ sal_to_string $ sal_take 480 s)
where dn x = if sal_null x || sal_head x /= '\n' then x else sal_tail x
\end{code}
\begin{code}
lines_starting_with_ending_with :: Stringalike s
=> Char -> Char -> s -> Maybe ([s],s)
lines_starting_with_ending_with st en s = lswew s
where
lswew x | sal_null x = Nothing
lswew x =
if sal_head x == en
then Just ([], sal_tail x)
else if sal_head x /= st
then Nothing
else case sal_breakOn '\n' $ sal_tail x of
(l,r) -> case lswew $ sal_tail r of
Just (ls,r') -> Just (l:ls,r')
Nothing ->
case sal_breakLast en l of
Just (l2,_) ->
Just ([l2], sal_drop (sal_length l2+2) x)
Nothing -> Nothing
\end{code}
\begin{code}
htmlPatchInfo :: RepoPatchInfo -> Html
htmlPatchInfo (RPI r pi@(PatchInfo ct _ author _ _)) =
toHtml $ (td << patch_link r pi) `above`
((td ! [align "right"] << mail_link (unpackPS author)) `beside`
(td << (friendly_d ct)))
patch_link :: String -> PatchInfo -> Html
patch_link r pi@(PatchInfo _ name _ _ _) =
toHtml $ hotlink
("darcs?"++r++"**"++make_filename pi)
[toHtml $ unpackPS name]
mail_link :: String -> Html
mail_link email = toHtml $ hotlink ("mailto:"++email) [toHtml email]
\end{code}