MailboxRefKey boilerplate

This commit is contained in:
voidlizard 2024-10-11 05:41:33 +03:00
parent 549a64a6c0
commit d69ea63319
3 changed files with 42 additions and 0 deletions

View File

@ -166,6 +166,7 @@ library
HBS2.Peer.Proto.Mailbox.Types
HBS2.Peer.Proto.Mailbox.Message
HBS2.Peer.Proto.Mailbox.Entry
HBS2.Peer.Proto.Mailbox.Ref
HBS2.Peer.Proto.BrowserPlugin
HBS2.Peer.RPC.Client

View File

@ -4,6 +4,7 @@ module HBS2.Peer.Proto.Mailbox
( module HBS2.Peer.Proto.Mailbox
, module HBS2.Peer.Proto.Mailbox.Message
, module HBS2.Peer.Proto.Mailbox.Types
, module HBS2.Peer.Proto.Mailbox.Ref
) where
import HBS2.Prelude.Plated
@ -17,6 +18,7 @@ import HBS2.Actors.Peer.Types
import HBS2.Peer.Proto.Mailbox.Types
import HBS2.Peer.Proto.Mailbox.Message
import HBS2.Peer.Proto.Mailbox.Entry
import HBS2.Peer.Proto.Mailbox.Ref
import Data.Maybe
import Control.Monad.Trans.Cont

View File

@ -0,0 +1,39 @@
{-# Language UndecidableInstances #-}
module HBS2.Peer.Proto.Mailbox.Ref where
import HBS2.Prelude
import HBS2.Hash
import HBS2.Base58
import HBS2.Net.Proto.Types
import HBS2.Data.Types.Refs
import Data.Maybe (fromMaybe)
import Data.Hashable hiding (Hashed)
newtype MailboxRefKey s = MailboxRefKey (PubKey 'Sign s)
instance RefMetaData (MailboxRefKey s)
deriving stock instance IsRefPubKey s => Eq (MailboxRefKey s)
instance (IsRefPubKey s) => Hashable (MailboxRefKey s) where
hashWithSalt s k = hashWithSalt s (hashObject @HbSync k)
instance (IsRefPubKey s) => Hashed HbSync (MailboxRefKey s) where
hashObject (MailboxRefKey pk) = hashObject ("mailboxv1|" <> serialise pk)
instance IsRefPubKey s => FromStringMaybe (MailboxRefKey s) where
fromStringMay s = MailboxRefKey <$> fromStringMay s
instance IsRefPubKey s => IsString (MailboxRefKey s) where
fromString s = fromMaybe (error "bad public key base58") (fromStringMay s)
instance Pretty (AsBase58 (PubKey 'Sign s)) => Pretty (AsBase58 (MailboxRefKey s)) where
pretty (AsBase58 (MailboxRefKey k)) = pretty (AsBase58 k)
instance Pretty (AsBase58 (PubKey 'Sign s)) => Pretty (MailboxRefKey s) where
pretty (MailboxRefKey k) = pretty (AsBase58 k)