module Darcs.Patch.Inspect
       ( PatchInspect(..)
       )
       where

import Darcs.Prelude

import Darcs.Patch.Witnesses.Ordered ( FL, RL, reverseRL, mapFL )
import Darcs.Util.Path ( AnchoredPath )

import qualified Data.ByteString.Char8 as BC
import Data.List ( nub )

-- TODO Whether a patch touches a given file is not an invariant property of a
-- patch: it depends on the context i.e. it changes when we re-order patches.
-- Can we define an interface where this becomes an invariant property?

-- TODO This interface only makes sense if @ApplyState p ~ Tree@. To support
-- other ApplyStates we need to devise an abstraction for "objects" of the
-- ApplyState.

class PatchInspect p where
    listTouchedFiles :: p wX wY -> [AnchoredPath]
    hunkMatches :: (BC.ByteString -> Bool) -> p wX wY -> Bool

instance PatchInspect p => PatchInspect (FL p) where
    listTouchedFiles :: FL p wX wY -> [AnchoredPath]
listTouchedFiles FL p wX wY
xs = [AnchoredPath] -> [AnchoredPath]
forall a. Eq a => [a] -> [a]
nub ([AnchoredPath] -> [AnchoredPath])
-> [AnchoredPath] -> [AnchoredPath]
forall a b. (a -> b) -> a -> b
$ [[AnchoredPath]] -> [AnchoredPath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[AnchoredPath]] -> [AnchoredPath])
-> [[AnchoredPath]] -> [AnchoredPath]
forall a b. (a -> b) -> a -> b
$ (forall wW wZ. p wW wZ -> [AnchoredPath])
-> FL p wX wY -> [[AnchoredPath]]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL forall wW wZ. p wW wZ -> [AnchoredPath]
forall (p :: * -> * -> *) wX wY.
PatchInspect p =>
p wX wY -> [AnchoredPath]
listTouchedFiles FL p wX wY
xs
    hunkMatches :: (ByteString -> Bool) -> FL p wX wY -> Bool
hunkMatches ByteString -> Bool
f = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Bool] -> Bool) -> (FL p wX wY -> [Bool]) -> FL p wX wY -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall wW wZ. p wW wZ -> Bool) -> FL p wX wY -> [Bool]
forall (a :: * -> * -> *) b wX wY.
(forall wW wZ. a wW wZ -> b) -> FL a wX wY -> [b]
mapFL ((ByteString -> Bool) -> p wW wZ -> Bool
forall (p :: * -> * -> *) wX wY.
PatchInspect p =>
(ByteString -> Bool) -> p wX wY -> Bool
hunkMatches ByteString -> Bool
f)

instance PatchInspect p => PatchInspect (RL p) where
    listTouchedFiles :: RL p wX wY -> [AnchoredPath]
listTouchedFiles = FL p wX wY -> [AnchoredPath]
forall (p :: * -> * -> *) wX wY.
PatchInspect p =>
p wX wY -> [AnchoredPath]
listTouchedFiles (FL p wX wY -> [AnchoredPath])
-> (RL p wX wY -> FL p wX wY) -> RL p wX wY -> [AnchoredPath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RL p wX wY -> FL p wX wY
forall (a :: * -> * -> *) wX wZ. RL a wX wZ -> FL a wX wZ
reverseRL
    hunkMatches :: (ByteString -> Bool) -> RL p wX wY -> Bool
hunkMatches ByteString -> Bool
f = (ByteString -> Bool) -> FL p wX wY -> Bool
forall (p :: * -> * -> *) wX wY.
PatchInspect p =>
(ByteString -> Bool) -> p wX wY -> Bool
hunkMatches ByteString -> Bool
f (FL p wX wY -> Bool)
-> (RL p wX wY -> FL p wX wY) -> RL p wX wY -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RL p wX wY -> FL p wX wY
forall (a :: * -> * -> *) wX wZ. RL a wX wZ -> FL a wX wZ
reverseRL