[tests] dummy WebSocketPending HasClient implementation

parent dca7d379
...@@ -1012,6 +1012,7 @@ test-suite garg-test-tasty ...@@ -1012,6 +1012,7 @@ test-suite garg-test-tasty
, raw-strings-qq , raw-strings-qq
, recover-rtti >= 0.4 && < 0.5 , recover-rtti >= 0.4 && < 0.5
, resource-pool >= 0.2.3.2 && < 0.2.4 , resource-pool >= 0.2.3.2 && < 0.2.4
, servant >= 0.18.3 && < 0.20
, servant-auth , servant-auth
, servant-auth , servant-auth
, servant-auth-client , servant-auth-client
...@@ -1019,6 +1020,7 @@ test-suite garg-test-tasty ...@@ -1019,6 +1020,7 @@ test-suite garg-test-tasty
, servant-client-core , servant-client-core
, servant-job , servant-job
, servant-server , servant-server
, servant-websockets >= 2.0.0 && < 2.1
, shelly >= 1.9 && < 2 , shelly >= 1.9 && < 2
, stm ^>= 2.5.0.1 , stm ^>= 2.5.0.1
, split , split
...@@ -1105,12 +1107,14 @@ test-suite garg-test-hspec ...@@ -1105,12 +1107,14 @@ test-suite garg-test-hspec
, raw-strings-qq , raw-strings-qq
, recover-rtti >= 0.4 && < 0.5 , recover-rtti >= 0.4 && < 0.5
, resource-pool >= 0.2.3.2 && < 0.2.4 , resource-pool >= 0.2.3.2 && < 0.2.4
, servant >= 0.18.3 && < 0.20
, servant-auth , servant-auth
, servant-auth-client , servant-auth-client
, servant-client , servant-client
, servant-client-core , servant-client-core
, servant-job , servant-job
, servant-server , servant-server
, servant-websockets >= 2.0.0 && < 2.1
, shelly >= 1.9 && < 2 , shelly >= 1.9 && < 2
, stm ^>= 2.5.0.1 , stm ^>= 2.5.0.1
, tasty ^>= 1.4.2.1 , tasty ^>= 1.4.2.1
......
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ViewPatterns #-}
...@@ -9,22 +8,37 @@ module Test.API.Routes where ...@@ -9,22 +8,37 @@ module Test.API.Routes where
import Data.Text.Encoding qualified as TE import Data.Text.Encoding qualified as TE
import Fmt (Builder, (+|), (|+)) import Fmt (Builder, (+|), (|+))
import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, Token) import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, Token)
import Gargantext.API.Errors
import Gargantext.API.Ngrams.Types ( NgramsTable, NgramsTablePatch, OrderBy, TabType, Versioned, VersionedWithCount ) import Gargantext.API.Ngrams.Types ( NgramsTable, NgramsTablePatch, OrderBy, TabType, Versioned, VersionedWithCount )
import Gargantext.API.Routes.Named import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.Node
import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI)
import Gargantext.API.Routes.Named.Table import Gargantext.API.Routes.Named.Table
import Gargantext.API.Types () -- MimeUnrender instances
import Gargantext.Core.Types (ListId, NodeId) import Gargantext.Core.Types (ListId, NodeId)
import Gargantext.Core.Types.Main (ListType) import Gargantext.Core.Types.Main (ListType)
import Gargantext.Core.Types.Query (Limit, MaxSize, MinSize, Offset) import Gargantext.Core.Types.Query (Limit, MaxSize, MinSize, Offset)
import Gargantext.Prelude import Gargantext.Prelude
import Network.HTTP.Types qualified as H
import Network.Wai.Handler.Warp (Port) import Network.Wai.Handler.Warp (Port)
import Servant.API.WebSocket qualified as WS
import Servant.Auth.Client qualified as S
import Servant.Client (ClientM) import Servant.Client (ClientM)
import Servant.Client.Core (RunClient, HasClient(..), Request)
import Servant.Client.Generic ( genericClient, AsClientT ) import Servant.Client.Generic ( genericClient, AsClientT )
import Gargantext.API.Types () -- MimeUnrender instances
import Gargantext.API.Errors
import Gargantext.API.Routes.Named.Private hiding (tableNgramsAPI)
import Gargantext.API.Routes.Named.Node
import Servant.Auth.Client qualified as S
instance RunClient m => HasClient m WS.WebSocketPending where
type Client m WS.WebSocketPending = H.Method -> m ()
clientWithRoute :: Proxy m -> Proxy WS.WebSocketPending -> Request -> Client m WS.WebSocketPending
clientWithRoute _pm Proxy _req _httpMethod = do
panicTrace "[WebSocket client] this is not implemented!"
return ()
hoistClientMonad _ _ f cl = \meth -> f (cl meth)
-- This is for requests made by http.client directly to hand-crafted URLs -- This is for requests made by http.client directly to hand-crafted URLs
curApi :: Builder curApi :: Builder
curApi = "v1.0" curApi = "v1.0"
......
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