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