_envEncryptionKeys :: Map -> HashMap

This commit is contained in:
Sergey Ivanov 2023-07-18 22:11:51 +04:00
parent 9bad166566
commit c2c1dd84a0
2 changed files with 25 additions and 3 deletions

View File

@ -35,7 +35,7 @@ import Data.Map (Map)
import Data.Map qualified as Map import Data.Map qualified as Map
import Data.Maybe import Data.Maybe
import GHC.TypeLits import GHC.TypeLits
import Lens.Micro.Platform import Lens.Micro.Platform as Lens
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import Data.HashMap.Strict qualified as HashMap import Data.HashMap.Strict qualified as HashMap
import Control.Concurrent.STM.TVar import Control.Concurrent.STM.TVar
@ -157,9 +157,16 @@ data PeerEnv e =
, _envReqMsgLimit :: Cache (Peer e, Integer, Encoded e) () , _envReqMsgLimit :: Cache (Peer e, Integer, Encoded e) ()
, _envReqProtoLimit :: Cache (Peer e, Integer) () , _envReqProtoLimit :: Cache (Peer e, Integer) ()
, _envAsymmetricKeyPair :: AsymmKeypair (Encryption e) , _envAsymmetricKeyPair :: AsymmKeypair (Encryption e)
, _envEncryptionKeys :: TVar (Map (PeerData L4Proto) (CommonSecret (Encryption L4Proto))) , _envEncryptionKeys :: TVar (HashMap (PeerData L4Proto) (CommonSecret (Encryption L4Proto)))
} }
setEncryptionKey ::
( Hashable (PubKey 'Sign (Encryption L4Proto))
, Hashable PeerNonce
) => PeerEnv L4Proto -> PeerData L4Proto -> Maybe (CommonSecret (Encryption L4Proto)) -> IO ()
setEncryptionKey penv pd msecret =
atomically $ modifyTVar' (_envEncryptionKeys penv) $ Lens.at pd .~ msecret
newtype PeerM e m a = PeerM { fromPeerM :: ReaderT (PeerEnv e) m a } newtype PeerM e m a = PeerM { fromPeerM :: ReaderT (PeerEnv e) m a }
deriving newtype ( Functor deriving newtype ( Functor
, Applicative , Applicative

View File

@ -1,7 +1,9 @@
{-# Language UndecidableInstances #-} {-# Language UndecidableInstances #-}
module HBS2.Data.Types.Peer where module HBS2.Data.Types.Peer where
import Codec.Serialise
import Data.ByteString qualified as BS import Data.ByteString qualified as BS
import Data.Hashable
import Lens.Micro.Platform import Lens.Micro.Platform
import HBS2.Prelude import HBS2.Prelude
@ -20,9 +22,22 @@ data PeerData e =
} }
deriving stock (Typeable,Generic) deriving stock (Typeable,Generic)
deriving instance
( Eq (PubKey 'Sign (Encryption e))
, Eq PeerNonce
)
=> Eq (PeerData e)
instance
( Hashable (PubKey 'Sign (Encryption e))
, Hashable PeerNonce
)
=> Hashable (PeerData e) where
hashWithSalt s PeerData{..} = hashWithSalt s (_peerOwnNonce)
deriving instance deriving instance
( Show (PubKey 'Sign (Encryption e)) ( Show (PubKey 'Sign (Encryption e))
, Show (Nonce ()) , Show PeerNonce
) )
=> Show (PeerData e) => Show (PeerData e)