Commit 133d581e authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[graphql] /gql endpoint for authorized users

Also, fixed morpheus version: turns out one can unprefix without a
patch to current library.

https://github.com/morpheusgraphql/morpheus-graphql/pull/639#issuecomment-962113983
parent 872564e3
......@@ -8,6 +8,7 @@
module Gargantext.API.GraphQL where
import Control.Lens ((#))
import Control.Monad.Base (liftBase)
import Control.Monad.IO.Class (liftIO)
import Data.ByteString.Lazy.Char8
......@@ -47,9 +48,10 @@ import Data.Text (Text)
import qualified Data.Text.Lazy as LT
import Data.Text.Lazy.Encoding (decodeUtf8)
import Data.Typeable (Typeable)
import Gargantext.API.Admin.Auth.Types (AuthenticatedUser)
import qualified Gargantext.API.GraphQL.User as GQLUser
import qualified Gargantext.API.GraphQL.UserInfo as GQLUserInfo
import Gargantext.API.Prelude (GargServerT, GargM, GargError)
import Gargantext.API.Prelude (GargServerT, GargM, GargError, _ServerError)
import Gargantext.Database.Prelude (Cmd, HasConnectionPool, HasConfig)
import Gargantext.Database.Schema.User (UserPoly(..))
import Gargantext.Prelude
......@@ -71,7 +73,10 @@ import Servant
Post,
ReqBody,
ServerT,
err401
)
import qualified Servant.Auth as SA
import qualified Servant.Auth.Server as SAS
-- | Represents possible GraphQL queries.
data Query m
......@@ -137,7 +142,8 @@ type GQAPI = ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse
type Playground = Get '[HTML] ByteString
-- type API' (name :: Symbol) = name :> (GQAPI :<|> Schema :<|> Playground)
-- | Our API consists of `GQAPI` and `Playground`.
type API = "gql" :> (GQAPI :<|> Playground)
type API = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
:> "gql" :> (GQAPI :<|> Playground)
-- serveEndpoint ::
-- ( SubApp ServerApp e
......@@ -156,4 +162,5 @@ type API = "gql" :> (GQAPI :<|> Playground)
api
:: (Typeable env, HasConnectionPool env, HasConfig env)
=> ServerT API (GargM env GargError)
api = httpPubApp [] app :<|> pure httpPlayground
api (SAS.Authenticated _auser) = httpPubApp [] app :<|> pure httpPlayground
api _ = panic "401 in graphql" --SAS.throwAll (_ServerError # err401)
......@@ -185,6 +185,8 @@ ui_cwOfficeL = contactWhereL . cw_office
ui_cwRoleL :: Traversal' HyperdataUser (Maybe Text)
ui_cwRoleL = contactWhereL . cw_role
ui_cwTouchMailL :: Traversal' HyperdataUser (Maybe Text)
ui_cwTouchMailL = contactWhereL . cw_touch . _Just . ct_mail
ui_cwTouchMailL = hu_shared . _Just . (hc_where . (ix 0) . cw_touch . _Just . ct_mail)
--ui_cwTouchMailL = contactWhereL . cw_touch . _Just . ct_mail
ui_cwTouchPhoneL :: Traversal' HyperdataUser (Maybe Text)
ui_cwTouchPhoneL = contactWhereL . cw_touch . _Just . ct_phone
ui_cwTouchPhoneL = hu_shared . _Just . (hc_where . (ix 0) . cw_touch . _Just . ct_phone)
--ui_cwTouchPhoneL = contactWhereL . cw_touch . _Just . ct_phone
module Gargantext.API.GraphQL.Utils where
import Data.Morpheus.Types (GQLTypeOptions(..))
import Data.Morpheus.Types (GQLTypeOptions, fieldLabelModifier)
import qualified Data.Text as T
import Gargantext.Core.Utils.Prefix (unCapitalize, dropPrefix)
import Gargantext.Prelude
unPrefix :: T.Text -> GQLTypeOptions -> GQLTypeOptions
unPrefix prefix (GQLTypeOptions { fieldLabelModifier, .. }) = GQLTypeOptions { fieldLabelModifier = nflm, .. }
unPrefix prefix options = options { fieldLabelModifier = nflm }
where
nflm label = unCapitalize $ dropPrefix (T.unpack prefix) $ fieldLabelModifier label
nflm label = unCapitalize $ dropPrefix (T.unpack prefix) $ ( fieldLabelModifier options ) label
......@@ -86,15 +86,6 @@ extra-deps:
commit: 83ada76e78ac10d9559af8ed6bd4064ec81308e4
- accelerate-arithmetic-1.0.0.1@sha256:555639232aa5cad411e89247b27871d09352b987a754230a288c690b6de6d888,2096
- git: https://github.com/CGenie/morpheus-graphql.git
commit: 899b7bf21274739beae84b27812f76e2a5e67e29
subdirs:
- .
- morpheus-graphql-app
- morpheus-graphql-core
- morpheus-graphql-code-gen
- morpheus-graphql-subscriptions
# Others dependencies (using stack resolver)
- constraints-extras-0.3.1.0@sha256:12016ebb91ad5ed2c82bf7e48c6bd6947d164d33c9dca5ac3965de1bb6c780c0,1777
- KMP-0.2.0.0@sha256:6dfbac03ef00ebd9347234732cb86a40f62ab5a80c0cc6bedb8eb51766f7df28,2562
......
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