[refactor] add newtype Limit, newtype Query

This is safer than type Limit = Int
parent df6f1dde
Pipeline #3877 failed with stage
in 29 minutes and 20 seconds
...@@ -30,6 +30,7 @@ import Gargantext.API.Node () -- instances ...@@ -30,6 +30,7 @@ import Gargantext.API.Node () -- instances
import Gargantext.API.Prelude (GargError) import Gargantext.API.Prelude (GargError)
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Types.Query (Limit)
import Gargantext.Database.Action.Flow (flowCorpusFile, flowAnnuaire, TermType(..)) import Gargantext.Database.Action.Flow (flowCorpusFile, flowAnnuaire, TermType(..))
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument) import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument)
...@@ -49,7 +50,7 @@ main = do ...@@ -49,7 +50,7 @@ main = do
--tt = (Unsupervised EN 6 0 Nothing) --tt = (Unsupervised EN 6 0 Nothing)
tt = (Multi EN) tt = (Multi EN)
format = CsvGargV3 -- CsvHal --WOS format = CsvGargV3 -- CsvHal --WOS
limit' = case (readMaybe limit :: Maybe Int) of limit' = case (readMaybe limit :: Maybe Limit) of
Nothing -> panic $ "Cannot read limit: " <> (Text.pack limit) Nothing -> panic $ "Cannot read limit: " <> (Text.pack limit)
Just l -> l Just l -> l
corpus :: forall m. (FlowCmdM DevEnv GargError m, MonadJobStatus m, JobHandle m ~ DevJobHandle) => m CorpusId corpus :: forall m. (FlowCmdM DevEnv GargError m, MonadJobStatus m, JobHandle m ~ DevJobHandle) => m CorpusId
......
...@@ -72,6 +72,7 @@ library ...@@ -72,6 +72,7 @@ library
Gargantext.Core.Types Gargantext.Core.Types
Gargantext.Core.Types.Individu Gargantext.Core.Types.Individu
Gargantext.Core.Types.Main Gargantext.Core.Types.Main
Gargantext.Core.Types.Query
Gargantext.Core.Utils Gargantext.Core.Utils
Gargantext.Core.Utils.Prefix Gargantext.Core.Utils.Prefix
Gargantext.Core.Viz.Graph Gargantext.Core.Viz.Graph
......
...@@ -98,6 +98,7 @@ library: ...@@ -98,6 +98,7 @@ library:
- Gargantext.Core.Types - Gargantext.Core.Types
- Gargantext.Core.Types.Individu - Gargantext.Core.Types.Individu
- Gargantext.Core.Types.Main - Gargantext.Core.Types.Main
- Gargantext.Core.Types.Query
- Gargantext.Core.Utils - Gargantext.Core.Utils
- Gargantext.Core.Utils.Prefix - Gargantext.Core.Utils.Prefix
- Gargantext.Core.Viz.Graph - Gargantext.Core.Viz.Graph
...@@ -557,4 +558,3 @@ tests: ...@@ -557,4 +558,3 @@ tests:
# - OverloadedStrings # - OverloadedStrings
# - RankNTypes # - RankNTypes
# #
...@@ -40,11 +40,8 @@ module Gargantext.API.Admin.Auth ...@@ -40,11 +40,8 @@ module Gargantext.API.Admin.Auth
import Control.Lens (view, (#)) import Control.Lens (view, (#))
import Data.Aeson import Data.Aeson
import Data.Swagger (ToSchema(..)) import Data.Swagger (ToSchema(..))
import Data.Text (Text)
import Data.Text.Lazy (toStrict)
import Data.UUID (UUID, fromText, toText) import Data.UUID (UUID, fromText, toText)
import Data.UUID.V4 (nextRandom) import Data.UUID.V4 (nextRandom)
import GHC.Generics (Generic)
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.EnvTypes (GargJob(..), Env) import Gargantext.API.Admin.EnvTypes (GargJob(..), Env)
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
...@@ -64,6 +61,7 @@ import Gargantext.Database.Schema.Node (NodePoly(_node_id)) ...@@ -64,6 +61,7 @@ import Gargantext.Database.Schema.Node (NodePoly(_node_id))
import Gargantext.Prelude hiding (reverse) import Gargantext.Prelude hiding (reverse)
import Gargantext.Prelude.Crypto.Pass.User (gargPass) import Gargantext.Prelude.Crypto.Pass.User (gargPass)
import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..)) import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Protolude hiding (to)
import Servant import Servant
import Servant.Auth.Server import Servant.Auth.Server
import qualified Data.Text as Text import qualified Data.Text as Text
......
...@@ -27,7 +27,8 @@ import Gargantext.API.Ngrams.NgramsTree ...@@ -27,7 +27,8 @@ import Gargantext.API.Ngrams.NgramsTree
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal) import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal)
import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..)) import Gargantext.Core.Types (CorpusId, ListId, ListType(..))
import Gargantext.Core.Types.Query (Limit)
import Gargantext.Core.Viz.Chart import Gargantext.Core.Viz.Chart
import Gargantext.Core.Viz.Types import Gargantext.Core.Viz.Types
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree)
...@@ -49,12 +50,12 @@ import qualified Gargantext.Database.Action.Metrics as Metrics ...@@ -49,12 +50,12 @@ import qualified Gargantext.Database.Action.Metrics as Metrics
type ScatterAPI = Summary "SepGen IncExc metrics" type ScatterAPI = Summary "SepGen IncExc metrics"
:> QueryParam "list" ListId :> QueryParam "list" ListId
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParam "limit" Int :> QueryParam "limit" Limit
:> Get '[JSON] (HashedResponse Metrics) :> Get '[JSON] (HashedResponse Metrics)
:<|> Summary "Scatter update" :<|> Summary "Scatter update"
:> QueryParam "list" ListId :> QueryParam "list" ListId
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParam "limit" Int :> QueryParam "limit" Limit
:> Post '[JSON] () :> Post '[JSON] ()
:<|> "hash" :> Summary "Scatter Hash" :<|> "hash" :> Summary "Scatter Hash"
:> QueryParam "list" ListId :> QueryParam "list" ListId
...@@ -149,7 +150,7 @@ type ChartApi = Summary " Chart API" ...@@ -149,7 +150,7 @@ type ChartApi = Summary " Chart API"
:<|> Summary "Chart update" :<|> Summary "Chart update"
:> QueryParam "list" ListId :> QueryParam "list" ListId
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParam "limit" Int :> QueryParam "limit" Limit
:> Post '[JSON] () :> Post '[JSON] ()
:<|> "hash" :> Summary "Chart Hash" :<|> "hash" :> Summary "Chart Hash"
:> QueryParam "list" ListId :> QueryParam "list" ListId
...@@ -236,7 +237,7 @@ type PieApi = Summary "Pie Chart" ...@@ -236,7 +237,7 @@ type PieApi = Summary "Pie Chart"
:<|> Summary "Pie Chart update" :<|> Summary "Pie Chart update"
:> QueryParam "list" ListId :> QueryParam "list" ListId
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParam "limit" Int :> QueryParam "limit" Limit
:> Post '[JSON] () :> Post '[JSON] ()
:<|> "hash" :> Summary "Pie Hash" :<|> "hash" :> Summary "Pie Hash"
:> QueryParam "list" ListId :> QueryParam "list" ListId
......
...@@ -104,7 +104,8 @@ import Gargantext.API.Admin.Types (HasSettings) ...@@ -104,7 +104,8 @@ import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, TODO, assertValid, HasInvalidError) import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, TODO, assertValid, HasInvalidError)
import Gargantext.Core.Types.Query (Limit(..), Offset(..))
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Action.Metrics.NgramsByContext (getOccByNgramsOnlyFast) import Gargantext.Database.Action.Metrics.NgramsByContext (getOccByNgramsOnlyFast)
...@@ -545,7 +546,7 @@ getTableNgrams _nType nId tabType listId limit_ offset ...@@ -545,7 +546,7 @@ getTableNgrams _nType nId tabType listId limit_ offset
-- lIds <- selectNodesWithUsername NodeList userMaster -- lIds <- selectNodesWithUsername NodeList userMaster
let let
ngramsType = ngramsTypeFromTabType tabType ngramsType = ngramsTypeFromTabType tabType
offset' = maybe 0 identity offset offset' = getOffset $ maybe 0 identity offset
listType' = maybe (const True) (==) listType listType' = maybe (const True) (==) listType
minSize' = maybe (const True) (<=) minSize minSize' = maybe (const True) (<=) minSize
maxSize' = maybe (const True) (>=) maxSize maxSize' = maybe (const True) (>=) maxSize
...@@ -590,7 +591,7 @@ getTableNgrams _nType nId tabType listId limit_ offset ...@@ -590,7 +591,7 @@ getTableNgrams _nType nId tabType listId limit_ offset
-- | Paginate the results -- | Paginate the results
sortAndPaginate :: [NgramsElement] -> [NgramsElement] sortAndPaginate :: [NgramsElement] -> [NgramsElement]
sortAndPaginate = take limit_ sortAndPaginate = take (getLimit limit_)
. drop offset' . drop offset'
. sortOnOrder orderBy . sortOnOrder orderBy
......
...@@ -47,6 +47,7 @@ import Gargantext.API.Table ...@@ -47,6 +47,7 @@ import Gargantext.API.Table
import Gargantext.Core.Types (NodeTableResult) import Gargantext.Core.Types (NodeTableResult)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Types.Main (Tree, NodeTree) import Gargantext.Core.Types.Main (Tree, NodeTree)
import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Core.Viz.Phylo.API (PhyloAPI, phyloAPI) import Gargantext.Core.Viz.Phylo.API (PhyloAPI, phyloAPI)
import Gargantext.Database.Action.Flow.Pairing (pairing) import Gargantext.Database.Action.Flow.Pairing (pairing)
...@@ -169,8 +170,8 @@ type PostNodeApi = Summary " PostNode Node with ParentId as {id}" ...@@ -169,8 +170,8 @@ type PostNodeApi = Summary " PostNode Node with ParentId as {id}"
type ChildrenApi a = Summary " Summary children" type ChildrenApi a = Summary " Summary children"
:> QueryParam "type" NodeType :> QueryParam "type" NodeType
:> QueryParam "offset" Int :> QueryParam "offset" Offset
:> QueryParam "limit" Int :> QueryParam "limit" Limit
-- :> Get '[JSON] [Node a] -- :> Get '[JSON] [Node a]
:> Get '[JSON] (NodeTableResult a) :> Get '[JSON] (NodeTableResult a)
...@@ -296,8 +297,8 @@ scoreApi = putScore ...@@ -296,8 +297,8 @@ scoreApi = putScore
type PairingApi = Summary " Pairing API" type PairingApi = Summary " Pairing API"
:> QueryParam "view" TabType :> QueryParam "view" TabType
-- TODO change TabType -> DocType (CorpusId for pairing) -- TODO change TabType -> DocType (CorpusId for pairing)
:> QueryParam "offset" Int :> QueryParam "offset" Offset
:> QueryParam "limit" Int :> QueryParam "limit" Limit
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> Get '[JSON] [FacetDoc] :> Get '[JSON] [FacetDoc]
......
...@@ -23,6 +23,7 @@ import Data.Swagger hiding (fieldLabelModifier, Contact) ...@@ -23,6 +23,7 @@ import Data.Swagger hiding (fieldLabelModifier, Contact)
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Core.Types.Search import Gargantext.Core.Types.Search
import Gargantext.Core.Utils.Prefix (unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Database.Action.Flow.Pairing (isPairedWith) import Gargantext.Database.Action.Flow.Pairing (isPairedWith)
...@@ -40,8 +41,8 @@ import Test.QuickCheck.Arbitrary ...@@ -40,8 +41,8 @@ import Test.QuickCheck.Arbitrary
-- TODO-EVENTS: No event, this is a read-only query. -- TODO-EVENTS: No event, this is a read-only query.
type API results = Summary "Search endpoint" type API results = Summary "Search endpoint"
:> ReqBody '[JSON] SearchQuery :> ReqBody '[JSON] SearchQuery
:> QueryParam "offset" Int :> QueryParam "offset" Offset
:> QueryParam "limit" Int :> QueryParam "limit" Limit
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> Post '[JSON] results :> Post '[JSON] results
----------------------------------------------------------------------- -----------------------------------------------------------------------
......
...@@ -43,7 +43,8 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) ...@@ -43,7 +43,8 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams.Types (TabType(..)) import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Types (Offset, Limit, TableResult(..)) import Gargantext.Core.Types (TableResult(..))
import Gargantext.Core.Types.Query (Offset, Limit)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike) import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike)
import Gargantext.Database.Action.Search import Gargantext.Database.Action.Search
...@@ -58,8 +59,8 @@ import Gargantext.Prelude ...@@ -58,8 +59,8 @@ import Gargantext.Prelude
type TableApi = Summary "Table API" type TableApi = Summary "Table API"
:> QueryParam "tabType" TabType :> QueryParam "tabType" TabType
:> QueryParam "list" ListId :> QueryParam "list" ListId
:> QueryParam "limit" Int :> QueryParam "limit" Limit
:> QueryParam "offset" Int :> QueryParam "offset" Offset
:> QueryParam "orderBy" OrderBy :> QueryParam "orderBy" OrderBy
:> QueryParam "query" Text :> QueryParam "query" Text
:> QueryParam "year" Text :> QueryParam "year" Text
...@@ -73,8 +74,8 @@ type TableApi = Summary "Table API" ...@@ -73,8 +74,8 @@ type TableApi = Summary "Table API"
:> Get '[JSON] Text :> Get '[JSON] Text
data TableQuery = TableQuery data TableQuery = TableQuery
{ tq_offset :: Int { tq_offset :: Offset
, tq_limit :: Int , tq_limit :: Limit
, tq_orderBy :: OrderBy , tq_orderBy :: OrderBy
, tq_view :: TabType , tq_view :: TabType
, tq_query :: Text , tq_query :: Text
...@@ -105,8 +106,8 @@ getTableApi :: HasNodeError err ...@@ -105,8 +106,8 @@ getTableApi :: HasNodeError err
=> NodeId => NodeId
-> Maybe TabType -> Maybe TabType
-> Maybe ListId -> Maybe ListId
-> Maybe Int -> Maybe Limit
-> Maybe Int -> Maybe Offset
-> Maybe OrderBy -> Maybe OrderBy
-> Maybe Text -> Maybe Text
-> Maybe Text -> Maybe Text
......
...@@ -111,11 +111,6 @@ fromListTypeId i = lookup i ...@@ -111,11 +111,6 @@ fromListTypeId i = lookup i
-- | Then a Node can be a Score which has some synonyms -- | Then a Node can be a Score which has some synonyms
-- Queries
type Limit = Int
type Offset = Int
type IsTrash = Bool
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- All the Database is structured as a hierarchical Tree -- All the Database is structured as a hierarchical Tree
data Tree a = TreeN { _tn_node :: a, _tn_children :: [Tree a] } data Tree a = TreeN { _tn_node :: a, _tn_children :: [Tree a] }
......
{-# LANGUAGE DerivingStrategies #-}
module Gargantext.Core.Types.Query where
import qualified Data.Aeson as Aeson
import qualified Database.PostgreSQL.Simple.FromField as PSQL
import qualified Database.PostgreSQL.Simple.ToField as PSQL
import qualified Data.Swagger as Swagger
import Protolude
import qualified Servant.API as Servant
-- newtype wrappers based on
-- https://www.haskellforall.com/2023/04/ergonomic-newtypes-for-haskell-strings.html
-- These give stronger type guarantees than `type Offset = Int`.
-- Queries
newtype Limit = Limit { getLimit :: Int }
deriving newtype ( Aeson.FromJSON, Aeson.ToJSON
, Eq, Num, Read, Show
, PSQL.FromField, PSQL.ToField
, Servant.FromHttpApiData, Servant.ToHttpApiData
, Swagger.ToParamSchema, Swagger.ToSchema)
newtype Offset = Offset { getOffset :: Int }
deriving newtype ( Aeson.FromJSON, Aeson.ToJSON
, Eq, Num, Read, Show
, PSQL.FromField, PSQL.ToField
, Servant.FromHttpApiData, Servant.ToHttpApiData
, Swagger.ToParamSchema, Swagger.ToSchema)
type IsTrash = Bool
...@@ -88,6 +88,7 @@ import Gargantext.Core.Text.Terms.Mono.Stem.En (stemIt) ...@@ -88,6 +88,7 @@ import Gargantext.Core.Text.Terms.Mono.Stem.En (stemIt)
import Gargantext.Core.Types (POS(NP), TermsCount) import Gargantext.Core.Types (POS(NP), TermsCount)
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Types.Main import Gargantext.Core.Types.Main
import Gargantext.Core.Types.Query (Limit)
import Gargantext.Core.Utils (addTuples) import Gargantext.Core.Utils (addTuples)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Flow.List import Gargantext.Database.Action.Flow.List
...@@ -303,10 +304,10 @@ flow c u cn la mfslw (mLength, docsC) jobHandle = do ...@@ -303,10 +304,10 @@ flow c u cn la mfslw (mLength, docsC) jobHandle = do
let maxIdx = maximum (fst <$> docs) let maxIdx = maximum (fst <$> docs)
case mLength of case mLength of
Nothing -> pure () Nothing -> pure ()
Just len -> do Just _len -> do
let succeeded = fromIntegral (1 + maxIdx) let succeeded = fromIntegral (1 + maxIdx)
let remaining = fromIntegral (len - maxIdx) -- let remaining = fromIntegral (len - maxIdx)
-- Reconstruct the correct update state by using 'markStarted' and the other primitives. -- Reconstruct the correct update state by using 'markStarted' and the other primitives.
-- We do this slightly awkward arithmetic such that when we call 'markProgress' we reduce -- We do this slightly awkward arithmetic such that when we call 'markProgress' we reduce
-- the number of 'remaining' of exactly '1 + maxIdx', and we will end up with a 'JobLog' -- the number of 'remaining' of exactly '1 + maxIdx', and we will end up with a 'JobLog'
...@@ -317,7 +318,7 @@ flow c u cn la mfslw (mLength, docsC) jobHandle = do ...@@ -317,7 +318,7 @@ flow c u cn la mfslw (mLength, docsC) jobHandle = do
-- , _scst_remaining = Just $ fromIntegral $ len - maxIdx -- , _scst_remaining = Just $ fromIntegral $ len - maxIdx
-- , _scst_events = Just [] -- , _scst_events = Just []
-- } -- }
markStarted (remaining + succeeded) jobHandle -- markStarted (remaining + succeeded) jobHandle
markProgress succeeded jobHandle markProgress succeeded jobHandle
pure ids pure ids
......
...@@ -18,7 +18,7 @@ module Gargantext.Database.Action.Learn ...@@ -18,7 +18,7 @@ module Gargantext.Database.Action.Learn
import Data.Maybe import Data.Maybe
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types (Offset, Limit) import Gargantext.Core.Types.Query (Offset, Limit(..))
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Query.Facet import Gargantext.Database.Query.Facet
...@@ -70,7 +70,7 @@ moreLikeWith cId o l order ft priors = do ...@@ -70,7 +70,7 @@ moreLikeWith cId o l order ft priors = do
$ filter ((==) (Just $ not $ fav2bool ft) . snd) $ filter ((==) (Just $ not $ fav2bool ft) . snd)
$ map (\f -> (f, detectDefaultWithPriors text priors f)) docs_test $ map (\f -> (f, detectDefaultWithPriors text priors f)) docs_test
pure $ List.take (maybe 10 identity l) results pure $ List.take (getLimit $ maybe 10 identity l) results
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
fav2bool :: FavOrTrash -> Bool fav2bool :: FavOrTrash -> Bool
......
...@@ -30,7 +30,8 @@ import Gargantext.Core.Mail.Types (HasMail) ...@@ -30,7 +30,8 @@ import Gargantext.Core.Mail.Types (HasMail)
import Gargantext.Core.NodeStory hiding (runPGSQuery) import Gargantext.Core.NodeStory hiding (runPGSQuery)
import Gargantext.Core.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-}) import Gargantext.Core.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-})
import Database.PostgreSQL.Simple.ToField (toField, Action{-, ToField-}) import Database.PostgreSQL.Simple.ToField (toField, Action{-, ToField-})
import Gargantext.Core.Types (ListType(..), Limit, NodeType(..), ContextId) import Gargantext.Core.Types (ListType(..), NodeType(..), ContextId)
import Gargantext.Core.Types.Query (Limit(..))
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Action.Metrics.NgramsByContext (getContextsByNgramsOnlyUser{-, getTficfWith-}) import Gargantext.Database.Action.Metrics.NgramsByContext (getContextsByNgramsOnlyUser{-, getTficfWith-})
import Gargantext.Database.Admin.Config (userMaster) import Gargantext.Database.Admin.Config (userMaster)
...@@ -240,6 +241,6 @@ getNgrams lId tabType = do ...@@ -240,6 +241,6 @@ getNgrams lId tabType = do
pure (lists, maybeSyn) pure (lists, maybeSyn)
-- Some useful Tools -- Some useful Tools
take' :: Maybe Int -> [a] -> [a] take' :: Maybe Limit -> [a] -> [a]
take' Nothing xs = xs take' Nothing xs = xs
take' (Just n) xs = take n xs take' (Just n) xs = take (getLimit n) xs
...@@ -22,6 +22,7 @@ module Gargantext.Database.Action.Metrics.Lists ...@@ -22,6 +22,7 @@ module Gargantext.Database.Action.Metrics.Lists
import Gargantext.API.Ngrams.Types (TabType(..)) import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.Core.Text.Metrics (Scored(..)) import Gargantext.Core.Text.Metrics (Scored(..))
import Gargantext.Core.Types -- (NodePoly(..), NodeCorpus, ListId) import Gargantext.Core.Types -- (NodePoly(..), NodeCorpus, ListId)
import Gargantext.Core.Types.Query (Limit)
import Gargantext.Database.Action.Flow.Types (FlowCmdM) import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Prelude hiding (sum, head) import Gargantext.Prelude hiding (sum, head)
import Prelude hiding (null, id, map, sum) import Prelude hiding (null, id, map, sum)
...@@ -42,7 +43,7 @@ trainModel u = do ...@@ -42,7 +43,7 @@ trainModel u = do
getMetrics' :: FlowCmdM env err m getMetrics' :: FlowCmdM env err m
=> CorpusId -> Maybe ListId -> TabType -> Maybe Int => CorpusId -> Maybe ListId -> TabType -> Maybe Limit
-> m (Map.Map ListType [Vec.Vector Double]) -> m (Map.Map ListType [Vec.Vector Double])
getMetrics' cId maybeListId tabType maybeLimit = do getMetrics' cId maybeListId tabType maybeLimit = do
(ngs', scores) <- Metrics.getMetrics cId maybeListId tabType maybeLimit (ngs', scores) <- Metrics.getMetrics cId maybeListId tabType maybeLimit
......
...@@ -23,6 +23,7 @@ import Data.Text (Text, unpack, intercalate) ...@@ -23,6 +23,7 @@ import Data.Text (Text, unpack, intercalate)
import Data.Time (UTCTime) import Data.Time (UTCTime)
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query (IsTrash, Limit, Offset)
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..), HyperdataContact(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..), HyperdataContact(..))
import Gargantext.Database.Prelude (Cmd, runOpaQuery, runCountOpaQuery) import Gargantext.Database.Prelude (Cmd, runOpaQuery, runCountOpaQuery)
import Gargantext.Database.Query.Facet import Gargantext.Database.Query.Facet
......
...@@ -9,6 +9,7 @@ import Database.PostgreSQL.Simple (Query) ...@@ -9,6 +9,7 @@ import Database.PostgreSQL.Simple (Query)
import Database.PostgreSQL.Simple.ToField import Database.PostgreSQL.Simple.ToField
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Database.Prelude (Cmd, runPGSQuery) import Gargantext.Database.Prelude (Cmd, runPGSQuery)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Core.Text.Terms.Mono.Stem.En (stemIt) import Gargantext.Core.Text.Terms.Mono.Stem.En (stemIt)
...@@ -74,5 +75,3 @@ textSearch :: HasDBid NodeType ...@@ -74,5 +75,3 @@ textSearch :: HasDBid NodeType
textSearch q p l o ord = runPGSQuery textSearchQuery (q,p,p,typeId,ord,o,l) textSearch q p l o ord = runPGSQuery textSearchQuery (q,p,p,typeId,ord,o,l)
where where
typeId = toDBid NodeDocument typeId = toDBid NodeDocument
...@@ -47,6 +47,7 @@ import qualified Opaleye.Internal.Unpackspec() ...@@ -47,6 +47,7 @@ import qualified Opaleye.Internal.Unpackspec()
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query (Limit, Offset, IsTrash)
import Gargantext.Database.Query.Filter import Gargantext.Database.Query.Filter
import Gargantext.Database.Query.Table.Context import Gargantext.Database.Query.Table.Context
import Gargantext.Database.Query.Table.ContextNodeNgrams import Gargantext.Database.Query.Table.ContextNodeNgrams
...@@ -230,8 +231,8 @@ viewDocumentsQuery cId t ntId mQuery mYear = proc () -> do ...@@ -230,8 +231,8 @@ viewDocumentsQuery cId t ntId mQuery mYear = proc () -> do
------------------------------------------------------------------------ ------------------------------------------------------------------------
filterWith :: (SqlOrd date, SqlOrd title, SqlOrd category, SqlOrd score, hyperdata ~ SqlJsonb) => filterWith :: (SqlOrd date, SqlOrd title, SqlOrd category, SqlOrd score, hyperdata ~ SqlJsonb) =>
Maybe Gargantext.Core.Types.Offset Maybe Offset
-> Maybe Gargantext.Core.Types.Limit -> Maybe Limit
-> Maybe OrderBy -> Maybe OrderBy
-> Select (Facet id (Field date) (Field title) (Field hyperdata) (FieldNullable category) ngramCount (FieldNullable score)) -> Select (Facet id (Field date) (Field title) (Field hyperdata) (FieldNullable category) ngramCount (FieldNullable score))
-> Select (Facet id (Field date) (Field title) (Field hyperdata)(FieldNullable category) ngramCount (FieldNullable score)) -> Select (Facet id (Field date) (Field title) (Field hyperdata)(FieldNullable category) ngramCount (FieldNullable score))
...@@ -261,8 +262,8 @@ orderWith _ = asc facetDoc_created ...@@ -261,8 +262,8 @@ orderWith _ = asc facetDoc_created
filterWith' :: (SqlOrd date, SqlOrd title, SqlOrd category, SqlOrd score, hyperdata ~ SqlJsonb, SqlOrd ngramCount) => filterWith' :: (SqlOrd date, SqlOrd title, SqlOrd category, SqlOrd score, hyperdata ~ SqlJsonb, SqlOrd ngramCount) =>
Maybe Gargantext.Core.Types.Offset Maybe Offset
-> Maybe Gargantext.Core.Types.Limit -> Maybe Limit
-> Maybe OrderBy -> Maybe OrderBy
-> Select (Facet id (Field date) (Field title) (Field hyperdata) (Field category) (Field ngramCount) (Field score)) -> Select (Facet id (Field date) (Field title) (Field hyperdata) (Field category) (Field ngramCount) (Field score))
-> Select (Facet id (Field date) (Field title) (Field hyperdata) (Field category) (Field ngramCount) (Field score)) -> Select (Facet id (Field date) (Field title) (Field hyperdata) (Field category) (Field ngramCount) (Field score))
......
...@@ -18,12 +18,12 @@ Portability : POSIX ...@@ -18,12 +18,12 @@ Portability : POSIX
module Gargantext.Database.Query.Filter module Gargantext.Database.Query.Filter
where where
import Gargantext.Core.Types (Limit, Offset) import Gargantext.Core.Types.Query (Limit(..), Offset(..))
import Data.Maybe (Maybe, maybe) import Data.Maybe (Maybe, maybe)
import Opaleye (Select, limit, offset) import Opaleye (Select, limit, offset)
limit' :: Maybe Limit -> Select a -> Select a limit' :: Maybe Limit -> Select a -> Select a
limit' maybeLimit query = maybe query (\l -> limit l query) maybeLimit limit' maybeLimit query = maybe query (\l -> limit (getLimit l) query) maybeLimit
offset' :: Maybe Offset -> Select a -> Select a offset' :: Maybe Offset -> Select a -> Select a
offset' maybeOffset query = maybe query (\o -> offset o query) maybeOffset offset' maybeOffset query = maybe query (\o -> offset (getOffset o) query) maybeOffset
...@@ -23,6 +23,7 @@ module Gargantext.Database.Query.Table.Context ...@@ -23,6 +23,7 @@ module Gargantext.Database.Query.Table.Context
import Control.Arrow (returnA) import Control.Arrow (returnA)
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Filter (limit', offset') import Gargantext.Database.Query.Filter (limit', offset')
......
...@@ -32,6 +32,7 @@ import Prelude hiding (null, id, map, sum) ...@@ -32,6 +32,7 @@ import Prelude hiding (null, id, map, sum)
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Hyperdata.Default import Gargantext.Database.Admin.Types.Hyperdata.Default
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
......
...@@ -20,6 +20,7 @@ import Control.Arrow (returnA) ...@@ -20,6 +20,7 @@ import Control.Arrow (returnA)
import Data.Proxy import Data.Proxy
import Gargantext.Core import Gargantext.Core
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument, HyperdataContact) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument, HyperdataContact)
import Gargantext.Database.Prelude import Gargantext.Database.Prelude
import Gargantext.Database.Query.Filter import Gargantext.Database.Query.Filter
......
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