Commit 1c8e66d9 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ngrams] NgramsTerm as a newtype

This is to disallow for NgramsTerm keys with spaces.

Can be modified for other kinds of term normalization later.
parent a70b2a4e
Pipeline #1075 failed with stage
...@@ -40,6 +40,8 @@ module Gargantext.API.Ngrams ...@@ -40,6 +40,8 @@ module Gargantext.API.Ngrams
, NgramsTablePatch , NgramsTablePatch
, NgramsTableMap , NgramsTableMap
, NgramsTerm(..)
, NgramsElement(..) , NgramsElement(..)
, mkNgramsElement , mkNgramsElement
, mergeNgramsElement , mergeNgramsElement
...@@ -114,11 +116,12 @@ import Data.Patch.Class (Replace, replace, Action(act), Group, Applicable(..), C ...@@ -114,11 +116,12 @@ import Data.Patch.Class (Replace, replace, Action(act), Group, Applicable(..), C
import Data.Set (Set) import Data.Set (Set)
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Set as Set import qualified Data.Set as Set
import Data.String (IsString, fromString)
import Data.Swagger hiding (version, patch) import Data.Swagger hiding (version, patch)
import Data.Text (Text, count, isInfixOf, unpack) import Data.Text (Text, count, isInfixOf, pack, strip, unpack)
import Data.Text.Lazy.IO as DTL import Data.Text.Lazy.IO as DTL
import Data.Validity import Data.Validity
import Database.PostgreSQL.Simple.FromField (FromField, fromField) import Database.PostgreSQL.Simple.FromField (FromField, fromField, ResultError(ConversionFailed), returnError)
import Formatting (hprint, int, (%)) import Formatting (hprint, int, (%))
import Formatting.Clock (timeSpecs) import Formatting.Clock (timeSpecs)
import GHC.Generics (Generic) import GHC.Generics (Generic)
...@@ -208,7 +211,25 @@ instance (ToJSONKey a, ToSchema a) => ToSchema (MSet a) where ...@@ -208,7 +211,25 @@ instance (ToJSONKey a, ToSchema a) => ToSchema (MSet a) where
declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO) declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO)
------------------------------------------------------------------------ ------------------------------------------------------------------------
type NgramsTerm = Text newtype NgramsTerm = NgramsTerm { unNgramsTerm :: Text }
deriving (Ord, Eq, Show, Generic, ToJSONKey, ToJSON, FromJSON, Semigroup, Arbitrary, Serialise, ToSchema)
instance FromJSONKey NgramsTerm where
fromJSONKey = FromJSONKeyTextParser $ \t -> pure $ NgramsTerm $ strip t
instance IsString NgramsTerm where
fromString s = NgramsTerm $ pack s
instance FromField NgramsTerm
where
fromField field mb = do
v <- fromField field mb
case fromJSON v of
Success a -> pure $ NgramsTerm $ strip a
Error _err -> returnError ConversionFailed field
$ List.intercalate " " [ "cannot parse hyperdata for JSON: "
, show v
]
data RootParent = RootParent data RootParent = RootParent
{ _rp_root :: NgramsTerm { _rp_root :: NgramsTerm
...@@ -265,7 +286,7 @@ mkNgramsElement ngrams list rp children = ...@@ -265,7 +286,7 @@ mkNgramsElement ngrams list rp children =
NgramsElement ngrams size list 1 (_rp_root <$> rp) (_rp_parent <$> rp) children NgramsElement ngrams size list 1 (_rp_root <$> rp) (_rp_parent <$> rp) children
where where
-- TODO review -- TODO review
size = 1 + count " " ngrams size = 1 + (count " " $ unNgramsTerm ngrams)
newNgramsElement :: Maybe ListType -> NgramsTerm -> NgramsElement newNgramsElement :: Maybe ListType -> NgramsTerm -> NgramsElement
newNgramsElement mayList ngrams = newNgramsElement mayList ngrams =
...@@ -937,7 +958,8 @@ setListNgrams listId ngramsType ns = do ...@@ -937,7 +958,8 @@ setListNgrams listId ngramsType ns = do
putListNgrams :: (HasInvalidError err, RepoCmdM env err m) putListNgrams :: (HasInvalidError err, RepoCmdM env err m)
=> NodeId => NodeId
-> TableNgrams.NgramsType -> TableNgrams.NgramsType
-> [NgramsElement] -> m () -> [NgramsElement]
-> m ()
putListNgrams _ _ [] = pure () putListNgrams _ _ [] = pure ()
putListNgrams nodeId ngramsType nes = putListNgrams' nodeId ngramsType m putListNgrams nodeId ngramsType nes = putListNgrams' nodeId ngramsType m
where where
...@@ -949,9 +971,9 @@ putListNgrams' :: (HasInvalidError err, RepoCmdM env err m) ...@@ -949,9 +971,9 @@ putListNgrams' :: (HasInvalidError err, RepoCmdM env err m)
-> Map NgramsTerm NgramsRepoElement -> Map NgramsTerm NgramsRepoElement
-> m () -> m ()
putListNgrams' nodeId ngramsType ns = do putListNgrams' nodeId ngramsType ns = do
-- printDebug "[putLictNgrams'] nodeId" nodeId printDebug "[putListNgrams'] nodeId" nodeId
-- printDebug "[putLictNgrams'] ngramsType" ngramsType printDebug "[putListNgrams'] ngramsType" ngramsType
-- printDebug "[putListNgrams'] ns" ns printDebug "[putListNgrams'] ns" ns
let p1 = NgramsTablePatch . PM.fromMap $ NgramsReplace Nothing . Just <$> ns let p1 = NgramsTablePatch . PM.fromMap $ NgramsReplace Nothing . Just <$> ns
(p0, p0_validity) = PM.singleton nodeId p1 (p0, p0_validity) = PM.singleton nodeId p1
...@@ -1002,8 +1024,8 @@ commitStatePatch (Versioned p_version p) = do ...@@ -1002,8 +1024,8 @@ commitStatePatch (Versioned p_version p) = do
q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history) q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
(p', q') = transformWith ngramsStatePatchConflictResolution p q (p', q') = transformWith ngramsStatePatchConflictResolution p q
r' = r & r_version +~ 1 r' = r & r_version +~ 1
& r_state %~ act p' & r_state %~ act p'
& r_history %~ (p' :) & r_history %~ (p' :)
{- {-
-- Ideally we would like to check these properties. However: -- Ideally we would like to check these properties. However:
-- * They should be checked only to debug the code. The client data -- * They should be checked only to debug the code. The client data
...@@ -1040,7 +1062,8 @@ tableNgramsPull listId ngramsType p_version = do ...@@ -1040,7 +1062,8 @@ tableNgramsPull listId ngramsType p_version = do
-- client. -- client.
-- TODO-ACCESS check -- TODO-ACCESS check
tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m) tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m)
=> TabType -> ListId => TabType
-> ListId
-> Versioned NgramsTablePatch -> Versioned NgramsTablePatch
-> m (Versioned NgramsTablePatch) -> m (Versioned NgramsTablePatch)
tableNgramsPut tabType listId (Versioned p_version p_table) tableNgramsPut tabType listId (Versioned p_version p_table)
...@@ -1157,7 +1180,7 @@ getTableNgrams _nType nId tabType listId limit_ offset ...@@ -1157,7 +1180,7 @@ getTableNgrams _nType nId tabType listId limit_ offset
setScores :: forall t. Each t t NgramsElement NgramsElement => Bool -> t -> m t setScores :: forall t. Each t t NgramsElement NgramsElement => Bool -> t -> m t
setScores False table = pure table setScores False table = pure table
setScores True table = do setScores True table = do
let ngrams_terms = (table ^.. each . ne_ngrams) let ngrams_terms = unNgramsTerm <$> (table ^.. each . ne_ngrams)
t1 <- getTime' t1 <- getTime'
occurrences <- getOccByNgramsOnlyFast' nId occurrences <- getOccByNgramsOnlyFast' nId
listId listId
...@@ -1174,7 +1197,7 @@ getTableNgrams _nType nId tabType listId limit_ offset ...@@ -1174,7 +1197,7 @@ getTableNgrams _nType nId tabType listId limit_ offset
ngrams_terms ngrams_terms
-} -}
let let
setOcc ne = ne & ne_occurrences .~ sumOf (at (ne ^. ne_ngrams) . _Just) occurrences setOcc ne = ne & ne_occurrences .~ sumOf (at (unNgramsTerm (ne ^. ne_ngrams)) . _Just) occurrences
pure $ table & each %~ setOcc pure $ table & each %~ setOcc
--------------------------------------- ---------------------------------------
...@@ -1216,13 +1239,13 @@ scoresRecomputeTableNgrams nId tabType listId = do ...@@ -1216,13 +1239,13 @@ scoresRecomputeTableNgrams nId tabType listId = do
setScores :: forall t. Each t t NgramsElement NgramsElement => t -> m t setScores :: forall t. Each t t NgramsElement NgramsElement => t -> m t
setScores table = do setScores table = do
let ngrams_terms = (table ^.. each . ne_ngrams) let ngrams_terms = unNgramsTerm <$> (table ^.. each . ne_ngrams)
occurrences <- getOccByNgramsOnlyFast' nId occurrences <- getOccByNgramsOnlyFast' nId
listId listId
ngramsType ngramsType
ngrams_terms ngrams_terms
let let
setOcc ne = ne & ne_occurrences .~ sumOf (at (ne ^. ne_ngrams) . _Just) occurrences setOcc ne = ne & ne_occurrences .~ sumOf (at (unNgramsTerm (ne ^. ne_ngrams)) . _Just) occurrences
pure $ table & each %~ setOcc pure $ table & each %~ setOcc
...@@ -1305,7 +1328,7 @@ getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool ...@@ -1305,7 +1328,7 @@ getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool
getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy mt = getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy mt =
getTableNgrams NodeCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery getTableNgrams NodeCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
where where
searchQuery = maybe (const True) isInfixOf mt searchQuery (NgramsTerm nt) = maybe (const True) isInfixOf mt nt
getTableNgramsVersion :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env) getTableNgramsVersion :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
=> NodeId => NodeId
...@@ -1332,7 +1355,7 @@ getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orde ...@@ -1332,7 +1355,7 @@ getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orde
ns <- selectNodesWithUsername NodeList userMaster ns <- selectNodesWithUsername NodeList userMaster
let ngramsType = ngramsTypeFromTabType tabType let ngramsType = ngramsTypeFromTabType tabType
ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
let searchQuery = flip S.member (S.fromList ngs) let searchQuery (NgramsTerm nt) = flip S.member (S.fromList ngs) nt
getTableNgrams NodeDocument dId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery getTableNgrams NodeDocument dId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
......
...@@ -14,13 +14,8 @@ Portability : POSIX ...@@ -14,13 +14,8 @@ Portability : POSIX
module Gargantext.API.Ngrams.NTree module Gargantext.API.Ngrams.NTree
where where
import Data.Text (Text)
import Gargantext.Prelude
import GHC.Generics (Generic)
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger) import Data.Text (Text)
import Gargantext.Core.Types (ListType(..), NodeId)
import Gargantext.API.Ngrams
import Data.Tree import Data.Tree
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Data.Map (Map) import Data.Map (Map)
...@@ -29,8 +24,15 @@ import Data.Swagger ...@@ -29,8 +24,15 @@ import Data.Swagger
import qualified Data.Set as Set import qualified Data.Set as Set
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.List as List import qualified Data.List as List
import GHC.Generics (Generic)
import Test.QuickCheck import Test.QuickCheck
import Gargantext.Prelude
import Gargantext.API.Ngrams
import Gargantext.Core.Types (ListType(..), NodeId)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
type Children = Text type Children = Text
type Root = Text type Root = Text
...@@ -53,19 +55,21 @@ instance Arbitrary MyTree ...@@ -53,19 +55,21 @@ instance Arbitrary MyTree
toTree :: ListType -> Map Text (Set NodeId) -> Map Text NgramsRepoElement -> [MyTree] toTree :: ListType -> Map Text (Set NodeId) -> Map Text NgramsRepoElement -> [MyTree]
toTree lt vs m = map toMyTree $ unfoldForest buildNode roots toTree lt vs m = map toMyTree $ unfoldForest buildNode roots
where where
buildNode r = maybe ((r, value r),[]) (\x -> ((r, value r), mSetToList $ _nre_children x)) (Map.lookup r m) buildNode r = maybe ((r, value r),[])
(\x -> ((r, value r), unNgramsTerm <$> (mSetToList $ _nre_children x)))
(Map.lookup r m)
value l = maybe 0 (fromIntegral . Set.size) $ Map.lookup l vs value l = maybe 0 (fromIntegral . Set.size) $ Map.lookup l vs
rootsCandidates :: [NgramsTerm]
rootsCandidates = catMaybes rootsCandidates = catMaybes
$ List.nub $ List.nub
$ map (\(c,c') -> case _nre_root c' of $ map (\(c, c') -> case _nre_root c' of
Nothing -> Just c Nothing -> Just $ NgramsTerm c
_ -> _nre_root c' ) (Map.toList m) _ -> _nre_root c') (Map.toList m)
roots = map fst roots = map fst
$ filter (\(_,l) -> l == lt) $ filter (\(_,l) -> l == lt)
$ catMaybes $ catMaybes
$ map (\c -> (,) <$> Just c <*> (_nre_list <$> Map.lookup c m)) rootsCandidates $ map (\c -> (,) <$> Just c <*> (_nre_list <$> Map.lookup c m))
$ (unNgramsTerm <$> rootsCandidates)
...@@ -17,15 +17,16 @@ import Control.Concurrent ...@@ -17,15 +17,16 @@ import Control.Concurrent
import Control.Lens (_Just, (^.), at, view) import Control.Lens (_Just, (^.), at, view)
import Control.Monad.Reader import Control.Monad.Reader
import Data.Map.Strict (Map) import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Data.Set (Set) import Data.Set (Set)
import Data.Text (Text) import Data.Text (Text)
import Data.Validity import Data.Validity
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.Core.Types (ListType(..), NodeId, ListId) import Gargantext.Core.Types (ListType(..), NodeId, ListId)
import Gargantext.Database.Schema.Ngrams (NgramsType) import Gargantext.Database.Schema.Ngrams (NgramsType)
import Gargantext.Prelude import Gargantext.Prelude
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
type RootTerm = Text type RootTerm = Text
...@@ -36,12 +37,12 @@ getRepo = do ...@@ -36,12 +37,12 @@ getRepo = do
listNgramsFromRepo :: [ListId] -> NgramsType listNgramsFromRepo :: [ListId] -> NgramsType
-> NgramsRepo -> Map Text NgramsRepoElement -> NgramsRepo -> Map Text NgramsRepoElement
listNgramsFromRepo nodeIds ngramsType repo = ngrams listNgramsFromRepo nodeIds ngramsType repo = Map.mapKeys unNgramsTerm ngrams
where where
ngramsMap = repo ^. r_state . at ngramsType . _Just ngramsMap = repo ^. r_state . at ngramsType . _Just
ngrams = Map.unionsWith mergeNgramsElement ngrams = Map.unionsWith mergeNgramsElement
[ ngramsMap ^. at nodeId . _Just | nodeId <- nodeIds ] [ ngramsMap ^. at nodeId . _Just | nodeId <- nodeIds ]
-- TODO-ACCESS: We want to do the security check before entering here. -- TODO-ACCESS: We want to do the security check before entering here.
-- Add a static capability parameter would be nice. -- Add a static capability parameter would be nice.
...@@ -72,7 +73,7 @@ mapTermListRoot :: [ListId] ...@@ -72,7 +73,7 @@ mapTermListRoot :: [ListId]
-> NgramsRepo -> NgramsRepo
-> Map Text (ListType, (Maybe Text)) -> Map Text (ListType, (Maybe Text))
mapTermListRoot nodeIds ngramsType repo = mapTermListRoot nodeIds ngramsType repo =
Map.fromList [ (t, (_nre_list nre, _nre_root nre)) Map.fromList [ (t, (_nre_list nre, unNgramsTerm <$> _nre_root nre))
| (t, nre) <- Map.toList ngrams | (t, nre) <- Map.toList ngrams
] ]
where ngrams = listNgramsFromRepo nodeIds ngramsType repo where ngrams = listNgramsFromRepo nodeIds ngramsType repo
......
...@@ -17,7 +17,15 @@ module Gargantext.Core.Text.List ...@@ -17,7 +17,15 @@ module Gargantext.Core.Text.List
import Data.Map (Map) import Data.Map (Map)
import Data.Set (Set) import Data.Set (Set)
import Data.Text (Text) import Data.Text (Text)
import Gargantext.API.Ngrams (NgramsElement, mkNgramsElement, RootParent(..), mSetFromList) import qualified Data.Char as Char
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Text as Text
import Gargantext.Prelude
import Gargantext.API.Ngrams (NgramsElement, mkNgramsElement, NgramsTerm(..), RootParent(..), mSetFromList)
-- import Gargantext.API.Ngrams.Tools (getCoocByNgrams', Diagonal(..)) -- import Gargantext.API.Ngrams.Tools (getCoocByNgrams', Diagonal(..))
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Types (ListType(..), MasterCorpusId, UserCorpusId, Ordering(..)) import Gargantext.Core.Types (ListType(..), MasterCorpusId, UserCorpusId, Ordering(..))
...@@ -26,14 +34,8 @@ import Gargantext.Database.Action.Metrics.TFICF (getTficf) ...@@ -26,14 +34,8 @@ import Gargantext.Database.Action.Metrics.TFICF (getTficf)
import Gargantext.Core.Text.Metrics.TFICF (sortTficf) import Gargantext.Core.Text.Metrics.TFICF (sortTficf)
import Gargantext.Database.Prelude (Cmd) import Gargantext.Database.Prelude (Cmd)
import Gargantext.Database.Schema.Ngrams (NgramsType(..)) import Gargantext.Database.Schema.Ngrams (NgramsType(..))
import Gargantext.Prelude
import Gargantext.Core.Text.List.Learn (Model(..)) import Gargantext.Core.Text.List.Learn (Model(..))
-- import Gargantext.Core.Text.Metrics (takeScored) -- import Gargantext.Core.Text.Metrics (takeScored)
import qualified Data.Char as Char
import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Text as Text
data NgramsListBuilder = BuilderStepO { stemSize :: Int data NgramsListBuilder = BuilderStepO { stemSize :: Int
...@@ -86,8 +88,8 @@ buildNgramsOthersList uCid groupIt nt = do ...@@ -86,8 +88,8 @@ buildNgramsOthersList uCid groupIt nt = do
] ]
where where
toElements nType x = toElements nType x =
Map.fromList [(nt, [ mkNgramsElement t nType Nothing (mSetFromList []) Map.fromList [(nt, [ mkNgramsElement (NgramsTerm t) nType Nothing (mSetFromList [])
| (t,_ns) <- x | (t, _ns) <- x
] ]
)] )]
...@@ -146,14 +148,14 @@ toNgramsElement (GroupedText listType label _ setNgrams) = ...@@ -146,14 +148,14 @@ toNgramsElement (GroupedText listType label _ setNgrams) =
where where
parent = label parent = label
children = Set.toList setNgrams children = Set.toList setNgrams
parentElem = mkNgramsElement parent parentElem = mkNgramsElement (NgramsTerm parent)
listType listType
Nothing Nothing
(mSetFromList children) (mSetFromList (NgramsTerm <$> children))
childrenElems = map (\t -> mkNgramsElement t listType childrenElems = map (\t -> mkNgramsElement t listType
(Just $ RootParent parent parent) (Just $ RootParent (NgramsTerm parent) (NgramsTerm parent))
(mSetFromList []) (mSetFromList [])
) children ) (NgramsTerm <$> children)
toGargList :: (b -> Bool) -> ListType -> b -> (ListType, b) toGargList :: (b -> Bool) -> ListType -> b -> (ListType, b)
......
...@@ -26,7 +26,7 @@ import Data.Map (Map, toList) ...@@ -26,7 +26,7 @@ import Data.Map (Map, toList)
import Data.Maybe (Maybe(..), catMaybes) import Data.Maybe (Maybe(..), catMaybes)
import Data.Text (Text) import Data.Text (Text)
import Gargantext.API.Ngrams (NgramsElement(..), putListNgrams) import Gargantext.API.Ngrams (NgramsElement(..), NgramsTerm(..), putListNgrams)
import Gargantext.Core.Flow.Types import Gargantext.Core.Flow.Types
import Gargantext.Core.Types.Main (ListType(CandidateTerm)) import Gargantext.Core.Types.Main (ListType(CandidateTerm))
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
...@@ -97,10 +97,10 @@ flowList_DbRepo :: FlowCmdM env err m ...@@ -97,10 +97,10 @@ flowList_DbRepo :: FlowCmdM env err m
flowList_DbRepo lId ngs = do flowList_DbRepo lId ngs = do
-- printDebug "listId flowList" lId -- printDebug "listId flowList" lId
mapCgramsId <- listInsertDb lId toNodeNgramsW (Map.toList ngs) mapCgramsId <- listInsertDb lId toNodeNgramsW (Map.toList ngs)
let toInsert = catMaybes [ (,) <$> (getCgramsId mapCgramsId ntype <$> parent) let toInsert = catMaybes [ (,) <$> (getCgramsId mapCgramsId ntype <$> (unNgramsTerm <$> parent))
<*> getCgramsId mapCgramsId ntype ngram <*> getCgramsId mapCgramsId ntype ngram
| (ntype, ngs') <- Map.toList ngs | (ntype, ngs') <- Map.toList ngs
, NgramsElement ngram _ _ _ _ parent _ <- ngs' , NgramsElement (NgramsTerm ngram) _ _ _ _ parent _ <- ngs'
] ]
-- Inserting groups of ngrams -- Inserting groups of ngrams
_r <- insert_Node_NodeNgrams_NodeNgrams _r <- insert_Node_NodeNgrams_NodeNgrams
...@@ -123,7 +123,7 @@ toNodeNgramsW l ngs = List.concat $ map (toNodeNgramsW'' l) ngs ...@@ -123,7 +123,7 @@ toNodeNgramsW l ngs = List.concat $ map (toNodeNgramsW'' l) ngs
-> [NodeNgramsW] -> [NodeNgramsW]
toNodeNgramsW'' l' (ngrams_type, elms) = toNodeNgramsW'' l' (ngrams_type, elms) =
[ NodeNgrams Nothing l' list_type ngrams_terms' ngrams_type Nothing Nothing Nothing 0 | [ NodeNgrams Nothing l' list_type ngrams_terms' ngrams_type Nothing Nothing Nothing 0 |
(NgramsElement ngrams_terms' _size list_type _occ _root _parent _children) <- elms (NgramsElement (NgramsTerm ngrams_terms') _size list_type _occ _root _parent _children) <- elms
] ]
......
...@@ -33,8 +33,6 @@ import Data.Word (Word16) ...@@ -33,8 +33,6 @@ import Data.Word (Word16)
import Database.PostgreSQL.Simple (Connection, connect) import Database.PostgreSQL.Simple (Connection, connect)
import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError) import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError)
import Database.PostgreSQL.Simple.Internal (Field) import Database.PostgreSQL.Simple.Internal (Field)
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig())
import Opaleye (Query, Unpackspec, showSqlForPostgres, FromFields, Select, runQuery) import Opaleye (Query, Unpackspec, showSqlForPostgres, FromFields, Select, runQuery)
import Opaleye.Aggregate (countRows) import Opaleye.Aggregate (countRows)
import System.IO (FilePath) import System.IO (FilePath)
...@@ -44,6 +42,9 @@ import qualified Data.ByteString as DB ...@@ -44,6 +42,9 @@ import qualified Data.ByteString as DB
import qualified Data.List as DL import qualified Data.List as DL
import qualified Database.PostgreSQL.Simple as PGS import qualified Database.PostgreSQL.Simple as PGS
import Gargantext.Prelude
import Gargantext.Prelude.Config (GargConfig())
------------------------------------------------------- -------------------------------------------------------
class HasConnectionPool env where class HasConnectionPool env where
connPool :: Getter env (Pool Connection) connPool :: Getter env (Pool Connection)
......
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