Commit 4d0b27ac authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] Json instance prefix rename

parent 16b9aff8
{-|
Module : Gargantext.API.HashedResponse
Description :
Copyright : (c) CNRS, 2020-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
module Gargantext.API.HashedResponse where
import Data.Aeson
......
......@@ -31,6 +31,7 @@ module Gargantext.API.Node
where
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson.TH (deriveJSON)
import Data.Maybe
import Data.Swagger
import Data.Text (Text())
......@@ -45,9 +46,10 @@ import Gargantext.API.Table
import Gargantext.Core.Types (NodeTableResult)
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Types.Main (Tree, NodeTree)
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.Action.Flow.Pairing (pairing)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude -- (Cmd, CmdM)
import Gargantext.Database.Query.Facet (FacetDoc, OrderBy(..))
import Gargantext.Database.Query.Table.Node
......@@ -227,12 +229,6 @@ nodeAPI p uId id' = withAccess (Proxy :: Proxy (NodeAPI a)) Proxy uId (PathNode
data RenameNode = RenameNode { r_name :: Text }
deriving (Generic)
-- TODO unPrefix "r_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON RenameNode
instance ToJSON RenameNode
instance ToSchema RenameNode
instance Arbitrary RenameNode where
arbitrary = elements [RenameNode "test"]
------------------------------------------------------------------------
------------------------------------------------------------------------
type CatApi = Summary " To Categorize NodeNodes: 0 for delete, 1/null neutral, 2 favorite"
......@@ -315,4 +311,12 @@ moveNode :: User
-> Cmd err [Int]
moveNode _u n p = update (Move n p)
-------------------------------------------------------------
$(deriveJSON (unPrefix "r_" ) ''RenameNode )
instance ToSchema RenameNode
instance Arbitrary RenameNode where
arbitrary = elements [RenameNode "test"]
-------------------------------------------------------------
......@@ -16,7 +16,6 @@ Portability : POSIX
module Gargantext.Viz.Graph
where
import Control.Lens (makeLenses)
import Data.ByteString.Lazy as DBL (readFile, writeFile)
import Data.Text (Text, pack)
......
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