2 Module : Gargantext.API.GraphQL.Utils
3 Description : Utils for GraphQL API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
11 module Gargantext.API.GraphQL.Utils where
13 import Data.Morpheus.Types (GQLTypeOptions, fieldLabelModifier)
14 import qualified Data.Text as T
15 import Gargantext.Core.Utils.Prefix (unCapitalize, dropPrefix)
16 import Gargantext.Prelude
17 import Data.Text (Text)
18 import Data.Text.Encoding (encodeUtf8)
19 import Gargantext.API.Admin.Types (jwtSettings, HasSettings (settings))
20 import Servant.Auth.Server (verifyJWT, JWTSettings)
21 import Control.Lens.Getter (view)
22 import Gargantext.Database.Prelude (Cmd')
23 import Gargantext.API.Admin.Auth.Types (AuthenticatedUser (AuthenticatedUser, _authUser_id))
24 import Data.ByteString (ByteString)
25 import Gargantext.Database.Admin.Types.Node (NodeId)
27 unPrefix :: T.Text -> GQLTypeOptions -> GQLTypeOptions
28 unPrefix prefix options = options { fieldLabelModifier = nflm }
30 nflm label = unCapitalize $ dropPrefix (T.unpack prefix) $ ( fieldLabelModifier options ) label
32 data AuthStatus = Valid | Invalid
34 authUser :: (HasSettings env) => NodeId -> Text -> Cmd' env err AuthStatus
35 authUser ui_id token = do
36 let token' = encodeUtf8 token
37 jwtS <- view $ settings . jwtSettings
38 u <- liftBase $ getUserFromToken jwtS token'
40 Nothing -> pure Invalid
46 nId AuthenticatedUser {_authUser_id} = _authUser_id
48 getUserFromToken :: JWTSettings -> ByteString -> IO (Maybe AuthenticatedUser)
49 getUserFromToken = verifyJWT