Added the manifest update command, fixed bugs

This commit is contained in:
Vladimir Krutkin 2024-07-19 15:06:16 +03:00
parent 573a9f3377
commit f7119564fb
11 changed files with 202 additions and 70 deletions

View File

@ -668,8 +668,8 @@ Cloning into '8vFu9S79ysdWag4wek53YWXbC5nCRLF7arGp6181G4js'...
git hbs2 export --encrypted ./gk-new.key C6tTuapmG7sE8QktQo4q4tBr8kNWKvBruNb36HYThpuy git hbs2 export --encrypted ./gk-new.key C6tTuapmG7sE8QktQo4q4tBr8kNWKvBruNb36HYThpuy
\end{verbatim} \end{verbatim}
Для обновления манифеста --- редактировать файл \texttt{.hbs2-git/manifest} и сделать Для обновления манифеста --- редактировать файл \texttt{.hbs2-git/manifest}
git commit/push либо же вызвать \texttt{git hbs2 export <LWWREF>} и вызвать \texttt{git hbs2 manifest update <LWWREF>}
\subsubsection{Смотреть групповой ключ} \subsubsection{Смотреть групповой ключ}

View File

@ -8,7 +8,7 @@ import Data.ByteString (ByteString)
-- TODO: encryption-type-into-tags -- TODO: encryption-type-into-tags
-- FIXME: show-scrambled? -- FIXME: show-scrambled?
newtype EncryptedBox t = EncryptedBox { unEncryptedBox :: ByteString } newtype EncryptedBox t = EncryptedBox { unEncryptedBox :: ByteString }
deriving stock (Generic,Show,Data) deriving stock (Eq,Generic,Show,Data)
instance Serialise (EncryptedBox t) instance Serialise (EncryptedBox t)

View File

@ -77,6 +77,12 @@ data instance GroupKey 'Symm s =
} }
deriving stock (Generic) deriving stock (Generic)
deriving instance
( Eq (PubKey 'Encrypt s)
, Eq (EncryptedBox GroupSecret)
)
=> Eq (GroupKey 'Symm s)
instance ForGroupKeySymm s => Monoid (GroupKey 'Symm s) where instance ForGroupKeySymm s => Monoid (GroupKey 'Symm s) where
mempty = GroupKeySymm mempty mempty = GroupKeySymm mempty

View File

@ -1,11 +1,12 @@
{-# Language UndecidableInstances #-} {-# Language UndecidableInstances #-}
module Main where module Main where
import HBS2.Git.Client.Prelude hiding (info) import HBS2.Git.Client.Prelude hiding (info, Input(..))
import HBS2.Git.Client.App import HBS2.Git.Client.App
import HBS2.Git.Client.Export import HBS2.Git.Client.Export
import HBS2.Git.Client.Import import HBS2.Git.Client.Import
import HBS2.Git.Client.State import HBS2.Git.Client.State
import HBS2.Git.Client.Manifest
import HBS2.Data.Types.SignedBox import HBS2.Data.Types.SignedBox
import HBS2.Git.Data.RepoHead import HBS2.Git.Data.RepoHead
@ -25,6 +26,8 @@ import Data.Text qualified as Text
import Data.Text.IO qualified as Text import Data.Text.IO qualified as Text
import Data.HashSet qualified as HS import Data.HashSet qualified as HS
import Data.Maybe import Data.Maybe
import Data.List (nubBy)
import Data.Function (on)
import Data.Coerce import Data.Coerce
import Options.Applicative as O import Options.Applicative as O
import Data.ByteString.Lazy qualified as LBS import Data.ByteString.Lazy qualified as LBS
@ -177,26 +180,28 @@ pShowRef = do
pManifest :: GitPerks m => Parser (GitCLI m ()) pManifest :: GitPerks m => Parser (GitCLI m ())
pManifest = hsubparser ( command "list" (info pManifestList (progDesc "list all manifest")) pManifest = hsubparser ( command "list" (info pManifestList (progDesc "list all manifest"))
<> command "show" (info pManifestShow (progDesc "show manifest")) <> command "show" (info pManifestShow (progDesc "show manifest"))
<> command "update" (info pManifestUpdate (progDesc "update manifest"))
) )
pManifestList :: GitPerks m => Parser (GitCLI m ()) 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 ASC what repoHeadRefs' <- withState $ selectRepoHeadsFor ASC what
sto <- getStorage sto <- getStorage
for_ heads $ \h -> runMaybeT do repoHeads <- for repoHeadRefs' $ \repoHeadRef -> runMaybeT $ do
repoHead <- runExceptT (readFromMerkle sto (SimpleKey (coerce repoHeadRef)))
rhead <- runExceptT (readFromMerkle sto (SimpleKey (coerce h))) >>= toMPlus
>>= toMPlus <&> deserialiseOrFail @RepoHead
<&> deserialiseOrFail @RepoHead >>= toMPlus
>>= toMPlus pure (repoHeadRef, repoHead)
let removeDuplicates = nubBy ((==) `on` (_repoManifest . snd))
let mfsize = maybe 0 Text.length (_repoManifest rhead) let filteredRepoHeads = removeDuplicates $ catMaybes repoHeads
let mf = parens ( "manifest" <+> pretty mfsize) for_ filteredRepoHeads $ \(repoHeadRef, repoHead) -> do
let mfLen = maybe 0 Text.length (_repoManifest repoHead)
liftIO $ print $ pretty (_repoHeadTime rhead) let mf = parens ("manifest length" <+> pretty mfLen)
<+> pretty h liftIO $ print $ pretty (_repoHeadTime repoHead)
<+> pretty repoHeadRef
<+> mf <+> mf
pManifestShow :: GitPerks m => Parser (GitCLI m ()) pManifestShow :: GitPerks m => Parser (GitCLI m ())
@ -212,6 +217,71 @@ pManifestShow = do
liftIO $ for_ (_repoManifest rhead) Text.putStrLn liftIO $ for_ (_repoManifest rhead) Text.putStrLn
data Input
= FileInput FilePath
| StdInput
manifestFileInput :: Parser Input
manifestFileInput = FileInput <$> strOption
( long "file"
<> short 'f'
<> metavar "FILENAME"
<> help "Read manifest from file" )
manifestStdInput :: Parser Input
manifestStdInput = flag' StdInput
( long "stdin"
<> help "Read manifest from stdin" )
pManifestUpdate :: (GitPerks m) => Parser (GitCLI m ())
pManifestUpdate = do
what <- argument pLwwKey (metavar "LWWREF")
manifestInput <- manifestFileInput <|> manifestStdInput
et <-
flag
ExportInc
ExportNew
( long "new" <> help "This flag is used for new repositories. It allows you to skip the step of downloading data from peers."
)
pure do
manifest <- case manifestInput of
FileInput f -> do
t <- liftIO $ Text.readFile f
addManifestBriefAndName $ Just t
StdInput -> do
t <- liftIO $ Text.getContents
addManifestBriefAndName $ Just t
env <- ask
enc <- getRepoEnc
let manifestUpdateEnv = Just $ ManifestUpdateEnv {_manifest = manifest}
withGitEnv
( env
& set gitApplyHeads False
& set gitExportType et
& set gitExportEnc enc
& set gitManifestUpdateEnv manifestUpdateEnv
)
do
unless (et == ExportNew) do
importRepoWait what
export what mempty
importRepoWait what
getRepoEnc :: (GitPerks m) => GitCLI m ExportEncryption
getRepoEnc = do
sto <- asks _storage
mgkh <- runMaybeT do
tx <- withState do
selectMaxAppliedTx >>= lift . toMPlus <&> fst
(_, rh) <-
TX.readRepoHeadFromTx sto tx
>>= toMPlus
toMPlus $ _repoHeadGK0 rh
case mgkh of
Nothing -> pure ExportPublic
Just gkh -> do
gk <- runExceptT (readGK0 sto gkh) >>= orThrowUser "failed to read encryption key"
pure $ ExportPrivateGK gk
pKey :: GitPerks m => Parser (GitCLI m ()) pKey :: GitPerks m => Parser (GitCLI m ())
pKey = hsubparser ( command "show" (info pKeyShow (progDesc "show current key")) pKey = hsubparser ( command "show" (info pKeyShow (progDesc "show current key"))

View File

@ -35,7 +35,7 @@ data GitOption = GitTrace
| GitExport ExportType | GitExport ExportType
| GitEnc ExportEncryption | GitEnc ExportEncryption
| GitDontApplyHeads | GitDontApplyHeads
deriving stock (Eq,Ord) deriving stock (Eq)
@ -93,6 +93,7 @@ newGitEnv :: GitPerks m
newGitEnv p opts path cpath conf peer reflog rchan lww sto = do newGitEnv p opts path cpath conf peer reflog rchan lww sto = do
let dbfile = cpath </> "state.db" let dbfile = cpath </> "state.db"
let dOpt = dbPipeOptsDef { dbLogger = \x -> debug ("state:" <+> pretty x) } let dOpt = dbPipeOptsDef { dbLogger = \x -> debug ("state:" <+> pretty x) }
let manifestUpdateEnv = Nothing
db <- newDBPipeEnv dOpt dbfile db <- newDBPipeEnv dOpt dbfile
cache <- newTVarIO mempty cache <- newTVarIO mempty
pure $ GitEnv pure $ GitEnv
@ -101,6 +102,7 @@ newGitEnv p opts path cpath conf peer reflog rchan lww sto = do
applyHeadsOpt applyHeadsOpt
exportType exportType
exportEnc exportEnc
manifestUpdateEnv
path path
cpath cpath
conf conf

View File

@ -6,6 +6,8 @@ import HBS2.Git.Client.Prelude hiding (info)
import HBS2.Git.Client.Progress import HBS2.Git.Client.Progress
import HBS2.Git.Data.GK
import HBS2.Net.Auth.GroupKeySymm import HBS2.Net.Auth.GroupKeySymm
import Data.Config.Suckless import Data.Config.Suckless
@ -20,7 +22,8 @@ data ExportType = ExportNew
data ExportEncryption = data ExportEncryption =
ExportPublic ExportPublic
| ExportPrivate FilePath | ExportPrivate FilePath
deriving stock (Eq,Ord,Generic,Show) | ExportPrivateGK GK0
deriving stock (Eq)
type Config = [Syntax C] type Config = [Syntax C]
@ -30,24 +33,30 @@ class Monad m => HasProgressIndicator m where
class HasAPI api proto m where class HasAPI api proto m where
getAPI :: m (ServiceCaller api proto) getAPI :: m (ServiceCaller api proto)
data ManifestUpdateEnv =
ManifestUpdateEnv
{ _manifest :: (Text, Text, Maybe Text)
}
data GitEnv = data GitEnv =
GitEnv GitEnv
{ _gitTraceEnabled :: Bool { _gitTraceEnabled :: Bool
, _gitDebugEnabled :: Bool , _gitDebugEnabled :: Bool
, _gitApplyHeads :: Bool , _gitApplyHeads :: Bool
, _gitExportType :: ExportType , _gitExportType :: ExportType
, _gitExportEnc :: ExportEncryption , _gitExportEnc :: ExportEncryption
, _gitPath :: FilePath , _gitManifestUpdateEnv :: Maybe ManifestUpdateEnv
, _configPath :: FilePath , _gitPath :: FilePath
, _config :: Config , _configPath :: FilePath
, _peerAPI :: ServiceCaller PeerAPI UNIX , _config :: Config
, _refLogAPI :: ServiceCaller RefLogAPI UNIX , _peerAPI :: ServiceCaller PeerAPI UNIX
, _refChanAPI :: ServiceCaller RefChanAPI UNIX , _refLogAPI :: ServiceCaller RefLogAPI UNIX
, _lwwRefAPI :: ServiceCaller LWWRefAPI UNIX , _refChanAPI :: ServiceCaller RefChanAPI UNIX
, _storage :: AnyStorage -- ServiceCaller StorageAPI UNIX , _lwwRefAPI :: ServiceCaller LWWRefAPI UNIX
, _db :: DBPipeEnv , _storage :: AnyStorage -- ServiceCaller StorageAPI UNIX
, _progress :: AnyProgress , _db :: DBPipeEnv
, _keyringCache :: TVar (HashMap HashRef [KeyringEntry 'HBS2Basic]) , _progress :: AnyProgress
, _keyringCache :: TVar (HashMap HashRef [KeyringEntry 'HBS2Basic])
} }

View File

@ -1,4 +1,4 @@
module HBS2.Git.Client.Config (getConfigDir, readConfig, getManifest, hbs2Name) where module HBS2.Git.Client.Config (getConfigDir, readConfig, hbs2Name) where
import HBS2.Git.Client.Prelude import HBS2.Git.Client.Prelude
import HBS2.Git.Client.App.Types import HBS2.Git.Client.App.Types
@ -6,8 +6,6 @@ import HBS2.Git.Client.App.Types
import HBS2.System.Dir import HBS2.System.Dir
import HBS2.Git.Local.CLI import HBS2.Git.Local.CLI
import Data.List qualified as L
import Data.Text qualified as Text
import Data.Either import Data.Either
import Text.InterpolatedString.Perl6 (qc) import Text.InterpolatedString.Perl6 (qc)
@ -34,31 +32,6 @@ getConfigDir = do
else do else do
pure $ git </> ".hbs2-git" pure $ git </> ".hbs2-git"
getManifest :: GitPerks m => m (Text, Text, Maybe Text)
getManifest = do
dir <- getConfigDir
let mf = dir </> "manifest"
let defname = takeFileName (takeDirectory dir) & Text.pack
let defbrief = "n/a"
content <- liftIO (try @_ @IOException $ readFile mf)
<&> fromRight ""
let txt = if L.null content then Nothing else Just (Text.pack content)
-- FIXME: size-hardcode
let header = lines (take 1024 content)
& takeWhile ( not . L.null )
& unlines
& parseTop
& fromRight mempty
let name = lastDef defname [ n | ListVal [ SymbolVal "name:", LitStrVal n ] <- header ]
let brief = lastDef defbrief [ n | ListVal [ SymbolVal "brief:", LitStrVal n ] <- header ]
pure (name,brief,txt)
readConfig :: (GitPerks m) => Bool -> m Config readConfig :: (GitPerks m) => Bool -> m Config
readConfig canTouch = do readConfig canTouch = do
{- HLINT ignore "Functor law" -} {- HLINT ignore "Functor law" -}

View File

@ -3,7 +3,7 @@ module HBS2.Git.Client.Export (export) where
import HBS2.Git.Client.Prelude hiding (info) import HBS2.Git.Client.Prelude hiding (info)
import HBS2.Git.Client.App.Types import HBS2.Git.Client.App.Types
import HBS2.Git.Client.Config import HBS2.Git.Client.Manifest
import HBS2.Git.Client.RefLog import HBS2.Git.Client.RefLog
import HBS2.Git.Client.State import HBS2.Git.Client.State
import HBS2.Git.Client.Progress import HBS2.Git.Client.Progress
@ -142,8 +142,10 @@ storeNewGK0 = do
sto <- asks _storage sto <- asks _storage
enc <- asks _gitExportEnc enc <- asks _gitExportEnc
runMaybeT do runMaybeT do
gkf <- headMay [ f | ExportPrivate f <- [enc] ] & toMPlus gk <- case enc of
gk <- loadGK0FromFile gkf >>= toMPlus ExportPrivate f -> loadGK0FromFile f >>= toMPlus
ExportPrivateGK k -> toMPlus $ Just k
_ -> toMPlus Nothing
epoch <- getEpoch epoch <- getEpoch
writeAsMerkle sto (serialise gk) <&> HashRef <&> (,epoch) writeAsMerkle sto (serialise gk) <&> HashRef <&> (,epoch)
@ -160,6 +162,7 @@ export key refs = do
git <- asks _gitPath git <- asks _gitPath
sto <- asks _storage sto <- asks _storage
new <- asks _gitExportType <&> (== ExportNew) new <- asks _gitExportType <&> (== ExportNew)
manifestUpdateEnv <- asks _gitManifestUpdateEnv
reflog <- asks _refLogAPI reflog <- asks _refLogAPI
ip <- asks _progress ip <- asks _progress
@ -194,7 +197,10 @@ export key refs = do
let rh0 = snd <$> rh let rh0 = snd <$> rh
(name,brief,mf) <- lift getManifest (name,brief,mf) <- case manifestUpdateEnv of
-- TODO: do not update manifest if not needed
Nothing -> lift $ getLastManifestFromStorage key
Just (ManifestUpdateEnv manifest) -> pure manifest
gk0new0 <- loadNewGK0 puk tx0 gk0new0 <- loadNewGK0 puk tx0
@ -226,7 +232,9 @@ export key refs = do
objs <- lift enumAllGitObjects objs <- lift enumAllGitObjects
>>= withState . filterM (notInTx tx0) >>= withState . filterM (notInTx tx0)
when (null objs && not new && oldRefs == myrefs) do let updateManifest = isJust manifestUpdateEnv
when (null objs && not new && oldRefs == myrefs && not updateManifest) do
exit () exit ()
debug $ red "REFS-FOR-EXPORT:" <+> pretty myrefs debug $ red "REFS-FOR-EXPORT:" <+> pretty myrefs

View File

@ -0,0 +1,48 @@
module HBS2.Git.Client.Manifest (getLastManifestFromStorage, addManifestBriefAndName) where
import Data.Coerce
import Data.Either
import Data.List qualified as L
import Data.Maybe
import Data.Text qualified as Text
import HBS2.Git.Client.App.Types
import HBS2.Git.Client.Config
import HBS2.Git.Client.Prelude
import HBS2.Git.Client.State
import HBS2.Git.Data.RepoHead
import HBS2.Storage.Operations.ByteString
import HBS2.System.Dir
addManifestBriefAndName :: (GitPerks m) => Maybe Text -> m (Text, Text, Maybe Text)
addManifestBriefAndName manifest = do
dir <- getConfigDir
let defBrief = "n/a"
defName = takeFileName (takeDirectory dir) & Text.pack
-- FIXME: size-hardcode
header =
lines (take 1024 (Text.unpack $ fromMaybe "" manifest))
& takeWhile (not . L.null)
& unlines
& parseTop
& fromRight mempty
name = lastDef defName [n | ListVal [SymbolVal "name:", LitStrVal n] <- header]
brief = lastDef defBrief [n | ListVal [SymbolVal "brief:", LitStrVal n] <- header]
pure (name, brief, manifest)
getLastManifestFromStorage ::
( MonadReader GitEnv m,
GitPerks m
) =>
LWWRefKey 'HBS2Basic ->
m (Text, Text, Maybe Text)
getLastManifestFromStorage lwwref = do
manifest <- runMaybeT do
sto <- asks _storage
headRef <- MaybeT $ withState $ selectLastRepoHeadFor lwwref
rhead <-
runExceptT (readFromMerkle sto (SimpleKey (coerce headRef)))
>>= toMPlus
<&> deserialiseOrFail @RepoHead
>>= toMPlus
MaybeT $ pure $ _repoManifest rhead
addManifestBriefAndName manifest

View File

@ -401,7 +401,7 @@ SELECT hash, seq, reflog FROM lww
selectRepoHeadsFor :: (MonadIO m, HasStorage m) selectRepoHeadsFor :: (MonadIO m)
=> SortOrder => SortOrder
-> LWWRefKey 'HBS2Basic -> LWWRefKey 'HBS2Basic
-> DBPipeM m [TaggedHashRef RepoHead] -> DBPipeM m [TaggedHashRef RepoHead]
@ -417,6 +417,21 @@ 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
selectLastRepoHeadFor :: (MonadIO m)
=> LWWRefKey 'HBS2Basic
-> DBPipeM m (Maybe (TaggedHashRef RepoHead))
selectLastRepoHeadFor what = do
let q = [qc|
SELECT t.head
FROM lww l join tx t on l.reflog = t.reflog
WHERE l.hash = ?
ORDER BY t.seq DESC
LIMIT 1
|]
select @(Only (TaggedHashRef RepoHead)) q (Only $ Base58Field what)
<&> (fmap fromOnly . listToMaybe)
instance (Monad m, HasStorage m) => HasStorage (DBPipeM m) where instance (Monad m, HasStorage m) => HasStorage (DBPipeM m) where
getStorage = lift getStorage getStorage = lift getStorage

View File

@ -116,6 +116,7 @@ library
HBS2.Git.Client.Export HBS2.Git.Client.Export
HBS2.Git.Client.Import HBS2.Git.Client.Import
HBS2.Git.Client.Progress HBS2.Git.Client.Progress
HBS2.Git.Client.Manifest
build-depends: base build-depends: base
, base16-bytestring , base16-bytestring