| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Lorentz.UStore.Migration.Diff
Synopsis
- type FieldInfo = (Symbol, Type)
- data DiffKind
- type DiffItem = (DiffKind, FieldInfo)
- type BuildDiff oldTemplate newTemplate = LiftToDiff 'ToAdd (LinearizeUStore newTemplate // LinearizeUStore oldTemplate) ++ LiftToDiff 'ToDel (LinearizeUStore oldTemplate // LinearizeUStore newTemplate)
- type ShowDiff diff = 'Text "Migration is incomplete, remaining diff:" :$$: ShowDiffItems diff
- type family RequireEmptyDiff (diff :: [DiffItem]) :: Constraint where ...
- type LinearizeUStore a = GLinearizeUStore (Rep a)
- data LinearizeUStoreF (template :: Type) :: Exp [FieldInfo]
- type family AllUStoreFieldsF (template :: Type) :: Exp [Symbol] where ...
- data DiffCoverage
- type family CoverDiff (cover :: DiffCoverage) (field :: Symbol) (diff :: [DiffItem]) :: (Type, [DiffItem]) where ...
- type family CoverDiffMany (diff :: [DiffItem]) (covers :: [DiffCoverageItem]) :: [DiffItem] where ...
Documentation
What should happen with a particular UStoreItem.
Instances
| (RequireEmptyDiff d1, t1 ~ t2) => MigrationFinishCheckPosition (MigrationBlocks o n d1 t1 ('[] :: [DiffItem]) t2) Source # | This version can be used in |
Defined in Lorentz.UStore.Migration.Blocks Methods migrationFinish :: MigrationBlocks o n d1 t1 '[] t2 Source # | |
type BuildDiff oldTemplate newTemplate = LiftToDiff 'ToAdd (LinearizeUStore newTemplate // LinearizeUStore oldTemplate) ++ LiftToDiff 'ToDel (LinearizeUStore oldTemplate // LinearizeUStore newTemplate) Source #
Make up a migration diff between given old and new UStore templates.
type ShowDiff diff = 'Text "Migration is incomplete, remaining diff:" :$$: ShowDiffItems diff Source #
Renders human-readable message describing given diff.
type family RequireEmptyDiff (diff :: [DiffItem]) :: Constraint where ... Source #
Helper type family which dumps error message about remaining diff if such is present.
Equations
| RequireEmptyDiff '[] = () | |
| RequireEmptyDiff diff = TypeError (ShowDiff diff) |
type LinearizeUStore a = GLinearizeUStore (Rep a) Source #
Get information about all fields of UStore template in a list.
In particular, this recursivelly traverses template and retrives
names and types of fields. Semantic wrappers like UStoreField
and |~> in field types are returned as-is.
data LinearizeUStoreF (template :: Type) :: Exp [FieldInfo] Source #
Instances
| type Eval (LinearizeUStoreF template :: [FieldInfo] -> Type) Source # | |
Defined in Lorentz.UStore.Migration.Diff | |
type family AllUStoreFieldsF (template :: Type) :: Exp [Symbol] where ... Source #
Get only field names of UStore template.
Equations
| AllUStoreFieldsF template = Map Fst =<< LinearizeUStoreF template |
data DiffCoverage Source #
Cover the respective part of diff. Maybe fail if such action is not required.
This type is very similar to DiffKind, but we still use another type as
1. Their kinds will differ - no chance to mix up anything.
2. One day there might appear more complex actions.
type family CoverDiff (cover :: DiffCoverage) (field :: Symbol) (diff :: [DiffItem]) :: (Type, [DiffItem]) where ... Source #
Apply given diff coverage, returning type of affected field and modified diff.
type family CoverDiffMany (diff :: [DiffItem]) (covers :: [DiffCoverageItem]) :: [DiffItem] where ... Source #
Apply multiple coverage steps.
Equations
| CoverDiffMany diff '[] = diff | |
| CoverDiffMany diff ('(dc, '(field, ty)) ': cs) = CoverDiffMany (HandleCoverRes field ty (CoverDiff dc field diff)) cs |