Share.hs 4.45 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21
{-|
Module      : Gargantext.API.Node.Share
Description :
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}

{-# LANGUAGE TemplateHaskell    #-}
{-# LANGUAGE TypeOperators      #-}

module Gargantext.API.Node.Share
      where

import Data.Aeson
import Data.Swagger
import Data.Text (Text)
import GHC.Generics (Generic)
22
import Gargantext.API.Prelude
23
import Gargantext.Core.NLP (HasNLPServer)
24
import Gargantext.Core.Types.Individu (User(..), arbitraryUsername)
25 26
import Gargantext.Database.Action.Share (ShareNodeWith(..))
import Gargantext.Database.Action.Share as DB (shareNodeWith, unPublish)
27 28
import Gargantext.Database.Action.User
import Gargantext.Database.Action.User.New
29 30 31
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
32
import Gargantext.Database.Query.Tree (findNodesWithType)
33
import Gargantext.Prelude
34 35 36 37
import Servant
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import qualified Data.List as List
38 39
import qualified Data.Text as Text
import qualified Gargantext.Utils.Aeson as GUA
40 41

------------------------------------------------------------------------
42 43
data ShareNodeParams = ShareTeamParams   { username :: Text  }
                     | SharePublicParams { node_id  :: NodeId}
44 45 46
  deriving (Generic)
------------------------------------------------------------------------
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
47
instance FromJSON  ShareNodeParams where
48
  parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
49
instance ToJSON    ShareNodeParams where
50
  toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
51 52 53 54
instance ToSchema  ShareNodeParams
instance Arbitrary ShareNodeParams where
  arbitrary = elements [ ShareTeamParams "user1"
                       , SharePublicParams (NodeId 1)
55 56 57
                       ]
------------------------------------------------------------------------
-- TODO permission
58
-- TODO refactor userId which is used twice
59
-- TODO change return type for better warning/info/success/error handling on the front
60
api :: (HasNodeError err, HasNLPServer env, CmdRandom env err m)
61 62
    => User
    -> NodeId
63
    -> ShareNodeParams
64
    -> m Int
65
api userInviting nId (ShareTeamParams user') = do
66 67 68
  let user'' = Text.toLower user'
  user <- case guessUserName user'' of
    Nothing    -> pure user''
69 70 71
    Just (u,_) -> do
      isRegistered <- getUserId' (UserName u)
      case isRegistered of
72
        Just _  -> do
73
          -- printDebug "[G.A.N.Share.api]" ("Team shared with " <> u)
74
          pure u
75
        Nothing -> do
76 77 78
          username' <- getUsername userInviting
          _ <- case List.elem username' arbitraryUsername of
            True  -> do
79
              -- printDebug "[G.A.N.Share.api]" ("Demo users are not allowed to invite" :: Text)
80 81
              pure ()
            False -> do
82 83 84 85 86 87
              -- TODO better analysis of the composition of what is shared
              children <- findNodesWithType nId [NodeList] [ NodeFolderShared
                                                           , NodeTeam
                                                           , NodeFolder
                                                           , NodeCorpus
                                                           ]
88 89
              _ <- case List.null children of
                True -> do
90
                  -- printDebug "[G.A.N.Share.api]" ("Invitation is enabled if you share a corpus at least" :: Text)
91
                  pure 0
92
                False -> do
93
                  -- printDebug "[G.A.N.Share.api]" ("Your invitation is sent to: " <> user'')
94
                  newUser user''
95
              pure ()
96 97
          pure u

98
  fromIntegral <$> DB.shareNodeWith (ShareNodeWith_User NodeFolderShared (UserName user)) nId
99
api _uId nId2 (SharePublicParams nId1) =
100

101
  fromIntegral <$> DB.shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId1) nId2
102 103 104

------------------------------------------------------------------------
type API = Summary " Share Node with username"
105
         :> ReqBody '[JSON] ShareNodeParams
106 107
         :> Post    '[JSON] Int

108 109 110 111
------------------------------------------------------------------------
type Unpublish = Summary " Unpublish Node"
               :> Capture "node_id" NodeId
               :> Put '[JSON] Int
112

113 114
unPublish :: NodeId -> GargServer Unpublish
unPublish n = DB.unPublish n