module Darcs.Patch.Show
( ShowPatchBasic(..)
, displayPatch
, ShowPatchFor(..)
, ShowPatch(..)
, ShowContextPatch(..)
, formatFileName
) where
import Darcs.Prelude
import qualified Data.ByteString.Char8 as BC ( unpack )
import Darcs.Patch.Apply ( ApplyState )
import Darcs.Patch.ApplyMonad ( ApplyMonad )
import Darcs.Patch.Format ( FileNameFormat(..) )
import Darcs.Patch.Witnesses.Ordered ( FL, mapFL )
import Darcs.Util.ByteString ( packStringToUTF8, encodeLocale )
import Darcs.Util.English ( plural, Noun(Noun) )
import Darcs.Util.Path ( AnchoredPath, encodeWhite, anchorPath )
import Darcs.Util.Printer ( Doc, vcat, text, packedString )
data ShowPatchFor = ForDisplay | ForStorage
displayPatch :: ShowPatchBasic p => p wX wY -> Doc
displayPatch :: p wX wY -> Doc
displayPatch p wX wY
p = ShowPatchFor -> p wX wY -> Doc
forall (p :: * -> * -> *) wX wY.
ShowPatchBasic p =>
ShowPatchFor -> p wX wY -> Doc
showPatch ShowPatchFor
ForDisplay p wX wY
p
class ShowPatchBasic p where
showPatch :: ShowPatchFor -> p wX wY -> Doc
class ShowPatchBasic p => ShowContextPatch p where
showContextPatch :: (ApplyMonad (ApplyState p) m)
=> ShowPatchFor -> p wX wY -> m Doc
class ShowPatchBasic p => ShowPatch p where
content :: p wX wY -> Doc
content = p wX wY -> Doc
forall a. Monoid a => a
mempty
description :: p wX wY -> Doc
description = p wX wY -> Doc
forall (p :: * -> * -> *) wX wY. ShowPatchBasic p => p wX wY -> Doc
displayPatch
summary :: p wX wY -> Doc
summaryFL :: FL p wX wY -> Doc
summaryFL = [Doc] -> Doc
vcat ([Doc] -> Doc) -> (FL p wX wY -> [Doc]) -> FL p wX wY -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall wW wZ. p wW wZ -> Doc) -> FL p wX wY -> [Doc]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL forall wW wZ. p wW wZ -> Doc
forall (p :: * -> * -> *) wW wZ. ShowPatch p => p wW wZ -> Doc
summary
thing :: p wX wY -> String
thing p wX wY
_ = String
"patch"
things :: p wX wY -> String
things p wX wY
x = Noun -> ShowS
forall a. Countable a => a -> ShowS
plural (String -> Noun
Noun (String -> Noun) -> String -> Noun
forall a b. (a -> b) -> a -> b
$ p wX wY -> String
forall (p :: * -> * -> *) wX wY. ShowPatch p => p wX wY -> String
thing p wX wY
x) String
""
formatFileName :: FileNameFormat -> AnchoredPath -> Doc
formatFileName :: FileNameFormat -> AnchoredPath -> Doc
formatFileName FileNameFormat
FileNameFormatV1 = ByteString -> Doc
packedString (ByteString -> Doc)
-> (AnchoredPath -> ByteString) -> AnchoredPath -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
packStringToUTF8 (String -> ByteString)
-> (AnchoredPath -> String) -> AnchoredPath -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
BC.unpack (ByteString -> String)
-> (AnchoredPath -> ByteString) -> AnchoredPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ByteString
encodeLocale (String -> ByteString)
-> (AnchoredPath -> String) -> AnchoredPath -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
encodeWhite ShowS -> (AnchoredPath -> String) -> AnchoredPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredPath -> String
ap2fp
formatFileName FileNameFormat
FileNameFormatV2 = String -> Doc
text (String -> Doc) -> (AnchoredPath -> String) -> AnchoredPath -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
encodeWhite ShowS -> (AnchoredPath -> String) -> AnchoredPath -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredPath -> String
ap2fp
formatFileName FileNameFormat
FileNameFormatDisplay = String -> Doc
text (String -> Doc) -> (AnchoredPath -> String) -> AnchoredPath -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnchoredPath -> String
ap2fp
ap2fp :: AnchoredPath -> FilePath
ap2fp :: AnchoredPath -> String
ap2fp AnchoredPath
ap = Char
'.' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'/' Char -> ShowS
forall a. a -> [a] -> [a]
: String -> AnchoredPath -> String
anchorPath String
"" AnchoredPath
ap