[REFACT] FlowList integration to Terms with instances
[gargantext.git] / src / Gargantext / API / Node / Corpus / Export.hs
index ed2039512e8e0a3b9b6dbefb665bde29609d3083..098f6dafeb5cd87dde19a9011ad9f7e0ca2f3796 100644 (file)
@@ -13,27 +13,20 @@ Main exports of Gargantext:
 - lists
 -}
 
-{-# LANGUAGE TemplateHaskell   #-}
-{-# LANGUAGE TypeOperators     #-}
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-
 module Gargantext.API.Node.Corpus.Export
   where
 
 
-import Data.Aeson.TH (deriveJSON)
 import Data.Map (Map)
 import Data.Maybe (fromMaybe)
 import Data.Set (Set)
-import Data.Swagger
 import Data.Text (Text)
-import GHC.Generics (Generic)
-import Gargantext.API.Ngrams
+import Gargantext.API.Node.Corpus.Export.Types
+import Gargantext.API.Ngrams.Types
 import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo)
 import Gargantext.API.Prelude (GargNoServer)
 import Gargantext.Prelude.Crypto.Hash (hash)
 import Gargantext.Core.Types
-import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
 import Gargantext.Database.Action.Metrics.NgramsByNode (getNgramsByNodeOnlyUser)
 import Gargantext.Database.Admin.Config (userMaster)
 import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
@@ -45,60 +38,10 @@ import Gargantext.Database.Query.Table.NodeNode (selectDocNodes)
 import Gargantext.Database.Schema.Ngrams (NgramsType(..))
 import Gargantext.Database.Schema.Node (_node_id, _node_hyperdata)
 import Gargantext.Prelude
-import Servant
 import qualified Data.List as List
 import qualified Data.Map as Map
 import qualified Data.Set as Set
 
-
--- Corpus Export
-data Corpus =
-  Corpus { _c_corpus :: [Document]
-         , _c_hash   :: Hash
-         } deriving (Generic)
-
--- | Document Export
-data Document =
-  Document { _d_document :: Node HyperdataDocument
-           , _d_ngrams   :: Ngrams
-           , _d_hash     :: Hash
-           } deriving (Generic)
-
-data Ngrams =
-  Ngrams { _ng_ngrams :: [Text]
-         , _ng_hash   :: Hash
-         } deriving (Generic)
-
-type Hash = Text
--------
-instance ToSchema Corpus where
-  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_c_")
-
-instance ToSchema Document where
-  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_d_")
-
-instance ToSchema Ngrams where
-  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_ng_")
-
-instance (ToSchema a) => ToSchema (Node a) where
-  declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_node_")
-
--------
-instance ToParamSchema Corpus where
-  toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
-
-instance ToParamSchema Document where
-  toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
-
-instance ToParamSchema Ngrams where
-  toParamSchema _ = toParamSchema (Proxy :: Proxy TODO)
---------------------------------------------------
-type API = Summary "Corpus Export"
-            :> "export"
-            :> QueryParam "listId"     ListId
-            :> QueryParam "ngramsType" NgramsType
-            :> Get '[JSON] Corpus
-
 --------------------------------------------------
 -- | Hashes are ordered by Set
 getCorpus :: CorpusId
@@ -144,14 +87,6 @@ getNodeNgrams cId lId' nt repo = do
   r <- getNgramsByNodeOnlyUser cId (lIds <> [lId]) nt (Map.keys ngs)
   pure r
 
-
-$(deriveJSON (unPrefix "_c_") ''Corpus)
-$(deriveJSON (unPrefix "_d_") ''Document)
-$(deriveJSON (unPrefix "_ng_") ''Ngrams)
-
-
 -- TODO
 -- Exports List
--- Version number of the list
-
-
+-- Version number of the list
\ No newline at end of file