Move types

This commit is contained in:
Sergey Ivanov 2023-07-18 21:37:02 +04:00
parent fec0c23a7f
commit 9bad166566
14 changed files with 86 additions and 42 deletions

View File

@ -59,6 +59,7 @@ common shared-properties
, TupleSections , TupleSections
, TypeApplications , TypeApplications
, TypeFamilies , TypeFamilies
, TemplateHaskell
@ -74,6 +75,7 @@ library
, HBS2.Data.Detect , HBS2.Data.Detect
, HBS2.Data.Types , HBS2.Data.Types
, HBS2.Data.Types.Crypto , HBS2.Data.Types.Crypto
, HBS2.Data.Types.Peer
, HBS2.Data.Types.Refs , HBS2.Data.Types.Refs
, HBS2.Defaults , HBS2.Defaults
, HBS2.Events , HBS2.Events

View File

@ -7,6 +7,7 @@ module HBS2.Actors.Peer where
import HBS2.Actors import HBS2.Actors
import HBS2.Clock import HBS2.Clock
import HBS2.Data.Types.Peer
import HBS2.Defaults import HBS2.Defaults
import HBS2.Events import HBS2.Events
import HBS2.Hash import HBS2.Hash
@ -30,6 +31,7 @@ import Data.Cache (Cache)
import Data.Cache qualified as Cache import Data.Cache qualified as Cache
import Data.Dynamic import Data.Dynamic
import Data.Foldable hiding (find) import Data.Foldable hiding (find)
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
@ -155,6 +157,7 @@ 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)))
} }
newtype PeerM e m a = PeerM { fromPeerM :: ReaderT (PeerEnv e) m a } newtype PeerM e m a = PeerM { fromPeerM :: ReaderT (PeerEnv e) m a }

View File

@ -1,13 +1,13 @@
module HBS2.Data.Types module HBS2.Data.Types
( module HBS2.Hash ( module X
, module HBS2.Data.Types.Refs
-- , module HBS2.Data.Types.Crypto -- , module HBS2.Data.Types.Crypto
, AsSyntax(..) , AsSyntax(..)
) )
where where
import HBS2.Hash import HBS2.Hash as X
import HBS2.Data.Types.Refs import HBS2.Data.Types.Refs as X
import HBS2.Data.Types.Peer as X
-- import HBS2.Data.Types.Crypto -- import HBS2.Data.Types.Crypto
-- import Data.Config.Suckless -- import Data.Config.Suckless

View File

@ -1,4 +1,29 @@
module HBS2.Data.Types.Crypto where module HBS2.Data.Types.Crypto where
import Codec.Serialise
import Crypto.Saltine.Core.Box qualified as Encrypt
import Crypto.Saltine.Core.Sign qualified as Sign
import HBS2.Net.Auth.Credentials
import HBS2.Net.Proto.Types
import HBS2.Prelude
-- type SignPubKey = () -- type SignPubKey = ()
-- type EncryptPubKey = () -- type EncryptPubKey = ()
type instance PubKey 'Sign HBS2Basic = Sign.PublicKey
type instance PrivKey 'Sign HBS2Basic = Sign.SecretKey
type instance PubKey 'Encrypt HBS2Basic = Encrypt.PublicKey
type instance PrivKey 'Encrypt HBS2Basic = Encrypt.SecretKey
instance Serialise Sign.PublicKey
instance Serialise Encrypt.PublicKey
instance Serialise Sign.SecretKey
instance Serialise Encrypt.SecretKey
instance Serialise Sign.Signature
instance Signatures HBS2Basic where
type Signature HBS2Basic = Sign.Signature
makeSign = Sign.signDetached
verifySign = Sign.signVerifyDetached

View File

@ -0,0 +1,30 @@
{-# Language UndecidableInstances #-}
module HBS2.Data.Types.Peer where
import Data.ByteString qualified as BS
import Lens.Micro.Platform
import HBS2.Prelude
import HBS2.Data.Types.Crypto
import HBS2.Net.Auth.Credentials
import HBS2.Net.Proto.Types
type PingSign e = Signature (Encryption e)
type PingNonce = BS.ByteString
data PeerData e =
PeerData
{ _peerSignKey :: PubKey 'Sign (Encryption e)
, _peerOwnNonce :: PeerNonce -- TODO: to use this field to detect if it's own peer to avoid loops
}
deriving stock (Typeable,Generic)
deriving instance
( Show (PubKey 'Sign (Encryption e))
, Show (Nonce ())
)
=> Show (PeerData e)
makeLenses 'PeerData

View File

@ -7,6 +7,7 @@ module HBS2.Net.Proto.Definition
where where
import HBS2.Clock import HBS2.Clock
import HBS2.Data.Types.Crypto
import HBS2.Defaults import HBS2.Defaults
import HBS2.Hash import HBS2.Hash
import HBS2.Net.Auth.Credentials import HBS2.Net.Auth.Credentials
@ -32,15 +33,11 @@ import Crypto.Saltine.Class qualified as Crypto
import Crypto.Saltine.Core.Sign qualified as Sign import Crypto.Saltine.Core.Sign qualified as Sign
import Crypto.Saltine.Core.Box qualified as Encrypt import Crypto.Saltine.Core.Box qualified as Encrypt
import HBS2.Data.Types.Crypto
type instance Encryption L4Proto = HBS2Basic type instance Encryption L4Proto = HBS2Basic
type instance PubKey 'Sign HBS2Basic = Sign.PublicKey
type instance PrivKey 'Sign HBS2Basic = Sign.SecretKey
type instance PubKey 'Encrypt HBS2Basic = Encrypt.PublicKey
type instance PrivKey 'Encrypt HBS2Basic = Encrypt.SecretKey
-- FIXME: proper-serialise-for-keys -- FIXME: proper-serialise-for-keys
-- Возможно, нужно написать ручные инстансы Serialise -- Возможно, нужно написать ручные инстансы Serialise
-- использовать encode/decode для каждого инстанса ниже $(c:end + 4) -- использовать encode/decode для каждого инстанса ниже $(c:end + 4)
@ -48,11 +45,6 @@ type instance PrivKey 'Encrypt HBS2Basic = Encrypt.SecretKey
-- но возможно, будет работать и так, ведь ключи -- но возможно, будет работать и так, ведь ключи
-- это же всего лишь байтстроки внутри. -- это же всего лишь байтстроки внутри.
instance Serialise Sign.PublicKey
instance Serialise Encrypt.PublicKey
instance Serialise Sign.SecretKey
instance Serialise Encrypt.SecretKey
deserialiseCustom :: (Serialise a, MonadPlus m) => ByteString -> m a deserialiseCustom :: (Serialise a, MonadPlus m) => ByteString -> m a
deserialiseCustom = either (const mzero) pure . deserialiseOrFail deserialiseCustom = either (const mzero) pure . deserialiseOrFail
-- deserialiseCustom = either (\msg -> trace ("deserialiseCustom: " <> show msg) mzero) pure . deserialiseOrFail -- deserialiseCustom = either (\msg -> trace ("deserialiseCustom: " <> show msg) mzero) pure . deserialiseOrFail
@ -194,13 +186,6 @@ instance MonadIO m => HasNonces () m where
n <- liftIO ( Encrypt.newNonce <&> Crypto.encode ) n <- liftIO ( Encrypt.newNonce <&> Crypto.encode )
pure $ BS.take 32 n pure $ BS.take 32 n
instance Serialise Sign.Signature
instance Signatures HBS2Basic where
type Signature HBS2Basic = Sign.Signature
makeSign = Sign.signDetached
verifySign = Sign.signVerifyDetached
instance Asymm HBS2Basic where instance Asymm HBS2Basic where
type AsymmKeypair HBS2Basic = Encrypt.Keypair type AsymmKeypair HBS2Basic = Encrypt.Keypair
type AsymmPrivKey HBS2Basic = Encrypt.SecretKey type AsymmPrivKey HBS2Basic = Encrypt.SecretKey

View File

@ -1,6 +1,7 @@
module HBS2.Net.Proto.Event.PeerExpired where module HBS2.Net.Proto.Event.PeerExpired where
import HBS2.Clock import HBS2.Clock
import HBS2.Data.Types.Peer
import HBS2.Events import HBS2.Events
import HBS2.Net.Proto import HBS2.Net.Proto
import HBS2.Net.Proto.Peer import HBS2.Net.Proto.Peer

View File

@ -23,24 +23,6 @@ import Data.String.Conversions (cs)
import Lens.Micro.Platform import Lens.Micro.Platform
import Type.Reflection (someTypeRep) import Type.Reflection (someTypeRep)
type PingSign e = Signature (Encryption e)
type PingNonce = BS.ByteString
data PeerData e =
PeerData
{ _peerSignKey :: PubKey 'Sign (Encryption e)
, _peerOwnNonce :: PeerNonce -- TODO: to use this field to detect if it's own peer to avoid loops
}
deriving stock (Typeable,Generic)
deriving instance
( Show (PubKey 'Sign (Encryption e))
, Show (Nonce ())
)
=> Show (PeerData e)
makeLenses 'PeerData
data PeerHandshake e = data PeerHandshake e =
PeerPing PingNonce PeerPing PingNonce
| PeerPong PingNonce (Signature (Encryption e)) (PeerData e) | PeerPong PingNonce (Signature (Encryption e)) (PeerData e)

View File

@ -1,6 +1,7 @@
module HBS2.Prelude module HBS2.Prelude
( module Data.String ( module Data.String
, module Safe , module Safe
, module X
, MonadIO(..) , MonadIO(..)
, void, guard, when, unless , void, guard, when, unless
, maybe1 , maybe1
@ -17,6 +18,9 @@ module HBS2.Prelude
, Text.Text , Text.Text
) where ) where
import Data.Typeable as X
import GHC.Generics as X (Generic)
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.String (IsString(..)) import Data.String (IsString(..))
import Safe import Safe

View File

@ -1,6 +1,7 @@
{-# Language AllowAmbiguousTypes #-} {-# Language AllowAmbiguousTypes #-}
module Bootstrap where module Bootstrap where
import HBS2.Data.Types.Peer
import HBS2.Prelude import HBS2.Prelude
import HBS2.Net.Proto.Types import HBS2.Net.Proto.Types
import HBS2.Net.Proto.Peer import HBS2.Net.Proto.Peer

View File

@ -4,6 +4,7 @@ module PeerInfo where
import HBS2.Actors.Peer import HBS2.Actors.Peer
import HBS2.Clock import HBS2.Clock
import HBS2.Data.Types
import HBS2.Events import HBS2.Events
import HBS2.Net.Auth.Credentials import HBS2.Net.Auth.Credentials
import HBS2.Net.PeerLocator import HBS2.Net.PeerLocator

View File

@ -11,6 +11,7 @@ import HBS2.Clock
import HBS2.Defaults import HBS2.Defaults
import HBS2.Events import HBS2.Events
import HBS2.Hash import HBS2.Hash
import HBS2.Data.Types
import HBS2.Data.Types.Refs (RefLogKey(..)) import HBS2.Data.Types.Refs (RefLogKey(..))
import HBS2.Merkle import HBS2.Merkle
import HBS2.Net.Auth.Credentials import HBS2.Net.Auth.Credentials
@ -576,12 +577,19 @@ runPeer opts = U.handle (\e -> myException e
void $ async $ runMessagingTCP tcpEnv void $ async $ runMessagingTCP tcpEnv
pure $ Just tcpEnv pure $ Just tcpEnv
proxy <- newProxyMessaging mess tcp (proxy, penv) <- mdo
proxy <- newProxyMessaging mess tcp >>= \p -> do
pure p
{ _proxy_getEncryptionKey = undefined
, _proxy_clearEncryptionKey = undefined
, _proxy_sendResetEncryptionKeys = undefined
, _proxy_sendBeginEncryptionExchange = undefined
}
penv <- newPeerEnv (AnyStorage s) (Fabriq proxy) (getOwnPeer mess)
pure (proxy, penv)
proxyThread <- async $ runProxyMessaging proxy proxyThread <- async $ runProxyMessaging proxy
penv <- newPeerEnv (AnyStorage s) (Fabriq proxy) (getOwnPeer mess)
let peerMeta = mkPeerMeta conf penv let peerMeta = mkPeerMeta conf penv
nbcache <- liftIO $ Cache.newCache (Just $ toTimeSpec ( 600 :: Timeout 'Seconds)) nbcache <- liftIO $ Cache.newCache (Just $ toTimeSpec ( 600 :: Timeout 'Seconds))

View File

@ -6,6 +6,7 @@ module PeerTypes where
import HBS2.Actors.Peer import HBS2.Actors.Peer
import HBS2.Clock import HBS2.Clock
import HBS2.Data.Types.Peer
import HBS2.Defaults import HBS2.Defaults
import HBS2.Events import HBS2.Events
import HBS2.Hash import HBS2.Hash

View File

@ -107,6 +107,7 @@ common shared-properties
, OverloadedStrings , OverloadedStrings
, QuasiQuotes , QuasiQuotes
, RecordWildCards , RecordWildCards
, RecursiveDo
, ScopedTypeVariables , ScopedTypeVariables
, StandaloneDeriving , StandaloneDeriving
, TupleSections , TupleSections