]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node/Share.hs
[graphql] endpoint for contexts_for_ngrams
[gargantext.git] / src / Gargantext / API / Node / Share.hs
1 {-|
2 Module : Gargantext.API.Node.Share
3 Description :
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE TemplateHaskell #-}
13 {-# LANGUAGE TypeOperators #-}
14
15 module Gargantext.API.Node.Share
16 where
17
18 import Data.Aeson
19 import Data.Swagger
20 import Data.Text (Text)
21 import GHC.Generics (Generic)
22 import Gargantext.API.Prelude
23 import Gargantext.Core.Types.Individu (User(..), arbitraryUsername)
24 import Gargantext.Database.Action.Share (ShareNodeWith(..))
25 import Gargantext.Database.Action.Share as DB (shareNodeWith, unPublish)
26 import Gargantext.Database.Action.User
27 import Gargantext.Database.Action.User.New
28 import Gargantext.Database.Admin.Types.Node
29 import Gargantext.Database.Prelude
30 import Gargantext.Database.Query.Tree (findNodesWithType)
31 import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
32 import Gargantext.Prelude
33 import qualified Gargantext.Utils.Aeson as GUA
34 import Servant
35 import Test.QuickCheck (elements)
36 import Test.QuickCheck.Arbitrary
37 import qualified Data.List as List
38
39 ------------------------------------------------------------------------
40 data ShareNodeParams = ShareTeamParams { username :: Text }
41 | SharePublicParams { node_id :: NodeId}
42 deriving (Generic)
43 ------------------------------------------------------------------------
44 -- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
45 instance FromJSON ShareNodeParams where
46 parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
47 instance ToJSON ShareNodeParams where
48 toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
49 instance ToSchema ShareNodeParams
50 instance Arbitrary ShareNodeParams where
51 arbitrary = elements [ ShareTeamParams "user1"
52 , SharePublicParams (NodeId 1)
53 ]
54 ------------------------------------------------------------------------
55 -- TODO permission
56 -- TODO refactor userId which is used twice
57 -- TODO change return type for better warning/info/success/error handling on the front
58 api :: HasNodeError err
59 => User
60 -> NodeId
61 -> ShareNodeParams
62 -> CmdR err Int
63 api userInviting nId (ShareTeamParams user') = do
64 user <- case guessUserName user' of
65 Nothing -> pure user'
66 Just (u,_) -> do
67 isRegistered <- getUserId' (UserName u)
68 case isRegistered of
69 Just _ -> do
70 printDebug "[G.A.N.Share.api]" ("Team shared with " <> u)
71 pure u
72 Nothing -> do
73 username' <- getUsername userInviting
74 _ <- case List.elem username' arbitraryUsername of
75 True -> do
76 printDebug "[G.A.N.Share.api]" ("Demo users are not allowed to invite" :: Text)
77 pure ()
78 False -> do
79 -- TODO better analysis of the composition of what is shared
80 children <- findNodesWithType nId [NodeList] [ NodeFolderShared
81 , NodeTeam
82 , NodeFolder
83 , NodeCorpus
84 ]
85 _ <- case List.null children of
86 True -> do
87 printDebug "[G.A.N.Share.api]" ("Invitation is enabled if you share a corpus at least" :: Text)
88 pure 0
89 False -> do
90 printDebug "[G.A.N.Share.api]" ("Your invitation is sent to: " <> user')
91 newUsers [user']
92 pure ()
93 pure u
94
95 fromIntegral <$> DB.shareNodeWith (ShareNodeWith_User NodeFolderShared (UserName user)) nId
96 api _uId nId2 (SharePublicParams nId1) =
97
98 fromIntegral <$> DB.shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId1) nId2
99
100 ------------------------------------------------------------------------
101 type API = Summary " Share Node with username"
102 :> ReqBody '[JSON] ShareNodeParams
103 :> Post '[JSON] Int
104
105 ------------------------------------------------------------------------
106 type Unpublish = Summary " Unpublish Node"
107 :> Capture "node_id" NodeId
108 :> Put '[JSON] Int
109
110 unPublish :: NodeId -> GargServer Unpublish
111 unPublish n = DB.unPublish n