module Darcs.Patch.Object where
import Darcs.Prelude
import qualified Data.ByteString.Char8 as BC ( unpack )
import Darcs.Patch.Format ( FileNameFormat(..) )
import Darcs.Util.ByteString ( packStringToUTF8, encodeLocale )
import Darcs.Util.Path ( AnchoredPath, encodeWhite, anchorPath )
import Darcs.Util.Printer ( Doc, text, packedString )
import Darcs.Util.Tree ( Tree )
type family ObjectIdOf (state :: (* -> *) -> *)
class Eq oid => ObjectId oid where
formatObjectId :: FileNameFormat -> oid -> Doc
type instance ObjectIdOf Tree = AnchoredPath
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
. String -> String
encodeWhite (String -> String)
-> (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
. String -> String
encodeWhite (String -> String)
-> (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
instance ObjectId AnchoredPath where
formatObjectId :: FileNameFormat -> AnchoredPath -> Doc
formatObjectId = FileNameFormat -> AnchoredPath -> Doc
formatFileName
ap2fp :: AnchoredPath -> FilePath
ap2fp :: AnchoredPath -> String
ap2fp AnchoredPath
ap = String
"./" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> AnchoredPath -> String
anchorPath String
"" AnchoredPath
ap