Node.hs 3.84 KB
Newer Older
1 2 3 4 5
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DuplicateRecordFields #-}

module Gargantext.API.GraphQL.Node where

6
import Data.Aeson
7
import Data.Either (Either(..))
8
import qualified Data.HashMap.Strict as HashMap
9 10 11 12 13 14 15
import Data.Morpheus.Types
  ( GQLType
  , Resolver
  , QUERY
  , lift
  )
import Data.Text (Text)
16
import qualified Data.Text as T
17
import Gargantext.API.Prelude (GargM, GargError)
18
import Gargantext.Database.Admin.Types.Node (NodeId(..), NodeType)
19 20
import qualified Gargantext.Database.Admin.Types.Node as NN
import Gargantext.Database.Query.Table.Node (getClosestParentIdByType, getNode)
21
import Gargantext.Database.Prelude (CmdCommon)  -- , JSONB)
22 23 24
import qualified Gargantext.Database.Schema.Node as N
import Gargantext.Prelude
import GHC.Generics (Generic)
25
import qualified Prelude
26
import qualified PUBMED.Types as PUBMED
27
import Text.Read (readEither)
28

29 30 31 32 33 34 35 36
data Corpus = Corpus
  { id           :: Int
  , name         :: Text
  , parent_id    :: Maybe Int
  , pubmedAPIKey :: Maybe PUBMED.APIKey
  , type_id      :: Int
  } deriving (Show, Generic, GQLType)

37
data Node = Node
38 39 40 41
  { id           :: Int
  , name         :: Text
  , parent_id    :: Maybe Int
  , type_id      :: Int
42 43
  } deriving (Show, Generic, GQLType)

44 45 46 47 48
data CorpusArgs
  = CorpusArgs
    { corpus_id :: Int
    } deriving (Generic, GQLType)

49 50
data NodeArgs
  = NodeArgs
51
    { node_id :: Int
52 53 54 55 56 57
    } deriving (Generic, GQLType)

type GqlM e env = Resolver QUERY e (GargM env GargError)

-- | Function to resolve user from a query.
resolveNodes
58
  :: (CmdCommon env)
59 60 61
  => NodeArgs -> GqlM e env [Node]
resolveNodes NodeArgs { node_id } = dbNodes node_id

62 63 64 65 66
resolveNodesCorpus
  :: (CmdCommon env)
  => CorpusArgs -> GqlM e env [Corpus]
resolveNodesCorpus CorpusArgs { corpus_id } = dbNodesCorpus corpus_id

67
dbNodes
68
  :: (CmdCommon env)
69 70 71 72 73
  => Int -> GqlM e env [Node]
dbNodes node_id = do
  node <- lift $ getNode $ NodeId node_id
  pure [toNode node]

74 75 76 77 78 79 80
dbNodesCorpus
  :: (CmdCommon env)
  => Int -> GqlM e env [Corpus]
dbNodesCorpus corpus_id = do
  corpus <- lift $ getNode $ NodeId corpus_id
  pure [toCorpus corpus]

81 82
data NodeParentArgs
  = NodeParentArgs
83 84
    { node_id     :: Int
    , parent_type :: Text
85 86 87
    } deriving (Generic, GQLType)

resolveNodeParent
88
  :: (CmdCommon env)
89
  => NodeParentArgs -> GqlM e env [Node]
90
resolveNodeParent NodeParentArgs { node_id, parent_type } = dbParentNodes node_id parent_type
91 92

dbParentNodes
93
  :: (CmdCommon env)
94 95 96 97 98 99 100 101 102 103 104 105 106 107
  => Int -> Text -> GqlM e env [Node]
dbParentNodes node_id parent_type = do
  let mParentType = readEither (T.unpack parent_type) :: Either Prelude.String NodeType
  case mParentType of
    Left err -> do
      lift $ printDebug "[dbParentNodes] error reading parent type" (T.pack err)
      pure []
    Right parentType -> do
      mNodeId <- lift $ getClosestParentIdByType (NodeId node_id) parentType -- (fromNodeTypeId parent_type_id)
      case mNodeId of
        Nothing -> pure []
        Just id -> do
          node <- lift $ getNode id
          pure [toNode node]
108 109

toNode :: NN.Node json -> Node
110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129
toNode N.Node { .. } = Node { id = NN.unNodeId _node_id
                            , name = _node_name
                            , parent_id = NN.unNodeId <$> _node_parent_id
                            , type_id = _node_typename }

toCorpus :: NN.Node Value -> Corpus
toCorpus N.Node { .. } = Corpus { id = NN.unNodeId _node_id
                                , name = _node_name
                                , parent_id = NN.unNodeId <$> _node_parent_id
                                , pubmedAPIKey = pubmedAPIKeyFromValue _node_hyperdata
                                , type_id = _node_typename }

pubmedAPIKeyFromValue :: Value -> Maybe PUBMED.APIKey
pubmedAPIKeyFromValue (Object kv) =
  case HashMap.lookup "pubmed_api_key" kv of
    Nothing -> Nothing
    Just v  -> case fromJSON v of
      Error _    -> Nothing
      Success v' -> Just v'
pubmedAPIKeyFromValue _           = Nothing