[refactoring] fix .cabal so that tests should work

More import refactoring
parent 63902615
Pipeline #7039 failed with stages
in 67 minutes and 56 seconds
......@@ -172,6 +172,7 @@ library
Gargantext.API.Routes.Named.Viz
Gargantext.API.Routes.Types
Gargantext.API.Search.Types
Gargantext.API.Table.Types
Gargantext.API.Types
Gargantext.API.Viz.Types
Gargantext.API.Worker
......@@ -343,7 +344,6 @@ library
Gargantext.API.Server.Named.Viz
Gargantext.API.Swagger
Gargantext.API.Table
Gargantext.API.Table.Types
Gargantext.API.ThrowAll
Gargantext.Core.Ext.IMT
Gargantext.Core.Ext.IMTUser
......
......@@ -15,8 +15,8 @@ module Gargantext.API.Node.Get
where
import Data.Aeson
import Data.Swagger
import Gargantext.Database.Admin.Types.Node
import Data.Swagger (ToSchema)
import Gargantext.Database.Admin.Types.Node (NodeId, NodeType)
import Gargantext.Prelude
------------------------------------------------------------------------
......
......@@ -15,9 +15,9 @@ import Data.Aeson (Value)
import Data.Text qualified as T
import Gargantext.API.Prelude (GargNoServer, IsGargServer)
import Gargantext.API.Routes.Named.Viz qualified as Named
import Gargantext.Core.Viz.Phylo.API.Tools
import Gargantext.Core.Viz.Phylo.API.Tools (getPhyloData, phylo2dot, phylo2dot2json)
import Gargantext.Core.Viz.Phylo.Example (phyloCleopatre)
import Gargantext.Database.Admin.Types.Node (PhyloId, NodeId,)
import Gargantext.Database.Admin.Types.Node (PhyloId, NodeId)
import Gargantext.Prelude
import Servant
import Servant.Server.Generic (AsServerT)
......
......@@ -16,10 +16,10 @@ module Gargantext.API.Routes.Named.Annuaire (
AddAnnuaireWithForm(..)
) where
import GHC.Generics
import GHC.Generics (Generic)
import Gargantext.API.Node.Corpus.Annuaire (AnnuaireWithForm)
import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Node (AnnuaireId)
import Servant
newtype AddAnnuaireWithForm mode = AddAnnuaireWithForm
......
......@@ -10,12 +10,12 @@ module Gargantext.API.Routes.Named.Contact (
) where
import GHC.Generics
import GHC.Generics (Generic)
import Gargantext.API.Node.Contact.Types (AddContactParams(..))
import Gargantext.API.Routes.Named.Node (NodeNodeAPI(..))
import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Database.Admin.Types.Hyperdata.Contact
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Hyperdata.Contact (HyperdataContact)
import Gargantext.Database.Admin.Types.Node (NodeId)
import Servant
......
......@@ -5,8 +5,8 @@ module Gargantext.API.Routes.Named.Context (
ContextAPI(..)
) where
import GHC.Generics
import Gargantext.Database.Admin.Types.Node
import GHC.Generics (Generic)
import Gargantext.Database.Admin.Types.Node (Node)
import Servant
data ContextAPI a mode = ContextAPI
......
......@@ -25,13 +25,12 @@ import Data.Aeson.TH (deriveJSON)
import Data.Swagger (ToSchema(..), genericDeclareNamedSchema)
import Data.Text (Text)
import GHC.Generics
-- import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Node.Corpus.Export.Types
import Gargantext.API.Node.Types
import Gargantext.API.Node.Corpus.Export.Types (Corpus)
import Gargantext.API.Node.Types (NewWithForm, WithQuery)
import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Core.Text.Ngrams (NgramsType(..))
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Node (CorpusId, ListId)
import Gargantext.Prelude (Bool)
import Servant
......
......@@ -8,9 +8,9 @@ module Gargantext.API.Routes.Named.Count (
, module X
) where
import GHC.Generics
import Servant
import GHC.Generics (Generic)
import Gargantext.API.Count.Types as X
import Servant
newtype CountAPI mode = CountAPI
......
......@@ -24,8 +24,8 @@ module Gargantext.API.Routes.Named.Document (
) where
import Data.Text (Text)
import GHC.Generics
import Gargantext.API.Node.Document.Export.Types
import GHC.Generics (Generic)
import Gargantext.API.Node.Document.Export.Types (DocumentExport, DocumentExportZIP)
import Gargantext.API.Node.DocumentsFromWriteNodes.Types ( Params(..) )
import Gargantext.API.Node.DocumentUpload.Types ( DocumentUpload(..), )
import Gargantext.API.Worker (WorkerAPI)
......
......@@ -6,7 +6,7 @@ module Gargantext.API.Routes.Named.EKG (
) where
import Data.Text (Text)
import GHC.Generics
import GHC.Generics (Generic)
import Servant
import System.Metrics.Json qualified as J
......
......@@ -7,9 +7,9 @@ module Gargantext.API.Routes.Named.File (
) where
import Data.Text (Text)
import GHC.Generics
import Gargantext.API.Node.File.Types
import Gargantext.API.Node.Types
import GHC.Generics (Generic)
import Gargantext.API.Node.File.Types (BSResponse, RESPONSE)
import Gargantext.API.Node.Types (NewWithFile)
import Gargantext.API.Worker (WorkerAPI)
import Servant
......
......@@ -5,10 +5,10 @@ module Gargantext.API.Routes.Named.FrameCalc (
FrameCalcAPI(..)
) where
import Servant
import GHC.Generics
import Gargantext.API.Node.FrameCalcUpload.Types (FrameCalcUpload)
import Gargantext.API.Worker (WorkerAPI)
import GHC.Generics (Generic)
import Servant
newtype FrameCalcAPI mode = FrameCalcAPI
......
......@@ -19,12 +19,12 @@ module Gargantext.API.Routes.Named.List (
) where
import Data.Text (Text)
import GHC.Generics
import Gargantext.API.Ngrams.List.Types
import Gargantext.API.Ngrams.Types
import GHC.Generics (Generic)
import Gargantext.API.Ngrams.List.Types (WithJsonFile, WithTextFile)
import Gargantext.API.Ngrams.Types (NgramsList, NgramsListZIP, NgramsTableMap)
import Gargantext.API.Types (HTML)
import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Node (ListId)
import Gargantext.Utils.Servant qualified as GUS
import Servant
......
......@@ -10,17 +10,17 @@ module Gargantext.API.Routes.Named.Metrics (
) where
import Data.Text (Text)
import Data.Time
import Data.Vector
import GHC.Generics
import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams.NgramsTree
import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types.Main
import Data.Time (UTCTime)
import Data.Vector (Vector)
import GHC.Generics (Generic)
import Gargantext.API.HashedResponse (HashedResponse)
import Gargantext.API.Ngrams.NgramsTree (NgramsTree)
import Gargantext.API.Ngrams.Types (QueryParamR, TabType)
import Gargantext.Core.Types.Main (ListType)
import Gargantext.Core.Types.Query (Limit)
import Gargantext.Core.Viz.Types
import Gargantext.Database.Admin.Types.Metrics
import Gargantext.Database.Admin.Types.Node
import Gargantext.Core.Viz.Types (Histo)
import Gargantext.Database.Admin.Types.Metrics (ChartMetrics, Metrics)
import Gargantext.Database.Admin.Types.Node (ListId)
import Servant
......
......@@ -7,9 +7,9 @@ module Gargantext.API.Routes.Named.Public (
, NodeAPI(..)
) where
import GHC.Generics
import GHC.Generics (Generic)
import Gargantext.API.Public.Types qualified as Public
import Gargantext.API.Routes.Named.File
import Gargantext.API.Routes.Named.File (FileAPI)
import Gargantext.Database.Admin.Types.Node ( NodeId )
import Servant.API
......
......@@ -14,23 +14,21 @@ Portability : POSIX
module Gargantext.API.Types where
import Data.Aeson
import Data.Aeson (ToJSON, encode, eitherDecode)
import Data.ByteString.Lazy.Char8 qualified as BS8
import Data.Either (Either(..))
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.Text (Text)
import Data.Typeable
import Gargantext.API.Ngrams.Types ()
import Gargantext.API.Node.Document.Export.Types ()
import Data.Text.Encoding qualified as E
import Data.Typeable (Typeable)
import Gargantext.Core.Viz.Graph.Types (Graph(..))
import Network.HTTP.Media ((//), (/:))
import Prelude (($))
import Prelude qualified
import Servant.API.ContentTypes ( Accept(..) , MimeRender(..) , MimeUnrender(..) )
import Servant.HTML.Blaze qualified as Blaze
import Servant.Swagger.UI.Core
import Servant.Swagger.UI.Core (SwaggerUiHtml(..))
import Servant.XML.Conduit qualified as S
import qualified Data.ByteString.Lazy.Char8 as BS8
import qualified Data.Text.Encoding as E
import qualified Prelude
data HTML deriving (Typeable)
instance Accept HTML where
......
......@@ -196,7 +196,7 @@ instance Arbitrary TableQuery where
arbitrary = elements [TableQuery { tq_offset = 0
, tq_limit = 10
, tq_orderBy = DateAsc
, tq_view = Docs
, tq_view = Ngrams.Docs
, tq_query = "electrodes" }]
......
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