[graphql] get contexts for ngrams fix

parent d19839d8
Pipeline #7657 passed with stages
in 48 minutes and 49 seconds
......@@ -15,7 +15,6 @@ Portability : POSIX
{-# LANGUAGE KindSignatures #-} -- for use of Endpoint (name :: Symbol)
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PartialTypeSignatures #-} -- to automatically use suggested type hole signatures during compilation
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Gargantext.API.GraphQL where
......
......@@ -22,8 +22,7 @@ import Data.Morpheus.Types
, ResolverM
, QUERY
)
import Data.Text (pack, unpack)
import Data.Text qualified as Text
import Data.Text (pack)
import Data.Time.Format.ISO8601 (iso8601Show)
import Gargantext.API.Admin.Auth.Types ( AuthenticatedUser )
import Gargantext.API.Auth.PolicyCheck ( nodeWriteChecks, AccessPolicyManager )
......@@ -97,7 +96,7 @@ data ContextsForNgramsArgs
= ContextsForNgramsArgs
{ corpus_id :: Int
, ngrams_terms :: [Text]
, and_logic :: Text
, and_logic :: Bool
} deriving (Generic, GQLType)
data NodeContextCategoryMArgs = NodeContextCategoryMArgs
......@@ -153,9 +152,10 @@ dbNodeContext context_id node_id = do
-- | Returns list of `ContextGQL` for given ngrams in given corpus id.
dbContextForNgrams
:: (IsDBEnvExtra env)
=> Int -> [Text] -> Text -> GqlM e env [ContextGQL]
=> Int -> [Text] -> Bool -> GqlM e env [ContextGQL]
dbContextForNgrams node_id ngrams_terms and_logic = do
contextsForNgramsTerms <- lift $ runDBQuery $ getContextsForNgramsTerms (UnsafeMkNodeId node_id) ngrams_terms ( readMaybe $ unpack $ Text.toTitle and_logic )
contextsForNgramsTerms <- lift $ runDBQuery $
getContextsForNgramsTerms (UnsafeMkNodeId node_id) ngrams_terms and_logic
--lift $ printDebug "[dbContextForNgrams] contextsForNgramsTerms" contextsForNgramsTerms
pure $ toContextGQL <$> contextsForNgramsTerms
......
......@@ -151,9 +151,9 @@ data ContextForNgramsTerms =
getContextsForNgramsTerms :: HasNodeError err
=> NodeId
-> [Text]
-> Maybe Bool
-> Bool
-> DBQuery err x [ContextForNgramsTerms]
getContextsForNgramsTerms cId ngramsTerms (Just True) = do
getContextsForNgramsTerms cId ngramsTerms True = do
let terms_length = length ngramsTerms
res <- mkPGQuery query (cId, PGS.In ngramsTerms, terms_length)
pure $ (\( _cfnt_nodeId
......
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