Node.hs 3.07 KB
Newer Older
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86
{-|
Module      : Gargantext.Database.Action.Node
Description :
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX
-}

{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# OPTIONS_GHC -fno-warn-orphans        #-}

{-# LANGUAGE Arrows                 #-}
{-# LANGUAGE ConstraintKinds        #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TemplateHaskell        #-}
{-# LANGUAGE TypeFamilies           #-}

module Gargantext.Database.Action.Node
  where

import Gargantext.Core.Types (Name)
import Gargantext.Database.Query.Table.Node
import Gargantext.Database.Query.Table.Node.User
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude (Cmd)
import Prelude hiding (null, id, map, sum)

------------------------------------------------------------------------
-- | TODO mk all others nodes
mkNodeWithParent :: HasNodeError err
                 => NodeType
                 -> Maybe ParentId
                 -> UserId
                 -> Name
                 -> Cmd err [NodeId]
mkNodeWithParent NodeUser (Just _) _   _    = nodeError UserNoParent

------------------------------------------------------------------------
mkNodeWithParent NodeUser Nothing uId name =
  insertNodesWithParentR Nothing [node NodeUser name fake_HyperdataUser Nothing uId]

mkNodeWithParent _ Nothing _ _ = nodeError HasParent
------------------------------------------------------------------------
mkNodeWithParent NodeFolder (Just i) uId name =
   insertNodesWithParentR (Just i) [node NodeFolder name hd Nothing uId]
    where
      hd = defaultFolder

mkNodeWithParent NodeFolderPrivate (Just i) uId _ =
   insertNodesWithParentR (Just i) [node NodeFolderPrivate "Private" hd Nothing uId]
    where
      hd = defaultFolder

mkNodeWithParent NodeFolderShared (Just i) uId _ =
   insertNodesWithParentR (Just i) [node NodeFolderShared "Shared" hd Nothing uId]
    where
      hd = defaultFolder

mkNodeWithParent NodeFolderPublic (Just i) uId _ =
   insertNodesWithParentR (Just i) [node NodeFolderPublic "Public" hd Nothing uId]
    where
      hd = defaultFolder

mkNodeWithParent NodeTeam (Just i) uId name =
   insertNodesWithParentR (Just i) [node NodeTeam name hd Nothing uId]
    where
      hd = defaultFolder
------------------------------------------------------------------------
mkNodeWithParent NodeCorpus (Just i) uId name =
   insertNodesWithParentR (Just i) [node NodeCorpus name hd Nothing uId]
    where
      hd = defaultCorpus

mkNodeWithParent NodeAnnuaire (Just i) uId name =
   insertNodesWithParentR (Just i) [node NodeAnnuaire name hd Nothing uId]
    where
      hd = defaultAnnuaire

mkNodeWithParent NodeList (Just i) uId name =
   insertNodesWithParentR (Just i) [node NodeList name hd Nothing uId]
    where
      hd = defaultAnnuaire

87
mkNodeWithParent NodeGraph (Just i) uId _name =
88 89 90 91
   insertNodesWithParentR (Just i) [node NodeGraph "Graph" hd Nothing uId]
    where
      hd = arbitraryGraph

92 93
mkNodeWithParent _ _ _ _       = nodeError NotImplYet