repo head extracted

This commit is contained in:
Dmitry Zuikov 2024-04-17 07:22:26 +03:00
parent 1d4d978d1e
commit b0ef09210c
5 changed files with 41 additions and 28 deletions

View File

@ -27,6 +27,7 @@ newtype TaggedHashRef t = TaggedHashRef { fromTaggedHashRef :: HashRef }
deriving newtype (Eq,Ord,IsString,Pretty,Hashable,Hashed HbSync)
deriving stock (Data,Generic,Show)
instance Pretty (AsBase58 HashRef) where
pretty (AsBase58 x) = pretty x
-- TODO: should be instance Pretty (AsBase58 (Hash HbSync))

View File

@ -0,0 +1,33 @@
module HBS2.Git.Data.RepoHead where
import HBS2.Prelude.Plated
import HBS2.Data.Types.Refs
import HBS2.Git.Local
import Data.Word
import Codec.Serialise
data RepoHeadType = RepoHeadType1
deriving stock (Enum,Generic)
data RepoHeadExt = RepoHeadExt
deriving stock Generic
data RepoHead =
RepoHeadSimple
{ _repoHeadType :: RepoHeadType
, _repoHeadTime :: Word64
, _repoHeadGK0 :: Maybe HashRef
, _repoHeadName :: Text
, _repoHeadBrief :: Text
, _repoManifest :: Maybe Text
, _repoHeadRefs :: [(GitRef, GitHash)]
, _repoHeadExt :: [RepoHeadExt]
}
deriving stock (Generic)
instance Serialise RepoHeadType
instance Serialise RepoHeadExt
instance Serialise RepoHead

View File

@ -1,6 +1,7 @@
module HBS2.Git.Data.Tx.Git
( module HBS2.Git.Data.Tx.Git
, OperationError(..)
, RepoHead(..)
) where
import HBS2.Git.Client.Prelude
@ -16,6 +17,7 @@ import HBS2.Storage.Operations.ByteString
import HBS2.Storage.Operations.Missed
import HBS2.Git.Data.GK
import HBS2.Git.Data.RepoHead
import HBS2.Git.Local
@ -38,29 +40,6 @@ type LBS = LBS.ByteString
type RepoTx = RefLogUpdate L4Proto
data RepoHeadType = RepoHeadType1
deriving stock (Enum,Generic)
data RepoHeadExt = RepoHeadExt
deriving stock Generic
data RepoHead =
RepoHeadSimple
{ _repoHeadType :: RepoHeadType
, _repoHeadTime :: Word64
, _repoHeadGK0 :: Maybe HashRef
, _repoHeadName :: Text
, _repoHeadBrief :: Text
, _repoManifest :: Maybe Text
, _repoHeadRefs :: [(GitRef, GitHash)]
, _repoHeadExt :: [RepoHeadExt]
}
deriving stock (Generic)
instance Serialise RepoHeadType
instance Serialise RepoHeadExt
instance Serialise RepoHead
data TxKeyringNotFound = TxKeyringNotFound
deriving stock (Show, Typeable, Generic)

View File

@ -3,15 +3,14 @@
module HBS2.Git.Data.Tx.Index where
import HBS2.Git.Client.Prelude
import HBS2.Data.Types.Refs
import HBS2.Data.Types.SignedBox
import HBS2.Git.Data.RepoHead
import HBS2.Data.Types.SignedBox
import HBS2.Storage.Operations.Class
import Data.ByteString (ByteString)
import Data.ByteString.Lazy qualified as LBS
import Data.Coerce
import Control.Monad.Identity
import Data.Word
@ -34,6 +33,7 @@ data GitRepoAnnounce s =
GitRepoAnnounce
{ repoLwwRef :: LWWRefKey s
, repoForkInfo :: Maybe (RepoForkInfo s)
, repoHeadInfo :: Maybe (TaggedHashRef RepoHead)
}
deriving stock (Generic)
@ -78,7 +78,7 @@ makeNotificationTx :: forall s . (ForGitIndex s)
-> SignedBox ByteString s
makeNotificationTx ncred lww lwsk forkInfo = do
let creds = coerce ncred :: PeerCredentials s
let annData = GitRepoAnnounce @s lww forkInfo
let annData = GitRepoAnnounce @s lww forkInfo Nothing
let lwpk = coerce lww :: PubKey 'Sign s
let repoAnn = makeSignedBox @s lwpk lwsk (LBS.toStrict $ serialise annData)
makeSignedBox @s (view peerSignPk creds) (view peerSignSk creds) (LBS.toStrict $ serialise repoAnn)
@ -101,4 +101,3 @@ unpackNotificationTx box = do
& orThrowError UnsupportedFormat

View File

@ -102,6 +102,7 @@ library
HBS2.Git.Data.Tx.Git
HBS2.Git.Data.Tx.Index
HBS2.Git.Data.RepoHead
HBS2.Git.Data.GK
HBS2.Git.Data.RefLog
HBS2.Git.Data.LWWBlock