[graphql] nodeContext score update mutation

parent 3d4b9b63
Pipeline #3570 failed with stage
in 72 minutes and 56 seconds
......@@ -80,8 +80,9 @@ data Query m
data Mutation m
= Mutation
{ update_user_info :: GQLUserInfo.UserInfoMArgs -> m Int
{ update_user_info :: GQLUserInfo.UserInfoMArgs -> m Int
, delete_team_membership :: GQLTeam.TeamDeleteMArgs -> m [Int]
, update_node_context_category :: GQLCTX.NodeContextCategoryMArgs -> m [Int]
} deriving (Generic, GQLType)
-- | Possible GraphQL Events, i.e. here we describe how we will
......@@ -117,7 +118,8 @@ rootResolver =
, tree = GQLTree.resolveTree
, team = GQLTeam.resolveTeam }
, mutationResolver = Mutation { update_user_info = GQLUserInfo.updateUserInfo
, delete_team_membership = GQLTeam.deleteTeamMembership }
, delete_team_membership = GQLTeam.deleteTeamMembership
, update_node_context_category = GQLCTX.updateNodeContextCategory }
, subscriptionResolver = Undefined }
-- | Main GraphQL "app".
......
......@@ -8,14 +8,17 @@ module Gargantext.API.GraphQL.Context where
import Data.Morpheus.Types
( GQLType
, Resolver
, ResolverM
, QUERY
, lift
)
import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Prelude (GargM, GargError)
import Gargantext.Core.Mail.Types (HasMail)
import Gargantext.Database.Admin.Types.Node (NodeId(..))
import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
import Gargantext.Database.Query.Table.NodeContext (getNodeContext)
import qualified Gargantext.Database.Query.Table.NodeContext as DNC
import Gargantext.Database.Schema.NodeContext (NodeContext, NodeContextPoly(..))
import Gargantext.Prelude
import GHC.Generics (Generic)
......@@ -36,7 +39,14 @@ data NodeContextArgs
, node_id :: Int
} deriving (Generic, GQLType)
data NodeContextCategoryMArgs = NodeContextCategoryMArgs
{ context_id :: Int
, node_id :: Int
, category :: Int
} deriving (Generic, GQLType)
type GqlM e env = Resolver QUERY e (GargM env GargError)
type GqlM' e env a = ResolverM e (GargM env GargError) a
-- | Function to resolve context from a query.
resolveNodeContext
......@@ -65,3 +75,10 @@ toNodeContextGQL (NodeContext { _nc_node_id = NodeId nc_node_id
, nc_context_id
, nc_score = _nc_score
, nc_category = _nc_category }
updateNodeContextCategory :: (HasConnectionPool env, HasConfig env, HasMail env, HasSettings env) =>
NodeContextCategoryMArgs -> GqlM' e env [Int]
updateNodeContextCategory NodeContextCategoryMArgs { context_id, node_id, category } = do
_ <- lift $ DNC.updateNodeContextCategory (NodeId context_id) (NodeId node_id) category
pure [1]
......@@ -7,17 +7,17 @@ import Gargantext.Prelude
import GHC.Generics (Generic)
import Data.Morpheus.Types (GQLType, Resolver, QUERY, ResolverM, lift)
import Data.Text ( Text )
import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.GraphQL.Utils (authUser, AuthStatus (Invalid, Valid))
import Gargantext.API.Prelude (GargM, GargError)
import Gargantext.Database.Action.Share (membersOf, deleteMemberShip)
import Gargantext.Core.Mail.Types (HasMail)
import Gargantext.Core.Types (NodeId(..), unNodeId)
import Gargantext.Database.Prelude (HasConnectionPool)
import Gargantext.Database (HasConfig)
import Gargantext.Core.Mail.Types (HasMail)
import Gargantext.Database.Action.Share (membersOf, deleteMemberShip)
import Gargantext.Database.Prelude (HasConnectionPool)
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.API.GraphQL.Utils (authUser, AuthStatus (Invalid, Valid))
import Gargantext.Database.Schema.Node (NodePoly(Node, _node_id), _node_user_id)
import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.Database.Query.Table.User (getUsersWithNodeHyperdata)
import Gargantext.Database.Schema.Node (NodePoly(Node, _node_id), _node_user_id)
import qualified Data.Text as T
import Gargantext.Database.Schema.User (UserLight(..))
......
......@@ -28,6 +28,7 @@ module Gargantext.Database.Query.Table.NodeContext
, nodeContextsScore
, getNodeContexts
, getNodeContext
, updateNodeContextCategory
, insertNodeContext
, deleteNodeContext
, selectPublicContexts
......@@ -88,6 +89,16 @@ getNodeContext c n = do
restrict -< _nc_node_id ns .== n'
returnA -< ns
updateNodeContextCategory :: ContextId -> NodeId -> Int -> Cmd err Int64
updateNodeContextCategory cId nId cat = do
execPGSQuery upScore (cat, cId, nId)
where
upScore :: PGS.Query
upScore = [sql| UPDATE nodes_contexts
SET category = ?
WHERE context_id = ?
AND node_id = ? |]
------------------------------------------------------------------------
insertNodeContext :: [NodeContext] -> Cmd err Int
insertNodeContext ns = mkCmd $ \conn -> fromIntegral <$> (runInsert_ conn
......
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