{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
module U.Codebase.Sqlite.LocalizeObject
( localizeBranch,
localizeBranchG,
localizePatch,
localizePatchG,
)
where
import Control.Lens
import Control.Monad.State.Strict
import Control.Monad.Trans.State.Strict qualified as State
import Data.Bitraversable (bitraverse)
import Data.Generics.Product (HasField (..))
import Data.Map.Strict qualified as Map
import U.Codebase.Reference (Reference')
import U.Codebase.Referent (Referent')
import U.Codebase.Sqlite.Branch.Format (BranchLocalIds)
import U.Codebase.Sqlite.Branch.Format qualified as Branch
import U.Codebase.Sqlite.Branch.Full (Branch' (..), DbBranch, LocalBranch)
import U.Codebase.Sqlite.Branch.Full qualified as Branch
import U.Codebase.Sqlite.LocalIds
( LocalBranchChildId (..),
LocalDefnId (..),
LocalHashId (..),
LocalPatchObjectId (..),
LocalTextId (..),
)
import U.Codebase.Sqlite.Patch.Format (PatchLocalIds, PatchLocalIds')
import U.Codebase.Sqlite.Patch.Format qualified as Patch
import U.Codebase.Sqlite.Patch.Full (LocalPatch, Patch, Patch' (..))
import U.Codebase.Sqlite.Patch.TermEdit (LocalTermEdit, TermEdit')
import U.Codebase.Sqlite.Patch.TypeEdit (LocalTypeEdit, TypeEdit')
import U.Codebase.Sqlite.Reference (LocalReference, LocalReferenceH)
import U.Codebase.Sqlite.Referent (LocalReferent, LocalReferentH)
import Unison.Prelude
import Unison.Util.Map qualified as Map
import Unison.Util.Set qualified as Set
localizeBranch :: DbBranch -> (BranchLocalIds, LocalBranch)
localizeBranch :: DbBranch -> (BranchLocalIds, LocalBranch)
localizeBranch = DbBranch -> (BranchLocalIds, LocalBranch)
forall t d p c.
(Ord t, Ord d, Ord p, Ord c) =>
Branch' t d p c -> (BranchLocalIds' t d p c, LocalBranch)
localizeBranchG
localizeBranchG :: forall t d p c. (Ord t, Ord d, Ord p, Ord c) => Branch' t d p c -> (Branch.BranchLocalIds' t d p c, LocalBranch)
localizeBranchG :: forall t d p c.
(Ord t, Ord d, Ord p, Ord c) =>
Branch' t d p c -> (BranchLocalIds' t d p c, LocalBranch)
localizeBranchG (Branch Map t (Map (Referent'' t d) (MetadataSetFormat' t d))
terms Map t (Map (TypeReference' t d) (MetadataSetFormat' t d))
types Map t p
patches Map t c
children) =
(Identity (BranchLocalIds' t d p c, LocalBranch)
-> (BranchLocalIds' t d p c, LocalBranch)
forall a. Identity a -> a
runIdentity (Identity (BranchLocalIds' t d p c, LocalBranch)
-> (BranchLocalIds' t d p c, LocalBranch))
-> (StateT (LocalizeBranchState t d p c) Identity LocalBranch
-> Identity (BranchLocalIds' t d p c, LocalBranch))
-> StateT (LocalizeBranchState t d p c) Identity LocalBranch
-> (BranchLocalIds' t d p c, LocalBranch)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT (LocalizeBranchState t d p c) Identity LocalBranch
-> Identity (BranchLocalIds' t d p c, LocalBranch)
forall (m :: * -> *) t d p c a.
(Monad m, Ord t, Ord d, Ord p, Ord c) =>
StateT (LocalizeBranchState t d p c) m a
-> m (BranchLocalIds' t d p c, a)
runLocalizeBranch) do
Map
LocalTextId
(Map
(Referent'' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map
LocalTextId
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map LocalTextId LocalPatchObjectId
-> Map LocalTextId LocalBranchChildId
-> LocalBranch
forall t h p c.
Map t (Map (Referent'' t h) (MetadataSetFormat' t h))
-> Map t (Map (TypeReference' t h) (MetadataSetFormat' t h))
-> Map t p
-> Map t c
-> Branch' t h p c
Branch
(Map
LocalTextId
(Map
(Referent'' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map
LocalTextId
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map LocalTextId LocalPatchObjectId
-> Map LocalTextId LocalBranchChildId
-> LocalBranch)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
LocalTextId
(Map
(Referent'' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId)))
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
LocalTextId
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map LocalTextId LocalPatchObjectId
-> Map LocalTextId LocalBranchChildId
-> LocalBranch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId)
-> (Map (Referent'' t d) (MetadataSetFormat' t d)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
(Referent'' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId)))
-> Map t (Map (Referent'' t d) (MetadataSetFormat' t d))
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
LocalTextId
(Map
(Referent'' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId)))
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText ((Referent'' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(Referent'' LocalTextId LocalDefnId))
-> (MetadataSetFormat' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map (Referent'' t d) (MetadataSetFormat' t d)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
(Referent'' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse Referent'' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(Referent'' LocalTextId LocalDefnId)
forall d t s (m :: * -> *).
(ContainsDefns d s, ContainsText t s, Monad m) =>
Referent' (Reference' t d) (Reference' t d)
-> StateT s m (Referent'' LocalTextId LocalDefnId)
localizeReferent MetadataSetFormat' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(MetadataSetFormat' LocalTextId LocalDefnId)
localizeBranchMetadata) Map t (Map (Referent'' t d) (MetadataSetFormat' t d))
terms
StateT
(LocalizeBranchState t d p c)
Identity
(Map
LocalTextId
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map LocalTextId LocalPatchObjectId
-> Map LocalTextId LocalBranchChildId
-> LocalBranch)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
LocalTextId
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId)))
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalPatchObjectId
-> Map LocalTextId LocalBranchChildId -> LocalBranch)
forall a b.
StateT (LocalizeBranchState t d p c) Identity (a -> b)
-> StateT (LocalizeBranchState t d p c) Identity a
-> StateT (LocalizeBranchState t d p c) Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId)
-> (Map (TypeReference' t d) (MetadataSetFormat' t d)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId)))
-> Map t (Map (TypeReference' t d) (MetadataSetFormat' t d))
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
LocalTextId
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId)))
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText ((TypeReference' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(Reference' LocalTextId LocalDefnId))
-> (MetadataSetFormat' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(MetadataSetFormat' LocalTextId LocalDefnId))
-> Map (TypeReference' t d) (MetadataSetFormat' t d)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map
(Reference' LocalTextId LocalDefnId)
(MetadataSetFormat' LocalTextId LocalDefnId))
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse TypeReference' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(Reference' LocalTextId LocalDefnId)
forall d s t (m :: * -> *).
(ContainsDefns d s, ContainsText t s, Monad m) =>
Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId)
localizeReference MetadataSetFormat' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(MetadataSetFormat' LocalTextId LocalDefnId)
localizeBranchMetadata) Map t (Map (TypeReference' t d) (MetadataSetFormat' t d))
types
StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalPatchObjectId
-> Map LocalTextId LocalBranchChildId -> LocalBranch)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalPatchObjectId)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalBranchChildId -> LocalBranch)
forall a b.
StateT (LocalizeBranchState t d p c) Identity (a -> b)
-> StateT (LocalizeBranchState t d p c) Identity a
-> StateT (LocalizeBranchState t d p c) Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId)
-> (p
-> StateT
(LocalizeBranchState t d p c) Identity LocalPatchObjectId)
-> Map t p
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalPatchObjectId)
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText p
-> StateT (LocalizeBranchState t d p c) Identity LocalPatchObjectId
forall p s (m :: * -> *).
(ContainsPatches p s, Monad m) =>
p -> StateT s m LocalPatchObjectId
localizePatchReference Map t p
patches
StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalBranchChildId -> LocalBranch)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalBranchChildId)
-> StateT (LocalizeBranchState t d p c) Identity LocalBranch
forall a b.
StateT (LocalizeBranchState t d p c) Identity (a -> b)
-> StateT (LocalizeBranchState t d p c) Identity a
-> StateT (LocalizeBranchState t d p c) Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId)
-> (c
-> StateT
(LocalizeBranchState t d p c) Identity LocalBranchChildId)
-> Map t c
-> StateT
(LocalizeBranchState t d p c)
Identity
(Map LocalTextId LocalBranchChildId)
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse t -> StateT (LocalizeBranchState t d p c) Identity LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText c
-> StateT (LocalizeBranchState t d p c) Identity LocalBranchChildId
forall c s (m :: * -> *).
(ContainsBranches c s, Monad m) =>
c -> StateT s m LocalBranchChildId
localizeBranchReference Map t c
children
where
localizeBranchMetadata ::
Branch.MetadataSetFormat' t d ->
State (LocalizeBranchState t d p c) (Branch.MetadataSetFormat' LocalTextId LocalDefnId)
localizeBranchMetadata :: MetadataSetFormat' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(MetadataSetFormat' LocalTextId LocalDefnId)
localizeBranchMetadata (Branch.Inline Set (TypeReference' t d)
refs) =
Set (Reference' LocalTextId LocalDefnId)
-> MetadataSetFormat' LocalTextId LocalDefnId
forall t h. Set (Reference' t h) -> MetadataSetFormat' t h
Branch.Inline (Set (Reference' LocalTextId LocalDefnId)
-> MetadataSetFormat' LocalTextId LocalDefnId)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Set (Reference' LocalTextId LocalDefnId))
-> StateT
(LocalizeBranchState t d p c)
Identity
(MetadataSetFormat' LocalTextId LocalDefnId)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (TypeReference' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(Reference' LocalTextId LocalDefnId))
-> Set (TypeReference' t d)
-> StateT
(LocalizeBranchState t d p c)
Identity
(Set (Reference' LocalTextId LocalDefnId))
forall (f :: * -> *) b a.
(Applicative f, Ord b) =>
(a -> f b) -> Set a -> f (Set b)
Set.traverse TypeReference' t d
-> StateT
(LocalizeBranchState t d p c)
Identity
(Reference' LocalTextId LocalDefnId)
forall d s t (m :: * -> *).
(ContainsDefns d s, ContainsText t s, Monad m) =>
Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId)
localizeReference Set (TypeReference' t d)
refs
localizePatch :: Patch -> (PatchLocalIds, LocalPatch)
localizePatch :: Patch -> (PatchLocalIds, LocalPatch)
localizePatch = Patch -> (PatchLocalIds, LocalPatch)
forall t h d.
(Ord t, Ord h, Ord d) =>
Patch' t h d -> (PatchLocalIds' t h d, LocalPatch)
localizePatchG
localizePatchG :: forall t h d. (Ord t, Ord h, Ord d) => Patch' t h d -> (PatchLocalIds' t h d, LocalPatch)
localizePatchG :: forall t h d.
(Ord t, Ord h, Ord d) =>
Patch' t h d -> (PatchLocalIds' t h d, LocalPatch)
localizePatchG (Patch Map (Referent'' t h) (Set (TermEdit' t d))
termEdits Map (Reference' t h) (Set (TypeEdit' t d))
typeEdits) =
(Identity (PatchLocalIds' t h d, LocalPatch)
-> (PatchLocalIds' t h d, LocalPatch)
forall a. Identity a -> a
runIdentity (Identity (PatchLocalIds' t h d, LocalPatch)
-> (PatchLocalIds' t h d, LocalPatch))
-> (StateT (LocalizePatchState t h d) Identity LocalPatch
-> Identity (PatchLocalIds' t h d, LocalPatch))
-> StateT (LocalizePatchState t h d) Identity LocalPatch
-> (PatchLocalIds' t h d, LocalPatch)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT (LocalizePatchState t h d) Identity LocalPatch
-> Identity (PatchLocalIds' t h d, LocalPatch)
forall t h d a (m :: * -> *).
(Monad m, Ord t, Ord h, Ord d) =>
StateT (LocalizePatchState t h d) m a
-> m (PatchLocalIds' t h d, a)
runLocalizePatch) do
Map
(Referent'' LocalTextId LocalHashId)
(Set (TermEdit' LocalTextId LocalDefnId))
-> Map
(Reference' LocalTextId LocalHashId)
(Set (TypeEdit' LocalTextId LocalDefnId))
-> LocalPatch
forall t h o.
Map (Referent'' t h) (Set (TermEdit' t o))
-> Map (Reference' t h) (Set (TypeEdit' t o)) -> Patch' t h o
Patch
(Map
(Referent'' LocalTextId LocalHashId)
(Set (TermEdit' LocalTextId LocalDefnId))
-> Map
(Reference' LocalTextId LocalHashId)
(Set (TypeEdit' LocalTextId LocalDefnId))
-> LocalPatch)
-> StateT
(LocalizePatchState t h d)
Identity
(Map
(Referent'' LocalTextId LocalHashId)
(Set (TermEdit' LocalTextId LocalDefnId)))
-> StateT
(LocalizePatchState t h d)
Identity
(Map
(Reference' LocalTextId LocalHashId)
(Set (TypeEdit' LocalTextId LocalDefnId))
-> LocalPatch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Referent'' t h
-> StateT
(LocalizePatchState t h d)
Identity
(Referent'' LocalTextId LocalHashId))
-> (Set (TermEdit' t d)
-> StateT
(LocalizePatchState t h d)
Identity
(Set (TermEdit' LocalTextId LocalDefnId)))
-> Map (Referent'' t h) (Set (TermEdit' t d))
-> StateT
(LocalizePatchState t h d)
Identity
(Map
(Referent'' LocalTextId LocalHashId)
(Set (TermEdit' LocalTextId LocalDefnId)))
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse Referent'' t h
-> StateT
(LocalizePatchState t h d)
Identity
(Referent'' LocalTextId LocalHashId)
forall h s t (m :: * -> *) r.
(ContainsHashes h s, ContainsText t s, Monad m,
r ~ Reference' t h) =>
Referent' r r -> StateT s m (Referent'' LocalTextId LocalHashId)
localizeReferentH ((TermEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TermEdit' LocalTextId LocalDefnId))
-> Set (TermEdit' t d)
-> StateT
(LocalizePatchState t h d)
Identity
(Set (TermEdit' LocalTextId LocalDefnId))
forall (f :: * -> *) b a.
(Applicative f, Ord b) =>
(a -> f b) -> Set a -> f (Set b)
Set.traverse TermEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TermEdit' LocalTextId LocalDefnId)
localizeTermEdit) Map (Referent'' t h) (Set (TermEdit' t d))
termEdits
StateT
(LocalizePatchState t h d)
Identity
(Map
(Reference' LocalTextId LocalHashId)
(Set (TypeEdit' LocalTextId LocalDefnId))
-> LocalPatch)
-> StateT
(LocalizePatchState t h d)
Identity
(Map
(Reference' LocalTextId LocalHashId)
(Set (TypeEdit' LocalTextId LocalDefnId)))
-> StateT (LocalizePatchState t h d) Identity LocalPatch
forall a b.
StateT (LocalizePatchState t h d) Identity (a -> b)
-> StateT (LocalizePatchState t h d) Identity a
-> StateT (LocalizePatchState t h d) Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Reference' t h
-> StateT
(LocalizePatchState t h d)
Identity
(Reference' LocalTextId LocalHashId))
-> (Set (TypeEdit' t d)
-> StateT
(LocalizePatchState t h d)
Identity
(Set (TypeEdit' LocalTextId LocalDefnId)))
-> Map (Reference' t h) (Set (TypeEdit' t d))
-> StateT
(LocalizePatchState t h d)
Identity
(Map
(Reference' LocalTextId LocalHashId)
(Set (TypeEdit' LocalTextId LocalDefnId)))
forall (f :: * -> *) a' a b b'.
(Applicative f, Ord a') =>
(a -> f a') -> (b -> f b') -> Map a b -> f (Map a' b')
Map.bitraverse Reference' t h
-> StateT
(LocalizePatchState t h d)
Identity
(Reference' LocalTextId LocalHashId)
forall h s t (m :: * -> *).
(ContainsHashes h s, ContainsText t s, Monad m) =>
Reference' t h -> StateT s m (Reference' LocalTextId LocalHashId)
localizeReferenceH ((TypeEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TypeEdit' LocalTextId LocalDefnId))
-> Set (TypeEdit' t d)
-> StateT
(LocalizePatchState t h d)
Identity
(Set (TypeEdit' LocalTextId LocalDefnId))
forall (f :: * -> *) b a.
(Applicative f, Ord b) =>
(a -> f b) -> Set a -> f (Set b)
Set.traverse TypeEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TypeEdit' LocalTextId LocalDefnId)
localizeTypeEdit) Map (Reference' t h) (Set (TypeEdit' t d))
typeEdits
where
localizeTermEdit :: (TermEdit' t d) -> State (LocalizePatchState t h d) LocalTermEdit
localizeTermEdit :: TermEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TermEdit' LocalTextId LocalDefnId)
localizeTermEdit =
(t -> StateT (LocalizePatchState t h d) Identity LocalTextId)
-> (d -> StateT (LocalizePatchState t h d) Identity LocalDefnId)
-> TermEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TermEdit' LocalTextId LocalDefnId)
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> TermEdit' a b -> f (TermEdit' c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse t -> StateT (LocalizePatchState t h d) Identity LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText d -> StateT (LocalizePatchState t h d) Identity LocalDefnId
forall d s (m :: * -> *).
(ContainsDefns d s, Monad m) =>
d -> StateT s m LocalDefnId
localizeDefn
localizeTypeEdit :: TypeEdit' t d -> State (LocalizePatchState t h d) LocalTypeEdit
localizeTypeEdit :: TypeEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TypeEdit' LocalTextId LocalDefnId)
localizeTypeEdit =
(t -> StateT (LocalizePatchState t h d) Identity LocalTextId)
-> (d -> StateT (LocalizePatchState t h d) Identity LocalDefnId)
-> TypeEdit' t d
-> StateT
(LocalizePatchState t h d)
Identity
(TypeEdit' LocalTextId LocalDefnId)
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> TypeEdit' a b -> f (TypeEdit' c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse t -> StateT (LocalizePatchState t h d) Identity LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText d -> StateT (LocalizePatchState t h d) Identity LocalDefnId
forall d s (m :: * -> *).
(ContainsDefns d s, Monad m) =>
d -> StateT s m LocalDefnId
localizeDefn
class (Ord c) => ContainsBranches c s where
branches_ :: Lens' s (Map c LocalBranchChildId)
class (Ord d) => ContainsDefns d s where
defns_ :: Lens' s (Map d LocalDefnId)
class (Ord h) => ContainsHashes h s where
hashes_ :: Lens' s (Map h LocalHashId)
class (Ord p) => ContainsPatches p s where
patches_ :: Lens' s (Map p LocalPatchObjectId)
class (Ord t) => ContainsText t s where
texts_ :: Lens' s (Map t LocalTextId)
data LocalizeBranchState t d p c = LocalizeBranchState
{ forall t d p c. LocalizeBranchState t d p c -> Map t LocalTextId
texts :: Map t LocalTextId,
forall t d p c. LocalizeBranchState t d p c -> Map d LocalDefnId
defns :: Map d LocalDefnId,
forall t d p c.
LocalizeBranchState t d p c -> Map p LocalPatchObjectId
patches :: Map p LocalPatchObjectId,
forall t d p c.
LocalizeBranchState t d p c -> Map c LocalBranchChildId
branches :: Map c LocalBranchChildId
}
deriving (Int -> LocalizeBranchState t d p c -> ShowS
[LocalizeBranchState t d p c] -> ShowS
LocalizeBranchState t d p c -> String
(Int -> LocalizeBranchState t d p c -> ShowS)
-> (LocalizeBranchState t d p c -> String)
-> ([LocalizeBranchState t d p c] -> ShowS)
-> Show (LocalizeBranchState t d p c)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall t d p c.
(Show t, Show d, Show p, Show c) =>
Int -> LocalizeBranchState t d p c -> ShowS
forall t d p c.
(Show t, Show d, Show p, Show c) =>
[LocalizeBranchState t d p c] -> ShowS
forall t d p c.
(Show t, Show d, Show p, Show c) =>
LocalizeBranchState t d p c -> String
$cshowsPrec :: forall t d p c.
(Show t, Show d, Show p, Show c) =>
Int -> LocalizeBranchState t d p c -> ShowS
showsPrec :: Int -> LocalizeBranchState t d p c -> ShowS
$cshow :: forall t d p c.
(Show t, Show d, Show p, Show c) =>
LocalizeBranchState t d p c -> String
show :: LocalizeBranchState t d p c -> String
$cshowList :: forall t d p c.
(Show t, Show d, Show p, Show c) =>
[LocalizeBranchState t d p c] -> ShowS
showList :: [LocalizeBranchState t d p c] -> ShowS
Show, (forall x.
LocalizeBranchState t d p c -> Rep (LocalizeBranchState t d p c) x)
-> (forall x.
Rep (LocalizeBranchState t d p c) x -> LocalizeBranchState t d p c)
-> Generic (LocalizeBranchState t d p c)
forall x.
Rep (LocalizeBranchState t d p c) x -> LocalizeBranchState t d p c
forall x.
LocalizeBranchState t d p c -> Rep (LocalizeBranchState t d p c) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall t d p c x.
Rep (LocalizeBranchState t d p c) x -> LocalizeBranchState t d p c
forall t d p c x.
LocalizeBranchState t d p c -> Rep (LocalizeBranchState t d p c) x
$cfrom :: forall t d p c x.
LocalizeBranchState t d p c -> Rep (LocalizeBranchState t d p c) x
from :: forall x.
LocalizeBranchState t d p c -> Rep (LocalizeBranchState t d p c) x
$cto :: forall t d p c x.
Rep (LocalizeBranchState t d p c) x -> LocalizeBranchState t d p c
to :: forall x.
Rep (LocalizeBranchState t d p c) x -> LocalizeBranchState t d p c
Generic)
instance (Ord t) => ContainsText t (LocalizeBranchState t d p c) where
texts_ :: Lens' (LocalizeBranchState t d p c) (Map t LocalTextId)
texts_ = forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"texts"
instance (Ord d) => ContainsDefns d (LocalizeBranchState t d p c) where
defns_ :: Lens' (LocalizeBranchState t d p c) (Map d LocalDefnId)
defns_ = forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"defns"
instance (Ord p) => ContainsPatches p (LocalizeBranchState t d p c) where
patches_ :: Lens' (LocalizeBranchState t d p c) (Map p LocalPatchObjectId)
patches_ = forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"patches"
instance (Ord c) => ContainsBranches c (LocalizeBranchState t d p c) where
branches_ :: Lens' (LocalizeBranchState t d p c) (Map c LocalBranchChildId)
branches_ = forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"branches"
runLocalizeBranch :: forall m t d p c a. (Monad m, Ord t, Ord d, Ord p, Ord c) => StateT (LocalizeBranchState t d p c) m a -> m (Branch.BranchLocalIds' t d p c, a)
runLocalizeBranch :: forall (m :: * -> *) t d p c a.
(Monad m, Ord t, Ord d, Ord p, Ord c) =>
StateT (LocalizeBranchState t d p c) m a
-> m (BranchLocalIds' t d p c, a)
runLocalizeBranch StateT (LocalizeBranchState t d p c) m a
action = do
(a
result, (LocalizeBranchState Map t LocalTextId
localTexts Map d LocalDefnId
localDefns Map p LocalPatchObjectId
localPatches Map c LocalBranchChildId
localChildren)) <- StateT (LocalizeBranchState t d p c) m a
-> LocalizeBranchState t d p c
-> m (a, LocalizeBranchState t d p c)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
State.runStateT StateT (LocalizeBranchState t d p c) m a
action (Map t LocalTextId
-> Map d LocalDefnId
-> Map p LocalPatchObjectId
-> Map c LocalBranchChildId
-> LocalizeBranchState t d p c
forall t d p c.
Map t LocalTextId
-> Map d LocalDefnId
-> Map p LocalPatchObjectId
-> Map c LocalBranchChildId
-> LocalizeBranchState t d p c
LocalizeBranchState Map t LocalTextId
forall a. Monoid a => a
mempty Map d LocalDefnId
forall a. Monoid a => a
mempty Map p LocalPatchObjectId
forall a. Monoid a => a
mempty Map c LocalBranchChildId
forall a. Monoid a => a
mempty)
let branchLocalIds :: Branch.BranchLocalIds' t d p c
branchLocalIds :: BranchLocalIds' t d p c
branchLocalIds =
Branch.LocalIds
{ $sel:branchTextLookup:LocalIds :: Vector t
Branch.branchTextLookup = Map LocalTextId t -> Vector t
forall k v. Map k v -> Vector v
Map.valuesVector (Map t LocalTextId -> Map LocalTextId t
forall b a. Ord b => Map a b -> Map b a
Map.swap Map t LocalTextId
localTexts),
$sel:branchDefnLookup:LocalIds :: Vector d
Branch.branchDefnLookup = Map LocalDefnId d -> Vector d
forall k v. Map k v -> Vector v
Map.valuesVector (Map d LocalDefnId -> Map LocalDefnId d
forall b a. Ord b => Map a b -> Map b a
Map.swap Map d LocalDefnId
localDefns),
$sel:branchPatchLookup:LocalIds :: Vector p
Branch.branchPatchLookup = Map LocalPatchObjectId p -> Vector p
forall k v. Map k v -> Vector v
Map.valuesVector (Map p LocalPatchObjectId -> Map LocalPatchObjectId p
forall b a. Ord b => Map a b -> Map b a
Map.swap Map p LocalPatchObjectId
localPatches),
$sel:branchChildLookup:LocalIds :: Vector c
Branch.branchChildLookup = Map LocalBranchChildId c -> Vector c
forall k v. Map k v -> Vector v
Map.valuesVector (Map c LocalBranchChildId -> Map LocalBranchChildId c
forall b a. Ord b => Map a b -> Map b a
Map.swap Map c LocalBranchChildId
localChildren)
}
(BranchLocalIds' t d p c, a) -> m (BranchLocalIds' t d p c, a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BranchLocalIds' t d p c
branchLocalIds, a
result)
data LocalizePatchState t h d = LocalizePatchState
{ forall t h d. LocalizePatchState t h d -> Map t LocalTextId
texts :: Map t LocalTextId,
forall t h d. LocalizePatchState t h d -> Map h LocalHashId
hashes :: Map h LocalHashId,
forall t h d. LocalizePatchState t h d -> Map d LocalDefnId
defns :: Map d LocalDefnId
}
deriving (Int -> LocalizePatchState t h d -> ShowS
[LocalizePatchState t h d] -> ShowS
LocalizePatchState t h d -> String
(Int -> LocalizePatchState t h d -> ShowS)
-> (LocalizePatchState t h d -> String)
-> ([LocalizePatchState t h d] -> ShowS)
-> Show (LocalizePatchState t h d)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall t h d.
(Show t, Show h, Show d) =>
Int -> LocalizePatchState t h d -> ShowS
forall t h d.
(Show t, Show h, Show d) =>
[LocalizePatchState t h d] -> ShowS
forall t h d.
(Show t, Show h, Show d) =>
LocalizePatchState t h d -> String
$cshowsPrec :: forall t h d.
(Show t, Show h, Show d) =>
Int -> LocalizePatchState t h d -> ShowS
showsPrec :: Int -> LocalizePatchState t h d -> ShowS
$cshow :: forall t h d.
(Show t, Show h, Show d) =>
LocalizePatchState t h d -> String
show :: LocalizePatchState t h d -> String
$cshowList :: forall t h d.
(Show t, Show h, Show d) =>
[LocalizePatchState t h d] -> ShowS
showList :: [LocalizePatchState t h d] -> ShowS
Show, (forall x.
LocalizePatchState t h d -> Rep (LocalizePatchState t h d) x)
-> (forall x.
Rep (LocalizePatchState t h d) x -> LocalizePatchState t h d)
-> Generic (LocalizePatchState t h d)
forall x.
Rep (LocalizePatchState t h d) x -> LocalizePatchState t h d
forall x.
LocalizePatchState t h d -> Rep (LocalizePatchState t h d) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall t h d x.
Rep (LocalizePatchState t h d) x -> LocalizePatchState t h d
forall t h d x.
LocalizePatchState t h d -> Rep (LocalizePatchState t h d) x
$cfrom :: forall t h d x.
LocalizePatchState t h d -> Rep (LocalizePatchState t h d) x
from :: forall x.
LocalizePatchState t h d -> Rep (LocalizePatchState t h d) x
$cto :: forall t h d x.
Rep (LocalizePatchState t h d) x -> LocalizePatchState t h d
to :: forall x.
Rep (LocalizePatchState t h d) x -> LocalizePatchState t h d
Generic)
instance (Ord t) => ContainsText t (LocalizePatchState t h d) where
texts_ :: Lens' (LocalizePatchState t h d) (Map t LocalTextId)
texts_ = forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"texts"
instance (Ord h) => ContainsHashes h (LocalizePatchState t h d) where
hashes_ :: Lens' (LocalizePatchState t h d) (Map h LocalHashId)
hashes_ = forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"hashes"
instance (Ord d) => ContainsDefns d (LocalizePatchState t h d) where
defns_ :: Lens' (LocalizePatchState t h d) (Map d LocalDefnId)
defns_ = forall (field :: Symbol) s t a b.
HasField field s t a b =>
Lens s t a b
field @"defns"
runLocalizePatch :: forall t h d a m. (Monad m, Ord t, Ord h, Ord d) => StateT (LocalizePatchState t h d) m a -> m (PatchLocalIds' t h d, a)
runLocalizePatch :: forall t h d a (m :: * -> *).
(Monad m, Ord t, Ord h, Ord d) =>
StateT (LocalizePatchState t h d) m a
-> m (PatchLocalIds' t h d, a)
runLocalizePatch StateT (LocalizePatchState t h d) m a
action = do
(a
result, (LocalizePatchState Map t LocalTextId
localTexts Map h LocalHashId
localHashes Map d LocalDefnId
localDefns)) <- StateT (LocalizePatchState t h d) m a
-> LocalizePatchState t h d -> m (a, LocalizePatchState t h d)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
State.runStateT StateT (LocalizePatchState t h d) m a
action (Map t LocalTextId
-> Map h LocalHashId
-> Map d LocalDefnId
-> LocalizePatchState t h d
forall t h d.
Map t LocalTextId
-> Map h LocalHashId
-> Map d LocalDefnId
-> LocalizePatchState t h d
LocalizePatchState Map t LocalTextId
forall a. Monoid a => a
mempty Map h LocalHashId
forall a. Monoid a => a
mempty Map d LocalDefnId
forall a. Monoid a => a
mempty)
let patchLocalIds :: PatchLocalIds' t h d
patchLocalIds :: PatchLocalIds' t h d
patchLocalIds =
Patch.LocalIds
{ $sel:patchTextLookup:LocalIds :: Vector t
Patch.patchTextLookup = Map LocalTextId t -> Vector t
forall k v. Map k v -> Vector v
Map.valuesVector (Map t LocalTextId -> Map LocalTextId t
forall b a. Ord b => Map a b -> Map b a
Map.swap Map t LocalTextId
localTexts),
$sel:patchHashLookup:LocalIds :: Vector h
Patch.patchHashLookup = Map LocalHashId h -> Vector h
forall k v. Map k v -> Vector v
Map.valuesVector (Map h LocalHashId -> Map LocalHashId h
forall b a. Ord b => Map a b -> Map b a
Map.swap Map h LocalHashId
localHashes),
$sel:patchDefnLookup:LocalIds :: Vector d
Patch.patchDefnLookup = Map LocalDefnId d -> Vector d
forall k v. Map k v -> Vector v
Map.valuesVector (Map d LocalDefnId -> Map LocalDefnId d
forall b a. Ord b => Map a b -> Map b a
Map.swap Map d LocalDefnId
localDefns)
}
(PatchLocalIds' t h d, a) -> m (PatchLocalIds' t h d, a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PatchLocalIds' t h d
patchLocalIds, a
result)
localizeBranchReference :: (ContainsBranches c s, Monad m) => c -> StateT s m LocalBranchChildId
localizeBranchReference :: forall c s (m :: * -> *).
(ContainsBranches c s, Monad m) =>
c -> StateT s m LocalBranchChildId
localizeBranchReference =
LensLike'
(Zoomed (StateT (Map c LocalBranchChildId) m) LocalBranchChildId)
s
(Map c LocalBranchChildId)
-> StateT (Map c LocalBranchChildId) m LocalBranchChildId
-> StateT s m LocalBranchChildId
forall c.
LensLike'
(Zoomed (StateT (Map c LocalBranchChildId) m) c)
s
(Map c LocalBranchChildId)
-> StateT (Map c LocalBranchChildId) m c -> StateT s m c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom (Map c LocalBranchChildId
-> Focusing m LocalBranchChildId (Map c LocalBranchChildId))
-> s -> Focusing m LocalBranchChildId s
LensLike'
(Zoomed (StateT (Map c LocalBranchChildId) m) LocalBranchChildId)
s
(Map c LocalBranchChildId)
forall c s.
ContainsBranches c s =>
Lens' s (Map c LocalBranchChildId)
Lens' s (Map c LocalBranchChildId)
branches_ (StateT (Map c LocalBranchChildId) m LocalBranchChildId
-> StateT s m LocalBranchChildId)
-> (c -> StateT (Map c LocalBranchChildId) m LocalBranchChildId)
-> c
-> StateT s m LocalBranchChildId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> StateT (Map c LocalBranchChildId) m LocalBranchChildId
forall localId (m :: * -> *) realId.
(Coercible localId Word64, Monad m, Ord realId) =>
realId -> StateT (Map realId localId) m localId
localize
localizeDefn :: (ContainsDefns d s, Monad m) => d -> StateT s m LocalDefnId
localizeDefn :: forall d s (m :: * -> *).
(ContainsDefns d s, Monad m) =>
d -> StateT s m LocalDefnId
localizeDefn =
LensLike'
(Zoomed (StateT (Map d LocalDefnId) m) LocalDefnId)
s
(Map d LocalDefnId)
-> StateT (Map d LocalDefnId) m LocalDefnId
-> StateT s m LocalDefnId
forall c.
LensLike'
(Zoomed (StateT (Map d LocalDefnId) m) c) s (Map d LocalDefnId)
-> StateT (Map d LocalDefnId) m c -> StateT s m c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom (Map d LocalDefnId -> Focusing m LocalDefnId (Map d LocalDefnId))
-> s -> Focusing m LocalDefnId s
LensLike'
(Zoomed (StateT (Map d LocalDefnId) m) LocalDefnId)
s
(Map d LocalDefnId)
forall d s. ContainsDefns d s => Lens' s (Map d LocalDefnId)
Lens' s (Map d LocalDefnId)
defns_ (StateT (Map d LocalDefnId) m LocalDefnId
-> StateT s m LocalDefnId)
-> (d -> StateT (Map d LocalDefnId) m LocalDefnId)
-> d
-> StateT s m LocalDefnId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> StateT (Map d LocalDefnId) m LocalDefnId
forall localId (m :: * -> *) realId.
(Coercible localId Word64, Monad m, Ord realId) =>
realId -> StateT (Map realId localId) m localId
localize
localizeHash :: (ContainsHashes h s, Monad m) => h -> StateT s m LocalHashId
localizeHash :: forall h s (m :: * -> *).
(ContainsHashes h s, Monad m) =>
h -> StateT s m LocalHashId
localizeHash =
LensLike'
(Zoomed (StateT (Map h LocalHashId) m) LocalHashId)
s
(Map h LocalHashId)
-> StateT (Map h LocalHashId) m LocalHashId
-> StateT s m LocalHashId
forall c.
LensLike'
(Zoomed (StateT (Map h LocalHashId) m) c) s (Map h LocalHashId)
-> StateT (Map h LocalHashId) m c -> StateT s m c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom (Map h LocalHashId -> Focusing m LocalHashId (Map h LocalHashId))
-> s -> Focusing m LocalHashId s
LensLike'
(Zoomed (StateT (Map h LocalHashId) m) LocalHashId)
s
(Map h LocalHashId)
forall h s. ContainsHashes h s => Lens' s (Map h LocalHashId)
Lens' s (Map h LocalHashId)
hashes_ (StateT (Map h LocalHashId) m LocalHashId
-> StateT s m LocalHashId)
-> (h -> StateT (Map h LocalHashId) m LocalHashId)
-> h
-> StateT s m LocalHashId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. h -> StateT (Map h LocalHashId) m LocalHashId
forall localId (m :: * -> *) realId.
(Coercible localId Word64, Monad m, Ord realId) =>
realId -> StateT (Map realId localId) m localId
localize
localizePatchReference :: (ContainsPatches p s, Monad m) => p -> StateT s m LocalPatchObjectId
localizePatchReference :: forall p s (m :: * -> *).
(ContainsPatches p s, Monad m) =>
p -> StateT s m LocalPatchObjectId
localizePatchReference =
LensLike'
(Zoomed (StateT (Map p LocalPatchObjectId) m) LocalPatchObjectId)
s
(Map p LocalPatchObjectId)
-> StateT (Map p LocalPatchObjectId) m LocalPatchObjectId
-> StateT s m LocalPatchObjectId
forall c.
LensLike'
(Zoomed (StateT (Map p LocalPatchObjectId) m) c)
s
(Map p LocalPatchObjectId)
-> StateT (Map p LocalPatchObjectId) m c -> StateT s m c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom (Map p LocalPatchObjectId
-> Focusing m LocalPatchObjectId (Map p LocalPatchObjectId))
-> s -> Focusing m LocalPatchObjectId s
LensLike'
(Zoomed (StateT (Map p LocalPatchObjectId) m) LocalPatchObjectId)
s
(Map p LocalPatchObjectId)
forall p s.
ContainsPatches p s =>
Lens' s (Map p LocalPatchObjectId)
Lens' s (Map p LocalPatchObjectId)
patches_ (StateT (Map p LocalPatchObjectId) m LocalPatchObjectId
-> StateT s m LocalPatchObjectId)
-> (p -> StateT (Map p LocalPatchObjectId) m LocalPatchObjectId)
-> p
-> StateT s m LocalPatchObjectId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p -> StateT (Map p LocalPatchObjectId) m LocalPatchObjectId
forall localId (m :: * -> *) realId.
(Coercible localId Word64, Monad m, Ord realId) =>
realId -> StateT (Map realId localId) m localId
localize
localizeReference :: (ContainsDefns d s, ContainsText t s, Monad m) => Reference' t d -> StateT s m LocalReference
localizeReference :: forall d s t (m :: * -> *).
(ContainsDefns d s, ContainsText t s, Monad m) =>
Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId)
localizeReference =
(t -> StateT s m LocalTextId)
-> (d -> StateT s m LocalDefnId)
-> Reference' t d
-> StateT s m (Reference' LocalTextId LocalDefnId)
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> Reference' a b -> f (Reference' c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse t -> StateT s m LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText d -> StateT s m LocalDefnId
forall d s (m :: * -> *).
(ContainsDefns d s, Monad m) =>
d -> StateT s m LocalDefnId
localizeDefn
localizeReferenceH :: (ContainsHashes h s, ContainsText t s, Monad m) => Reference' t h -> StateT s m LocalReferenceH
localizeReferenceH :: forall h s t (m :: * -> *).
(ContainsHashes h s, ContainsText t s, Monad m) =>
Reference' t h -> StateT s m (Reference' LocalTextId LocalHashId)
localizeReferenceH =
(t -> StateT s m LocalTextId)
-> (h -> StateT s m LocalHashId)
-> Reference' t h
-> StateT s m (Reference' LocalTextId LocalHashId)
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> Reference' a b -> f (Reference' c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse t -> StateT s m LocalTextId
forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText h -> StateT s m LocalHashId
forall h s (m :: * -> *).
(ContainsHashes h s, Monad m) =>
h -> StateT s m LocalHashId
localizeHash
localizeReferent :: forall d t s m. (ContainsDefns d s, ContainsText t s, Monad m) => (Referent' (Reference' t d) (Reference' t d)) -> StateT s m LocalReferent
localizeReferent :: forall d t s (m :: * -> *).
(ContainsDefns d s, ContainsText t s, Monad m) =>
Referent' (Reference' t d) (Reference' t d)
-> StateT s m (Referent'' LocalTextId LocalDefnId)
localizeReferent =
(Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId))
-> (Reference' t d
-> StateT s m (Reference' LocalTextId LocalDefnId))
-> Referent' (Reference' t d) (Reference' t d)
-> StateT s m (Referent'' LocalTextId LocalDefnId)
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> Referent' a b -> f (Referent' c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId)
forall d s t (m :: * -> *).
(ContainsDefns d s, ContainsText t s, Monad m) =>
Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId)
localizeReference Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId)
forall d s t (m :: * -> *).
(ContainsDefns d s, ContainsText t s, Monad m) =>
Reference' t d -> StateT s m (Reference' LocalTextId LocalDefnId)
localizeReference
localizeReferentH :: (ContainsHashes h s, ContainsText t s, Monad m, r ~ Reference' t h) => Referent' r r -> StateT s m LocalReferentH
localizeReferentH :: forall h s t (m :: * -> *) r.
(ContainsHashes h s, ContainsText t s, Monad m,
r ~ Reference' t h) =>
Referent' r r -> StateT s m (Referent'' LocalTextId LocalHashId)
localizeReferentH =
(r -> StateT s m (Reference' LocalTextId LocalHashId))
-> (r -> StateT s m (Reference' LocalTextId LocalHashId))
-> Referent' r r
-> StateT s m (Referent'' LocalTextId LocalHashId)
forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> Referent' a b -> f (Referent' c d)
forall (t :: * -> * -> *) (f :: * -> *) a c b d.
(Bitraversable t, Applicative f) =>
(a -> f c) -> (b -> f d) -> t a b -> f (t c d)
bitraverse r -> StateT s m (Reference' LocalTextId LocalHashId)
Reference' t h -> StateT s m (Reference' LocalTextId LocalHashId)
forall h s t (m :: * -> *).
(ContainsHashes h s, ContainsText t s, Monad m) =>
Reference' t h -> StateT s m (Reference' LocalTextId LocalHashId)
localizeReferenceH r -> StateT s m (Reference' LocalTextId LocalHashId)
Reference' t h -> StateT s m (Reference' LocalTextId LocalHashId)
forall h s t (m :: * -> *).
(ContainsHashes h s, ContainsText t s, Monad m) =>
Reference' t h -> StateT s m (Reference' LocalTextId LocalHashId)
localizeReferenceH
localizeText :: (ContainsText t s, Monad m) => t -> StateT s m LocalTextId
localizeText :: forall t s (m :: * -> *).
(ContainsText t s, Monad m) =>
t -> StateT s m LocalTextId
localizeText =
LensLike'
(Zoomed (StateT (Map t LocalTextId) m) LocalTextId)
s
(Map t LocalTextId)
-> StateT (Map t LocalTextId) m LocalTextId
-> StateT s m LocalTextId
forall c.
LensLike'
(Zoomed (StateT (Map t LocalTextId) m) c) s (Map t LocalTextId)
-> StateT (Map t LocalTextId) m c -> StateT s m c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
zoom (Map t LocalTextId -> Focusing m LocalTextId (Map t LocalTextId))
-> s -> Focusing m LocalTextId s
LensLike'
(Zoomed (StateT (Map t LocalTextId) m) LocalTextId)
s
(Map t LocalTextId)
forall t s. ContainsText t s => Lens' s (Map t LocalTextId)
Lens' s (Map t LocalTextId)
texts_ (StateT (Map t LocalTextId) m LocalTextId
-> StateT s m LocalTextId)
-> (t -> StateT (Map t LocalTextId) m LocalTextId)
-> t
-> StateT s m LocalTextId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> StateT (Map t LocalTextId) m LocalTextId
forall localId (m :: * -> *) realId.
(Coercible localId Word64, Monad m, Ord realId) =>
realId -> StateT (Map realId localId) m localId
localize
localize :: (Coercible localId Word64, Monad m, Ord realId) => realId -> StateT (Map realId localId) m localId
localize :: forall localId (m :: * -> *) realId.
(Coercible localId Word64, Monad m, Ord realId) =>
realId -> StateT (Map realId localId) m localId
localize realId
realId = do
Map realId localId
mapping <- StateT (Map realId localId) m (Map realId localId)
forall (m :: * -> *) s. Monad m => StateT s m s
State.get
case realId -> Map realId localId -> Maybe localId
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup realId
realId Map realId localId
mapping of
Maybe localId
Nothing -> do
let nextLocalId :: localId
nextLocalId = forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @Word64 (Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Map realId localId -> Int
forall k a. Map k a -> Int
Map.size Map realId localId
mapping))
Map realId localId -> StateT (Map realId localId) m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
State.put (Map realId localId -> StateT (Map realId localId) m ())
-> Map realId localId -> StateT (Map realId localId) m ()
forall a b. (a -> b) -> a -> b
$! realId -> localId -> Map realId localId -> Map realId localId
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert realId
realId localId
nextLocalId Map realId localId
mapping
pure localId
nextLocalId
Just localId
localId -> localId -> StateT (Map realId localId) m localId
forall a. a -> StateT (Map realId localId) m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure localId
localId