module Darcs.Repository.Match
    (
      getRecordedUpToMatch
    , getOnePatchset
    ) where
import Darcs.Prelude
import Darcs.Patch.Match
    ( rollbackToPatchSetMatch
    , PatchSetMatch(..)
    , getMatchingTag
    , matchAPatchset
    )
import Darcs.Patch.Bundle ( readContextFile )
import Darcs.Patch.ApplyMonad ( ApplyMonad(..) )
import Darcs.Patch.Apply( ApplyState )
import Darcs.Patch ( RepoPatch, IsRepoType )
import Darcs.Patch.Set ( Origin, PatchSet(..), SealedPatchSet, patchSetDrop )
import Darcs.Repository.Flags
    ( WithWorkingDir (WithWorkingDir) )
import Darcs.Repository.ApplyPatches ( DefaultIO, runDefault )
import Darcs.Repository.InternalTypes ( Repository )
import Darcs.Repository.Hashed ( readRepo )
import Darcs.Repository.Pristine ( createPristineDirectoryTree )
import Darcs.Util.Tree ( Tree )
import Darcs.Util.Path ( toFilePath )
getRecordedUpToMatch :: (ApplyMonad (ApplyState p) DefaultIO, IsRepoType rt, RepoPatch p, ApplyState p ~ Tree)
                     => Repository rt p wR wU wT
                     -> PatchSetMatch
                     -> IO ()
getRecordedUpToMatch r = withRecordedMatch r . rollbackToPatchSetMatch
getOnePatchset :: (IsRepoType rt, RepoPatch p)
               => Repository rt p wR wU wR
               -> PatchSetMatch
               -> IO (SealedPatchSet rt p Origin)
getOnePatchset repository pm =
  case pm of
    IndexMatch n -> patchSetDrop (n-1) <$> readRepo repository
    PatchMatch m -> matchAPatchset m <$> readRepo repository
    TagMatch m -> getMatchingTag m <$> readRepo repository
    ContextMatch path -> do
      ref <- readRepo repository
      readContextFile ref (toFilePath path)
withRecordedMatch :: (IsRepoType rt, RepoPatch p)
                  => Repository rt p wR wU wT
                  -> (PatchSet rt p Origin wR -> DefaultIO ())
                  -> IO ()
withRecordedMatch r job
    = do createPristineDirectoryTree r "." WithWorkingDir
         readRepo r >>= runDefault . job