darcs-2.16.1: a distributed, interactive, smart revision control system

Safe HaskellNone
LanguageHaskell2010

Darcs.Patch.FromPrim

Documentation

class PrimPatch (PrimOf p) => PrimPatchBase p Source #

Associated Types

type PrimOf (p :: * -> * -> *) :: * -> * -> * Source #

Instances
PrimPatchBase p => PrimPatchBase (RL p) Source # 
Instance details

Defined in Darcs.Patch.FromPrim

Associated Types

type PrimOf (RL p) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (FL p) Source # 
Instance details

Defined in Darcs.Patch.FromPrim

Associated Types

type PrimOf (FL p) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RepoPatchV1 prim) Source # 
Instance details

Defined in Darcs.Patch.V1.Core

Associated Types

type PrimOf (RepoPatchV1 prim) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Associated Types

type PrimOf (RepoPatchV2 prim) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (Named p) Source # 
Instance details

Defined in Darcs.Patch.Named

Associated Types

type PrimOf (Named p) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RebaseFixup prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Fixup

Associated Types

type PrimOf (RebaseFixup prim) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (WithDroppedDeps p) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Associated Types

type PrimOf (WithDroppedDeps p) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RebaseChange prim) Source # 
Instance details

Defined in Darcs.Patch.Rebase.Change

Associated Types

type PrimOf (RebaseChange prim) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (Invertible p) Source # 
Instance details

Defined in Darcs.Patch.Invertible

Associated Types

type PrimOf (Invertible p) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (PatchInfoAndG rt p) Source # 
Instance details

Defined in Darcs.Patch.PatchInfoAnd

Associated Types

type PrimOf (PatchInfoAndG rt p) :: Type -> Type -> Type Source #

PrimPatchBase p => PrimPatchBase (WrappedNamed rt p) Source # 
Instance details

Defined in Darcs.Patch.Named.Wrapped

Associated Types

type PrimOf (WrappedNamed rt p) :: Type -> Type -> Type Source #

PrimPatch prim => PrimPatchBase (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Associated Types

type PrimOf (RepoPatchV3 name prim) :: Type -> Type -> Type Source #

class FromPrim p where Source #

Minimal complete definition

fromAnonymousPrim

Methods

fromAnonymousPrim :: PrimOf p wX wY -> p wX wY Source #

fromPrim :: PatchId p -> PrimOf p wX wY -> p wX wY Source #

fromPrims :: PatchInfo -> FL (PrimOf p) wX wY -> FL p wX wY Source #

fromPrim :: PatchId p ~ () => PatchId p -> PrimOf p wX wY -> p wX wY Source #

fromPrims :: PatchId p ~ () => PatchInfo -> FL (PrimOf p) wX wY -> FL p wX wY Source #

Instances
FromPrim (RepoPatchV1 prim) Source # 
Instance details

Defined in Darcs.Patch.V1.Core

Methods

fromAnonymousPrim :: PrimOf (RepoPatchV1 prim) wX wY -> RepoPatchV1 prim wX wY Source #

fromPrim :: PatchId (RepoPatchV1 prim) -> PrimOf (RepoPatchV1 prim) wX wY -> RepoPatchV1 prim wX wY Source #

fromPrims :: PatchInfo -> FL (PrimOf (RepoPatchV1 prim)) wX wY -> FL (RepoPatchV1 prim) wX wY Source #

FromPrim (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

fromAnonymousPrim :: PrimOf (RepoPatchV2 prim) wX wY -> RepoPatchV2 prim wX wY Source #

fromPrim :: PatchId (RepoPatchV2 prim) -> PrimOf (RepoPatchV2 prim) wX wY -> RepoPatchV2 prim wX wY Source #

fromPrims :: PatchInfo -> FL (PrimOf (RepoPatchV2 prim)) wX wY -> FL (RepoPatchV2 prim) wX wY Source #

FromPrim (RepoPatchV3 prim) Source # 
Instance details

Defined in Darcs.Patch.V3

Methods

fromAnonymousPrim :: PrimOf (RepoPatchV3 prim) wX wY -> RepoPatchV3 prim wX wY Source #

fromPrim :: PatchId (RepoPatchV3 prim) -> PrimOf (RepoPatchV3 prim) wX wY -> RepoPatchV3 prim wX wY Source #

fromPrims :: PatchInfo -> FL (PrimOf (RepoPatchV3 prim)) wX wY -> FL (RepoPatchV3 prim) wX wY Source #

class ToPrim p where Source #

Methods

toPrim :: p wX wY -> Maybe (PrimOf p wX wY) Source #

Instances
ToPrim (RepoPatchV1 prim) Source # 
Instance details

Defined in Darcs.Patch.V1.Core

Methods

toPrim :: RepoPatchV1 prim wX wY -> Maybe (PrimOf (RepoPatchV1 prim) wX wY) Source #

ToPrim (RepoPatchV2 prim) Source # 
Instance details

Defined in Darcs.Patch.V2.RepoPatch

Methods

toPrim :: RepoPatchV2 prim wX wY -> Maybe (PrimOf (RepoPatchV2 prim) wX wY) Source #

ToPrim (RepoPatchV3 name prim) Source # 
Instance details

Defined in Darcs.Patch.V3.Core

Methods

toPrim :: RepoPatchV3 name prim wX wY -> Maybe (PrimOf (RepoPatchV3 name prim) wX wY) Source #