-- Copyright (C) 2003 David Roundy -- -- This program is free software; you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation; either version 2, or (at your option) -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program; see the file COPYING. If not, write to -- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, -- Boston, MA 02110-1301, USA. {-# LANGUAGE EmptyDataDecls, StandaloneDeriving #-} module Darcs.Patch.Set ( PatchSet(..) , Tagged(..) , SealedPatchSet , Origin , progressPatchSet , tags , emptyPatchSet , appendPSFL , patchSet2RL , patchSet2FL , patchSetfMap ) where import Prelude () import Darcs.Prelude import Darcs.Patch.Info ( PatchInfo ) import Darcs.Patch.PatchInfoAnd ( PatchInfoAnd, info ) import Darcs.Patch.Witnesses.Sealed ( Sealed ) import Darcs.Patch.Witnesses.Ordered ( FL, RL(..), (+<+), reverseFL, reverseRL, mapRL_RL, concatRL, mapRL ) import Darcs.Patch.Witnesses.Show ( Show1(..), Show2(..), ShowDict(ShowDictClass) ) import Darcs.Util.Progress ( progress ) -- |'Origin' is a type used to represent the initial context of a repo. data Origin type SealedPatchSet rt p wStart = Sealed ((PatchSet rt p) wStart) -- |The patches in a repository are stored in chunks broken up at \"clean\" -- tags. A tag is clean if the only patches before it in the current -- repository ordering are ones that the tag depends on (either directly -- or indirectly). Each chunk is stored in a separate inventory file on disk. -- -- A 'PatchSet' represents a repo's history as the list of patches since the -- last clean tag, and then a list of patch lists each delimited by clean tags. data PatchSet rt p wStart wY where PatchSet :: RL (Tagged rt p) wStart wX -> RL (PatchInfoAnd rt p) wX wY -> PatchSet rt p wStart wY deriving instance Show2 p => Show (PatchSet rt p wStart wY) instance Show2 p => Show1 (PatchSet rt p wStart) where showDict1 = ShowDictClass instance Show2 p => Show2 (PatchSet rt p) where showDict2 = ShowDictClass emptyPatchSet :: PatchSet rt p wX wX emptyPatchSet = PatchSet NilRL NilRL -- |A 'Tagged' is a single chunk of a 'PatchSet'. -- It has a 'PatchInfo' representing a clean tag, -- the hash of the previous inventory (if it exists), -- and the list of patches since that previous inventory. data Tagged rt p wX wZ where Tagged :: PatchInfoAnd rt p wY wZ -> Maybe String -> RL (PatchInfoAnd rt p) wX wY -> Tagged rt p wX wZ deriving instance Show2 p => Show (Tagged rt p wX wZ) instance Show2 p => Show1 (Tagged rt p wX) where showDict1 = ShowDictClass instance Show2 p => Show2 (Tagged rt p) where showDict2 = ShowDictClass -- |'patchSet2RL' takes a 'PatchSet' and returns an equivalent, linear 'RL' of -- patches. patchSet2RL :: PatchSet rt p wStart wX -> RL (PatchInfoAnd rt p) wStart wX patchSet2RL (PatchSet ts ps) = concatRL (mapRL_RL ts2rl ts) +<+ ps where ts2rl :: Tagged rt p wY wZ -> RL (PatchInfoAnd rt p) wY wZ ts2rl (Tagged t _ ps2) = ps2 :<: t -- |'patchSet2FL' takes a 'PatchSet' and returns an equivalent, linear 'FL' of -- patches. patchSet2FL :: PatchSet rt p wStart wX -> FL (PatchInfoAnd rt p) wStart wX patchSet2FL = reverseRL . patchSet2RL -- |'appendPSFL' takes a 'PatchSet' and a 'FL' of patches that "follow" the -- PatchSet, and concatenates the patches into the PatchSet. appendPSFL :: PatchSet rt p wStart wX -> FL (PatchInfoAnd rt p) wX wY -> PatchSet rt p wStart wY appendPSFL (PatchSet ts ps) newps = PatchSet ts (ps +<+ reverseFL newps) -- |Runs a progress action for each tag and patch in a given PatchSet, using -- the passed progress message. Does not alter the PatchSet. progressPatchSet :: String -> PatchSet rt p wStart wX -> PatchSet rt p wStart wX progressPatchSet k (PatchSet ts ps) = PatchSet (mapRL_RL progressTagged ts) (mapRL_RL prog ps) where prog = progress k progressTagged :: Tagged rt p wY wZ -> Tagged rt p wY wZ progressTagged (Tagged t h tps) = Tagged (prog t) h (mapRL_RL prog tps) -- |'tags' returns the PatchInfos corresponding to the tags of a given -- 'PatchSet'. tags :: PatchSet rt p wStart wX -> [PatchInfo] tags (PatchSet ts _) = mapRL taggedTagInfo ts where taggedTagInfo :: Tagged rt p wY wZ -> PatchInfo taggedTagInfo (Tagged t _ _) = info t patchSetfMap:: (forall wW wZ . PatchInfoAnd rt p wW wZ -> IO a) -> PatchSet rt p wW' wZ' -> IO [a] patchSetfMap f = sequence . mapRL f . patchSet2RL