Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
U.Codebase.Sqlite.Operations
Synopsis
- loadCausalHashAtPath :: CausalHash -> [NameSegment] -> Transaction (Maybe CausalHash)
- expectCausalHashAtPath :: CausalHash -> [NameSegment] -> Transaction CausalHash
- loadCausalBranchAtPath :: CausalHash -> [NameSegment] -> Transaction (Maybe (CausalBranch Transaction))
- loadBranchAtPath :: CausalHash -> [NameSegment] -> Transaction (Maybe (Branch Transaction))
- saveBranch :: HashHandle -> CausalBranch Transaction -> Transaction (BranchObjectId, CausalHashId)
- saveBranchV3 :: HashHandle -> CausalBranchV3 Transaction -> Transaction (BranchObjectId, CausalHashId)
- loadCausalBranchByCausalHash :: CausalHash -> Transaction (Maybe (CausalBranch Transaction))
- expectCausalBranchByCausalHash :: CausalHash -> Transaction (CausalBranch Transaction)
- expectBranchByCausalHashId :: CausalHashId -> Transaction (Branch Transaction)
- expectBranchByBranchHash :: BranchHash -> Transaction (Branch Transaction)
- expectBranchByBranchHashId :: BranchHashId -> Transaction (Branch Transaction)
- expectNamespaceStatsByHash :: BranchHash -> Transaction NamespaceStats
- expectNamespaceStatsByHashId :: BranchHashId -> Transaction NamespaceStats
- tryGetSquashResult :: BranchHash -> Transaction (Maybe CausalHash)
- saveSquashResult :: BranchHash -> CausalHash -> Transaction ()
- saveTermComponent :: HashHandle -> Maybe ByteString -> Hash -> [(Term Symbol, Type Symbol)] -> Transaction ObjectId
- loadTermComponent :: Hash -> MaybeT Transaction [(Term Symbol, Type Symbol)]
- loadTermByReference :: Id -> MaybeT Transaction (Term Symbol)
- loadTypeOfTermByTermReference :: Id -> MaybeT Transaction (Type Symbol)
- saveDeclComponent :: HashHandle -> Maybe ByteString -> Hash -> [Decl Symbol] -> Transaction ObjectId
- loadDeclComponent :: Hash -> MaybeT Transaction [Decl Symbol]
- loadDeclByReference :: Id -> MaybeT Transaction (Decl Symbol)
- expectDeclByReference :: Id -> Transaction (Decl Symbol)
- expectDeclNumConstructors :: Id -> Transaction Int
- expectDeclTypeById :: Id -> Transaction DeclType
- getCycleLen :: Hash -> Transaction (Maybe Word64)
- savePatch :: HashHandle -> PatchHash -> Patch -> Transaction PatchObjectId
- expectPatch :: PatchObjectId -> Transaction Patch
- objectExistsForHash :: Hash -> Transaction Bool
- saveWatch :: WatchKind -> Id -> Term Symbol -> Transaction ()
- loadWatch :: WatchKind -> Id -> MaybeT Transaction (Term Symbol)
- listWatches :: WatchKind -> Transaction [Id]
- clearWatches :: Transaction ()
- before :: CausalHash -> CausalHash -> Transaction (Maybe Bool)
- lca :: CausalHash -> CausalHash -> Transaction (Maybe CausalHash)
- componentReferencesByPrefix :: ObjectType -> Text -> Maybe Pos -> Transaction [Id]
- termReferentsByPrefix :: Text -> Maybe Word64 -> Transaction [Id]
- declReferentsByPrefix :: Text -> Maybe Pos -> Maybe ConstructorId -> Transaction [(Hash, Pos, DeclType, [ConstructorId])]
- causalHashesByPrefix :: ShortCausalHash -> Transaction (Set CausalHash)
- directDependenciesOfScope :: (Reference -> Bool) -> DefnsF Set TermReferenceId TypeReferenceId -> Transaction (DefnsF Set TermReference TypeReference)
- dependents :: DependentsSelector -> Reference -> Transaction (Set Id)
- dependentsOfComponent :: Hash -> Transaction (Set Id)
- directDependentsWithinScope :: Set Id -> Set Reference -> Transaction (DefnsF Set TermReferenceId TypeReferenceId)
- transitiveDependentsWithinScope :: DefnsF Set TermReferenceId TypeReferenceId -> Set Reference -> Transaction (DefnsF Set TermReferenceId TypeReferenceId)
- addTypeToIndexForTerm :: Id -> Reference -> Transaction ()
- termsHavingType :: Reference -> Transaction (Set Id)
- filterTermsByReferenceHavingType :: TypeReference -> [Id] -> Transaction [Id]
- filterTermsByReferentHavingType :: TypeReference -> [Id] -> Transaction [Id]
- addTypeMentionsToIndexForTerm :: Id -> Set Reference -> Transaction ()
- termsMentioningType :: Reference -> Transaction (Set Id)
- expectProjectAndBranchNames :: ProjectId -> ProjectBranchId -> Transaction (ProjectName, ProjectBranchName)
- expectProjectBranchHead :: ProjectId -> ProjectBranchId -> Transaction CausalHash
- getDeprecatedRootReflog :: Int -> Transaction [Entry CausalHash Text]
- getProjectReflog :: Int -> ProjectId -> Transaction [Entry Project ProjectBranch CausalHash]
- getProjectBranchReflog :: Int -> ProjectBranchId -> Transaction [Entry Project ProjectBranch CausalHash]
- getGlobalReflog :: Int -> Transaction [Entry Project ProjectBranch CausalHash]
- appendProjectReflog :: Entry ProjectId ProjectBranchId CausalHash -> Transaction ()
- expectDbBranch :: BranchObjectId -> Transaction DbBranch
- saveDbBranch :: HashHandle -> BranchHash -> NamespaceStats -> DbBranchV -> Transaction BranchObjectId
- saveDbBranchUnderHashId :: HashHandle -> BranchHashId -> NamespaceStats -> DbBranchV -> Transaction BranchObjectId
- expectDbPatch :: PatchObjectId -> Transaction Patch
- saveDbPatch :: HashHandle -> PatchHash -> PatchFormat -> Transaction PatchObjectId
- expectDbBranchByCausalHashId :: CausalHashId -> Transaction DbBranch
- namespaceStatsForDbBranch :: DbBranchV -> Transaction NamespaceStats
- c2sTextReference :: Reference -> TextReference
- s2cTextReference :: TextReference -> Reference
- c2sTextReferent :: Referent -> TextReferent
- s2cTextReferent :: TextReferent -> Referent
- c2sReferenceId :: Id -> Transaction Id
- c2sReferentId :: Id -> Transaction Id
- diffPatch :: LocalPatch -> LocalPatch -> LocalPatchDiff
- decodeTermElementWithType :: Pos -> ByteString -> Either DecodeError (LocalIds, Term, Type)
- loadTermWithTypeByReference :: Id -> MaybeT Transaction (Term Symbol, Type Symbol)
- s2cTermWithType :: LocalIds -> Term -> Type -> Transaction (Term Symbol, Type Symbol)
- s2cDecl :: LocalIds -> Decl Symbol -> Transaction (Decl Symbol)
- declReferencesByPrefix :: Text -> Maybe Word64 -> Transaction [Id]
- namespaceHashesByPrefix :: ShortNamespaceHash -> Transaction (Set BranchHash)
- derivedDependencies :: Id -> Transaction (Set Id)
- data BranchV m
- data DbBranchV
branches
loadCausalHashAtPath :: CausalHash -> [NameSegment] -> Transaction (Maybe CausalHash) Source #
Load the causal hash at the given path from the provided root, if Nothing, use the codebase root.
expectCausalHashAtPath :: CausalHash -> [NameSegment] -> Transaction CausalHash Source #
Expect the causal hash at the given path from the provided root, if Nothing, use the codebase root.
loadCausalBranchAtPath :: CausalHash -> [NameSegment] -> Transaction (Maybe (CausalBranch Transaction)) Source #
loadBranchAtPath :: CausalHash -> [NameSegment] -> Transaction (Maybe (Branch Transaction)) Source #
saveBranch :: HashHandle -> CausalBranch Transaction -> Transaction (BranchObjectId, CausalHashId) Source #
saveBranchV3 :: HashHandle -> CausalBranchV3 Transaction -> Transaction (BranchObjectId, CausalHashId) Source #
loadCausalBranchByCausalHash :: CausalHash -> Transaction (Maybe (CausalBranch Transaction)) Source #
expectNamespaceStatsByHash :: BranchHash -> Transaction NamespaceStats Source #
Looks up statistics for a given branch, if none exist, we compute them and save them then return them.
expectNamespaceStatsByHashId :: BranchHashId -> Transaction NamespaceStats Source #
Looks up statistics for a given branch, if none exist, we compute them and save them then return them.
tryGetSquashResult :: BranchHash -> Transaction (Maybe CausalHash) Source #
Get the causal hash which would be the result of squashing the provided branch hash. Returns Nothing if we haven't computed it before.
saveSquashResult :: BranchHash -> CausalHash -> Transaction () Source #
Saves the result of a squash
terms
Arguments
:: HashHandle | |
-> Maybe ByteString | The serialized term component if we already have it e.g. via sync |
-> Hash | term component hash |
-> [(Term Symbol, Type Symbol)] | term component |
-> Transaction ObjectId |
loadTermComponent :: Hash -> MaybeT Transaction [(Term Symbol, Type Symbol)] Source #
loadTermByReference :: Id -> MaybeT Transaction (Term Symbol) Source #
decls
saveDeclComponent :: HashHandle -> Maybe ByteString -> Hash -> [Decl Symbol] -> Transaction ObjectId Source #
loadDeclComponent :: Hash -> MaybeT Transaction [Decl Symbol] Source #
loadDeclByReference :: Id -> MaybeT Transaction (Decl Symbol) Source #
expectDeclByReference :: Id -> Transaction (Decl Symbol) Source #
terms/decls
getCycleLen :: Hash -> Transaction (Maybe Word64) Source #
patches
savePatch :: HashHandle -> PatchHash -> Patch -> Transaction PatchObjectId Source #
test for stuff in codebase
watch expression cache
loadWatch :: WatchKind -> Id -> MaybeT Transaction (Term Symbol) Source #
returns Nothing if the expression isn't cached.
listWatches :: WatchKind -> Transaction [Id] Source #
clearWatches :: Transaction () Source #
Delete all watches that were put by putWatch
.
indexes
nearest common ancestor
before :: CausalHash -> CausalHash -> Transaction (Maybe Bool) Source #
lca :: CausalHash -> CausalHash -> Transaction (Maybe CausalHash) Source #
prefix index
componentReferencesByPrefix :: ObjectType -> Text -> Maybe Pos -> Transaction [Id] Source #
termReferentsByPrefix :: Text -> Maybe Word64 -> Transaction [Id] Source #
declReferentsByPrefix :: Text -> Maybe Pos -> Maybe ConstructorId -> Transaction [(Hash, Pos, DeclType, [ConstructorId])] Source #
dependents index
directDependenciesOfScope :: (Reference -> Bool) -> DefnsF Set TermReferenceId TypeReferenceId -> Transaction (DefnsF Set TermReference TypeReference) Source #
dependents :: DependentsSelector -> Reference -> Transaction (Set Id) Source #
returns a list of known definitions referencing r
dependentsOfComponent :: Hash -> Transaction (Set Id) Source #
returns a list of known definitions referencing h
directDependentsWithinScope :: Set Id -> Set Reference -> Transaction (DefnsF Set TermReferenceId TypeReferenceId) Source #
`directDependentsWithinScope scope query` returns all direct dependents of query
that are in scope
(not
including query
itself).
transitiveDependentsWithinScope :: DefnsF Set TermReferenceId TypeReferenceId -> Set Reference -> Transaction (DefnsF Set TermReferenceId TypeReferenceId) Source #
`transitiveDependentsWithinScope scope query` returns all transitive dependents of query
that are in scope
(not
including query
itself).
type index
addTypeToIndexForTerm :: Id -> Reference -> Transaction () Source #
termsHavingType :: Reference -> Transaction (Set Id) Source #
filterTermsByReferenceHavingType :: TypeReference -> [Id] -> Transaction [Id] Source #
filterTermsByReferentHavingType :: TypeReference -> [Id] -> Transaction [Id] Source #
type mentions index
addTypeMentionsToIndexForTerm :: Id -> Set Reference -> Transaction () Source #
termsMentioningType :: Reference -> Transaction (Set Id) Source #
Projects
expectProjectAndBranchNames :: ProjectId -> ProjectBranchId -> Transaction (ProjectName, ProjectBranchName) Source #
reflog
getDeprecatedRootReflog :: Int -> Transaction [Entry CausalHash Text] Source #
Gets the specified number of reflog entries in chronological order, most recent first.
getProjectReflog :: Int -> ProjectId -> Transaction [Entry Project ProjectBranch CausalHash] Source #
Gets the specified number of reflog entries for the given project in chronological order, most recent first.
getProjectBranchReflog :: Int -> ProjectBranchId -> Transaction [Entry Project ProjectBranch CausalHash] Source #
Gets the specified number of reflog entries for the specified ProjectBranch in chronological order, most recent first.
getGlobalReflog :: Int -> Transaction [Entry Project ProjectBranch CausalHash] Source #
Gets the specified number of reflog entries in chronological order, most recent first.
low-level stuff
saveDbBranch :: HashHandle -> BranchHash -> NamespaceStats -> DbBranchV -> Transaction BranchObjectId Source #
Save a DbBranch
, given its hash (which the caller is expected to produce from the branch).
Note: long-standing question: should this package depend on the hashing package? (If so, we would only need to take the DbBranch, and hash internally).
saveDbBranchUnderHashId :: HashHandle -> BranchHashId -> NamespaceStats -> DbBranchV -> Transaction BranchObjectId Source #
Variant of saveDbBranch
that might be preferred by callers that already have a hash id, not a hash.
saveDbPatch :: HashHandle -> PatchHash -> PatchFormat -> Transaction PatchObjectId Source #
expectDbBranchByCausalHashId :: CausalHashId -> Transaction DbBranch Source #
Expect a branch value given its causal hash id.
reference conversions
somewhat unexpectedly unused definitions
c2sReferenceId :: Id -> Transaction Id Source #
c2sReferentId :: Id -> Transaction Id Source #
diffPatch :: LocalPatch -> LocalPatch -> LocalPatchDiff Source #
produces a diff diff = full - ref; full = diff + ref
decodeTermElementWithType :: Pos -> ByteString -> Either DecodeError (LocalIds, Term, Type) Source #
declReferencesByPrefix :: Text -> Maybe Word64 -> Transaction [Id] Source #
derivedDependencies :: Id -> Transaction (Set Id) Source #
returns empty set for unknown inputs; doesn't distinguish between term and decl
internal stuff that probably need not be exported, but the 1->2 migration needs it
Constructors
DbBranchV2 !DbBranch | |
DbBranchV3 !DbBranchV3 |