Commit 86165573 authored by Nicolas Pouillard's avatar Nicolas Pouillard

[NGRAMS-TABLE] multi select, scoreType, ngram normalisation

parent ed3127bc
...@@ -24,7 +24,7 @@ import Reactix.SyntheticEvent as E ...@@ -24,7 +24,7 @@ import Reactix.SyntheticEvent as E
import Gargantext.Types (CTabNgramType(..), TermList) import Gargantext.Types (CTabNgramType(..), TermList)
import Gargantext.Components.Annotation.Utils ( termBootstrapClass ) import Gargantext.Components.Annotation.Utils ( termBootstrapClass )
import Gargantext.Components.NgramsTable.Core (NgramsTable, NgramsTerm, findNgramTermList, highlightNgrams) import Gargantext.Components.NgramsTable.Core (NgramsTable, NgramsTerm, findNgramTermList, highlightNgrams, normNgram)
import Gargantext.Components.Annotation.Menu ( AnnotationMenu, annotationMenu, MenuType(..) ) import Gargantext.Components.Annotation.Menu ( AnnotationMenu, annotationMenu, MenuType(..) )
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Selection as Sel import Gargantext.Utils.Selection as Sel
...@@ -56,7 +56,7 @@ annotatedFieldComponent = R.hooksComponent "AnnotatedField" cpt ...@@ -56,7 +56,7 @@ annotatedFieldComponent = R.hooksComponent "AnnotatedField" cpt
let x = E.clientX event let x = E.clientX event
y = E.clientY event y = E.clientY event
setList t = do setList t = do
setTermList text' (Just list) t setTermList (normNgram CTabTerms text') (Just list) t
setMenu (const Nothing) setMenu (const Nothing)
setMenu (const $ Just {x, y, list: Just list, menuType: SetTermListItem, setList} ) setMenu (const $ Just {x, y, list: Just list, menuType: SetTermListItem, setList} )
...@@ -78,9 +78,10 @@ maybeShowMenu setMenu setTermList ngrams event = do ...@@ -78,9 +78,10 @@ maybeShowMenu setMenu setTermList ngrams event = do
sel' -> do sel' -> do
let x = E.clientX event let x = E.clientX event
y = E.clientY event y = E.clientY event
list = findNgramTermList CTabTerms ngrams sel' n = normNgram CTabTerms sel'
list = findNgramTermList ngrams n
setList t = do setList t = do
setTermList sel' list t setTermList n list t
setMenu (const Nothing) setMenu (const Nothing)
E.preventDefault event E.preventDefault event
setMenu (const $ Just { x, y, list, menuType: NewNgram, setList }) setMenu (const $ Just { x, y, list, menuType: NewNgram, setList })
......
...@@ -285,7 +285,7 @@ pageCpt = R.memo' $ R.hooksComponent "G.C.DocsTable.pageCpt" cpt where ...@@ -285,7 +285,7 @@ pageCpt = R.memo' $ R.hooksComponent "G.C.DocsTable.pageCpt" cpt where
pure $ T.table pure $ T.table
{ rows: rows localCategories { rows: rows localCategories
, container: T.defaultContainer { title: "Documents" } , container: T.defaultContainer { title: "Documents" }
, params, colNames, totalRecords } , params, colNames, totalRecords, wrapColElts }
where where
sid = sessionId session sid = sessionId session
gi Favorite = "glyphicon glyphicon-star" gi Favorite = "glyphicon glyphicon-star"
...@@ -296,6 +296,7 @@ pageCpt = R.memo' $ R.hooksComponent "G.C.DocsTable.pageCpt" cpt where ...@@ -296,6 +296,7 @@ pageCpt = R.memo' $ R.hooksComponent "G.C.DocsTable.pageCpt" cpt where
| Just cid <- corpusId = Routes.CorpusDocument sid cid listId | Just cid <- corpusId = Routes.CorpusDocument sid cid listId
| otherwise = Routes.Document sid listId | otherwise = Routes.Document sid listId
colNames = T.ColumnName <$> [ "Map", "Stop", "Date", "Title", "Source"] colNames = T.ColumnName <$> [ "Map", "Stop", "Date", "Title", "Source"]
wrapColElts = const identity
getCategory (localCategories /\ _) {_id, category} = maybe category identity (localCategories ^. at _id) getCategory (localCategories /\ _) {_id, category} = maybe category identity (localCategories ^. at _id)
rows localCategories = row <$> documents rows localCategories = row <$> documents
where where
......
...@@ -277,11 +277,12 @@ pageCpt :: R.Component PageProps ...@@ -277,11 +277,12 @@ pageCpt :: R.Component PageProps
pageCpt = R.staticComponent "G.C.FacetsTable.Page" cpt pageCpt = R.staticComponent "G.C.FacetsTable.Page" cpt
where where
cpt {totalRecords, container, deletions, documents, session, path: path@({nodeId, listId, query} /\ setPath)} _ = do cpt {totalRecords, container, deletions, documents, session, path: path@({nodeId, listId, query} /\ setPath)} _ = do
T.table { rows, container, colNames, totalRecords, params } T.table { rows, container, colNames, totalRecords, params, wrapColElts }
where where
setParams f = setPath $ \p@{params: ps} -> p {params = f ps} setParams f = setPath $ \p@{params: ps} -> p {params = f ps}
params = (fst path).params /\ setParams params = (fst path).params /\ setParams
colNames = T.ColumnName <$> [ "", "Date", "Title", "Source", "Authors", "Delete" ] colNames = T.ColumnName <$> [ "", "Date", "Title", "Source", "Authors", "Delete" ]
wrapColElts = const identity
-- TODO: how to interprete other scores? -- TODO: how to interprete other scores?
gi Favorite = "glyphicon glyphicon-star-empty" gi Favorite = "glyphicon glyphicon-star-empty"
gi _ = "glyphicon glyphicon-star" gi _ = "glyphicon glyphicon-star"
......
This diff is collapsed.
module Gargantext.Components.Nodes.Annuaire where module Gargantext.Components.Nodes.Annuaire where
import Prelude (bind, identity, pure, ($), (<$>), (<>)) import Prelude (bind, identity, pure, const, ($), (<$>), (<>))
import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?)) import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?))
import Data.Array (head) import Data.Array (head)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
...@@ -101,12 +101,13 @@ pageCpt = R.staticComponent "LoadedAnnuairePage" cpt ...@@ -101,12 +101,13 @@ pageCpt = R.staticComponent "LoadedAnnuairePage" cpt
where where
cpt { session, annuairePath, pagePath cpt { session, annuairePath, pagePath
, table: (AnnuaireTable {annuaireTable}) } _ = do , table: (AnnuaireTable {annuaireTable}) } _ = do
T.table { rows, params, container, colNames, totalRecords } T.table { rows, params, container, colNames, totalRecords, wrapColElts }
where where
totalRecords = 4361 -- TODO totalRecords = 4361 -- TODO
rows = (\c -> {row: contactCells session c, delete: false}) <$> annuaireTable rows = (\c -> {row: contactCells session c, delete: false}) <$> annuaireTable
container = T.defaultContainer { title: "Annuaire" } -- TODO container = T.defaultContainer { title: "Annuaire" } -- TODO
colNames = T.ColumnName <$> [ "", "Name", "Company", "Service", "Role"] colNames = T.ColumnName <$> [ "", "Name", "Company", "Service", "Role"]
wrapColElts = const identity
setParams f = snd pagePath $ \{nodeId, params: ps} -> setParams f = snd pagePath $ \{nodeId, params: ps} ->
{params: f ps, nodeId: fst annuairePath} {params: f ps, nodeId: fst annuairePath}
params = T.initialParams /\ setParams params = T.initialParams /\ setParams
......
...@@ -22,7 +22,7 @@ import Gargantext.Components.Annotation.AnnotatedField as AnnotatedField ...@@ -22,7 +22,7 @@ import Gargantext.Components.Annotation.AnnotatedField as AnnotatedField
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
import Gargantext.Types (CTabNgramType(..), NodeType(..), TabSubType(..), TabType(..), TermList) import Gargantext.Types (CTabNgramType(..), NodeType(..), TabSubType(..), TabType(..), TermList, ScoreType(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
type DocPath = type DocPath =
...@@ -295,11 +295,11 @@ docViewSpec = simpleSpec performAction render ...@@ -295,11 +295,11 @@ docViewSpec = simpleSpec performAction render
commitPatch path (Versioned {version: ngramsVersion, data: pt}) commitPatch path (Versioned {version: ngramsVersion, data: pt})
where where
pe = NgramsPatch { patch_list: pl, patch_children: mempty } pe = NgramsPatch { patch_list: pl, patch_children: mempty }
pt = singletonNgramsTablePatch CTabTerms n pe pt = singletonNgramsTablePatch n pe
performAction (AddNewNgram ngram termList) {path} {ngramsVersion} = performAction (AddNewNgram ngram termList) {path} {ngramsVersion} =
commitPatch path (Versioned {version: ngramsVersion, data: pt}) commitPatch path (Versioned {version: ngramsVersion, data: pt})
where where
pt = addNewNgram CTabTerms ngram termList pt = addNewNgram ngram termList
render :: Render State Props Action render :: Render State Props Action
render dispatch { loaded: { ngramsTable: Versioned { data: initTable }, document } } render dispatch { loaded: { ngramsTable: Versioned { data: initTable }, document } }
...@@ -379,8 +379,9 @@ loadData {session, nodeId, listIds, tabType} = do ...@@ -379,8 +379,9 @@ loadData {session, nodeId, listIds, tabType} = do
, listIds , listIds
, params: { offset : 0, limit : 100, orderBy: Nothing} , params: { offset : 0, limit : 100, orderBy: Nothing}
, tabType , tabType
, searchQuery : "" , searchQuery: ""
, termListFilter : Nothing , termListFilter: Nothing
, termSizeFilter : Nothing , termSizeFilter: Nothing
, scoreType: Occurrences
} }
pure {document, ngramsTable} pure {document, ngramsTable}
...@@ -12,6 +12,7 @@ import Effect (Effect) ...@@ -12,6 +12,7 @@ import Effect (Effect)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reactix (effectLink)
type TableContainerProps = type TableContainerProps =
( pageSizeControl :: R.Element ( pageSizeControl :: R.Element
...@@ -51,6 +52,8 @@ derive instance eqOrderByDirection :: Eq a => Eq (OrderByDirection a) ...@@ -51,6 +52,8 @@ derive instance eqOrderByDirection :: Eq a => Eq (OrderByDirection a)
type Props = type Props =
( colNames :: Array ColumnName ( colNames :: Array ColumnName
, wrapColElts :: ColumnName -> Array R.Element -> Array R.Element
-- ^ Use `const identity` as a default behavior.
, totalRecords :: Int , totalRecords :: Int
, params :: R.State Params , params :: R.State Params
, rows :: Rows , rows :: Rows
...@@ -126,7 +129,7 @@ table props = R.createElement tableCpt props [] ...@@ -126,7 +129,7 @@ table props = R.createElement tableCpt props []
tableCpt :: R.Component Props tableCpt :: R.Component Props
tableCpt = R.hooksComponent "G.C.Table.table" cpt tableCpt = R.hooksComponent "G.C.Table.table" cpt
where where
cpt {container, colNames, totalRecords, rows, params} _ = do cpt {container, colNames, wrapColElts, totalRecords, rows, params} _ = do
pageSize@(pageSize' /\ setPageSize) <- R.useState' PS10 pageSize@(pageSize' /\ setPageSize) <- R.useState' PS10
(page /\ setPage) <- R.useState' 1 (page /\ setPage) <- R.useState' 1
(orderBy /\ setOrderBy) <- R.useState' Nothing (orderBy /\ setOrderBy) <- R.useState' Nothing
...@@ -140,6 +143,7 @@ tableCpt = R.hooksComponent "G.C.Table.table" cpt ...@@ -140,6 +143,7 @@ tableCpt = R.hooksComponent "G.C.Table.table" cpt
lnk mc = effectLink (setOrderBy (const mc)) lnk mc = effectLink (setOrderBy (const mc))
cs :: Array R.Element cs :: Array R.Element
cs = cs =
wrapColElts c $
case orderBy of case orderBy of
Just (ASC d) | c == d -> [lnk (Just (DESC c)) "DESC ", lnk Nothing (columnName c)] Just (ASC d) | c == d -> [lnk (Just (DESC c)) "DESC ", lnk Nothing (columnName c)]
Just (DESC d) | c == d -> [lnk (Just (ASC c)) "ASC ", lnk Nothing (columnName c)] Just (DESC d) | c == d -> [lnk (Just (ASC c)) "ASC ", lnk Nothing (columnName c)]
...@@ -198,9 +202,6 @@ textDescription currPage pageSize totalRecords = ...@@ -198,9 +202,6 @@ textDescription currPage pageSize totalRecords =
end = if end' > totalRecords then totalRecords else end' end = if end' > totalRecords then totalRecords else end'
msg = "Showing " <> show start <> " to " <> show end <> " of " <> show totalRecords msg = "Showing " <> show start <> " to " <> show end <> " of " <> show totalRecords
effectLink :: Effect Unit -> String -> R.Element
effectLink eff msg = H.a {on: {click: const eff}} [H.text msg]
pagination :: (R2.Setter Int) -> Int -> Int -> R.Element pagination :: (R2.Setter Int) -> Int -> Int -> R.Element
pagination changePage tp cp = pagination changePage tp cp =
H.span {} $ H.span {} $
......
...@@ -127,6 +127,7 @@ sessionPath (R.GetNgrams opts i) = ...@@ -127,6 +127,7 @@ sessionPath (R.GetNgrams opts i) =
<> foldMap (\x -> "&list=" <> show x) opts.listIds <> foldMap (\x -> "&list=" <> show x) opts.listIds
<> foldMap (\x -> "&listType=" <> show x) opts.termListFilter <> foldMap (\x -> "&listType=" <> show x) opts.termListFilter
<> foldMap termSizeFilter opts.termSizeFilter <> foldMap termSizeFilter opts.termSizeFilter
<> "&scoreType=" <> show opts.scoreType
<> search opts.searchQuery <> search opts.searchQuery
where where
base (TabCorpus _) = sessionPath <<< R.NodeAPI Node i base (TabCorpus _) = sessionPath <<< R.NodeAPI Node i
......
...@@ -227,6 +227,13 @@ nodeTypePath Texts = "texts" ...@@ -227,6 +227,13 @@ nodeTypePath Texts = "texts"
type ListId = Int type ListId = Int
data ScoreType = Occurrences
derive instance genericScoreType :: Generic ScoreType _
instance showScoreType :: Show ScoreType where
show = genericShow
type NgramsGetOpts = type NgramsGetOpts =
{ tabType :: TabType { tabType :: TabType
, offset :: Offset , offset :: Offset
...@@ -235,6 +242,7 @@ type NgramsGetOpts = ...@@ -235,6 +242,7 @@ type NgramsGetOpts =
, listIds :: Array ListId , listIds :: Array ListId
, termListFilter :: Maybe TermList , termListFilter :: Maybe TermList
, termSizeFilter :: Maybe TermSize , termSizeFilter :: Maybe TermSize
, scoreType :: ScoreType
, searchQuery :: String , searchQuery :: String
} }
......
...@@ -18,6 +18,7 @@ import FFI.Simple ((...), defineProperty, delay, args2, args3) ...@@ -18,6 +18,7 @@ import FFI.Simple ((...), defineProperty, delay, args2, args3)
import React (class ReactPropFields, Children, ReactClass, ReactElement) import React (class ReactPropFields, Children, ReactClass, ReactElement)
import React as React import React as React
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H
import Reactix.DOM.HTML (ElemFactory, createDOM, text) import Reactix.DOM.HTML (ElemFactory, createDOM, text)
import Reactix.React (react) import Reactix.React (react)
import Reactix.SyntheticEvent as RE import Reactix.SyntheticEvent as RE
...@@ -167,3 +168,6 @@ useReductor' r = useReductor r pure ...@@ -167,3 +168,6 @@ useReductor' r = useReductor r pure
render :: R.Element -> DOM.Element -> Effect Unit render :: R.Element -> DOM.Element -> Effect Unit
render e d = delay unit $ \_ -> pure $ R.reactDOM ... "render" $ args2 e d render e d = delay unit $ \_ -> pure $ R.reactDOM ... "render" $ args2 e d
effectLink :: Effect Unit -> String -> R.Element
effectLink eff msg = H.a {on: {click: const eff}} [H.text msg]
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