This commit is contained in:
Dmitry Zuikov 2024-04-17 09:56:24 +03:00
parent 4bf4c3a792
commit f2451697db
3 changed files with 52 additions and 24 deletions

View File

@ -8,6 +8,7 @@ import HBS2.Git.Client.Import
import HBS2.Git.Client.State import HBS2.Git.Client.State
import HBS2.Data.Types.SignedBox import HBS2.Data.Types.SignedBox
import HBS2.Git.Data.RepoHead
import HBS2.Git.Data.RefLog import HBS2.Git.Data.RefLog
import HBS2.Git.Local.CLI qualified as Git import HBS2.Git.Local.CLI qualified as Git
import HBS2.Git.Data.Tx.Git qualified as TX import HBS2.Git.Data.Tx.Git qualified as TX
@ -182,7 +183,7 @@ pManifestList :: GitPerks m => Parser (GitCLI m ())
pManifestList = do pManifestList = do
what <- argument pLwwKey (metavar "LWWREF") what <- argument pLwwKey (metavar "LWWREF")
pure do pure do
heads <- withState $ selectRepoHeadsFor what heads <- withState $ selectRepoHeadsFor DESC what
sto <- getStorage sto <- getStorage
for_ heads $ \h -> runMaybeT do for_ heads $ \h -> runMaybeT do
@ -339,13 +340,12 @@ pGenRepoIndex :: GitPerks m => Parser (GitCLI m ())
pGenRepoIndex = do pGenRepoIndex = do
what <- argument pLwwKey (metavar "LWWREF") what <- argument pLwwKey (metavar "LWWREF")
pure do pure do
withState do hd <- withState $ selectRepoIndexEntryFor what
idx <- selectRepoIndexEntryFor what >>= orThrowUser "no decent repo head data found"
`orDie` "repo head not found"
liftIO $ print idx seq <- getEpoch
let tx = GitIndexTx what seq (GitIndexRepoDefine hd)
pure () liftIO $ LBS.putStr (serialise tx)
main :: IO () main :: IO ()
main = do main = do

View File

@ -22,7 +22,19 @@ import DBPipe.SQLite
import Data.Maybe import Data.Maybe
import Data.List qualified as List import Data.List qualified as List
import Text.InterpolatedString.Perl6 (qc) import Text.InterpolatedString.Perl6 (qc)
import Data.Text qualified as Text
import Data.Word import Data.Word
import Data.Coerce
import Streaming.Prelude qualified as S
data SortOrder = ASC | DESC
newtype SQL a = SQL a
instance Pretty (SQL SortOrder) where
pretty (SQL ASC) = "ASC"
pretty (SQL DESC) = "DESC"
newtype Base58Field a = Base58Field { fromBase58Field :: a } newtype Base58Field a = Base58Field { fromBase58Field :: a }
deriving stock (Eq,Ord,Generic) deriving stock (Eq,Ord,Generic)
@ -388,45 +400,57 @@ SELECT hash, seq, reflog FROM lww
selectRepoHeadsFor :: (MonadIO m, HasStorage m) selectRepoHeadsFor :: (MonadIO m, HasStorage m)
=> LWWRefKey 'HBS2Basic => SortOrder
-> LWWRefKey 'HBS2Basic
-> DBPipeM m [TaggedHashRef RepoHead] -> DBPipeM m [TaggedHashRef RepoHead]
selectRepoHeadsFor what = do selectRepoHeadsFor order what = do
let q = [qc| let q = [qc|
SELECT t.head SELECT t.head
FROM lww l join tx t on l.reflog = t.reflog FROM lww l join tx t on l.reflog = t.reflog
WHERE l.hash = ? WHERE l.hash = ?
ORDER BY t.seq ASC ORDER BY t.seq {pretty (SQL order)}
|] |]
select @(Only (TaggedHashRef RepoHead)) q (Only $ Base58Field what) select @(Only (TaggedHashRef RepoHead)) q (Only $ Base58Field what)
<&> fmap fromOnly <&> fmap fromOnly
instance (Monad m, HasStorage m) => HasStorage (DBPipeM m) where
getStorage = lift getStorage
selectRepoIndexEntryFor :: (MonadIO m, HasStorage m) selectRepoIndexEntryFor :: (MonadIO m, HasStorage m)
=> LWWRefKey 'HBS2Basic => LWWRefKey 'HBS2Basic
-> DBPipeM m (Maybe GitIndexRepoDefineData) -> DBPipeM m (Maybe GitIndexRepoDefineData)
selectRepoIndexEntryFor what = runMaybeT do selectRepoIndexEntryFor what = runMaybeT do
let q = [qc|
SELECT l.hash, t.head
FROM lww l join tx t on l.reflog = t.reflog
WHERE l.hash = ?
ORDER BY l.seq DESC
LIMIT 1
|]
(k,rh) <- lift (select @(LWWRefKey 'HBS2Basic, HashRef) q (Only $ Base58Field what)) headz <- lift $ selectRepoHeadsFor DESC what
<&> listToMaybe >>= toMPlus
sto <- lift $ lift getStorage rhh <- S.head_ do
for_ headz $ \ha -> do
rh' <- lift $ loadRepoHead ha
for_ rh' $ \rh -> do
when (notEmpty $ _repoManifest rh) do
S.yield rh
repohead <- runExceptT (readFromMerkle sto (SimpleKey (fromHashRef rh)))
>>= toMPlus repohead <- toMPlus rhh
<&> deserialiseOrFail @RepoHead
>>= toMPlus
pure $ GitIndexRepoDefineData (GitIndexRepoName $ _repoHeadName repohead) pure $ GitIndexRepoDefineData (GitIndexRepoName $ _repoHeadName repohead)
(GitIndexRepoBrief $ _repoHeadBrief repohead) (GitIndexRepoBrief $ _repoHeadBrief repohead)
where
notEmpty s = maybe 0 Text.length s > 0
loadRepoHead :: (HasStorage m, MonadIO m) => TaggedHashRef RepoHead -> m (Maybe RepoHead)
loadRepoHead rh = do
sto <- getStorage
runMaybeT do
runExceptT (readFromMerkle sto (SimpleKey (coerce rh)))
>>= toMPlus
<&> deserialiseOrFail @RepoHead
>>= toMPlus

View File

@ -77,6 +77,10 @@ data GitIndexTx s =
} }
deriving stock (Generic) deriving stock (Generic)
instance ForGitIndex s => Serialise (GitIndexTx s)
instance Serialise GitIndexRepoDefineData
instance Serialise GitIndexEntry
instance ForGitIndex s => Pretty (GitIndexTx s) where instance ForGitIndex s => Pretty (GitIndexTx s) where
pretty GitIndexTx{..} = case gitIndexTxPayload of pretty GitIndexTx{..} = case gitIndexTxPayload of
GitIndexRepoDefine{} -> "git-repo-define" <+> pretty gitIndexTxRef GitIndexRepoDefine{} -> "git-repo-define" <+> pretty gitIndexTxRef