mirror of https://github.com/voidlizard/hbs2
wip
This commit is contained in:
parent
e405142b8c
commit
d30207f838
|
@ -43,7 +43,7 @@ findFilesBy fp = liftIO do
|
||||||
|
|
||||||
findKeyRing :: forall s m . ( MonadUnliftIO m
|
findKeyRing :: forall s m . ( MonadUnliftIO m
|
||||||
, SerialisedCredentials s
|
, SerialisedCredentials s
|
||||||
, For'HBS2Basic s
|
, ForHBS2Basic s
|
||||||
)
|
)
|
||||||
=> [FilePattern]
|
=> [FilePattern]
|
||||||
-> PubKey 'Sign s
|
-> PubKey 'Sign s
|
||||||
|
@ -68,7 +68,7 @@ findKeyRing fp kr = do
|
||||||
findKeyRingEntries :: forall s m . ( MonadUnliftIO m
|
findKeyRingEntries :: forall s m . ( MonadUnliftIO m
|
||||||
, SerialisedCredentials s
|
, SerialisedCredentials s
|
||||||
, Hashable (PubKey 'Encrypt s)
|
, Hashable (PubKey 'Encrypt s)
|
||||||
-- , For'HBS2Basic s
|
-- , ForHBS2Basic s
|
||||||
)
|
)
|
||||||
=> [FilePattern]
|
=> [FilePattern]
|
||||||
-> [PubKey 'Encrypt s]
|
-> [PubKey 'Encrypt s]
|
||||||
|
|
|
@ -23,6 +23,9 @@ newtype HashRef = HashRef { fromHashRef :: Hash HbSync }
|
||||||
deriving newtype (Eq,Ord,IsString,Pretty,Hashable,Hashed HbSync)
|
deriving newtype (Eq,Ord,IsString,Pretty,Hashable,Hashed HbSync)
|
||||||
deriving stock (Data,Generic,Show)
|
deriving stock (Data,Generic,Show)
|
||||||
|
|
||||||
|
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
|
instance Pretty (AsBase58 HashRef) where
|
||||||
pretty (AsBase58 x) = pretty x
|
pretty (AsBase58 x) = pretty x
|
||||||
|
@ -65,6 +68,7 @@ data SequentialRef =
|
||||||
instance Serialise AnnotatedHashRef
|
instance Serialise AnnotatedHashRef
|
||||||
instance Serialise SequentialRef
|
instance Serialise SequentialRef
|
||||||
instance Serialise HashRef
|
instance Serialise HashRef
|
||||||
|
instance Serialise (TaggedHashRef e)
|
||||||
|
|
||||||
|
|
||||||
type IsRefPubKey s = ( Eq (PubKey 'Sign s)
|
type IsRefPubKey s = ( Eq (PubKey 'Sign s)
|
||||||
|
|
|
@ -90,7 +90,7 @@ data PeerCredentials s =
|
||||||
makeLenses 'KeyringEntry
|
makeLenses 'KeyringEntry
|
||||||
makeLenses 'PeerCredentials
|
makeLenses 'PeerCredentials
|
||||||
|
|
||||||
type For'HBS2Basic s = ( Signatures s
|
type ForHBS2Basic s = ( Signatures s
|
||||||
, PrivKey 'Sign s ~ Sign.SecretKey
|
, PrivKey 'Sign s ~ Sign.SecretKey
|
||||||
, PubKey 'Sign s ~ Sign.PublicKey
|
, PubKey 'Sign s ~ Sign.PublicKey
|
||||||
, Eq (PubKey 'Encrypt 'HBS2Basic)
|
, Eq (PubKey 'Encrypt 'HBS2Basic)
|
||||||
|
@ -147,7 +147,7 @@ addKeyPair txt cred = do
|
||||||
pure $ cred & over peerKeyring (List.nub . (<> [kp]))
|
pure $ cred & over peerKeyring (List.nub . (<> [kp]))
|
||||||
|
|
||||||
delKeyPair :: forall e m . ( MonadIO m
|
delKeyPair :: forall e m . ( MonadIO m
|
||||||
, For'HBS2Basic e
|
, ForHBS2Basic e
|
||||||
)
|
)
|
||||||
=> AsBase58 String -> PeerCredentials e -> m (PeerCredentials e)
|
=> AsBase58 String -> PeerCredentials e -> m (PeerCredentials e)
|
||||||
delKeyPair (AsBase58 pks) cred = do
|
delKeyPair (AsBase58 pks) cred = do
|
||||||
|
@ -157,7 +157,7 @@ delKeyPair (AsBase58 pks) cred = do
|
||||||
pure $ cred & set peerKeyring rest
|
pure $ cred & set peerKeyring rest
|
||||||
|
|
||||||
|
|
||||||
parseCredentials :: forall s . ( -- For'HBS2Basic s
|
parseCredentials :: forall s . ( -- ForHBS2Basic s
|
||||||
SerialisedCredentials s
|
SerialisedCredentials s
|
||||||
)
|
)
|
||||||
=> AsCredFile ByteString -> Maybe (PeerCredentials s)
|
=> AsCredFile ByteString -> Maybe (PeerCredentials s)
|
||||||
|
|
|
@ -217,7 +217,7 @@ pSendRepoNotify :: GitPerks m => Parser (GitCLI m ())
|
||||||
pSendRepoNotify = do
|
pSendRepoNotify = do
|
||||||
notifyChan <- argument pRefChanId (metavar "CHANNEL-KEY")
|
notifyChan <- argument pRefChanId (metavar "CHANNEL-KEY")
|
||||||
pure do
|
pure do
|
||||||
notice "JOPA"
|
notice "wip"
|
||||||
pure ()
|
pure ()
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
|
|
|
@ -87,6 +87,14 @@ data RefChanActionRequest =
|
||||||
|
|
||||||
instance Serialise RefChanActionRequest
|
instance Serialise RefChanActionRequest
|
||||||
|
|
||||||
|
type DisclosedCredentials e = PeerCredentials (Encryption e)
|
||||||
|
|
||||||
|
data RefChanHeadExt e =
|
||||||
|
RefChanDisclosedCredentials (TaggedHashRef (DisclosedCredentials e))
|
||||||
|
deriving stock (Generic)
|
||||||
|
|
||||||
|
instance SerialisedCredentials (Encryption e) => Serialise (RefChanHeadExt e)
|
||||||
|
|
||||||
data RefChanNotify e =
|
data RefChanNotify e =
|
||||||
Notify (RefChanId e) (SignedBox ByteString (Encryption e)) -- подписано ключом автора
|
Notify (RefChanId e) (SignedBox ByteString (Encryption e)) -- подписано ключом автора
|
||||||
-- довольно уместно будет добавить эти команды сюда -
|
-- довольно уместно будет добавить эти команды сюда -
|
||||||
|
@ -97,6 +105,7 @@ data RefChanNotify e =
|
||||||
|
|
||||||
instance ForRefChans e => Serialise (RefChanNotify e)
|
instance ForRefChans e => Serialise (RefChanNotify e)
|
||||||
|
|
||||||
|
|
||||||
newtype instance EventKey e (RefChanNotify e) =
|
newtype instance EventKey e (RefChanNotify e) =
|
||||||
RefChanNotifyEventKey (RefChanId e)
|
RefChanNotifyEventKey (RefChanId e)
|
||||||
|
|
||||||
|
@ -117,6 +126,7 @@ instance Expires (EventKey e (RefChanNotify e)) where
|
||||||
|
|
||||||
|
|
||||||
type ForRefChans e = ( Serialise (PubKey 'Sign (Encryption e))
|
type ForRefChans e = ( Serialise (PubKey 'Sign (Encryption e))
|
||||||
|
, Serialise (PrivKey 'Sign (Encryption e))
|
||||||
, Pretty (AsBase58 (PubKey 'Sign (Encryption e)))
|
, Pretty (AsBase58 (PubKey 'Sign (Encryption e)))
|
||||||
, FromStringMaybe (PubKey 'Sign (Encryption e))
|
, FromStringMaybe (PubKey 'Sign (Encryption e))
|
||||||
, FromStringMaybe (PubKey 'Encrypt (Encryption e))
|
, FromStringMaybe (PubKey 'Encrypt (Encryption e))
|
||||||
|
@ -261,6 +271,7 @@ instance ForRefChans e => FromStringMaybe (RefChanHeadBlock e) where
|
||||||
| (ListVal [SymbolVal "notifier", LitStrVal s] ) <- parsed
|
| (ListVal [SymbolVal "notifier", LitStrVal s] ) <- parsed
|
||||||
]
|
]
|
||||||
|
|
||||||
|
|
||||||
instance (ForRefChans e
|
instance (ForRefChans e
|
||||||
, Pretty (AsBase58 (PubKey 'Sign (Encryption e)))
|
, Pretty (AsBase58 (PubKey 'Sign (Encryption e)))
|
||||||
, Pretty (AsBase58 (PubKey 'Encrypt (Encryption e)))
|
, Pretty (AsBase58 (PubKey 'Encrypt (Encryption e)))
|
||||||
|
@ -284,6 +295,7 @@ instance (ForRefChans e
|
||||||
author p = parens ("author" <+> dquotes (pretty (AsBase58 p)))
|
author p = parens ("author" <+> dquotes (pretty (AsBase58 p)))
|
||||||
reader p = parens ("reader" <+> dquotes (pretty (AsBase58 p)))
|
reader p = parens ("reader" <+> dquotes (pretty (AsBase58 p)))
|
||||||
notifier p = parens ("notifier" <+> dquotes (pretty (AsBase58 p)))
|
notifier p = parens ("notifier" <+> dquotes (pretty (AsBase58 p)))
|
||||||
|
-- disclosed p =
|
||||||
|
|
||||||
lstOf f e | null e = mempty
|
lstOf f e | null e = mempty
|
||||||
| otherwise = vcat (fmap f e) <> line
|
| otherwise = vcat (fmap f e) <> line
|
||||||
|
|
|
@ -183,7 +183,7 @@ runHash opts _ = do
|
||||||
withBinaryFile (hashFp opts) ReadMode $ \h -> do
|
withBinaryFile (hashFp opts) ReadMode $ \h -> do
|
||||||
LBS.hGetContents h >>= print . pretty . hashObject @HbSync
|
LBS.hGetContents h >>= print . pretty . hashObject @HbSync
|
||||||
|
|
||||||
runCat :: forall s . For'HBS2Basic s => CatOpts -> SimpleStorage HbSync -> IO ()
|
runCat :: forall s . ForHBS2Basic s => CatOpts -> SimpleStorage HbSync -> IO ()
|
||||||
|
|
||||||
runCat opts ss | catRaw opts == Just True = do
|
runCat opts ss | catRaw opts == Just True = do
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue