Commit 3e4ade6d authored by Alexandre Delanoë's avatar Alexandre Delanoë

[MERGE] some fixes on the imports

parents c5017917 c5834e6c
Pipeline #1617 failed with stage
module Gargantext.Components.Charts.Options.Data where module Gargantext.Components.Charts.Options.Data where
import Gargantext.Components.Charts.Options.Font (TextStyle, Icon, ItemStyle)
import Gargantext.Components.Charts.Options.Legend (SelectedMode)
import Gargantext.Types (class Optional)
import Record.Unsafe (unsafeSet) import Record.Unsafe (unsafeSet)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Types (class Optional)
import Gargantext.Components.Charts.Options.Font (TextStyle, Icon, ItemStyle)
type DataLegend = type DataLegend =
{ name :: String { name :: String
...@@ -22,11 +23,15 @@ type RequiredData v o = ...@@ -22,11 +23,15 @@ type RequiredData v o =
} }
type OptionalData = type OptionalData =
( name :: String ( name :: String
, symbolSize :: Number , symbolSize :: Number
, itemStyle :: ItemStyle , itemStyle :: ItemStyle
-- ^ the style setting about single data point(bubble). -- ^ the style setting about single data point(bubble).
, label :: { show :: Boolean } , label :: { show :: Boolean }
, emphasis :: { itemStyle :: ItemStyle }
, selectedMode :: SelectedMode
, select :: { itemStyle :: ItemStyle }
-- ^ need "selectedMode" to be defined
) )
type DataSerie v = RequiredData v OptionalData type DataSerie v = RequiredData v OptionalData
......
...@@ -3,3 +3,31 @@ ...@@ -3,3 +3,31 @@
var ReactEcharts = require("echarts-for-react"); var ReactEcharts = require("echarts-for-react");
exports.eChartsClass = ReactEcharts.default; exports.eChartsClass = ReactEcharts.default;
/**
* @XXX "echarts-for-react" unsuitable to proper PureScript implementation
* regarding event listeners
* @name listenerFn1
* @param {function} fn
* @returns
*/
exports.listenerFn1 = function(fn) {
return function() {
var args = Array.prototype.slice.call(arguments);
fn(args[0])()
}
};
/**
* @link https://echarts.apache.org/en/api.html#echartsInstance.dispatchAction
* @name dispatchAction
* @param {object} eChartsInstance instanceof ECharts
* @param {object} opts
* @returns
*/
exports.dispatchAction = function(eChartsInstance) {
return function(opts) {
return function() {
eChartsInstance.dispatchAction(opts);
}
}
}
module Gargantext.Components.Charts.Options.ECharts where module Gargantext.Components.Charts.Options.ECharts where
import Prelude
import CSS.Common (normal) import CSS.Common (normal)
import CSS.FontStyle (FontStyle(..)) import CSS.FontStyle (FontStyle(..))
import Data.Maybe (Maybe(..))
import Data.Nullable (toMaybe)
import Effect (Effect)
import Gargantext.Components.Charts.Options.Color (transparent, violet, black) import Gargantext.Components.Charts.Options.Color (transparent, violet, black)
import Gargantext.Components.Charts.Options.Data (DataLegend, dataSerie) import Gargantext.Components.Charts.Options.Data (DataLegend, dataSerie)
import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon, mkTooltip, Tooltip, mkToolBox) import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon, mkTooltip, Tooltip, mkToolBox)
import Gargantext.Components.Charts.Options.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient) import Gargantext.Components.Charts.Options.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient)
import Gargantext.Components.Charts.Options.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition) import Gargantext.Components.Charts.Options.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition)
import Gargantext.Components.Charts.Options.Series (Series, seriesPieD1) import Gargantext.Components.Charts.Options.Series (Series, seriesPieD1)
import Gargantext.Components.Charts.Options.Type (DataZoom, Echarts, Legend, Option, Title, XAxis, YAxis, xAxis, yAxis) import Gargantext.Components.Charts.Options.Type (DataZoom, EChartsInstance, Echarts, Legend, MouseEvent, Option, Title, XAxis, YAxis, EChartRef, xAxis, yAxis)
import Gargantext.Utils.Reactix as R2
import Prelude
import React (ReactClass, unsafeCreateElementDynamic) import React (ReactClass, unsafeCreateElementDynamic)
import Reactix as R import Reactix as R
import Gargantext.Utils.Reactix as R2 import Record.Extra as RX
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
foreign import eChartsClass :: ReactClass Echarts foreign import eChartsClass :: ReactClass Echarts
foreign import listenerFn1 :: forall evt. (evt -> Effect Unit) -> Effect Unit
-- | @XXX some eCharts "actions" not working ("select", ...)
-- | https://echarts.apache.org/en/api.html#echartsInstance.dispatchAction
foreign import dispatchAction :: forall payload. EChartsInstance -> payload -> Effect Unit
chart :: Options -> R.Element chart :: Options -> R.Element
chart = echarts <<< chartWith <<< opts chart = echarts <<< chartWith
chartWith :: Option -> Echarts chartWith :: Options -> Echarts
chartWith option = chartWith options =
{ option { option : opts options
--, className : Nothing --, className : Nothing
--, style : Nothing --, style : Nothing
--, theme : Nothing --, theme : Nothing
...@@ -35,8 +42,24 @@ chartWith option = ...@@ -35,8 +42,24 @@ chartWith option =
--, optsLoading: Nothing --, optsLoading: Nothing
--, onReady : Nothing --, onReady : Nothing
--, resizable : Nothing --, resizable : Nothing
--, onEvents : Nothing , onEvents : getEvents options
, ref : refListener options
} }
where
getEvents (Options { onClick }) =
{ click: listenerFn1 \e -> case onClick of
-- sanitize parsing (see MouseEvent comment)
Just fn -> RX.pick (e :: MouseEvent) # fn
Nothing -> pure unit
}
refListener (Options { onInit }) = case onInit of
Nothing -> pure unit
Just fn -> listenerFn1 (_ # fn # execOnInit)
execOnInit fn = toMaybe >>> case _ of
Nothing -> pure unit
Just (ref :: Record EChartRef) -> fn =<< ref.getEchartsInstance
echarts :: Echarts -> R.Element echarts :: Echarts -> R.Element
echarts c = R2.buff $ unsafeCreateElementDynamic (unsafeCoerce eChartsClass) c [] echarts c = R2.buff $ unsafeCreateElementDynamic (unsafeCoerce eChartsClass) c []
...@@ -155,6 +178,20 @@ data Options = Options ...@@ -155,6 +178,20 @@ data Options = Options
, series :: Array Series , series :: Array Series
, addZoom :: Boolean , addZoom :: Boolean
, tooltip :: Tooltip , tooltip :: Tooltip
, onClick :: Maybe (MouseEvent -> Effect Unit)
-- (?) `onInit` custom listener
--
-- * in addition of the already existing `onReady` native listener
-- which is executed on chart mount, but does not provide any arg
-- * the React library also contained another native listener as
-- `ref`, which adds the React Ref of the mounted chart
-- * this additional `onInit` is executed after the "Apache Echarts"
-- has been "initialised" (see more details [1]),
-- it intends to return the `eChartsInstance` used for every
-- library actions
--
-- [1] https://echarts.apache.org/en/api.html#echarts.init
, onInit :: Maybe (EChartsInstance -> Effect Unit)
} }
tooltipTriggerAxis :: Tooltip tooltipTriggerAxis :: Tooltip
......
module Gargantext.Components.Charts.Options.Series where module Gargantext.Components.Charts.Options.Series where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, (.:), (~>), (:=))
import Data.Argonaut.Core (jsonEmptyObject)
import Data.Array (foldl) import Data.Array (foldl)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Record as Record import Gargantext.Components.Charts.Options.Data (DataD1, DataD2)
import Gargantext.Components.Charts.Options.Data (DataD1, DataD2)
import Gargantext.Components.Charts.Options.Font (ItemStyle, Tooltip)
import Gargantext.Components.Charts.Options.Font (ItemStyle, Tooltip)
import Gargantext.Components.Charts.Options.Legend (SelectedMode)
import Gargantext.Prelude
import Gargantext.Types (class Optional)
import Prelude (class Eq, class Show, bind, map, pure, show, ($), (+), (<<<), (<>), eq)
import Record as Record
import Record.Unsafe (unsafeSet) import Record.Unsafe (unsafeSet)
import Simple.JSON as JSON import Simple.JSON as JSON
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Types (class Optional)
import Gargantext.Components.Charts.Options.Font (ItemStyle, Tooltip)
import Gargantext.Components.Charts.Options.Data (DataD1, DataD2)
newtype SeriesType = SeriesType String newtype SeriesType = SeriesType String
...@@ -59,13 +64,16 @@ seriesType = SeriesType <<< show ...@@ -59,13 +64,16 @@ seriesType = SeriesType <<< show
-- | Scatter Dimension 2 data -- | Scatter Dimension 2 data
type OptionalSeries = type OptionalSeries =
( name :: String ( name :: String
, symbolSize :: Number , symbolSize :: Number
, itemStyle :: ItemStyle , itemStyle :: ItemStyle
-- ^ Graphic style of, *emphasis* is the style when it is highlighted, like being hovered by mouse, or highlighted via legend connect. -- ^ Graphic style of, *emphasis* is the style when it is highlighted, like being hovered by mouse, or highlighted via legend connect.
-- https://ecomfe.github.io/echarts-doc/public/en/option.html#series-scatter.itemStyle -- https://ecomfe.github.io/echarts-doc/public/en/option.html#series-scatter.itemStyle
, tooltip :: Tooltip , tooltip :: Tooltip
, emphasis :: { itemStyle :: ItemStyle }
, selectedMode :: SelectedMode
, select :: { itemStyle :: ItemStyle }
-- ^ need "selectedMode" to be defined
-- many more... -- many more...
) )
...@@ -217,5 +225,3 @@ labelP = SProxy :: SProxy "label" ...@@ -217,5 +225,3 @@ labelP = SProxy :: SProxy "label"
-- | TODO -- | TODO
-- https://ecomfe.github.io/echarts-examples/public/data/asset/data/life-expectancy-table.json -- https://ecomfe.github.io/echarts-examples/public/data/asset/data/life-expectancy-table.json
-- https://ecomfe.github.io/echarts-examples/public/editor.html?c=scatter3D-dataset&gl=1 -- https://ecomfe.github.io/echarts-examples/public/editor.html?c=scatter3D-dataset&gl=1
...@@ -2,6 +2,8 @@ module Gargantext.Components.Charts.Options.Type where ...@@ -2,6 +2,8 @@ module Gargantext.Components.Charts.Options.Type where
import Prelude import Prelude
import Data.Nullable (Nullable)
import Effect (Effect)
import Gargantext.Components.Charts.Options.Color (Color) import Gargantext.Components.Charts.Options.Color (Color)
import Gargantext.Components.Charts.Options.Data (DataLegend) import Gargantext.Components.Charts.Options.Data (DataLegend)
import Gargantext.Components.Charts.Options.Font (TextStyle, Tooltip, ToolBox) import Gargantext.Components.Charts.Options.Font (TextStyle, Tooltip, ToolBox)
...@@ -12,6 +14,9 @@ import Gargantext.Types (class Optional) ...@@ -12,6 +14,9 @@ import Gargantext.Types (class Optional)
import React as R import React as R
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
-- | https://echarts.apache.org/en/api.html#echartsInstance
foreign import data EChartsInstance :: Type
newtype ChartAlign = ChartAlign String newtype ChartAlign = ChartAlign String
-- TODO: Maybe is not working here => use Optional -- TODO: Maybe is not working here => use Optional
...@@ -29,7 +34,8 @@ type Echarts = ...@@ -29,7 +34,8 @@ type Echarts =
--, optsLoading :: Maybe OptsLoading -- PropTypes.object, --, optsLoading :: Maybe OptsLoading -- PropTypes.object,
--, onReady :: Maybe String -- PropTypes.func, --, onReady :: Maybe String -- PropTypes.func,
--, resizable :: Maybe Boolean -- PropTypes.bool, --, resizable :: Maybe Boolean -- PropTypes.bool,
--, onEvents :: Maybe String -- PropTypes.object , onEvents :: OnEvents -- PropTypes.object
, ref :: Effect Unit
} }
type Option = type Option =
...@@ -160,3 +166,53 @@ type AxisLabel = ...@@ -160,3 +166,53 @@ type AxisLabel =
} }
type Rich = {} type Rich = {}
---
-- | @XXX "echarts-for-react" third party library does not have an event
-- | dictionary
-- | these values had been picked from what we gather in the dist file
-- | "echarts/dist/echarts.common.js" and
-- | https://echarts.apache.org/en/api.html#events
type OnEvents =
{ click :: Effect Unit
-- ...
}
-- | @XXX "echarts-for-react" third party library bases on "apache-echarts"
-- | does not have strongly typed signature, nor determined arity
-- | (actual runtime event contains more key than what their docs describe)
-- |
-- | https://echarts.apache.org/en/api.html#events.Mouse%20events
type MouseEvent =
{ borderColor :: Nullable String
, color :: String
, componentIndex :: Int
, componentSubType :: String
, componentTyp :: String
-- , data :: -- Object
, dataIndex :: Int
, dataType :: Nullable String
-- , dimensionNames :: -- Array
-- , encore :: -- Object
-- , event :: -- instanceof Event
-- , marker :: -- String
, name :: String
, seriesId :: Nullable String
, seriesIndex :: Int
, seriesName :: String
, seriesType :: String
, type :: String
, value :: String -- or Array ??
}
----
-- | @XXX partial definition given by the third library author
-- | POJO containing a mix of ReactElement field and custom method attached
-- |
-- | https://github.com/hustcc/echarts-for-react#component-api--echarts-api
type EChartRef =
( getEchartsInstance :: Effect EChartsInstance
-- ...
)
-- TODO: this module should be replaced by FacetsTable -- TODO: this module should be replaced by FacetsTable
module Gargantext.Components.DocsTable where module Gargantext.Components.DocsTable where
import DOM.Simple.Console (log2)
import DOM.Simple.Event as DE
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>))
import Data.Array as A import Data.Array as A
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Lens ((^.)) import Data.Lens ((^.))
import Data.Lens.At (at) import Data.Lens.At (at)
import Data.Lens.Record (prop) import Data.Lens.Record (prop)
import Data.Map as Map
import Data.Maybe (Maybe(..), fromMaybe, isJust, maybe) import Data.Maybe (Maybe(..), fromMaybe, isJust, maybe)
import Data.Map as Map
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Ord.Down (Down(..)) import Data.Ord.Down (Down(..))
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import Data.String as Str import Data.String as Str
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import DOM.Simple.Console (log2)
import DOM.Simple.Event as DE
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
import Gargantext.Prelude
import Gargantext.Components.Category (rating) import Gargantext.Components.Category (rating)
import Gargantext.Components.Category.Types (Star(..)) import Gargantext.Components.Category.Types (Star(..))
import Gargantext.Components.DocsTable.Types import Gargantext.Components.DocsTable.Types (DocumentsView(..), Hyperdata(..), LocalUserScore, Query, Response(..), Year, sampleData)
( DocumentsView(..), Hyperdata(..), LocalUserScore, Query, Response(..), sampleData )
import Gargantext.Components.Table.Types as TT
import Gargantext.Components.Nodes.Lists.Types as NT import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Texts.Types as TextsT import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Table as TT import Gargantext.Components.Table as TT
import Gargantext.Components.Table.Types as TT
import Gargantext.Ends (Frontends, url) import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader, useLoaderWithCacheAPI, HashedResponse(..)) import Gargantext.Hooks.Loader (useLoader, useLoaderWithCacheAPI, HashedResponse(..))
import Gargantext.Routes as Routes import Gargantext.Prelude
import Gargantext.Prelude (class Ord, Unit, bind, const, discard, identity, mempty, otherwise, pure, show, unit, ($), (/=), (<$>), (<<<), (<>), (==))
import Gargantext.Routes (SessionRoute(NodeAPI)) import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, get, delete) import Gargantext.Sessions (Session, sessionId, get, delete)
import Gargantext.Types (ListId, NodeID, NodeType(..), OrderBy(..), SidePanelState(..), TableResult, TabSubType, TabType, showTabType') import Gargantext.Types (ListId, NodeID, NodeType(..), OrderBy(..), SidePanelState(..), TableResult, TabSubType, TabType, showTabType')
import Gargantext.Utils (sortWith) import Gargantext.Utils (sortWith)
import Gargantext.Utils.CacheAPI as GUC import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.QueryString (joinQueryStrings, mQueryParamS, queryParam, queryParamS) import Gargantext.Utils.QueryString (joinQueryStrings, mQueryParam, mQueryParamS, queryParam, queryParamS)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Prelude
import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.DocsTable" here = R2.here "Gargantext.Components.DocsTable"
...@@ -72,7 +72,8 @@ type CommonProps = ...@@ -72,7 +72,8 @@ type CommonProps =
, tabType :: TabType , tabType :: TabType
-- ^ tabType is not ideal here since it is too much entangled with tabs and -- ^ tabType is not ideal here since it is too much entangled with tabs and
-- ngramtable. Let's see how this evolves. ) -- ngramtable. Let's see how this evolves. )
, totalRecords :: Int , totalRecords :: Int
, yearFilter :: T.Box (Maybe Year)
) )
type LayoutProps = type LayoutProps =
...@@ -128,6 +129,7 @@ docViewCpt = here.component "docView" cpt where ...@@ -128,6 +129,7 @@ docViewCpt = here.component "docView" cpt where
, sidePanelState , sidePanelState
, tabType , tabType
, totalRecords , totalRecords
, yearFilter
} }
, params , params
, query , query
...@@ -153,6 +155,7 @@ docViewCpt = here.component "docView" cpt where ...@@ -153,6 +155,7 @@ docViewCpt = here.component "docView" cpt where
, sidePanelState , sidePanelState
, tabType , tabType
, totalRecords , totalRecords
, yearFilter
} [] ] ] ] } [] ] ] ]
type SearchBarProps = type SearchBarProps =
...@@ -209,12 +212,13 @@ mock :: Boolean ...@@ -209,12 +212,13 @@ mock :: Boolean
mock = false mock = false
type PageParams = { type PageParams = {
listId :: Int listId :: Int
, mCorpusId :: Maybe Int , mCorpusId :: Maybe Int
, nodeId :: Int , nodeId :: Int
, tabType :: TabType , tabType :: TabType
, query :: Query , query :: Query
, params :: TT.Params , params :: TT.Params
, yearFilter :: Maybe Year
} }
getPageHash :: Session -> PageParams -> Aff String getPageHash :: Session -> PageParams -> Aff String
...@@ -249,6 +253,12 @@ filterDocs query docs = A.filter filterFunc docs ...@@ -249,6 +253,12 @@ filterDocs query docs = A.filter filterFunc docs
filterFunc (Response { hyperdata: Hyperdata { title } }) = filterFunc (Response { hyperdata: Hyperdata { title } }) =
isJust $ Str.indexOf (Str.Pattern $ Str.toLower query) $ Str.toLower title isJust $ Str.indexOf (Str.Pattern $ Str.toLower query) $ Str.toLower title
filterDocsByYear :: Year -> Array Response -> Array Response
filterDocsByYear year docs = A.filter filterFunc docs
where
filterFunc :: Response -> Boolean
filterFunc (Response { hyperdata: Hyperdata { pub_year } }) = eq year $ show pub_year
pageLayout :: R2.Component PageLayoutProps pageLayout :: R2.Component PageLayoutProps
pageLayout = R.createElement pageLayoutCpt pageLayout = R.createElement pageLayoutCpt
...@@ -263,19 +273,30 @@ pageLayoutCpt = here.component "pageLayout" cpt where ...@@ -263,19 +273,30 @@ pageLayoutCpt = here.component "pageLayout" cpt where
, query , query
, session , session
, sidePanel , sidePanel
, tabType } _ = do , tabType
, yearFilter
} _ = do
cacheState' <- T.useLive T.unequal cacheState cacheState' <- T.useLive T.unequal cacheState
yearFilter' <- T.useLive T.unequal yearFilter
let path = { listId, mCorpusId, nodeId, params, query, tabType } let path = { listId, mCorpusId, nodeId, params, query, tabType, yearFilter: yearFilter' }
handleResponse :: HashedResponse (TableResult Response) -> Tuple Int (Array DocumentsView) handleResponse :: HashedResponse (TableResult Response) -> Tuple Int (Array DocumentsView)
handleResponse (HashedResponse { hash, value: res }) = ret handleResponse (HashedResponse { hash, value: res }) = ret
where where
docs = res2corpus <$> filterDocs query res.docs
filters = filterDocs query
>>> \res' -> case yearFilter' of
Nothing -> res'
Just year -> filterDocsByYear year res'
docs = res2corpus <$> filters res.docs
ret = if mock then ret = if mock then
--Tuple 0 (take limit $ drop offset sampleData) --Tuple 0 (take limit $ drop offset sampleData)
Tuple 0 sampleData Tuple 0 sampleData
else else
Tuple res.count docs Tuple res.count docs
case cacheState' of case cacheState' of
NT.CacheOn -> do NT.CacheOn -> do
let paint (Tuple count docs) = page { documents: docs let paint (Tuple count docs) = page { documents: docs
...@@ -527,9 +548,10 @@ tableRouteWithPage :: forall row. ...@@ -527,9 +548,10 @@ tableRouteWithPage :: forall row.
, params :: TT.Params , params :: TT.Params
, query :: Query , query :: Query
, tabType :: TabType , tabType :: TabType
, yearFilter :: Maybe Year
| row } -> SessionRoute | row } -> SessionRoute
tableRouteWithPage { listId, nodeId, params: { limit, offset, orderBy, searchType }, query, tabType } = tableRouteWithPage { listId, nodeId, params: { limit, offset, orderBy, searchType }, query, tabType, yearFilter } =
NodeAPI Node (Just nodeId) $ "table" <> joinQueryStrings [tt, lst, lmt, odb, ofs, st, q] NodeAPI Node (Just nodeId) $ "table" <> joinQueryStrings [tt, lst, lmt, odb, ofs, st, q, y]
where where
lmt = queryParam "limit" limit lmt = queryParam "limit" limit
lst = queryParam "list" listId lst = queryParam "list" listId
...@@ -538,6 +560,7 @@ tableRouteWithPage { listId, nodeId, params: { limit, offset, orderBy, searchTyp ...@@ -538,6 +560,7 @@ tableRouteWithPage { listId, nodeId, params: { limit, offset, orderBy, searchTyp
st = queryParam "searchType" searchType st = queryParam "searchType" searchType
tt = queryParamS "tabType" (showTabType' tabType) tt = queryParamS "tabType" (showTabType' tabType)
q = queryParamS "query" query q = queryParamS "query" query
y = mQueryParam "year" yearFilter
deleteAllDocuments :: Session -> Int -> Aff (Array Int) deleteAllDocuments :: Session -> Int -> Aff (Array Int)
deleteAllDocuments session = delete session <<< documentsRoute deleteAllDocuments session = delete session <<< documentsRoute
......
...@@ -97,6 +97,7 @@ instance JSON.ReadForeign Hyperdata where ...@@ -97,6 +97,7 @@ instance JSON.ReadForeign Hyperdata where
type LocalCategories = Map Int Category type LocalCategories = Map Int Category
type LocalUserScore = Map Int Star type LocalUserScore = Map Int Star
type Query = String type Query = String
type Year = String
--------------------------------------------------------- ---------------------------------------------------------
sampleData' :: DocumentsView sampleData' :: DocumentsView
......
...@@ -2,31 +2,32 @@ ...@@ -2,31 +2,32 @@
module Gargantext.Components.Nodes.Annuaire.Tabs where module Gargantext.Components.Nodes.Annuaire.Tabs where
import Prelude hiding (div) import Prelude hiding (div)
import Effect.Aff (Aff)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow) import Data.Show.Generic (genericShow)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (fst) import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Reactix as R import Effect.Aff (Aff)
import Record as Record
import Record.Extra as RX
import Toestand as T
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable.Types (Year)
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core as NTC import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Tab as Tab
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData)
import Gargantext.Components.Nodes.Lists.Types as LTypes import Gargantext.Components.Nodes.Lists.Types as LTypes
import Gargantext.Components.Nodes.Texts.Types as TTypes import Gargantext.Components.Nodes.Texts.Types as TTypes
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Tab as Tab
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), PTabNgramType(..), SidePanelState, TabType(..), TabSubType(..)) import Gargantext.Types (CTabNgramType(..), PTabNgramType(..), SidePanelState, TabType(..), TabSubType(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Reactix as R
import Record as Record
import Record.Extra as RX
import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs" here = R2.here "Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs"
...@@ -71,9 +72,10 @@ tabsCpt :: R.Component TabsProps ...@@ -71,9 +72,10 @@ tabsCpt :: R.Component TabsProps
tabsCpt = here.component "tabs" cpt where tabsCpt = here.component "tabs" cpt where
cpt props _ = do cpt props _ = do
activeTab <- T.useBox 0 activeTab <- T.useBox 0
yearFilter <- T.useBox (Nothing :: Maybe Year)
pure $ Tab.tabs { activeTab, tabs: tabs' props } pure $ Tab.tabs { activeTab, tabs: tabs' yearFilter props }
tabs' props@{ sidePanel, sidePanelState } = tabs' yearFilter props@{ sidePanel, sidePanelState } =
[ "Documents" /\ docs [ "Documents" /\ docs
, "Patents" /\ ngramsView (viewProps Patents) , "Patents" /\ ngramsView (viewProps Patents)
, "Books" /\ ngramsView (viewProps Books) , "Books" /\ ngramsView (viewProps Books)
...@@ -92,6 +94,7 @@ tabsCpt = here.component "tabs" cpt where ...@@ -92,6 +94,7 @@ tabsCpt = here.component "tabs" cpt where
, showSearch: true , showSearch: true
, tabType: TabPairing TabDocs , tabType: TabPairing TabDocs
, totalRecords , totalRecords
, yearFilter
} }
type DTCommon = type DTCommon =
......
...@@ -2,27 +2,28 @@ ...@@ -2,27 +2,28 @@
module Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs where module Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow) import Data.Show.Generic (genericShow)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (fst) import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Reactix as R
import Toestand as T
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable.Types (Year)
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core as NTC import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.Tab as Tab
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData') import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (ContactData')
import Gargantext.Components.Nodes.Lists.Types as LTypes