module Darcs.Patch.Prim.V1.Core
( Prim(..),
DirPatchType(..), FilePatchType(..),
isIdentity,
comparePrim,
)
where
import Darcs.Prelude
import qualified Data.ByteString as B (ByteString)
import Darcs.Util.Path ( AnchoredPath )
import Darcs.Patch.Witnesses.Eq ( Eq2(..), EqCheck(..) )
import Darcs.Patch.Witnesses.Unsafe ( unsafeCoerceP )
import Darcs.Patch.Debug ( PatchDebug(..) )
import Darcs.Patch.FileHunk ( FileHunk(..), IsHunk(..) )
import Darcs.Patch.Invert ( Invert(..) )
import Darcs.Patch.Inspect ( PatchInspect(..) )
import Darcs.Patch.Permutations ()
import Darcs.Patch.Prim.Class ( PrimConstruct(..), PrimClassify(..) )
data Prim wX wY where
Move :: !AnchoredPath -> !AnchoredPath -> Prim wX wY
DP :: !AnchoredPath -> !(DirPatchType wX wY) -> Prim wX wY
FP :: !AnchoredPath -> !(FilePatchType wX wY) -> Prim wX wY
ChangePref :: !String -> !String -> !String -> Prim wX wY
data FilePatchType wX wY
= RmFile
| AddFile
| Hunk !Int [B.ByteString] [B.ByteString]
| TokReplace !String !String !String
| Binary B.ByteString B.ByteString
deriving (FilePatchType wX wY -> FilePatchType wX wY -> Bool
(FilePatchType wX wY -> FilePatchType wX wY -> Bool)
-> (FilePatchType wX wY -> FilePatchType wX wY -> Bool)
-> Eq (FilePatchType wX wY)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
/= :: FilePatchType wX wY -> FilePatchType wX wY -> Bool
$c/= :: forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
== :: FilePatchType wX wY -> FilePatchType wX wY -> Bool
$c== :: forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
Eq,Eq (FilePatchType wX wY)
Eq (FilePatchType wX wY)
-> (FilePatchType wX wY -> FilePatchType wX wY -> Ordering)
-> (FilePatchType wX wY -> FilePatchType wX wY -> Bool)
-> (FilePatchType wX wY -> FilePatchType wX wY -> Bool)
-> (FilePatchType wX wY -> FilePatchType wX wY -> Bool)
-> (FilePatchType wX wY -> FilePatchType wX wY -> Bool)
-> (FilePatchType wX wY
-> FilePatchType wX wY -> FilePatchType wX wY)
-> (FilePatchType wX wY
-> FilePatchType wX wY -> FilePatchType wX wY)
-> Ord (FilePatchType wX wY)
FilePatchType wX wY -> FilePatchType wX wY -> Bool
FilePatchType wX wY -> FilePatchType wX wY -> Ordering
FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall wX wY. Eq (FilePatchType wX wY)
forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
forall wX wY.
FilePatchType wX wY -> FilePatchType wX wY -> Ordering
forall wX wY.
FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY
min :: FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY
$cmin :: forall wX wY.
FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY
max :: FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY
$cmax :: forall wX wY.
FilePatchType wX wY -> FilePatchType wX wY -> FilePatchType wX wY
>= :: FilePatchType wX wY -> FilePatchType wX wY -> Bool
$c>= :: forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
> :: FilePatchType wX wY -> FilePatchType wX wY -> Bool
$c> :: forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
<= :: FilePatchType wX wY -> FilePatchType wX wY -> Bool
$c<= :: forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
< :: FilePatchType wX wY -> FilePatchType wX wY -> Bool
$c< :: forall wX wY. FilePatchType wX wY -> FilePatchType wX wY -> Bool
compare :: FilePatchType wX wY -> FilePatchType wX wY -> Ordering
$ccompare :: forall wX wY.
FilePatchType wX wY -> FilePatchType wX wY -> Ordering
$cp1Ord :: forall wX wY. Eq (FilePatchType wX wY)
Ord)
type role FilePatchType nominal nominal
data DirPatchType wX wY = RmDir | AddDir
deriving (DirPatchType wX wY -> DirPatchType wX wY -> Bool
(DirPatchType wX wY -> DirPatchType wX wY -> Bool)
-> (DirPatchType wX wY -> DirPatchType wX wY -> Bool)
-> Eq (DirPatchType wX wY)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
/= :: DirPatchType wX wY -> DirPatchType wX wY -> Bool
$c/= :: forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
== :: DirPatchType wX wY -> DirPatchType wX wY -> Bool
$c== :: forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
Eq,Eq (DirPatchType wX wY)
Eq (DirPatchType wX wY)
-> (DirPatchType wX wY -> DirPatchType wX wY -> Ordering)
-> (DirPatchType wX wY -> DirPatchType wX wY -> Bool)
-> (DirPatchType wX wY -> DirPatchType wX wY -> Bool)
-> (DirPatchType wX wY -> DirPatchType wX wY -> Bool)
-> (DirPatchType wX wY -> DirPatchType wX wY -> Bool)
-> (DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY)
-> (DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY)
-> Ord (DirPatchType wX wY)
DirPatchType wX wY -> DirPatchType wX wY -> Bool
DirPatchType wX wY -> DirPatchType wX wY -> Ordering
DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall wX wY. Eq (DirPatchType wX wY)
forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Ordering
forall wX wY.
DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY
min :: DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY
$cmin :: forall wX wY.
DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY
max :: DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY
$cmax :: forall wX wY.
DirPatchType wX wY -> DirPatchType wX wY -> DirPatchType wX wY
>= :: DirPatchType wX wY -> DirPatchType wX wY -> Bool
$c>= :: forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
> :: DirPatchType wX wY -> DirPatchType wX wY -> Bool
$c> :: forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
<= :: DirPatchType wX wY -> DirPatchType wX wY -> Bool
$c<= :: forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
< :: DirPatchType wX wY -> DirPatchType wX wY -> Bool
$c< :: forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Bool
compare :: DirPatchType wX wY -> DirPatchType wX wY -> Ordering
$ccompare :: forall wX wY. DirPatchType wX wY -> DirPatchType wX wY -> Ordering
$cp1Ord :: forall wX wY. Eq (DirPatchType wX wY)
Ord)
type role DirPatchType nominal nominal
instance Eq2 FilePatchType where
unsafeCompare :: FilePatchType wA wB -> FilePatchType wC wD -> Bool
unsafeCompare FilePatchType wA wB
a FilePatchType wC wD
b = FilePatchType wA wB
a FilePatchType wA wB -> FilePatchType wA wB -> Bool
forall a. Eq a => a -> a -> Bool
== FilePatchType wC wD -> FilePatchType wA wB
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP FilePatchType wC wD
b
instance Invert FilePatchType where
invert :: FilePatchType wX wY -> FilePatchType wY wX
invert FilePatchType wX wY
RmFile = FilePatchType wY wX
forall wX wY. FilePatchType wX wY
AddFile
invert FilePatchType wX wY
AddFile = FilePatchType wY wX
forall wX wY. FilePatchType wX wY
RmFile
invert (Hunk Int
line [ByteString]
old [ByteString]
new) = Int -> [ByteString] -> [ByteString] -> FilePatchType wY wX
forall wX wY.
Int -> [ByteString] -> [ByteString] -> FilePatchType wX wY
Hunk Int
line [ByteString]
new [ByteString]
old
invert (TokReplace String
t String
o String
n) = String -> String -> String -> FilePatchType wY wX
forall wX wY. String -> String -> String -> FilePatchType wX wY
TokReplace String
t String
n String
o
invert (Binary ByteString
o ByteString
n) = ByteString -> ByteString -> FilePatchType wY wX
forall wX wY. ByteString -> ByteString -> FilePatchType wX wY
Binary ByteString
n ByteString
o
instance Eq2 DirPatchType where
unsafeCompare :: DirPatchType wA wB -> DirPatchType wC wD -> Bool
unsafeCompare DirPatchType wA wB
a DirPatchType wC wD
b = DirPatchType wA wB
a DirPatchType wA wB -> DirPatchType wA wB -> Bool
forall a. Eq a => a -> a -> Bool
== DirPatchType wC wD -> DirPatchType wA wB
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP DirPatchType wC wD
b
instance Invert DirPatchType where
invert :: DirPatchType wX wY -> DirPatchType wY wX
invert DirPatchType wX wY
RmDir = DirPatchType wY wX
forall wX wY. DirPatchType wX wY
AddDir
invert DirPatchType wX wY
AddDir = DirPatchType wY wX
forall wX wY. DirPatchType wX wY
RmDir
isIdentity :: Prim wX wY -> EqCheck wX wY
isIdentity :: Prim wX wY -> EqCheck wX wY
isIdentity (FP AnchoredPath
_ (Binary ByteString
old ByteString
new)) | ByteString
old ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
new = EqCheck Any Any -> EqCheck wX wY
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP EqCheck Any Any
forall wA. EqCheck wA wA
IsEq
isIdentity (FP AnchoredPath
_ (Hunk Int
_ [ByteString]
old [ByteString]
new)) | [ByteString]
old [ByteString] -> [ByteString] -> Bool
forall a. Eq a => a -> a -> Bool
== [ByteString]
new = EqCheck Any Any -> EqCheck wX wY
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP EqCheck Any Any
forall wA. EqCheck wA wA
IsEq
isIdentity (FP AnchoredPath
_ (TokReplace String
_ String
old String
new)) | String
old String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
new = EqCheck Any Any -> EqCheck wX wY
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP EqCheck Any Any
forall wA. EqCheck wA wA
IsEq
isIdentity (Move AnchoredPath
old AnchoredPath
new) | AnchoredPath
old AnchoredPath -> AnchoredPath -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredPath
new = EqCheck Any Any -> EqCheck wX wY
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP EqCheck Any Any
forall wA. EqCheck wA wA
IsEq
isIdentity Prim wX wY
_ = EqCheck wX wY
forall wA wB. EqCheck wA wB
NotEq
instance PrimClassify Prim where
primIsAddfile :: Prim wX wY -> Bool
primIsAddfile (FP AnchoredPath
_ FilePatchType wX wY
AddFile) = Bool
True
primIsAddfile Prim wX wY
_ = Bool
False
primIsRmfile :: Prim wX wY -> Bool
primIsRmfile (FP AnchoredPath
_ FilePatchType wX wY
RmFile) = Bool
True
primIsRmfile Prim wX wY
_ = Bool
False
primIsAdddir :: Prim wX wY -> Bool
primIsAdddir (DP AnchoredPath
_ DirPatchType wX wY
AddDir) = Bool
True
primIsAdddir Prim wX wY
_ = Bool
False
primIsRmdir :: Prim wX wY -> Bool
primIsRmdir (DP AnchoredPath
_ DirPatchType wX wY
RmDir) = Bool
True
primIsRmdir Prim wX wY
_ = Bool
False
primIsMove :: Prim wX wY -> Bool
primIsMove (Move AnchoredPath
_ AnchoredPath
_) = Bool
True
primIsMove Prim wX wY
_ = Bool
False
primIsHunk :: Prim wX wY -> Bool
primIsHunk (FP AnchoredPath
_ (Hunk Int
_ [ByteString]
_ [ByteString]
_)) = Bool
True
primIsHunk Prim wX wY
_ = Bool
False
primIsTokReplace :: Prim wX wY -> Bool
primIsTokReplace (FP AnchoredPath
_ (TokReplace String
_ String
_ String
_)) = Bool
True
primIsTokReplace Prim wX wY
_ = Bool
False
primIsBinary :: Prim wX wY -> Bool
primIsBinary (FP AnchoredPath
_ (Binary ByteString
_ ByteString
_)) = Bool
True
primIsBinary Prim wX wY
_ = Bool
False
primIsSetpref :: Prim wX wY -> Bool
primIsSetpref (ChangePref String
_ String
_ String
_) = Bool
True
primIsSetpref Prim wX wY
_ = Bool
False
is_filepatch :: Prim wX wY -> Maybe AnchoredPath
is_filepatch (FP AnchoredPath
f FilePatchType wX wY
_) = AnchoredPath -> Maybe AnchoredPath
forall a. a -> Maybe a
Just AnchoredPath
f
is_filepatch Prim wX wY
_ = Maybe AnchoredPath
forall a. Maybe a
Nothing
evalargs :: (a -> b -> c) -> a -> b -> c
evalargs :: (a -> b -> c) -> a -> b -> c
evalargs a -> b -> c
f a
x b
y = (a -> b -> c
f (a -> b -> c) -> a -> b -> c
forall a b. (a -> b) -> a -> b
$! a
x) (b -> c) -> b -> c
forall a b. (a -> b) -> a -> b
$! b
y
instance PrimConstruct Prim where
addfile :: AnchoredPath -> Prim wX wY
addfile AnchoredPath
f = AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> FilePatchType wX wY -> Prim wX wY
FP AnchoredPath
f FilePatchType wX wY
forall wX wY. FilePatchType wX wY
AddFile
rmfile :: AnchoredPath -> Prim wX wY
rmfile AnchoredPath
f = AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> FilePatchType wX wY -> Prim wX wY
FP AnchoredPath
f FilePatchType wX wY
forall wX wY. FilePatchType wX wY
RmFile
adddir :: AnchoredPath -> Prim wX wY
adddir AnchoredPath
d = AnchoredPath -> DirPatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> DirPatchType wX wY -> Prim wX wY
DP AnchoredPath
d DirPatchType wX wY
forall wX wY. DirPatchType wX wY
AddDir
rmdir :: AnchoredPath -> Prim wX wY
rmdir AnchoredPath
d = AnchoredPath -> DirPatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> DirPatchType wX wY -> Prim wX wY
DP AnchoredPath
d DirPatchType wX wY
forall wX wY. DirPatchType wX wY
RmDir
move :: AnchoredPath -> AnchoredPath -> Prim wX wY
move AnchoredPath
old AnchoredPath
new = AnchoredPath -> AnchoredPath -> Prim wX wY
forall wX wY. AnchoredPath -> AnchoredPath -> Prim wX wY
Move AnchoredPath
old AnchoredPath
new
changepref :: String -> String -> String -> Prim wX wY
changepref String
p String
f String
t = String -> String -> String -> Prim wX wY
forall wX wY. String -> String -> String -> Prim wX wY
ChangePref String
p String
f String
t
hunk :: AnchoredPath -> Int -> [ByteString] -> [ByteString] -> Prim wX wY
hunk AnchoredPath
f Int
line [ByteString]
old [ByteString]
new = (AnchoredPath -> FilePatchType wX wY -> Prim wX wY)
-> AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall a b c. (a -> b -> c) -> a -> b -> c
evalargs AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> FilePatchType wX wY -> Prim wX wY
FP AnchoredPath
f (Int -> [ByteString] -> [ByteString] -> FilePatchType wX wY
forall wX wY.
Int -> [ByteString] -> [ByteString] -> FilePatchType wX wY
Hunk Int
line [ByteString]
old [ByteString]
new)
tokreplace :: AnchoredPath -> String -> String -> String -> Prim wX wY
tokreplace AnchoredPath
f String
tokchars String
old String
new =
(AnchoredPath -> FilePatchType wX wY -> Prim wX wY)
-> AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall a b c. (a -> b -> c) -> a -> b -> c
evalargs AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> FilePatchType wX wY -> Prim wX wY
FP AnchoredPath
f (String -> String -> String -> FilePatchType wX wY
forall wX wY. String -> String -> String -> FilePatchType wX wY
TokReplace String
tokchars String
old String
new)
binary :: AnchoredPath -> ByteString -> ByteString -> Prim wX wY
binary AnchoredPath
f ByteString
old ByteString
new = AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> FilePatchType wX wY -> Prim wX wY
FP AnchoredPath
f (FilePatchType wX wY -> Prim wX wY)
-> FilePatchType wX wY -> Prim wX wY
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> FilePatchType wX wY
forall wX wY. ByteString -> ByteString -> FilePatchType wX wY
Binary ByteString
old ByteString
new
primFromHunk :: FileHunk wX wY -> Prim wX wY
primFromHunk (FileHunk AnchoredPath
f Int
line [ByteString]
before [ByteString]
after) = AnchoredPath -> FilePatchType wX wY -> Prim wX wY
forall wX wY. AnchoredPath -> FilePatchType wX wY -> Prim wX wY
FP AnchoredPath
f (Int -> [ByteString] -> [ByteString] -> FilePatchType wX wY
forall wX wY.
Int -> [ByteString] -> [ByteString] -> FilePatchType wX wY
Hunk Int
line [ByteString]
before [ByteString]
after)
instance IsHunk Prim where
isHunk :: Prim wX wY -> Maybe (FileHunk wX wY)
isHunk (FP AnchoredPath
f (Hunk Int
line [ByteString]
before [ByteString]
after)) = FileHunk wX wY -> Maybe (FileHunk wX wY)
forall a. a -> Maybe a
Just (AnchoredPath
-> Int -> [ByteString] -> [ByteString] -> FileHunk wX wY
forall wX wY.
AnchoredPath
-> Int -> [ByteString] -> [ByteString] -> FileHunk wX wY
FileHunk AnchoredPath
f Int
line [ByteString]
before [ByteString]
after)
isHunk Prim wX wY
_ = Maybe (FileHunk wX wY)
forall a. Maybe a
Nothing
instance Invert Prim where
invert :: Prim wX wY -> Prim wY wX
invert (FP AnchoredPath
f FilePatchType wX wY
p) = AnchoredPath -> FilePatchType wY wX -> Prim wY wX
forall wX wY. AnchoredPath -> FilePatchType wX wY -> Prim wX wY
FP AnchoredPath
f (FilePatchType wX wY -> FilePatchType wY wX
forall (p :: * -> * -> *) wX wY. Invert p => p wX wY -> p wY wX
invert FilePatchType wX wY
p)
invert (DP AnchoredPath
d DirPatchType wX wY
p) = AnchoredPath -> DirPatchType wY wX -> Prim wY wX
forall wX wY. AnchoredPath -> DirPatchType wX wY -> Prim wX wY
DP AnchoredPath
d (DirPatchType wX wY -> DirPatchType wY wX
forall (p :: * -> * -> *) wX wY. Invert p => p wX wY -> p wY wX
invert DirPatchType wX wY
p)
invert (Move AnchoredPath
f AnchoredPath
f') = AnchoredPath -> AnchoredPath -> Prim wY wX
forall wX wY. AnchoredPath -> AnchoredPath -> Prim wX wY
Move AnchoredPath
f' AnchoredPath
f
invert (ChangePref String
p String
f String
t) = String -> String -> String -> Prim wY wX
forall wX wY. String -> String -> String -> Prim wX wY
ChangePref String
p String
t String
f
instance PatchInspect Prim where
listTouchedFiles :: Prim wX wY -> [AnchoredPath]
listTouchedFiles (Move AnchoredPath
f1 AnchoredPath
f2) = [AnchoredPath
f1, AnchoredPath
f2]
listTouchedFiles (FP AnchoredPath
f FilePatchType wX wY
_) = [AnchoredPath
f]
listTouchedFiles (DP AnchoredPath
d DirPatchType wX wY
_) = [AnchoredPath
d]
listTouchedFiles (ChangePref String
_ String
_ String
_) = []
hunkMatches :: (ByteString -> Bool) -> Prim wX wY -> Bool
hunkMatches ByteString -> Bool
f (FP AnchoredPath
_ (Hunk Int
_ [ByteString]
remove [ByteString]
add)) = [ByteString] -> Bool
anyMatches [ByteString]
remove Bool -> Bool -> Bool
|| [ByteString] -> Bool
anyMatches [ByteString]
add
where anyMatches :: [ByteString] -> Bool
anyMatches = (ByteString -> Bool -> Bool) -> Bool -> [ByteString] -> Bool
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Bool -> Bool -> Bool
(||) (Bool -> Bool -> Bool)
-> (ByteString -> Bool) -> ByteString -> Bool -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Bool
f) Bool
False
hunkMatches ByteString -> Bool
_ (FP AnchoredPath
_ FilePatchType wX wY
_) = Bool
False
hunkMatches ByteString -> Bool
_ (DP AnchoredPath
_ DirPatchType wX wY
_) = Bool
False
hunkMatches ByteString -> Bool
_ (ChangePref String
_ String
_ String
_) = Bool
False
hunkMatches ByteString -> Bool
_ (Move AnchoredPath
_ AnchoredPath
_) = Bool
False
instance PatchDebug Prim
instance Eq2 Prim where
unsafeCompare :: Prim wA wB -> Prim wC wD -> Bool
unsafeCompare (Move AnchoredPath
a AnchoredPath
b) (Move AnchoredPath
c AnchoredPath
d) = AnchoredPath
a AnchoredPath -> AnchoredPath -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredPath
c Bool -> Bool -> Bool
&& AnchoredPath
b AnchoredPath -> AnchoredPath -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredPath
d
unsafeCompare (DP AnchoredPath
d1 DirPatchType wA wB
p1) (DP AnchoredPath
d2 DirPatchType wC wD
p2)
= AnchoredPath
d1 AnchoredPath -> AnchoredPath -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredPath
d2 Bool -> Bool -> Bool
&& DirPatchType wA wB
p1 DirPatchType wA wB -> DirPatchType wC wD -> Bool
forall (p :: * -> * -> *) wA wB wC wD.
Eq2 p =>
p wA wB -> p wC wD -> Bool
`unsafeCompare` DirPatchType wC wD
p2
unsafeCompare (FP AnchoredPath
f1 FilePatchType wA wB
fp1) (FP AnchoredPath
f2 FilePatchType wC wD
fp2)
= AnchoredPath
f1 AnchoredPath -> AnchoredPath -> Bool
forall a. Eq a => a -> a -> Bool
== AnchoredPath
f2 Bool -> Bool -> Bool
&& FilePatchType wA wB
fp1 FilePatchType wA wB -> FilePatchType wC wD -> Bool
forall (p :: * -> * -> *) wA wB wC wD.
Eq2 p =>
p wA wB -> p wC wD -> Bool
`unsafeCompare` FilePatchType wC wD
fp2
unsafeCompare (ChangePref String
a1 String
b1 String
c1) (ChangePref String
a2 String
b2 String
c2)
= String
c1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
c2 Bool -> Bool -> Bool
&& String
b1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
b2 Bool -> Bool -> Bool
&& String
a1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
a2
unsafeCompare Prim wA wB
_ Prim wC wD
_ = Bool
False
instance Eq (Prim wX wY) where
== :: Prim wX wY -> Prim wX wY -> Bool
(==) = Prim wX wY -> Prim wX wY -> Bool
forall (p :: * -> * -> *) wA wB wC wD.
Eq2 p =>
p wA wB -> p wC wD -> Bool
unsafeCompare
comparePrim :: Prim wX wY -> Prim wW wZ -> Ordering
comparePrim :: Prim wX wY -> Prim wW wZ -> Ordering
comparePrim (Move AnchoredPath
a AnchoredPath
b) (Move AnchoredPath
c AnchoredPath
d) = (AnchoredPath, AnchoredPath)
-> (AnchoredPath, AnchoredPath) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (AnchoredPath
a, AnchoredPath
b) (AnchoredPath
c, AnchoredPath
d)
comparePrim (Move AnchoredPath
_ AnchoredPath
_) Prim wW wZ
_ = Ordering
LT
comparePrim Prim wX wY
_ (Move AnchoredPath
_ AnchoredPath
_) = Ordering
GT
comparePrim (DP AnchoredPath
d1 DirPatchType wX wY
p1) (DP AnchoredPath
d2 DirPatchType wW wZ
p2) = (AnchoredPath, DirPatchType wX wY)
-> (AnchoredPath, DirPatchType wX wY) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (AnchoredPath
d1, DirPatchType wX wY
p1) ((AnchoredPath, DirPatchType wX wY) -> Ordering)
-> (AnchoredPath, DirPatchType wX wY) -> Ordering
forall a b. (a -> b) -> a -> b
$ (AnchoredPath, DirPatchType wW wZ)
-> (AnchoredPath, DirPatchType wX wY)
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP (AnchoredPath
d2, DirPatchType wW wZ
p2)
comparePrim (DP AnchoredPath
_ DirPatchType wX wY
_) Prim wW wZ
_ = Ordering
LT
comparePrim Prim wX wY
_ (DP AnchoredPath
_ DirPatchType wW wZ
_) = Ordering
GT
comparePrim (FP AnchoredPath
f1 FilePatchType wX wY
fp1) (FP AnchoredPath
f2 FilePatchType wW wZ
fp2) = (AnchoredPath, FilePatchType wX wY)
-> (AnchoredPath, FilePatchType wX wY) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (AnchoredPath
f1, FilePatchType wX wY
fp1) ((AnchoredPath, FilePatchType wX wY) -> Ordering)
-> (AnchoredPath, FilePatchType wX wY) -> Ordering
forall a b. (a -> b) -> a -> b
$ (AnchoredPath, FilePatchType wW wZ)
-> (AnchoredPath, FilePatchType wX wY)
forall (a :: * -> * -> *) wX wY wB wC. a wX wY -> a wB wC
unsafeCoerceP (AnchoredPath
f2, FilePatchType wW wZ
fp2)
comparePrim (FP AnchoredPath
_ FilePatchType wX wY
_) Prim wW wZ
_ = Ordering
LT
comparePrim Prim wX wY
_ (FP AnchoredPath
_ FilePatchType wW wZ
_) = Ordering
GT
comparePrim (ChangePref String
a1 String
b1 String
c1) (ChangePref String
a2 String
b2 String
c2)
= (String, String, String) -> (String, String, String) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (String
c1, String
b1, String
a1) (String
c2, String
b2, String
a2)