Commit 65978a65 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[API/Database] mk/post Node.

parent f40b051d
...@@ -46,7 +46,7 @@ import Gargantext.Database.Types.Node ...@@ -46,7 +46,7 @@ import Gargantext.Database.Types.Node
import Gargantext.Database.Node ( runCmd import Gargantext.Database.Node ( runCmd
, getNodesWithParentId , getNodesWithParentId
, getNode, getNodesWith , getNode, getNodesWith
, deleteNode, deleteNodes) , deleteNode, deleteNodes, mk)
import qualified Gargantext.Database.Node.Update as U (update, Update(..)) import qualified Gargantext.Database.Node.Update as U (update, Update(..))
import Gargantext.Database.Facet (FacetDoc, getDocFacet import Gargantext.Database.Facet (FacetDoc, getDocFacet
,FacetChart) ,FacetChart)
...@@ -71,21 +71,38 @@ type Roots = Get '[JSON] [Node Value] ...@@ -71,21 +71,38 @@ type Roots = Get '[JSON] [Node Value]
type NodesAPI = Delete '[JSON] Int type NodesAPI = Delete '[JSON] Int
------------------------------------------------------------------------
------------------------------------------------------------------------
data RenameNode = RenameNode { r_name :: Text }
deriving (Generic)
instance FromJSON RenameNode
instance ToJSON RenameNode
instance ToSchema RenameNode
instance Arbitrary RenameNode where
arbitrary = elements [RenameNode "test"]
------------------------------------------------------------------------
data Rename = Rename { name :: Text } data PostNode = PostNode { pn_name :: Text
, pn_typename :: NodeType}
deriving (Generic) deriving (Generic)
instance FromJSON Rename instance FromJSON PostNode
instance ToJSON Rename instance ToJSON PostNode
instance ToSchema Rename instance ToSchema PostNode
instance Arbitrary Rename where instance Arbitrary PostNode where
arbitrary = elements [Rename "test"] arbitrary = elements [PostNode "Node test" NodeCorpus]
------------------------------------------------------------------------
------------------------------------------------------------------------
type NodeAPI = Get '[JSON] (Node Value) type NodeAPI = Get '[JSON] (Node Value)
:<|> "rename" :> Summary " Rename Node" :<|> "rename" :> Summary " RenameNode Node"
:> ReqBody '[JSON] Rename :> ReqBody '[JSON] RenameNode
:> Put '[JSON] [Int] :> Put '[JSON] [Int]
:<|> Post '[JSON] Int :<|> Summary " PostNode Node with ParentId as {id}"
:> ReqBody '[JSON] PostNode
:> Post '[JSON] Int
:<|> Put '[JSON] Int :<|> Put '[JSON] Int
:<|> Delete '[JSON] Int :<|> Delete '[JSON] Int
:<|> "children" :> Summary " Summary children" :<|> "children" :> Summary " Summary children"
...@@ -163,14 +180,14 @@ nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode co ...@@ -163,14 +180,14 @@ nodeAPI conn id = liftIO (putStrLn ("/node" :: Text) >> getNode co
-- :<|> query -- :<|> query
-- | Check if the name is less than 255 char -- | Check if the name is less than 255 char
--rename :: Connection -> NodeId -> Rename -> Server NodeAPI --rename :: Connection -> NodeId -> Rename -> Server NodeAPI
rename :: Connection -> NodeId -> Rename -> Handler [Int] rename :: Connection -> NodeId -> RenameNode -> Handler [Int]
rename c nId (Rename name) = liftIO $ U.update (U.Rename nId name) c rename c nId (RenameNode name) = liftIO $ U.update (U.Rename nId name) c
nodesAPI :: Connection -> [NodeId] -> Server NodesAPI nodesAPI :: Connection -> [NodeId] -> Server NodesAPI
nodesAPI conn ids = deleteNodes' conn ids nodesAPI conn ids = deleteNodes' conn ids
postNode :: Connection -> NodeId -> Handler Int postNode :: Connection -> NodeId -> PostNode -> Handler Int
postNode = undefined -- TODO postNode c pId (PostNode name nt) = liftIO $ mk c pId nt name
putNode :: Connection -> NodeId -> Handler Int putNode :: Connection -> NodeId -> Handler Int
putNode = undefined -- TODO putNode = undefined -- TODO
......
...@@ -148,24 +148,25 @@ put u = mkCmd $ U.update u ...@@ -148,24 +148,25 @@ put u = mkCmd $ U.update u
-- jump NodeId -- jump NodeId
-- touch Dir -- touch Dir
type CorpusName = Text type Name = Text
mkCorpus :: ToJSON a => CorpusName -> (a -> Text) -> [a] -> Cmd NewNode
mkCorpus corpusName title ns = do mkCorpus :: ToJSON a => Name -> (a -> Text) -> [a] -> Cmd NewNode
mkCorpus name title ns = do
pid <- last <$> home pid <- last <$> home
let uid = 1 let uid = 1
postNode uid pid ( Node' NodeCorpus corpusName emptyObject postNode uid pid ( Node' NodeCorpus name emptyObject
(map (\n -> Node' Document (title n) (toJSON n) []) ns) (map (\n -> Node' Document (title n) (toJSON n) []) ns)
) )
-- | -- |
-- import IMTClient as C -- import IMTClient as C
-- postAnnuaire "Annuaire IMT" (\n -> (maybe "" identity (C.prenom n)) <> " " <> (maybe "" identity (C.nom n))) (take 30 annuaire) -- postAnnuaire "Annuaire IMT" (\n -> (maybe "" identity (C.prenom n)) <> " " <> (maybe "" identity (C.nom n))) (take 30 annuaire)
postAnnuaire :: ToJSON a => CorpusName -> (a -> Text) -> [a] -> Cmd NewNode postAnnuaire :: ToJSON a => Name -> (a -> Text) -> [a] -> Cmd NewNode
postAnnuaire corpusName title ns = do postAnnuaire name title ns = do
pid <- last <$> home pid <- last <$> home
let uid = 1 let uid = 1
postNode uid pid ( Node' Annuaire corpusName emptyObject postNode uid pid ( Node' Annuaire name emptyObject
(map (\n -> Node' UserPage (title n) (toJSON n) []) ns) (map (\n -> Node' UserPage (title n) (toJSON n) []) ns)
) )
......
...@@ -396,3 +396,9 @@ childWith uId pId (Node' Document txt v []) = node2table uId pId (Node' Document ...@@ -396,3 +396,9 @@ childWith uId pId (Node' Document txt v []) = node2table uId pId (Node' Document
childWith uId pId (Node' UserPage txt v []) = node2table uId pId (Node' UserPage txt v []) childWith uId pId (Node' UserPage txt v []) = node2table uId pId (Node' UserPage txt v [])
childWith _ _ (Node' _ _ _ _) = panic "This NodeType can not be a child" childWith _ _ (Node' _ _ _ _) = panic "This NodeType can not be a child"
mk :: Connection -> ParentId -> NodeType -> Text -> IO Int
mk c pId nt name = fromIntegral <$> mkNode pId [node 1 pId nt name ""] c
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment