| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Darcs.Patch.Rebase
- data Rebasing p wX wY where
- data RebaseItem p wX wY where- ToEdit :: Named p wX wY -> RebaseItem p wX wY
- Fixup :: RebaseFixup p wX wY -> RebaseItem p wX wY
 
- data RebaseName p wX wY where- AddName :: PatchInfo -> RebaseName p wX wY
- DelName :: PatchInfo -> RebaseName p wX wY
- Rename :: PatchInfo -> PatchInfo -> RebaseName p wX wY
 
- data RebaseFixup p wX wY where- PrimFixup :: PrimOf p wX wY -> RebaseFixup p wX wY
- NameFixup :: RebaseName p wX wY -> RebaseFixup p wX wY
 
- simplifyPush :: (PrimPatchBase p, Commute p, FromPrim p, Effect p) => DiffAlgorithm -> RebaseFixup p wX wY -> FL (RebaseItem p) wY wZ -> Sealed (FL (RebaseItem p) wX)
- simplifyPushes :: (PrimPatchBase p, Commute p, FromPrim p, Effect p) => DiffAlgorithm -> FL (RebaseFixup p) wX wY -> FL (RebaseItem p) wY wZ -> Sealed (FL (RebaseItem p) wX)
- mkSuspended :: FL (RebaseItem p) wX wY -> IO (Named (Rebasing p) wX wX)
- takeHeadRebase :: PatchSet (Rebasing p) wA wB -> (PatchInfoAnd (Rebasing p) wB wB, Sealed (FL (RebaseItem p) wB), PatchSet (Rebasing p) wA wB)
- takeHeadRebaseFL :: FL (PatchInfoAnd (Rebasing p)) wA wB -> (PatchInfoAnd (Rebasing p) wB wB, Sealed (FL (RebaseItem p) wB), FL (PatchInfoAnd (Rebasing p)) wA wB)
- takeHeadRebaseRL :: RL (PatchInfoAnd (Rebasing p)) wA wB -> (PatchInfoAnd (Rebasing p) wB wB, Sealed (FL (RebaseItem p) wB), RL (PatchInfoAnd (Rebasing p)) wA wB)
- takeAnyRebase :: PatchSet (Rebasing p) wA wB -> (Sealed2 (PatchInfoAnd (Rebasing p)), Sealed2 (FL (RebaseItem p)))
- takeAnyRebaseAndTrailingPatches :: PatchSet (Rebasing p) wA wB -> FlippedSeal (PatchInfoAnd (Rebasing p) :> RL (PatchInfoAnd (Rebasing p))) wB
- countToEdit :: FL (RebaseItem p) wX wY -> Int
Documentation
data Rebasing p wX wY where Source
A patch that lives in a repository where a rebase is in
 progress. Such a repository will consist of Normal patches
 along with exactly one Suspended patch.
Most rebase operations will require the Suspended patch
 to be at the end of the repository.
Normal represents a normal patch within a respository where a
 rebase is in progress. Normal p is given the same on-disk
 representation as p, so a repository can be switched into
 and out of rebasing mode simply by adding or removing a
 Suspended patch and setting the appropriate format flag.
The single Suspended patch contains the entire rebase
 state, in the form of RebaseItems.
Note that the witnesses are such that the Suspended
 patch has no effect on the context of the rest of the
 repository; in a sense the patches within it are
 dangling off to one side from the main repository.
See Note [Rebase representation] in the source for a discussion of the design choice to embed the rebase state in a single patch.
Constructors
| Normal :: p wX wY -> Rebasing p wX wY | |
| Suspended :: FL (RebaseItem p) wX wY -> Rebasing p wX wX | 
Instances
data RebaseItem p wX wY where Source
A single item in the rebase state consists of either a patch that is being edited, or a fixup that adjusts the context so that a subsequent patch that is being edited "makes sense".
ToEdit holds a patch that is being edited. The name (PatchInfo) of
 the patch will typically be the name the patch had before
 it was added to the rebase state; if it is moved back
 into the repository it must be given a fresh name to account
 for the fact that it will not necessarily have the same
 dependencies as the original patch. This is typically
 done by changing the Ignore-This junk.
Fixup adjusts the context so that a subsequent ToEdit patch
 is correct. Where possible, Fixup changes are commuted
 as far as possible into the rebase state, so any remaining
 ones will typically cause a conflict when the ToEdit patch
 is moved back into the repository.
Constructors
| ToEdit :: Named p wX wY -> RebaseItem p wX wY | |
| Fixup :: RebaseFixup p wX wY -> RebaseItem p wX wY | 
Instances
| (Show2 p, Show2 (PrimOf p)) => Show2 (RebaseItem p) Source | |
| (PrimPatchBase p, PatchListFormat p, ReadPatch p) => ReadPatch (RebaseItem p) Source | |
| Check p => Check (RebaseItem p) Source | |
| (PrimPatchBase p, PatchListFormat p, Apply p, CommuteNoConflicts p, Conflict p, IsHunk p, ShowPatch p) => ShowPatch (RebaseItem p) Source | |
| (PrimPatchBase p, PatchListFormat p, ShowPatchBasic p) => ShowPatchBasic (RebaseItem p) Source | |
| (Show2 p, Show2 (PrimOf p)) => Show1 (RebaseItem p wX) Source | |
| (Show2 p, Show2 (PrimOf p)) => Show (RebaseItem p wX wY) Source | 
data RebaseName p wX wY where Source
A RebaseName encapsulates the concept of the name of a patch,
 without any contents. This allows us to track explicit dependencies
 in the rebase state, changing them to follow uses of amend-record
 or unsuspend on a depended-on patch, and warning the user if any
 are lost entirely.
Constructors
| AddName :: PatchInfo -> RebaseName p wX wY | |
| DelName :: PatchInfo -> RebaseName p wX wY | |
| Rename :: PatchInfo -> PatchInfo -> RebaseName p wX wY | 
Instances
| Show2 (RebaseName p) Source | |
| MyEq (RebaseName p) Source | |
| PatchInspect (RebaseName p) Source | |
| ReadPatch (RebaseName p) Source | |
| Invert (RebaseName p) Source | |
| Commute (RebaseName p) Source | |
| Apply p => Apply (RebaseName p) Source | |
| ShowPatch (RebaseName p) Source | |
| ShowPatchBasic (RebaseName p) Source | |
| Apply p => Patchy (RebaseName p) Source | |
| PrimPatchBase p => PrimPatchBase (RebaseName p) Source | |
| Effect (RebaseName p) Source | |
| Show1 (RebaseName p wX) Source | |
| Show (RebaseName p wX wY) Source | |
| type ApplyState (RebaseName p) = ApplyState p Source | |
| type PrimOf (RebaseName p) = PrimOf p Source | 
data RebaseFixup p wX wY where Source
A single rebase fixup, needed to ensure that the actual patches being stored in the rebase state have the correct context.
Constructors
| PrimFixup :: PrimOf p wX wY -> RebaseFixup p wX wY | |
| NameFixup :: RebaseName p wX wY -> RebaseFixup p wX wY | 
Instances
| Show2 (PrimOf p) => Show2 (RebaseFixup p) Source | |
| MyEq (PrimOf p) => MyEq (RebaseFixup p) Source | |
| PatchInspect (PrimOf p) => PatchInspect (RebaseFixup p) Source | |
| Invert (PrimOf p) => Invert (RebaseFixup p) Source | |
| PrimPatchBase p => Commute (RebaseFixup p) Source | |
| (PrimPatchBase p, Apply p, (~) ((* -> *) -> *) (ApplyState p) (ApplyState (PrimOf p))) => Apply (RebaseFixup p) Source | |
| PrimPatchBase p => PrimPatchBase (RebaseFixup p) Source | |
| Effect (RebaseFixup p) Source | |
| Show2 (PrimOf p) => Show1 (RebaseFixup p wX) Source | |
| Show2 (PrimOf p) => Show (RebaseFixup p wX wY) Source | |
| type ApplyState (RebaseFixup p) = ApplyState p Source | |
| type PrimOf (RebaseFixup p) = PrimOf p Source | 
simplifyPush :: (PrimPatchBase p, Commute p, FromPrim p, Effect p) => DiffAlgorithm -> RebaseFixup p wX wY -> FL (RebaseItem p) wY wZ -> Sealed (FL (RebaseItem p) wX) Source
Given a list of rebase items, try to push a new fixup as far as possible into
 the list as possible, using both commutation and coalescing. If the fixup
 commutes past all the ToEdit patches then it is dropped entirely.
simplifyPushes :: (PrimPatchBase p, Commute p, FromPrim p, Effect p) => DiffAlgorithm -> FL (RebaseFixup p) wX wY -> FL (RebaseItem p) wY wZ -> Sealed (FL (RebaseItem p) wX) Source
Like simplifyPush but for a list of fixups.
mkSuspended :: FL (RebaseItem p) wX wY -> IO (Named (Rebasing p) wX wX) Source
takeHeadRebase :: PatchSet (Rebasing p) wA wB -> (PatchInfoAnd (Rebasing p) wB wB, Sealed (FL (RebaseItem p) wB), PatchSet (Rebasing p) wA wB) Source
given the repository contents, get the rebase container patch, its contents, and the rest of the repository contents. The rebase patch must be at the head of the repository.
takeHeadRebaseFL :: FL (PatchInfoAnd (Rebasing p)) wA wB -> (PatchInfoAnd (Rebasing p) wB wB, Sealed (FL (RebaseItem p) wB), FL (PatchInfoAnd (Rebasing p)) wA wB) Source
takeHeadRebaseRL :: RL (PatchInfoAnd (Rebasing p)) wA wB -> (PatchInfoAnd (Rebasing p) wB wB, Sealed (FL (RebaseItem p) wB), RL (PatchInfoAnd (Rebasing p)) wA wB) Source
takeAnyRebase :: PatchSet (Rebasing p) wA wB -> (Sealed2 (PatchInfoAnd (Rebasing p)), Sealed2 (FL (RebaseItem p))) Source
given the repository contents, get the rebase container patch, and its contents The rebase patch can be anywhere in the repository and is returned without being commuted to the end.
takeAnyRebaseAndTrailingPatches :: PatchSet (Rebasing p) wA wB -> FlippedSeal (PatchInfoAnd (Rebasing p) :> RL (PatchInfoAnd (Rebasing p))) wB Source
given the repository contents, get the rebase container patch, its contents, and the rest of the repository contents. Commutes the patch to the end of the repository if necessary. The rebase patch must be at the head of the repository.
countToEdit :: FL (RebaseItem p) wX wY -> Int Source