Commit 18d207f0 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Revert "Add _env_remote_transfer_keys field"

This reverts commit 3ea32b50.
parent 9cc5159a
...@@ -493,8 +493,6 @@ library ...@@ -493,8 +493,6 @@ library
, aeson ^>= 2.1.2.1 , aeson ^>= 2.1.2.1
, ansi-terminal , ansi-terminal
, array ^>= 0.5.4.0 , array ^>= 0.5.4.0
, asn1-encoding >= 0.9.6
, asn1-types
, async ^>= 2.2.4 , async ^>= 2.2.4
, attoparsec ^>= 0.14.4 , attoparsec ^>= 0.14.4
, base64-bytestring ^>= 1.2.1.0 , base64-bytestring ^>= 1.2.1.0
...@@ -515,8 +513,6 @@ library ...@@ -515,8 +513,6 @@ library
, crawlerIsidore , crawlerIsidore
, crawlerPubMed , crawlerPubMed
, cron ^>= 0.7.0 , cron ^>= 0.7.0
, crypton
, crypton-x509
, data-time-segment ^>= 0.1.0.0 , data-time-segment ^>= 0.1.0.0
, deferred-folds >= 0.9.18 && < 0.10 , deferred-folds >= 0.9.18 && < 0.10
, directory ^>= 1.3.7.1 , directory ^>= 1.3.7.1
...@@ -715,10 +711,6 @@ common testDependencies ...@@ -715,10 +711,6 @@ common testDependencies
, bytestring ^>= 0.11.5.3 , bytestring ^>= 0.11.5.3
, cache >= 0.1.3.0 , cache >= 0.1.3.0
, containers ^>= 0.6.7 , containers ^>= 0.6.7
, crawlerArxiv
, cryptohash
, crypton
, directory ^>= 1.3.7.1
, epo-api-client , epo-api-client
, fast-logger ^>= 3.2.2 , fast-logger ^>= 3.2.2
, filepath ^>= 1.4.2.2 , filepath ^>= 1.4.2.2
...@@ -834,7 +826,6 @@ test-suite garg-test-tasty ...@@ -834,7 +826,6 @@ test-suite garg-test-tasty
Test.Offline.Errors Test.Offline.Errors
Test.Offline.JSON Test.Offline.JSON
Test.Offline.Phylo Test.Offline.Phylo
Test.Offline.RemoteTransfer
Test.Offline.Stemming.Lancaster Test.Offline.Stemming.Lancaster
Test.Parsers.Date Test.Parsers.Date
Test.Parsers.Types Test.Parsers.Types
......
...@@ -55,7 +55,7 @@ import Gargantext.API.Errors (BackendInternalError(..), HasAuthenticationError, ...@@ -55,7 +55,7 @@ import Gargantext.API.Errors (BackendInternalError(..), HasAuthenticationError,
import Gargantext.API.Prelude (authenticationError, HasServerError, GargServerC, _ServerError, GargM, IsGargServer) import Gargantext.API.Prelude (authenticationError, HasServerError, GargServerC, _ServerError, GargM, IsGargServer)
import Gargantext.API.Routes.Named qualified as Named import Gargantext.API.Routes.Named qualified as Named
import Gargantext.API.Worker (serveWorkerAPI) import Gargantext.API.Worker (serveWorkerAPI)
import Gargantext.Core.Config (HasJWTSettings(..), HasRemoteTransferKeys(..)) import Gargantext.Core.Config (HasJWTSettings(..))
import Gargantext.Core.Mail (MailModel(..), mail) import Gargantext.Core.Mail (MailModel(..), mail)
import Gargantext.Core.Mail.Types (mailSettings) import Gargantext.Core.Mail.Types (mailSettings)
import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..)) import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..))
...@@ -114,11 +114,7 @@ checkAuthRequest couldBeEmail (GargPassword p) = do ...@@ -114,11 +114,7 @@ checkAuthRequest couldBeEmail (GargPassword p) = do
token <- makeTokenForUser nodeId userLight_id token <- makeTokenForUser nodeId userLight_id
pure $ Valid token nodeId userLight_id pure $ Valid token nodeId userLight_id
auth :: ( HasJWTSettings env auth :: (HasJWTSettings env, HasAuthenticationError err, IsDBCmd env err m)
, HasRemoteTransferKeys env
, HasAuthenticationError err
, IsDBCmd env err m
)
=> AuthRequest -> m AuthResponse => AuthRequest -> m AuthResponse
auth (AuthRequest u p) = do auth (AuthRequest u p) = do
checkAuthRequest' <- checkAuthRequest u p checkAuthRequest' <- checkAuthRequest u p
...@@ -127,9 +123,7 @@ auth (AuthRequest u p) = do ...@@ -127,9 +123,7 @@ auth (AuthRequest u p) = do
throwError $ _AuthenticationError # InvalidUsernameOrPassword throwError $ _AuthenticationError # InvalidUsernameOrPassword
InvalidPassword -> do InvalidPassword -> do
throwError $ _AuthenticationError # InvalidUsernameOrPassword throwError $ _AuthenticationError # InvalidUsernameOrPassword
Valid to trId uId -> do Valid to trId uId -> pure $ AuthResponse to trId uId
(pk, _) <- view remoteTransferKeys
pure $ AuthResponse to trId uId (pubKeyToRemotePubKey pk)
--type instance BasicAuthCfg = BasicAuthData -> IO (AuthResult AuthenticatedUser) --type instance BasicAuthCfg = BasicAuthData -> IO (AuthResult AuthenticatedUser)
......
...@@ -8,9 +8,7 @@ Stability : experimental ...@@ -8,9 +8,7 @@ Stability : experimental
Portability : POSIX Portability : POSIX
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveAnyClass #-}
module Gargantext.API.Admin.Auth.Types module Gargantext.API.Admin.Auth.Types
( -- * Types ( -- * Types
...@@ -29,7 +27,6 @@ module Gargantext.API.Admin.Auth.Types ...@@ -29,7 +27,6 @@ module Gargantext.API.Admin.Auth.Types
, ForgotPasswordResponse(..) , ForgotPasswordResponse(..)
, ForgotPasswordAsyncParams(..) , ForgotPasswordAsyncParams(..)
, ForgotPasswordGet(..) , ForgotPasswordGet(..)
, RemoteTransferPublicKey(..)
-- * Lenses -- * Lenses
, auth_node_id , auth_node_id
...@@ -37,34 +34,22 @@ module Gargantext.API.Admin.Auth.Types ...@@ -37,34 +34,22 @@ module Gargantext.API.Admin.Auth.Types
, authRes_token , authRes_token
, authRes_tree_id , authRes_tree_id
, authRes_user_id , authRes_user_id
, authRes_remote_transfer_pub_key
-- * Combinators -- * Combinators
, pubKeyToRemotePubKey
, remotePubKeyToPubKey
) where ) where
import Crypto.JWT qualified as Jose import Crypto.JWT qualified as Jose
import Crypto.PubKey.RSA qualified as RSA
import Data.Aeson.TH qualified as JSON import Data.Aeson.TH qualified as JSON
import Data.Aeson.Types (genericParseJSON, defaultOptions, genericToJSON) import Data.Aeson.Types (genericParseJSON, defaultOptions, genericToJSON)
import Data.ASN1.BinaryEncoding
import Data.ASN1.Encoding qualified as ASN1
import Data.ASN1.Types (toASN1, fromASN1)
import Data.ByteString.Base64 qualified as Base64
import Data.List (tail) import Data.List (tail)
import Data.Swagger ( ToSchema(..), genericDeclareNamedSchema ) import Data.Swagger ( ToSchema(..), genericDeclareNamedSchema )
import Data.Text.Encoding qualified as TE
import Data.Text qualified as T
import Data.X509 qualified as X509
import Gargantext.Core.Types.Individu (Username, GargPassword(..), arbitraryUsername, arbitraryPassword) import Gargantext.Core.Types.Individu (Username, GargPassword(..), arbitraryUsername, arbitraryPassword)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Admin.Types.Node (NodeId(..), ListId, DocId, UserId (..)) import Gargantext.Database.Admin.Types.Node (NodeId(..), ListId, DocId, UserId (..))
import Gargantext.Prelude hiding (reverse) import Gargantext.Prelude hiding (reverse)
import Prelude (String) import Servant.Auth.Server (CookieSettings, JWTSettings, ToJWT, FromJWT)
import Servant.Auth.Server
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
--------------------------------------------------- ---------------------------------------------------
...@@ -74,38 +59,9 @@ data AuthRequest = AuthRequest { _authReq_username :: Username ...@@ -74,38 +59,9 @@ data AuthRequest = AuthRequest { _authReq_username :: Username
} }
deriving (Generic) deriving (Generic)
newtype RemoteTransferPublicKey =
RemoteTransferPublicKey { _RemoteTransferPublicKey :: T.Text }
deriving stock (Generic, Eq, Show)
deriving newtype (ToJSON, FromJSON)
deriving anyclass (ToSchema)
instance NFData RemoteTransferPublicKey where
pubKeyToRemotePubKey :: RSA.PublicKey -> RemoteTransferPublicKey
pubKeyToRemotePubKey pubKey =
let x509pubKey = X509.PubKeyRSA pubKey
ans1Enc = ASN1.encodeASN1' DER ((toASN1 x509pubKey) [])
in RemoteTransferPublicKey $ TE.decodeUtf8 (Base64.encode ans1Enc)
remotePubKeyToPubKey :: RemoteTransferPublicKey -> Either String RSA.PublicKey
remotePubKeyToPubKey (RemoteTransferPublicKey pkeyTxt) = do
unwrappedB64 <- Base64.decode (TE.encodeUtf8 pkeyTxt)
case ASN1.decodeASN1' DER unwrappedB64 of
Left asn1Err -> Left $ show asn1Err
Right asn1Obj -> do
(x509Ty, _) <- fromASN1 asn1Obj
case x509Ty of
X509.PubKeyRSA pk -> pure (pk { RSA.public_size = 256 })
_ -> Left "remotePubKeyToPubKey: x509 incompatible type found."
data AuthResponse = AuthResponse { _authRes_token :: Token data AuthResponse = AuthResponse { _authRes_token :: Token
, _authRes_tree_id :: TreeId , _authRes_tree_id :: TreeId
, _authRes_user_id :: UserId , _authRes_user_id :: UserId
-- | The remote transfer public key which the
-- browser can save and later use in transfer
-- requests.
, _authRes_remote_transfer_pub_key :: RemoteTransferPublicKey
} }
deriving (Generic, Eq, Show) deriving (Generic, Eq, Show)
...@@ -149,11 +105,10 @@ instance Arbitrary AuthRequest where ...@@ -149,11 +105,10 @@ instance Arbitrary AuthRequest where
instance ToSchema AuthResponse where instance ToSchema AuthResponse where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_authRes_") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_authRes_")
instance Arbitrary AuthResponse where instance Arbitrary AuthResponse where
arbitrary = elements [ AuthResponse to' tr u k arbitrary = elements [ AuthResponse to' tr u
| to' <- ["token0", "token1"] | to' <- ["token0", "token1"]
, tr <- map UnsafeMkNodeId [1..3] , tr <- map UnsafeMkNodeId [1..3]
, u <- map UnsafeMkUserId [1..3] , u <- map UnsafeMkUserId [1..3]
, k <- pure $ RemoteTransferPublicKey "dummy-pubkey"
] ]
data PathId = PathNode NodeId | PathNodeNode ListId DocId data PathId = PathNode NodeId | PathNodeNode ListId DocId
......
...@@ -25,8 +25,7 @@ module Gargantext.API.Admin.EnvTypes ( ...@@ -25,8 +25,7 @@ module Gargantext.API.Admin.EnvTypes (
, env_jwt_settings , env_jwt_settings
, env_pool , env_pool
, env_nodeStory , env_nodeStory
, env_remote_transfer_keys
, menv_firewall , menv_firewall
, dev_env_logger , dev_env_logger
...@@ -36,18 +35,15 @@ module Gargantext.API.Admin.EnvTypes ( ...@@ -36,18 +35,15 @@ module Gargantext.API.Admin.EnvTypes (
, DevJobHandle(..) , DevJobHandle(..)
) where ) where
import Control.Lens hiding (Level, (:<), (.=)) import Control.Lens (to, view)
import Control.Monad.Except
import Control.Monad.Reader
import Crypto.PubKey.RSA.Types qualified as RSA
import Database.PostgreSQL.Simple (Connection)
import Data.List ((\\)) import Data.List ((\\))
import Data.Pool (Pool) import Data.Pool (Pool)
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.Admin.Orchestrator.Types import Database.PostgreSQL.Simple (Connection)
import Gargantext.API.Errors.Types import Gargantext.API.Admin.Orchestrator.Types (JobLog, noJobLog)
import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Prelude (GargM, IsGargServer) import Gargantext.API.Prelude (GargM, IsGargServer)
import Gargantext.Core.Config (GargConfig(..), gc_mail_config, gc_nlp_config, HasJWTSettings(..), HasConfig(..), HasRemoteTransferKeys(..), HasManager(..)) import Gargantext.Core.Config (GargConfig(..), gc_mail_config, gc_nlp_config, HasJWTSettings(..), HasConfig(..), HasManager(..))
import Gargantext.Core.Mail.Types (HasMail, mailSettings) import Gargantext.Core.Mail.Types (HasMail, mailSettings)
import Gargantext.Core.NLP (HasNLPServer(..), nlpServerMap) import Gargantext.Core.NLP (HasNLPServer(..), nlpServerMap)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
...@@ -104,14 +100,13 @@ instance HasLogger (GargM Env BackendInternalError) where ...@@ -104,14 +100,13 @@ instance HasLogger (GargM Env BackendInternalError) where
-- having to specify /everything/. This means that when we /construct/ an 'Env', -- having to specify /everything/. This means that when we /construct/ an 'Env',
-- we need to remember to force the fields to WHNF at that point. -- we need to remember to force the fields to WHNF at that point.
data Env = Env data Env = Env
{ _env_logger :: ~(Logger (GargM Env BackendInternalError)) { _env_logger :: ~(Logger (GargM Env BackendInternalError))
, _env_pool :: ~(Pool Connection) , _env_pool :: ~(Pool Connection)
, _env_nodeStory :: ~NodeStoryEnv , _env_nodeStory :: ~NodeStoryEnv
, _env_manager :: ~Manager , _env_manager :: ~Manager
, _env_config :: ~GargConfig , _env_config :: ~GargConfig
, _env_dispatcher :: ~Dispatcher , _env_dispatcher :: ~Dispatcher
, _env_jwt_settings :: ~JWTSettings , _env_jwt_settings :: ~JWTSettings
, _env_remote_transfer_keys :: ~(RSA.PublicKey, RSA.PrivateKey)
} }
deriving (Generic) deriving (Generic)
...@@ -149,9 +144,6 @@ instance CET.HasCentralExchangeNotification Env where ...@@ -149,9 +144,6 @@ instance CET.HasCentralExchangeNotification Env where
c <- asks (view env_config) c <- asks (view env_config)
liftBase $ CE.notify (_gc_notifications_config c) m liftBase $ CE.notify (_gc_notifications_config c) m
instance HasRemoteTransferKeys Env where
remoteTransferKeys = env_remote_transfer_keys
instance HasManager Env where instance HasManager Env where
gargHttpManager = env_manager gargHttpManager = env_manager
......
...@@ -20,18 +20,17 @@ where ...@@ -20,18 +20,17 @@ where
import Codec.Serialise (Serialise(), serialise) import Codec.Serialise (Serialise(), serialise)
import Crypto.PubKey.RSA qualified as RSA
import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo)
import Data.ByteString.Lazy qualified as L import Data.ByteString.Lazy qualified as L
import Data.Pool (Pool) import Data.Pool (Pool)
import Data.Pool qualified as Pool import Data.Pool qualified as Pool
import Gargantext.API.Admin.EnvTypes import Database.PostgreSQL.Simple (Connection, connect, close, ConnectInfo)
import Gargantext.API.Errors.Types import Gargantext.API.Admin.EnvTypes (Env(..))
import Gargantext.API.Prelude import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Prelude (GargM)
import Gargantext.Core.Notifications.Dispatcher qualified as D
import Gargantext.Core.Config (GargConfig(..)) import Gargantext.Core.Config (GargConfig(..))
import Gargantext.Core.Config.Types (jwtSettings) import Gargantext.Core.Config.Types (jwtSettings)
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory (fromDBNodeStoryEnv)
import Gargantext.Core.Notifications.Dispatcher qualified as D
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging (Logger) import Gargantext.System.Logging (Logger)
import Network.HTTP.Client.TLS (newTlsManager) import Network.HTTP.Client.TLS (newTlsManager)
...@@ -160,7 +159,6 @@ newEnv logger config dispatcher = do ...@@ -160,7 +159,6 @@ newEnv logger config dispatcher = do
!_env_jwt_settings <- jwtSettings (_gc_secrets config) !_env_jwt_settings <- jwtSettings (_gc_secrets config)
_env_remote_transfer_keys <- RSA.generate 256 65537
--_central_exchange <- forkIO $ CE.gServer (_gc_notifications_config config_env) --_central_exchange <- forkIO $ CE.gServer (_gc_notifications_config config_env)
...@@ -176,7 +174,6 @@ newEnv logger config dispatcher = do ...@@ -176,7 +174,6 @@ newEnv logger config dispatcher = do
, _env_config = config , _env_config = config
, _env_dispatcher = dispatcher , _env_dispatcher = dispatcher
, _env_jwt_settings , _env_jwt_settings
, _env_remote_transfer_keys
} }
newPool :: ConnectInfo -> IO (Pool Connection) newPool :: ConnectInfo -> IO (Pool Connection)
......
...@@ -35,19 +35,17 @@ module Gargantext.Core.Config ( ...@@ -35,19 +35,17 @@ module Gargantext.Core.Config (
, HasJWTSettings(..) , HasJWTSettings(..)
, HasConfig(..) , HasConfig(..)
, HasRemoteTransferKeys(..)
, HasManager(..) , HasManager(..)
) where ) where
import Control.Lens (Getter) import Control.Lens (Getter)
import Control.Monad.Logger (LogLevel(LevelDebug)) import Control.Monad.Logger (LogLevel(LevelDebug))
import Crypto.PubKey.RSA qualified as RSA
import Database.PostgreSQL.Simple qualified as PSQL
import Data.Text as T import Data.Text as T
import Database.PostgreSQL.Simple qualified as PSQL
import Gargantext.Core.Config.Mail (MailConfig) import Gargantext.Core.Config.Mail (MailConfig)
import Gargantext.Core.Config.NLP (NLPConfig) import Gargantext.Core.Config.NLP (NLPConfig)
import Gargantext.Core.Config.Types
import Gargantext.Core.Config.Worker (WorkerSettings) import Gargantext.Core.Config.Worker (WorkerSettings)
import Gargantext.Core.Config.Types
import Gargantext.Prelude import Gargantext.Prelude
import Network.HTTP.Client qualified as HTTP import Network.HTTP.Client qualified as HTTP
import Servant.Auth.Server (JWTSettings) import Servant.Auth.Server (JWTSettings)
...@@ -139,8 +137,5 @@ instance HasConfig GargConfig where ...@@ -139,8 +137,5 @@ instance HasConfig GargConfig where
class HasJWTSettings env where class HasJWTSettings env where
jwtSettings :: Getter env JWTSettings jwtSettings :: Getter env JWTSettings
class HasRemoteTransferKeys env where
remoteTransferKeys :: Getter env (RSA.PublicKey, RSA.PrivateKey)
class HasManager env where class HasManager env where
gargHttpManager :: Getter env HTTP.Manager gargHttpManager :: Getter env HTTP.Manager
...@@ -67,12 +67,9 @@ tests = sequential $ aroundAll withTestDBAndPort $ beforeAllWith (\ctx -> setupE ...@@ -67,12 +67,9 @@ tests = sequential $ aroundAll withTestDBAndPort $ beforeAllWith (\ctx -> setupE
_authRes_token = cannedToken _authRes_token = cannedToken
, _authRes_tree_id = fromMaybe (UnsafeMkNodeId 1) $ listToMaybe $ result0 ^.. _Right . authRes_tree_id , _authRes_tree_id = fromMaybe (UnsafeMkNodeId 1) $ listToMaybe $ result0 ^.. _Right . authRes_tree_id
, _authRes_user_id = fromMaybe (UnsafeMkUserId 1) $ listToMaybe $ result0 ^.. _Right . authRes_user_id , _authRes_user_id = fromMaybe (UnsafeMkUserId 1) $ listToMaybe $ result0 ^.. _Right . authRes_user_id
-- We can't compare the pub key as it's randomly-generate upon each server restart
, _authRes_remote_transfer_pub_key = RemoteTransferPublicKey "uncomparable"
} }
(result <&> \r -> r { _authRes_remote_transfer_pub_key = RemoteTransferPublicKey "uncomparable" }) result `shouldBe` Right expected
`shouldBe` Right expected
it "denies login for user 'alice' if password is invalid" $ \(SpecContext _testEnv port _app _) -> do it "denies login for user 'alice' if password is invalid" $ \(SpecContext _testEnv port _app _) -> do
let authPayload = AuthRequest "alice" (GargPassword "wrong") let authPayload = AuthRequest "alice" (GargPassword "wrong")
......
...@@ -17,17 +17,16 @@ import Control.Concurrent.MVar ...@@ -17,17 +17,16 @@ import Control.Concurrent.MVar
import Control.Exception.Safe import Control.Exception.Safe
import Control.Lens import Control.Lens
import Control.Monad.Reader import Control.Monad.Reader
import Crypto.PubKey.RSA qualified as RSA
import Data.ByteString.Lazy.Char8 qualified as C8L import Data.ByteString.Lazy.Char8 qualified as C8L
import Data.Cache qualified as InMemory import Data.Cache qualified as InMemory
import Data.Streaming.Network (bindPortTCP) import Data.Streaming.Network (bindPortTCP)
import Gargantext.API (makeApp)
import Gargantext.API.Admin.EnvTypes (Mode(Mock), Env (..), env_dispatcher) import Gargantext.API.Admin.EnvTypes (Mode(Mock), Env (..), env_dispatcher)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types
import Gargantext.API (makeApp)
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.Notifications (withNotifications)
import Gargantext.Core.Config (_gc_secrets, gc_frontend_config) import Gargantext.Core.Config (_gc_secrets, gc_frontend_config)
import Gargantext.Core.Config.Types (NotificationsConfig(..), fc_appPort, jwtSettings) import Gargantext.Core.Config.Types (NotificationsConfig(..), fc_appPort, jwtSettings)
import Gargantext.Core.Notifications (withNotifications)
import Gargantext.Core.Types.Individu import Gargantext.Core.Types.Individu
import Gargantext.Database.Action.Flow import Gargantext.Database.Action.Flow
import Gargantext.Database.Action.User.New import Gargantext.Database.Action.User.New
...@@ -45,10 +44,10 @@ import Network.HTTP.Client.TLS (newTlsManager) ...@@ -45,10 +44,10 @@ import Network.HTTP.Client.TLS (newTlsManager)
import Network.HTTP.Types import Network.HTTP.Types
import Network.Wai (Application, responseLBS) import Network.Wai (Application, responseLBS)
import Network.Wai.Handler.Warp.Internal import Network.Wai.Handler.Warp.Internal
import Network.WebSockets qualified as WS
import Network.Wai.Handler.Warp qualified as Warp import Network.Wai.Handler.Warp qualified as Warp
import Network.Wai.Handler.Warp (runSettingsSocket) import Network.Wai.Handler.Warp (runSettingsSocket)
import Network.Wai qualified as Wai import Network.Wai qualified as Wai
import Network.WebSockets qualified as WS
import Prelude hiding (show) import Prelude hiding (show)
import Servant.Auth.Client () import Servant.Auth.Client ()
import Test.Database.Setup (withTestDB) import Test.Database.Setup (withTestDB)
...@@ -83,7 +82,6 @@ newTestEnv testEnv logger port = do ...@@ -83,7 +82,6 @@ newTestEnv testEnv logger port = do
-- !nodeStory_env <- fromDBNodeStoryEnv pool -- !nodeStory_env <- fromDBNodeStoryEnv pool
!_env_jwt_settings <- jwtSettings (_gc_secrets config_env) !_env_jwt_settings <- jwtSettings (_gc_secrets config_env)
_env_remote_transfer_keys <- RSA.generate 256 65537
pure $ Env pure $ Env
{ _env_logger = logger { _env_logger = logger
...@@ -97,7 +95,6 @@ newTestEnv testEnv logger port = do ...@@ -97,7 +95,6 @@ newTestEnv testEnv logger port = do
-- , _env_central_exchange = central_exchange -- , _env_central_exchange = central_exchange
, _env_dispatcher = errorTrace "[Test.API.Setup.newTestEnv] dispatcher not needed, but forced somewhere" , _env_dispatcher = errorTrace "[Test.API.Setup.newTestEnv] dispatcher not needed, but forced somewhere"
, _env_jwt_settings , _env_jwt_settings
, _env_remote_transfer_keys
} }
......
{-# LANGUAGE ViewPatterns #-}
module Test.Offline.RemoteTransfer where
import Crypto.PubKey.RSA as RSA
import Gargantext.API.Admin.Auth.Types
import Prelude
import Test.Tasty
import Test.Tasty.QuickCheck
tests :: TestTree
tests = testGroup "RemoteTransfer" [
testProperty "PubKey serialisation roundtrip" pubKeySerializeRoundtrip
]
pubKeySerializeRoundtrip :: (Positive Integer, Positive Integer) -> Property
pubKeySerializeRoundtrip (getPositive -> n, getPositive -> e) =
let pk = RSA.PublicKey 256 n e
in remotePubKeyToPubKey (pubKeyToRemotePubKey pk) === Right pk
...@@ -29,7 +29,6 @@ import qualified Test.Utils.Crypto as Crypto ...@@ -29,7 +29,6 @@ import qualified Test.Utils.Crypto as Crypto
import qualified Test.Utils.Jobs as Jobs import qualified Test.Utils.Jobs as Jobs
import qualified Test.Core.Similarity as Similarity import qualified Test.Core.Similarity as Similarity
import qualified Test.Core.Notifications as Notifications import qualified Test.Core.Notifications as Notifications
import qualified Test.Offline.RemoteTransfer as RemoteTransfer
import Test.Tasty import Test.Tasty
import Test.Tasty.Hspec import Test.Tasty.Hspec
...@@ -66,5 +65,4 @@ main = do ...@@ -66,5 +65,4 @@ main = do
, Worker.tests , Worker.tests
, asyncUpdatesSpec , asyncUpdatesSpec
, Notifications.qcTests , Notifications.qcTests
, RemoteTransfer.tests
] ]
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment