{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ScopedTypeVariables #-} module Test.API.Private ( tests ) where import Gargantext.API.Routes.Named.Node import Gargantext.API.Routes.Named.Private import Gargantext.Core.Types (Node) import Gargantext.Core.Types.Individu import Gargantext.Database.Admin.Types.Hyperdata (HyperdataUser) import Gargantext.Prelude hiding (get) import Network.HTTP.Client hiding (Proxy) import Network.Wai import Servant.Auth.Client () import Servant.Client import Servant.Client.Generic (genericClient) import Test.API.Private.Share qualified as Share import Test.API.Routes (mkUrl) import Test.API.Setup (withTestDBAndPort, setupEnvironment, createAliceAndBob) import Test.Database.Types import Test.Hspec import Test.Hspec.Wai hiding (pendingWith) import Test.Hspec.Wai.Internal (withApplication) import Test.Hspec.Wai.JSON (json) import Test.Utils (protected, shouldRespondWithFragment, withValidLogin) privateTests :: SpecWith ((TestEnv, Int), Application) privateTests = describe "Private API" $ do baseUrl <- runIO $ parseBaseUrl "http://localhost" manager <- runIO $ newManager defaultManagerSettings let unauthenticatedClientEnv port = mkClientEnv manager (baseUrl { baseUrlPort = port }) describe "GET /api/v1.0/user" $ do -- FIXME(adn): unclear if this is useful at all. Doesn't do permission checking. it "doesn't allow someone with an invalid token to show the results" $ \((testEnv, port), _) -> do createAliceAndBob testEnv let gargAdminClient = (genericClient :: GargAdminAPI (AsClientT ClientM)) admin_user_api_get = (getRootsEp . rootsEp $ gargAdminClient :: ClientM [Node HyperdataUser]) result <- runClientM admin_user_api_get (unauthenticatedClientEnv port) length result `shouldBe` 0 -- FIXME(adn): unclear if this is useful at all. Doesn't do permission checking. it "allows 'alice' to see the results" $ \((_testEnv, port), _) -> do withValidLogin port "alice" (GargPassword "alice") $ \clientEnv _token -> do let gargAdminClient = (genericClient :: GargAdminAPI (AsClientT ClientM)) admin_user_api_get = (getRootsEp . rootsEp $ gargAdminClient :: ClientM [Node HyperdataUser]) _nodes <- runClientM admin_user_api_get clientEnv pendingWith "currently useless" describe "GET /api/v1.0/node" $ do it "unauthorised users shouldn't see anything" $ \((_testEnv, port), app) -> do withApplication app $ do get (mkUrl port "/node/1") `shouldRespondWith` 401 it "allows 'alice' to see her own node info" $ \((_testEnv, port), app) -> do withApplication app $ do withValidLogin port "alice" (GargPassword "alice") $ \_clientEnv token -> do protected token "GET" (mkUrl port "/node/8") "" `shouldRespondWithFragment` [json| {"id":8,"user_id":2,"name":"alice" } |] it "forbids 'alice' to see others node private info" $ \((_testEnv, port), app) -> do withApplication app $ do withValidLogin port "alice" (GargPassword "alice") $ \_clientEnv token -> do protected token "GET" (mkUrl port "/node/1") "" `shouldRespondWith` 403 describe "GET /api/v1.0/tree" $ do it "unauthorised users shouldn't see anything" $ \((_testEnv, port), app) -> do withApplication app $ do get (mkUrl port "/tree/1") `shouldRespondWith` 401 it "allows 'alice' to see her own node info" $ \((_testEnv, port), app) -> do withApplication app $ do withValidLogin port "alice" (GargPassword "alice") $ \_clientEnv token -> do protected token "GET" (mkUrl port "/tree/8") "" `shouldRespondWithFragment` [json| { "node": {"id":8, "name":"alice", "type": "NodeUser" } } |] it "forbids 'alice' to see others node private info" $ \((_testEnv, port), app) -> do withApplication app $ do withValidLogin port "alice" (GargPassword "alice") $ \_clientEnv token -> do protected token "GET" (mkUrl port "/tree/1") "" `shouldRespondWith` 403 tests :: Spec tests = do sequential $ aroundAll withTestDBAndPort $ do describe "Prelude" $ do it "setup DB triggers" $ \((testEnv, _), _) -> setupEnvironment testEnv privateTests describe "Share API" $ do Share.tests