% Copyright (C) 2002-2005 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} {-# OPTIONS_GHC -cpp -fno-warn-orphans -fglasgow-exts #-} {-# LANGUAGE CPP #-} module Darcs.Patch.Show ( showPatch_, showNamedPrefix ) where import Prelude hiding ( pi ) import Printer ( Doc, renderString, vcat, text, blueText, ($$), (<+>) ) import Darcs.Patch.Core ( Patch(..) ) import Darcs.Patch.Prim ( showPrim, FileNameFormat(..) ) import Darcs.Patch.Info ( PatchInfo, showPatchInfo ) import Darcs.Witnesses.Ordered ( FL(NilFL), mapFL ) #include "gadts.h" \end{code} \section{Patch string formatting} Of course, in order to store our patches in a file, we'll have to save them as some sort of strings. The convention is that each patch string will end with a newline, but on parsing we skip any amount of whitespace between patches. \begin{code} instance Show (Patch C(x y)) where show p = renderString (showPatch_ p) ++ "\n" showPatch_ :: Patch C(a b) -> Doc showPatch_ (PP p) = showPrim OldFormat p showPatch_ (ComP NilFL) = blueText "{" $$ blueText "}" showPatch_ (ComP ps) = blueText "{" $$ vcat (mapFL showPatch_ ps) $$ blueText "}" showPatch_ (Merger _ _ p1 p2) = showMerger "merger" p1 p2 showPatch_ (Regrem _ _ p1 p2) = showMerger "regrem" p1 p2 \end{code} \paragraph{Merger patches} Merge two patches. The MERGERVERSION is included to allow some degree of backwards compatibility if the merger algorithm needs to be changed. \begin{verbatim} merger MERGERVERSION \end{verbatim} \begin{code} showMerger :: String -> Patch C(a b) -> Patch C(d e) -> Doc showMerger merger_name p1 p2 = blueText merger_name <+> text "0.0" <+> blueText "(" $$ showPatch_ p1 $$ showPatch_ p2 $$ blueText ")" \end{code} \paragraph{Named patches} Named patches are displayed as a ``patch id'' which is in square brackets, followed by a patch. Optionally, after the patch id (but before the patch itself) can come a list of dependencies surrounded by angle brackets. Each dependency consists of a patch id. \begin{code} showNamedPrefix :: PatchInfo -> [PatchInfo] -> Doc showNamedPrefix n d = showPatchInfo n $$ blueText "<" $$ vcat (map showPatchInfo d) $$ blueText ">" \end{code}