[NGRAMS-REPO] basic filtering (groups are not considered)

parent a364ea38
...@@ -65,7 +65,7 @@ import Data.Either(Either(Left)) ...@@ -65,7 +65,7 @@ import Data.Either(Either(Left))
-- import Data.Map (lookup) -- import Data.Map (lookup)
import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
import Data.Swagger hiding (version, patch) import Data.Swagger hiding (version, patch)
import Data.Text (Text) import Data.Text (Text, isInfixOf, count)
import Data.Validity import Data.Validity
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Core.Utils.Prefix (unPrefix) import Gargantext.Core.Utils.Prefix (unPrefix)
...@@ -137,6 +137,7 @@ type NgramsTerm = Text ...@@ -137,6 +137,7 @@ type NgramsTerm = Text
data NgramsElement = data NgramsElement =
NgramsElement { _ne_ngrams :: NgramsTerm NgramsElement { _ne_ngrams :: NgramsTerm
, _ne_size :: Int
, _ne_list :: ListType , _ne_list :: ListType
, _ne_occurrences :: Int , _ne_occurrences :: Int
, _ne_parent :: Maybe NgramsTerm , _ne_parent :: Maybe NgramsTerm
...@@ -147,9 +148,16 @@ data NgramsElement = ...@@ -147,9 +148,16 @@ data NgramsElement =
deriveJSON (unPrefix "_ne_") ''NgramsElement deriveJSON (unPrefix "_ne_") ''NgramsElement
makeLenses ''NgramsElement makeLenses ''NgramsElement
mkNgramsElement :: NgramsTerm -> ListType -> Maybe NgramsTerm -> MSet NgramsTerm -> NgramsElement
mkNgramsElement ngrams list parent children =
NgramsElement ngrams size list 1 parent children
where
-- TODO review
size = 1 + count " " ngrams
instance ToSchema NgramsElement instance ToSchema NgramsElement
instance Arbitrary NgramsElement where instance Arbitrary NgramsElement where
arbitrary = elements [NgramsElement "sport" GraphList 1 Nothing mempty] arbitrary = elements [mkNgramsElement "sport" GraphList Nothing mempty]
------------------------------------------------------------------------ ------------------------------------------------------------------------
newtype NgramsTable = NgramsTable [NgramsElement] newtype NgramsTable = NgramsTable [NgramsElement]
...@@ -191,18 +199,18 @@ toNgramsElement ns = map toNgramsElement' ns ...@@ -191,18 +199,18 @@ toNgramsElement ns = map toNgramsElement' ns
mockTable :: NgramsTable mockTable :: NgramsTable
mockTable = NgramsTable mockTable = NgramsTable
[ NgramsElement "animal" GraphList 1 Nothing (mSetFromList ["dog", "cat"]) [ mkNgramsElement "animal" GraphList Nothing (mSetFromList ["dog", "cat"])
, NgramsElement "cat" GraphList 1 (Just "animal") mempty , mkNgramsElement "cat" GraphList (Just "animal") mempty
, NgramsElement "cats" StopList 4 Nothing mempty , mkNgramsElement "cats" StopList Nothing mempty
, NgramsElement "dog" GraphList 3 (Just "animal")(mSetFromList ["dogs"]) , mkNgramsElement "dog" GraphList (Just "animal")(mSetFromList ["dogs"])
, NgramsElement "dogs" StopList 4 (Just "dog") mempty , mkNgramsElement "dogs" StopList (Just "dog") mempty
, NgramsElement "fox" GraphList 1 Nothing mempty , mkNgramsElement "fox" GraphList Nothing mempty
, NgramsElement "object" CandidateList 2 Nothing mempty , mkNgramsElement "object" CandidateList Nothing mempty
, NgramsElement "nothing" StopList 4 Nothing mempty , mkNgramsElement "nothing" StopList Nothing mempty
, NgramsElement "organic" GraphList 3 Nothing (mSetFromList ["flower"]) , mkNgramsElement "organic" GraphList Nothing (mSetFromList ["flower"])
, NgramsElement "flower" GraphList 3 (Just "organic") mempty , mkNgramsElement "flower" GraphList (Just "organic") mempty
, NgramsElement "moon" CandidateList 1 Nothing mempty , mkNgramsElement "moon" CandidateList Nothing mempty
, NgramsElement "sky" StopList 1 Nothing mempty , mkNgramsElement "sky" StopList Nothing mempty
] ]
instance Arbitrary NgramsTable where instance Arbitrary NgramsTable where
...@@ -506,10 +514,14 @@ ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ n ...@@ -506,10 +514,14 @@ ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ n
------------------------------------------------------------------------ ------------------------------------------------------------------------
type TableNgramsApiGet = Summary " Table Ngrams API Get" type TableNgramsApiGet = Summary " Table Ngrams API Get"
:> QueryParam "ngramsType" TabType :> QueryParam "ngramsType" TabType
:> QueryParams "list" ListId :> QueryParams "list" ListId
:> QueryParam "limit" Limit :> QueryParam "limit" Limit
:> QueryParam "offset" Offset :> QueryParam "offset" Offset
:> QueryParam "listType" ListType
:> QueryParam "minTermSize" Int
:> QueryParam "maxTermSize" Int
:> QueryParam "search" Text
:> Get '[JSON] (Versioned NgramsTable) :> Get '[JSON] (Versioned NgramsTable)
type TableNgramsApi = Summary " Table Ngrams API Change" type TableNgramsApi = Summary " Table Ngrams API Change"
...@@ -792,6 +804,8 @@ getListNgrams nodeIds ngramsType = do ...@@ -792,6 +804,8 @@ getListNgrams nodeIds ngramsType = do
pure $ Versioned (repo ^. r_version) (NgramsTable (ngrams ^.. each)) pure $ Versioned (repo ^. r_version) (NgramsTable (ngrams ^.. each))
type MinSize = Int
type MaxSize = Int
-- | TODO Errors management -- | TODO Errors management
-- TODO: polymorphic for Annuaire or Corpus or ... -- TODO: polymorphic for Annuaire or Corpus or ...
...@@ -799,22 +813,34 @@ getListNgrams nodeIds ngramsType = do ...@@ -799,22 +813,34 @@ getListNgrams nodeIds ngramsType = do
getTableNgrams :: (RepoCmdM env err m, HasNodeError err, HasConnection env) getTableNgrams :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
=> CorpusId -> Maybe TabType => CorpusId -> Maybe TabType
-> [ListId] -> Maybe Limit -> Maybe Offset -> [ListId] -> Maybe Limit -> Maybe Offset
-- -> Maybe MinSize -> Maybe MaxSize -> Maybe ListType
-- -> Maybe ListType -> Maybe MinSize -> Maybe MaxSize
-- -> Maybe Text -- full text search -> Maybe Text -- full text search
-> m (Versioned NgramsTable) -> m (Versioned NgramsTable)
getTableNgrams _cId maybeTabType listIds mlimit moffset = do getTableNgrams _cId maybeTabType listIds mlimit moffset
mlistType mminSize mmaxSize msearchQuery = do
let ngramsType = ngramsTypeFromTabType maybeTabType let ngramsType = ngramsTypeFromTabType maybeTabType
let let
defaultLimit = 10 -- TODO defaultLimit = 10 -- TODO
limit_ = maybe defaultLimit identity mlimit limit_ = maybe defaultLimit identity mlimit
offset_ = maybe 0 identity moffset offset_ = maybe 0 identity moffset
listType = maybe (const True) (==) mlistType
minSize = maybe (const True) (<=) mminSize
maxSize = maybe (const True) (>=) mmaxSize
searchQuery = maybe (const True) isInfixOf msearchQuery
selected n = minSize s
&& maxSize s
&& searchQuery (n ^. ne_ngrams)
&& listType (n ^. ne_list)
where
s = n ^. ne_size
-- lists <- catMaybes <$> listsWith userMaster -- lists <- catMaybes <$> listsWith userMaster
-- trace (show lists) $ -- trace (show lists) $
getListNgrams ({-lists <>-} listIds) ngramsType getListNgrams ({-lists <>-} listIds) ngramsType
& mapped . v_data . _NgramsTable %~ (take limit_ . drop offset_) & mapped . v_data . _NgramsTable
%~ (filter selected . take limit_ . drop offset_)
...@@ -26,9 +26,10 @@ import Data.Aeson (FromJSON, ToJSON, toJSON) ...@@ -26,9 +26,10 @@ import Data.Aeson (FromJSON, ToJSON, toJSON)
import Data.Aeson as A import Data.Aeson as A
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Map (fromList, lookup) import Data.Map (fromList, lookup)
import Data.Either (Either(..))
import Data.Eq (Eq()) import Data.Eq (Eq())
import Data.Monoid ((<>)) import Data.Monoid ((<>))
import Data.Text (Text) import Data.Text (Text, unpack)
import Data.Swagger import Data.Swagger
import Gargantext.Database.Types.Node -- (NodeType(..), Node, Hyperdata(..)) import Gargantext.Database.Types.Node -- (NodeType(..), Node, Hyperdata(..))
...@@ -36,8 +37,10 @@ import Gargantext.Core.Utils.Prefix (unPrefix) ...@@ -36,8 +37,10 @@ import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Prelude import Gargantext.Prelude
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant.API (FromHttpApiData(..))
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Text.Read (read)
------------------------------------------------------------------------ ------------------------------------------------------------------------
data NodeTree = NodeTree { _nt_name :: Text data NodeTree = NodeTree { _nt_name :: Text
...@@ -85,14 +88,18 @@ type HashId = Text ...@@ -85,14 +88,18 @@ type HashId = Text
type TypeId = Int type TypeId = Int
-- TODO multiple ListType declaration, remove it -- TODO multiple ListType declaration, remove it
data ListType = StopList | CandidateList | GraphList data ListType = StopList | CandidateList | GraphList
deriving (Generic, Eq, Ord, Show, Enum, Bounded) deriving (Generic, Eq, Ord, Show, Read, Enum, Bounded)
instance ToJSON ListType instance ToJSON ListType
instance FromJSON ListType instance FromJSON ListType
instance ToSchema ListType instance ToSchema ListType
instance ToParamSchema ListType
instance Arbitrary ListType where instance Arbitrary ListType where
arbitrary = elements [minBound..maxBound] arbitrary = elements [minBound..maxBound]
instance FromHttpApiData ListType where
parseUrlPiece = Right . read . unpack
type ListTypeId = Int type ListTypeId = Int
listTypeId :: ListType -> ListTypeId listTypeId :: ListType -> ListTypeId
......
...@@ -64,7 +64,7 @@ import Gargantext.Text.Parsers (parseDocs, FileFormat) ...@@ -64,7 +64,7 @@ import Gargantext.Text.Parsers (parseDocs, FileFormat)
import System.FilePath (FilePath) import System.FilePath (FilePath)
import Gargantext.API.Ngrams (HasRepoVar) import Gargantext.API.Ngrams (HasRepoVar)
import Servant (ServantErr) import Servant (ServantErr)
import Gargantext.API.Ngrams (NgramsElement(..), putListNgrams, RepoCmdM) import Gargantext.API.Ngrams (NgramsElement, mkNgramsElement, putListNgrams, RepoCmdM)
--import Gargantext.Database.Schema.User (insertUsers, simpleUser, gargantuaUser) --import Gargantext.Database.Schema.User (insertUsers, simpleUser, gargantuaUser)
import qualified Data.Map as DM import qualified Data.Map as DM
...@@ -326,8 +326,8 @@ flowListUser uId cId ngsM _n = do ...@@ -326,8 +326,8 @@ flowListUser uId cId ngsM _n = do
trace ("flowListBase" <> show lId) flowListBase lId ngsM trace ("flowListBase" <> show lId) flowListBase lId ngsM
putListNgrams lId NgramsTerms $ putListNgrams lId NgramsTerms $
[ NgramsElement (tficf_ngramsTerms ng) GraphList 1 Nothing mempty [ mkNgramsElement (tficf_ngramsTerms ng) GraphList Nothing mempty
| ng <- ngs | ng <- ngs
] ]
pure lId pure lId
...@@ -357,7 +357,7 @@ ngrams2list m = ...@@ -357,7 +357,7 @@ ngrams2list m =
ngrams2list' :: Map NgramsIndexed (Map NgramsType a) ngrams2list' :: Map NgramsIndexed (Map NgramsType a)
-> Map NgramsType [NgramsElement] -> Map NgramsType [NgramsElement]
ngrams2list' m = fromListWith (<>) ngrams2list' m = fromListWith (<>)
[ (t, [NgramsElement (_ngramsTerms $ _ngrams ng) CandidateList 1 Nothing mempty]) [ (t, [mkNgramsElement (_ngramsTerms $ _ngrams ng) CandidateList Nothing mempty])
| (ng, tm) <- DM.toList m | (ng, tm) <- DM.toList m
, t <- DM.keys tm , t <- DM.keys tm
] ]
......
...@@ -26,7 +26,7 @@ import Data.Map.Strict (Map, fromListWith, elems) ...@@ -26,7 +26,7 @@ import Data.Map.Strict (Map, fromListWith, elems)
import Data.Monoid (mempty) import Data.Monoid (mempty)
import Data.Text (Text) import Data.Text (Text)
import Database.PostgreSQL.Simple.SqlQQ (sql) import Database.PostgreSQL.Simple.SqlQQ (sql)
import Gargantext.API.Ngrams (NgramsElement(..)) import Gargantext.API.Ngrams (NgramsElement, mkNgramsElement)
import Gargantext.Core.Types.Main (listTypeId, ListType(..)) import Gargantext.Core.Types.Main (listTypeId, ListType(..))
import Gargantext.Database.Access import Gargantext.Database.Access
import Gargantext.Database.Config (nodeTypeId) import Gargantext.Database.Config (nodeTypeId)
...@@ -206,7 +206,9 @@ getNgramsByNodeNodeIndexedJoin5 = leftJoin5 queryNodeTable ...@@ -206,7 +206,9 @@ getNgramsByNodeNodeIndexedJoin5 = leftJoin5 queryNodeTable
getNgramsElementsWithParentNodeId :: NodeId -> Cmd err (Map NgramsType [NgramsElement]) getNgramsElementsWithParentNodeId :: NodeId -> Cmd err (Map NgramsType [NgramsElement])
getNgramsElementsWithParentNodeId nId = do getNgramsElementsWithParentNodeId nId = do
ns <- getNgramsWithParentNodeId nId ns <- getNgramsWithParentNodeId nId
pure $ fromListWith (<>) [ (maybe (panic "error") identity $ fromNgramsTypeId nt, [NgramsElement ng CandidateList 1 Nothing mempty]) pure $ fromListWith (<>)
[ (maybe (panic "error") identity $ fromNgramsTypeId nt,
[mkNgramsElement ng CandidateList Nothing mempty])
| (_,(nt,ng)) <- ns | (_,(nt,ng)) <- ns
] ]
......
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