2 Module : Gargantext.API.Node.Share
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE TemplateHaskell #-}
13 {-# LANGUAGE TypeOperators #-}
15 module Gargantext.API.Node.Share
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 (findNodesId)
31 import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
32 import Gargantext.Prelude
34 import Test.QuickCheck (elements)
35 import Test.QuickCheck.Arbitrary
36 import qualified Data.List as List
38 ------------------------------------------------------------------------
39 data ShareNodeParams = ShareTeamParams { username :: Text }
40 | SharePublicParams { node_id :: NodeId}
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)
53 ------------------------------------------------------------------------
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
62 api userInviting nId (ShareTeamParams user') = do
63 user <- case guessUserName user' of
66 isRegistered <- getUserId' (UserName u)
69 printDebug "[G.A.N.Share.api]" ("Team shared with " <> u)
72 username' <- getUsername userInviting
73 _ <- case List.elem username' arbitraryUsername of
75 printDebug "[G.A.N.Share.api]" ("demo users are not allowed to invite" :: Text)
78 children <- findNodesId nId [NodeCorpus]
79 _ <- case List.null children of
81 printDebug "[G.A.N.Share.api]" ("Invitation is enabled if you share a corpus at least" :: Text)
84 printDebug "[G.A.N.Share.api]" ("Your invitation is sent to: " <> user')
89 fromIntegral <$> DB.shareNodeWith (ShareNodeWith_User NodeFolderShared (UserName user)) nId
90 api _uId nId2 (SharePublicParams nId1) =
92 fromIntegral <$> DB.shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId1) nId2
94 ------------------------------------------------------------------------
95 type API = Summary " Share Node with username"
96 :> ReqBody '[JSON] ShareNodeParams
99 ------------------------------------------------------------------------
100 type Unpublish = Summary " Unpublish Node"
101 :> Capture "node_id" NodeId
104 unPublish :: NodeId -> GargServer Unpublish
105 unPublish n = DB.unPublish n