]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node/Share.hs
[MERGE]
[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.Table.Node.Error (HasNodeError(..))
31 import Gargantext.Database.Query.Tree (findNodesWithType)
32 import Gargantext.Prelude
33 import Servant
34 import Test.QuickCheck (elements)
35 import Test.QuickCheck.Arbitrary
36 import qualified Data.List as List
37 import qualified Data.Text as Text
38 import qualified Gargantext.Utils.Aeson as GUA
39
40 ------------------------------------------------------------------------
41 data ShareNodeParams = ShareTeamParams { username :: Text }
42 | SharePublicParams { node_id :: NodeId}
43 deriving (Generic)
44 ------------------------------------------------------------------------
45 -- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
46 instance FromJSON ShareNodeParams where
47 parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
48 instance ToJSON ShareNodeParams where
49 toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
50 instance ToSchema ShareNodeParams
51 instance Arbitrary ShareNodeParams where
52 arbitrary = elements [ ShareTeamParams "user1"
53 , SharePublicParams (NodeId 1)
54 ]
55 ------------------------------------------------------------------------
56 -- TODO permission
57 -- TODO refactor userId which is used twice
58 -- TODO change return type for better warning/info/success/error handling on the front
59 api :: HasNodeError err
60 => User
61 -> NodeId
62 -> ShareNodeParams
63 -> CmdR err Int
64 api userInviting nId (ShareTeamParams user') = do
65 let user'' = Text.toLower user'
66 user <- case guessUserName user'' of
67 Nothing -> pure user''
68 Just (u,_) -> do
69 isRegistered <- getUserId' (UserName u)
70 case isRegistered of
71 Just _ -> do
72 printDebug "[G.A.N.Share.api]" ("Team shared with " <> u)
73 pure u
74 Nothing -> do
75 username' <- getUsername userInviting
76 _ <- case List.elem username' arbitraryUsername of
77 True -> do
78 printDebug "[G.A.N.Share.api]" ("Demo users are not allowed to invite" :: Text)
79 pure ()
80 False -> do
81 -- TODO better analysis of the composition of what is shared
82 children <- findNodesWithType nId [NodeList] [ NodeFolderShared
83 , NodeTeam
84 , NodeFolder
85 , NodeCorpus
86 ]
87 _ <- case List.null children of
88 True -> do
89 printDebug "[G.A.N.Share.api]" ("Invitation is enabled if you share a corpus at least" :: Text)
90 pure 0
91 False -> do
92 printDebug "[G.A.N.Share.api]" ("Your invitation is sent to: " <> user'')
93 newUsers [user'']
94 pure ()
95 pure u
96
97 fromIntegral <$> DB.shareNodeWith (ShareNodeWith_User NodeFolderShared (UserName user)) nId
98 api _uId nId2 (SharePublicParams nId1) =
99
100 fromIntegral <$> DB.shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId1) nId2
101
102 ------------------------------------------------------------------------
103 type API = Summary " Share Node with username"
104 :> ReqBody '[JSON] ShareNodeParams
105 :> Post '[JSON] Int
106
107 ------------------------------------------------------------------------
108 type Unpublish = Summary " Unpublish Node"
109 :> Capture "node_id" NodeId
110 :> Put '[JSON] Int
111
112 unPublish :: NodeId -> GargServer Unpublish
113 unPublish n = DB.unPublish n