{-|
Module      : Gargantext.API.Node.Share
Description :
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}


module Gargantext.API.Node.Share
      where

import Control.Monad.Random (MonadRandom)
import Data.List qualified as List
import Data.Text qualified as Text
import Gargantext.API.Node.Share.Types (ShareNodeParams(..))
import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Share qualified as Named
import Gargantext.Core.Types.Individu (User(..), arbitraryUsername)
import Gargantext.Database.Action.Share (ShareNodeWith(..))
import Gargantext.Database.Action.Share as DB (shareNodeWith, unshare)
import Gargantext.Database.Action.User (getUserId', getUsername)
import Gargantext.Database.Action.User.New (guessUserName, newUser)
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType(..), UserId(..))
import Gargantext.Database.Prelude (IsDBCmdExtra)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
import Gargantext.Database.Query.Tree (findNodesWithType)
import Gargantext.Prelude
import Servant.Server.Generic (AsServerT)

------------------------------------------------------------------------
-- TODO permission
-- TODO refactor userId which is used twice
-- TODO change return type for better warning/info/success/error handling on the front
api :: ( HasNodeError     err
       , IsDBCmdExtra env err m
       , MonadRandom          m
       )
    => User
    -> NodeId
    -> ShareNodeParams
    -> m Int
api userInviting nId (ShareTeamParams user') = do
  let user'' = Text.toLower user'
  user <- case guessUserName user'' of
    Nothing     -> pure user''
    Just (u, _) -> do
      isRegistered <- getUserId' (UserName u)
      case isRegistered of
        Right _  -> do
          -- printDebug "[G.A.N.Share.api]" ("Team shared with " <> u)
          pure u
        Left _err -> do
          username' <- getUsername userInviting
          unless (username' `List.elem` arbitraryUsername) $ do
            -- TODO better analysis of the composition of what is shared
            children <- findNodesWithType nId [NodeList] [ NodeFolderShared
                                                         , NodeTeam
                                                         , NodeFolder
                                                         , NodeCorpus
                                                         ]
            _ <- if List.null children
              then do
                -- printDebug "[G.A.N.Share.api]" ("Invitation is enabled if you share a corpus at least" :: Text)
                pure $ UnsafeMkUserId 0
              else do
                -- printDebug "[G.A.N.Share.api]" ("Your invitation is sent to: " <> user'')
                newUser user''
            pure ()
          pure u

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

  fromIntegral <$> DB.shareNodeWith (ShareNodeWith_Node NodeFolderPublic nId1) nId2

-- | Unshare a previously shared node via the /share endpoint.
unShare :: IsGargServer env err m => NodeId -> Named.UnshareNode (AsServerT m)
unShare = Named.UnshareNode . DB.unshare