Commit 38f1fe6f authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[toestand] refactoring of state params and ngrams table a bit

parent e9cb8c69
......@@ -282,20 +282,21 @@ pageLayoutCpt = here.component "pageLayout" cpt where
}
NT.CacheOff -> do
localCategories <- R.useState' (mempty :: LocalUserScore)
paramsS <- R.useState' params
paramsS <- T.useBox params
paramsS' <- T.useLive T.unequal paramsS
let loader p = do
let route = tableRouteWithPage (p { params = fst paramsS, query = query })
let route = tableRouteWithPage (p { params = paramsS', query = query })
res <- get session $ route
liftEffect $ do
log2 "[pageLayout] table route" route
log2 "[pageLayout] table res" res
pure $ handleResponse res
render (Tuple count documents) = pagePaintRaw { documents
, layout: props { params = fst paramsS
, layout: props { params = paramsS'
, totalRecords = count }
, localCategories
, params: paramsS } []
useLoader (path { params = fst paramsS }) loader render
useLoader (path { params = paramsS' }) loader render
type PageProps = (
documents :: Array DocumentsView
......@@ -309,13 +310,14 @@ page = R.createElement pageCpt
pageCpt :: R.Component PageProps
pageCpt = here.component "pageCpt" cpt where
cpt { documents, layout, params } _ = do
paramsS <- R.useState' params
paramsS <- T.useBox params
pure $ pagePaint { documents, layout, params: paramsS } []
type PagePaintProps = (
documents :: Array DocumentsView
, layout :: Record PageLayoutProps
, params :: R.State TT.Params
, params :: T.Box TT.Params
)
pagePaint :: R2.Component PagePaintProps
......@@ -325,14 +327,16 @@ pagePaintCpt :: R.Component PagePaintProps
pagePaintCpt = here.component "pagePaintCpt" cpt
where
cpt { documents, layout, params } _ = do
params' <- T.useLive T.unequal params
localCategories <- R.useState' (mempty :: LocalUserScore)
pure $ pagePaintRaw { documents: A.fromFoldable filteredRows
pure $ pagePaintRaw { documents: A.fromFoldable (filteredRows params')
, layout
, localCategories
, params } []
where
orderWith =
case convOrderBy (fst params).orderBy of
orderWith { orderBy } =
case convOrderBy orderBy of
Just DateAsc -> sortWith \(DocumentsView { date }) -> date
Just DateDesc -> sortWith \(DocumentsView { date }) -> Down date
Just SourceAsc -> sortWith \(DocumentsView { source }) -> Str.toLower source
......@@ -340,14 +344,14 @@ pagePaintCpt = here.component "pagePaintCpt" cpt
Just TitleAsc -> sortWith \(DocumentsView { title }) -> Str.toLower title
Just TitleDesc -> sortWith \(DocumentsView { title }) -> Down $ Str.toLower title
_ -> identity -- the server ordering is enough here
filteredRows = TT.filterRows { params: fst params } $ orderWith $ A.toUnfoldable documents
filteredRows params' = TT.filterRows { params: params' } $ (orderWith params') $ A.toUnfoldable documents
type PagePaintRawProps = (
documents :: Array DocumentsView
, layout :: Record PageLayoutProps
, localCategories :: R.State LocalUserScore
, params :: R.State TT.Params
, params :: T.Box TT.Params
)
pagePaintRaw :: R2.Component PagePaintRawProps
......
......@@ -18,9 +18,9 @@ import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Category (CategoryQuery(..), putCategories)
import Gargantext.Components.Category.Types (Category(..), decodeCategory, favCategory)
......@@ -124,14 +124,15 @@ docViewCpt = here.component "docView" cpt
where
cpt {frontends, session, nodeId, listId, query, totalRecords, chart, container} _ = do
deletions <- R.useState' initialDeletions
path <- R.useState' $ initialPagePath {nodeId, listId, query, session}
path <- T.useBox $ initialPagePath {nodeId, listId, query, session}
path' <- T.useLive T.unequal path
R.useEffect' $ do
let ipp = initialPagePath {nodeId, listId, query, session}
if fst path == ipp then
if path' == ipp then
pure unit
else
snd path $ const ipp
void $ T.write ipp path
pure $ H.div { className: "facets-doc-view container1" }
[ R2.row
......@@ -181,7 +182,8 @@ docViewGraphCpt = here.component "docViewGraph" cpt
let buttonStyle = { backgroundColor: "peru", padding : "9px"
, color : "white", border : "white", float: "right"}
let performClick = \_ -> performDeletions session nodeId deletions
path <- R.useState' $ initialPagePath { nodeId, listId, query, session }
path <- T.useBox $ initialPagePath { nodeId, listId, query, session }
pure $ R.fragment
[ H.br {}
, H.p {} [ H.text "" ]
......@@ -294,7 +296,7 @@ type PageLayoutProps =
, deletions :: R.State Deletions
, container :: Record T.TableContainerProps -> R.Element
, session :: Session
, path :: R.State PagePath
, path :: T.Box PagePath
)
type PageProps = ( rowsLoaded :: Rows | PageLayoutProps )
......@@ -307,7 +309,9 @@ pageLayoutCpt :: R.Component PageLayoutProps
pageLayoutCpt = here.component "pageLayout" cpt
where
cpt {frontends, totalRecords, deletions, container, session, path} _ = do
useLoader (fst path) loadPage $ \rowsLoaded ->
path' <- T.useLive T.unequal path
useLoader path' loadPage $ \rowsLoaded ->
page {frontends, totalRecords, deletions, container, session, path, rowsLoaded}
page :: Record PageProps -> R.Element
......@@ -316,14 +320,25 @@ page props = R.createElement pageCpt props []
pageCpt :: R.Component PageProps
pageCpt = here.component "page" cpt
where
cpt {frontends, totalRecords, container, deletions, rowsLoaded, session, path: path@({nodeId, listId, query} /\ setPath)} _ = do
pure $ T.table { syncResetButton : [ H.div {} [] ]
, rows, container, colNames
, totalRecords, params, wrapColElts
cpt { frontends
, totalRecords
, container
, deletions
, rowsLoaded
, session
, path } _ = do
path'@{ nodeId, listId, query } <- T.useLive T.unequal path
params <- T.useFocused (_.params) (\a b -> b { params = a }) path
pure $ T.table { colNames
, container
, params
, rows: rows path'
, syncResetButton : [ H.div {} [] ]
, totalRecords
, wrapColElts
}
where
setParams f = setPath $ \p@{params: ps} -> p {params = f ps}
params = (fst path).params /\ setParams
colNames = case rowsLoaded of
Docs _ -> T.ColumnName <$> [ "", "Date", "Title", "Journal", "", "" ]
Contacts _ -> T.ColumnName <$> [ "", "Contact", "Organization", "", "", "" ]
......@@ -336,22 +351,23 @@ pageCpt = here.component "page" cpt
isChecked id = Set.member id (fst deletions).pending
isDeleted (DocumentsView {id}) = Set.member id (fst deletions).deleted
documentUrl id { listId, nodeId } =
url frontends $ Routes.CorpusDocument (sessionId session) nodeId listId id
pairUrl (Pair {id,label})
| id > 1 = H.a { href, target: "blank" } [ H.text label ]
where href = url session $ NodePath (sessionId session) NodeContact (Just id)
| otherwise = H.text label
documentUrl id =
url frontends $ Routes.CorpusDocument (sessionId session) nodeId listId id
rows = case rowsLoaded of
Docs {docs} -> docRow <$> Seq.filter (not <<< isDeleted) docs
Contacts {contacts} -> contactRow <$> contacts
rows path' = case rowsLoaded of
Docs {docs} -> docRow path' <$> Seq.filter (not <<< isDeleted) docs
Contacts {contacts} -> contactRow path' <$> contacts
contactRow (ContactsView { id, hyperdata: HyperdataRowContact { firstname, lastname, labs}
, score, annuaireId, delete
contactRow path' (ContactsView { id, hyperdata: HyperdataRowContact { firstname, lastname, labs }
, score, annuaireId, delete
}) =
{ row:
T.makeRow [ H.div {} [ H.a { className: gi Favorite, on: {click: markClick} } [] ]
T.makeRow [ H.div {} [ H.a { className: gi Favorite, on: {click: markClick path'} } [] ]
, maybeStricken delete [ H.a {target: "_blank", href: contactUrl annuaireId id}
[ H.text $ firstname <> " " <> lastname ]
]
......@@ -360,14 +376,14 @@ pageCpt = here.component "page" cpt
, delete: true
}
where
markClick _ = markCategory session nodeId Favorite [id]
markClick { nodeId } _ = markCategory session nodeId Favorite [id]
contactUrl aId id' = url frontends $ Routes.ContactPage (sessionId session) annuaireId id'
docRow dv@(DocumentsView {id, score, title, source, authors, pairs, delete, category}) =
docRow path' dv@(DocumentsView {id, score, title, source, authors, pairs, delete, category}) =
{ row:
T.makeRow [ H.div {} [ H.a { className: gi category, on: {click: markClick} } [] ]
T.makeRow [ H.div {} [ H.a { className: gi category, on: {click: markClick path'} } [] ]
, maybeStricken delete [ H.text $ publicationDate dv ]
, maybeStricken delete [ H.a {target: "_blank", href: documentUrl id} [ H.text title ] ]
, maybeStricken delete [ H.a {target: "_blank", href: documentUrl id path'} [ H.text title ] ]
, maybeStricken delete [ H.text source ]
-- , maybeStricken delete [ H.text authors ]
-- , maybeStricken $ intercalate [comma] (pairUrl <$> pairs)
......@@ -379,7 +395,7 @@ pageCpt = here.component "page" cpt
]
, delete: true }
where
markClick _ = markCategory session nodeId category [id]
markClick { nodeId } _ = markCategory session nodeId category [id]
toggleClick _ = togglePendingDeletion deletions id
-- comma = H.span {} [ H.text ", " ]
......
......@@ -187,14 +187,14 @@ panelActionCpt = here.component "panelAction" cpt
cpt {action: Link {subTreeParams}, dispatch, id, nodeType, session, handed} _ =
pure $ linkNode {dispatch, id, nodeType, session, subTreeParams, handed} []
cpt {action : Share, dispatch, id, name } _ = do
isOpen <- T.useBox true >>= T.useFocused identity (\a _ -> a)
isOpen <- T.useBox true
pure $ panel
[ textInputBox
{ boxAction: Share.shareAction, boxName: "Share"
, dispatch, id, text: "username", isOpen } []
] (H.div {} [])
cpt {action : AddingContact, dispatch, id, name } _ = do
isOpen <- T.useBox true >>= T.useFocused identity (\a _ -> a)
isOpen <- T.useBox true
pure $ Contact.textInputBox
{ id, dispatch, isOpen, boxName:"addContact"
, params : {firstname:"First Name", lastname: "Last Name"}
......
This diff is collapsed.
......@@ -15,6 +15,7 @@ import Effect (Effect)
import FFI.Simple (delay)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Prelude
( Unit, bind, const, discard, map, not, otherwise
......@@ -34,8 +35,7 @@ here = R2.here "Gargantext.Components.NgramsTable.Components"
type SearchInputProps =
( key :: String -- to prevent refreshing & losing input
, onSearch :: String -> Effect Unit
, searchQuery :: String
, searchQuery :: T.Box String
)
searchInput :: Record SearchInputProps -> R.Element
......@@ -44,33 +44,34 @@ searchInput props = R.createElement searchInputCpt props []
searchInputCpt :: R.Component SearchInputProps
searchInputCpt = here.component "searchInput" cpt
where
cpt { onSearch, searchQuery } _ =
cpt { searchQuery } _ = do
searchQuery' <- T.useLive T.unequal searchQuery
pure $ R2.row [
H.div { className: "col-12" } [
H.div { className: "input-group" } [
searchButton
, fieldInput
H.div { className: "input-group" }
[ searchButton searchQuery'
, fieldInput searchQuery'
]
]
]
where
searchButton =
searchButton searchQuery' =
H.div { className: "input-group-prepend" }
[
if searchQuery /= ""
then removeButton
else H.span { className: "fa fa-search input-group-text" } []
]
[ if searchQuery' /= ""
then removeButton
else H.span { className: "fa fa-search input-group-text" } []
]
removeButton =
H.button { className: "btn btn-danger"
, on: {click: \e -> onSearch ""}}
[ H.span {className: "fa fa-times"} []]
, on: {click: \e -> T.write "" searchQuery}}
[ H.span {className: "fa fa-times"} []]
fieldInput =
fieldInput searchQuery' =
H.input { className: "form-control"
, defaultValue: searchQuery
, defaultValue: searchQuery'
, name: "search"
, on: { input: onSearch <<< R.unsafeEventValue }
, on: { input: \e -> T.write (R.unsafeEventValue e) searchQuery }
, placeholder: "Search"
, type: "value"
}
......
......@@ -1177,11 +1177,10 @@ chartsAfterSync :: forall props discard.
| props
}
-> T.Box (Maybe GAT.Reductor)
-> Int
-> T.Box T2.Reload
-> discard
-> Aff Unit
chartsAfterSync path' tasks nodeId reloadForest _ = do
chartsAfterSync path'@{ nodeId } tasks reloadForest _ = do
task <- postNgramsChartsAsync path'
liftEffect $ do
log2 "[chartsAfterSync] Synchronize task" task
......
......@@ -88,6 +88,6 @@ useCachedAPILoaderEffect { cacheEndpoint
if version == cacheReal then
pure vr'
else
throwError $ error $ "Fetched clean cache but hashes don't match"
throwError $ error $ "Fetched clean cache but hashes don't match: " <> show version <> " != " <> show cacheReal
liftEffect $ do
setState $ const $ Just $ handleResponse val
......@@ -19,8 +19,8 @@ import Gargantext.Prelude
import Gargantext.Components.NgramsTable.Loader (clearCache)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types as CT
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Table as T
import Gargantext.Components.Table.Types as T
import Gargantext.Components.Table as TT
import Gargantext.Components.Table.Types as TT
import Gargantext.Ends (url, Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..))
......@@ -73,13 +73,15 @@ annuaireLayoutWithKey props = R.createElement annuaireLayoutWithKeyCpt props []
annuaireLayoutWithKeyCpt :: R.Component KeyLayoutProps
annuaireLayoutWithKeyCpt = here.component "annuaireLayoutWithKey" cpt where
cpt { frontends, nodeId, session } _ = do
path <- R.useState' nodeId
useLoader (fst path) (getAnnuaireInfo session) $
path <- T.useBox nodeId
path' <- T.useLive T.unequal path
useLoader path' (getAnnuaireInfo session) $
\info -> annuaire { frontends, info, path, session }
type AnnuaireProps =
( session :: Session
, path :: R.State Int
, path :: T.Box Int
, info :: AnnuaireInfo
, frontends :: Frontends
)
......@@ -93,7 +95,9 @@ annuaireCpt :: R.Component AnnuaireProps
annuaireCpt = here.component "annuaire" cpt
where
cpt {session, path, info: info@(AnnuaireInfo {name, date: date'}), frontends} _ = do
pagePath <- R.useState' $ initialPagePath (fst path)
path' <- T.useLive T.unequal path
pagePath <- T.useBox $ initialPagePath path'
cacheState <- T.useBox NT.CacheOff
cacheState' <- T.useLive T.unequal cacheState
......@@ -101,7 +105,7 @@ annuaireCpt = here.component "annuaire" cpt
T.listen (\_ -> launchAff_ $ clearCache unit) cacheState
pure $ R.fragment
[ T.tableHeaderLayout
[ TT.tableHeaderLayout
{ cacheState
, date
, desc: name
......@@ -116,15 +120,15 @@ annuaireCpt = here.component "annuaire" cpt
where
date = "Last update: " <> date'
style = {width: "250px", display: "inline-block"}
initialPagePath nodeId = {nodeId, params: T.initialParams}
initialPagePath nodeId = {nodeId, params: TT.initialParams}
type PagePath = { nodeId :: Int, params :: T.Params }
type PagePath = { nodeId :: Int, params :: TT.Params }
type PageLayoutProps =
( session :: Session
, frontends :: Frontends
, info :: AnnuaireInfo
, pagePath :: R.State PagePath
, pagePath :: T.Box PagePath
)
pageLayout :: Record PageLayoutProps -> R.Element
......@@ -134,13 +138,15 @@ pageLayoutCpt :: R.Component PageLayoutProps
pageLayoutCpt = here.component "pageLayout" cpt
where
cpt { info, frontends, pagePath, session } _ = do
useLoader (fst pagePath) (loadPage session) $
pagePath' <- T.useLive T.unequal pagePath
useLoader pagePath' (loadPage session) $
\table -> page { session, table, frontends, pagePath }
type PageProps =
( session :: Session
, frontends :: Frontends
, pagePath :: R.State PagePath
, pagePath :: T.Box PagePath
-- , info :: AnnuaireInfo
, table :: TableResult CT.NodeContact
)
......@@ -151,25 +157,28 @@ page props = R.createElement pageCpt props []
pageCpt :: R.Component PageProps
pageCpt = here.component "page" cpt
where
cpt { session, pagePath, frontends
, table: ({count: totalRecords, docs})} _ = do
pure $ T.table { syncResetButton : [ H.div {} [] ]
, rows, params, container
, colNames, totalRecords
, wrapColElts
}
cpt { frontends
, pagePath
, session
, table: ({count: totalRecords, docs}) } _ = do
pagePath' <- T.useLive T.unequal pagePath
params <- T.useFocused (_.params) (\a b -> b { params = a }) pagePath
pure $ TT.table { colNames
, container
, params
, rows: rows pagePath'
, syncResetButton : [ H.div {} [] ]
, totalRecords
, wrapColElts
}
where
path = fst pagePath
rows = row <$> Seq.fromFoldable docs
row contact = { row: contactCells { annuaireId, frontends, contact, session }
, delete: false } where
annuaireId = (fst pagePath).nodeId
container = T.defaultContainer { title: "Annuaire" } -- TODO
colNames = T.ColumnName <$> [ "", "First Name", "Last Name", "Company", "Role"]
rows pagePath' = (row pagePath') <$> Seq.fromFoldable docs
row pagePath'@{ nodeId } contact = { row: contactCells { annuaireId: nodeId, frontends, contact, session }
, delete: false }
container = TT.defaultContainer { title: "Annuaire" } -- TODO
colNames = TT.ColumnName <$> [ "", "First Name", "Last Name", "Company", "Role"]
wrapColElts = const identity
setParams f = snd pagePath $ \pp@{params: ps} ->
pp {params = f ps}
params = (fst pagePath).params /\ setParams
type AnnuaireId = Int
......@@ -188,7 +197,7 @@ contactCellsCpt = here.component "contactCells" cpt where
cpt { annuaireId, frontends, session
, contact: CT.NodeContact
{ id, hyperdata: CT.HyperdataContact { who : Nothing }}} _ =
pure $ T.makeRow
pure $ TT.makeRow
[ H.text ""
, H.span {} [ H.text "Name" ]
--, H.a { href, target: "blank" } [ H.text $ fromMaybe "name" contact.title ]
......@@ -202,7 +211,7 @@ contactCellsCpt = here.component "contactCells" cpt where
{ id, hyperdata: CT.HyperdataContact
{ who: Just (CT.ContactWho { firstName, lastName })
, ou: ou }}} _ = do
pure $ T.makeRow [
pure $ TT.makeRow [
H.text ""
, H.a { target: "_blank", href: contactUrl annuaireId id }
[ H.text $ fromMaybe "First Name" firstName ]
......
......@@ -112,17 +112,20 @@ ngramsView props = R.createElement ngramsViewCpt props []
ngramsViewCpt :: R.Component NgramsViewTabsProps
ngramsViewCpt = here.component "ngramsView" cpt where
cpt props@{ defaultListId, mode, nodeId, session } _ = do
path <- R.useState' $
path <- T.useBox $
NTC.initialPageParams session nodeId
[ defaultListId ] (TabDocument TabDocs)
pure $ NT.mainNgramsTable (props' path) [] where
most = RX.pick props :: Record NTCommon
props' path =
Record.merge most
{ tabType: TabPairing (TabNgramType $ modeTabType mode)
, tabNgramType: modeTabType' mode
, withAutoUpdate: false
, afterSync, path } where
{ afterSync
, path
, tabType: TabPairing (TabNgramType $ modeTabType mode)
, tabNgramType: modeTabType' mode
, withAutoUpdate: false }
where
afterSync :: Unit -> Aff Unit
afterSync _ = pure unit
......
......@@ -157,7 +157,7 @@ ngramsViewCpt = here.component "ngramsView" cpt
, session
, sidePanelTriggers
, reloadForest } _ = do
path <- R.useState' $ NTC.initialPageParams session nodeId [defaultListId] (TabDocument TabDocs)
path <- T.useBox $ NTC.initialPageParams session nodeId [defaultListId] (TabDocument TabDocs)
pure $ NT.mainNgramsTable {
reloadRoot
......
......@@ -103,7 +103,7 @@ handleResponse (HashedResponse { value: ChartMetrics ms }) = ms."data"
mkRequest :: Session -> ReloadPath -> GUC.Request
mkRequest session (_ /\ path@{ corpusId, limit, listId, tabType }) = GUC.makeGetRequest session $ chartUrl path
pie :: Record Props -> R.Element
pie :: R2.Leaf Props
pie props = R.createElement pieCpt props []
pieCpt :: R.Component Props
......
......@@ -77,15 +77,15 @@ ngramsViewCpt = here.component "ngramsView" cpt where
, session
, sidePanelTriggers
, tasks } _ = do
chartType <- R.useState' Histo
chartsReload <- T.useBox T2.newReload
path <- R.useState' $ NTC.initialPageParams props.session initialPath.corpusId [initialPath.listId] initialPath.tabType
let listId' = fromMaybe defaultListId $ A.head (fst path).listIds
chartsReload' <- T.useLive T.unequal chartsReload
path <- T.useBox $ NTC.initialPageParams props.session initialPath.corpusId [initialPath.listId] initialPath.tabType
{ listIds, nodeId, params, tabType } <- T.useLive T.unequal path
let path' = {
corpusId: (fst path).nodeId
, limit: (fst path).params.limit
, listId: listId'
, tabType: (fst path).tabType
corpusId: nodeId
, limit: params.limit
, listId: fromMaybe defaultListId $ A.head listIds
, tabType: tabType
}
let chartParams = {
corpusId: path'.corpusId
......@@ -95,7 +95,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
}
pure $ R.fragment
( charts chartParams tabNgramType chartType chartsReload
( charts chartParams tabNgramType
<> [ NT.mainNgramsTable { afterSync: afterSync chartsReload
, cacheState
, defaultListId
......@@ -133,7 +133,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
, tabType
}
charts params CTabTerms (chartType /\ setChartType) _ = [
charts params CTabTerms = [
H.div {className: "row"}
[ H.div {className: "col-12 d-flex justify-content-center"}
[ H.img { src: "images/Gargantextuel-212x300.jpg"
......@@ -163,7 +163,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
, getChartFunction chartType $ { path: params, session }
-}
]
charts params _ _ _ = [ chart params mode ]
charts params _ = [ chart params mode ]
chart path Authors = pie { path, session }
chart path Institutes = tree { path, session }
......
......@@ -3,8 +3,6 @@ module Gargantext.Components.Table where
import Data.Array as A
import Data.Maybe (Maybe(..))
import Data.Sequence as Seq
import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -116,15 +114,23 @@ table props = R.createElement tableCpt props []
tableCpt :: R.Component Props
tableCpt = here.component "table" cpt
where
cpt {container, syncResetButton, colNames, wrapColElts, totalRecords, rows, params} _ = do
cpt { colNames
, container
, params
, rows
, syncResetButton
, totalRecords
, wrapColElts } _ = do
params' <- T.useLive T.unequal params
let
state = paramsState $ fst params
state = paramsState params'
ps = pageSizes2Int state.pageSize
totalPages = (totalRecords / ps) + min 1 (totalRecords `mod` ps)
colHeader :: ColumnName -> R.Element
colHeader c = H.th {scope: "col"} [ H.b {} cs ]
where
lnk mc = effectLink $ snd params $ _ { orderBy = mc }
lnk mc = effectLink $ void $ T.modify (_ { orderBy = mc }) params
cs :: Array R.Element
cs =
wrapColElts c $
......@@ -136,7 +142,7 @@ tableCpt = here.component "table" cpt
{ syncResetButton
, pageSizeControl: sizeDD { params }
, pageSizeDescription: textDescription state.page state.pageSize totalRecords
, paginationLinks: pagination params totalPages
, paginationLinks: pagination { params, totalPages }
, tableBody: map _.row $ A.fromFoldable rows
, tableHead: H.tr {} (colHeader <$> colNames)
}
......@@ -186,7 +192,7 @@ graphContainer {title} props =
type SizeDDProps =
(
params :: R.State Params
params :: T.Box Params
)
sizeDD :: Record SizeDDProps -> R.Element
......@@ -195,16 +201,18 @@ sizeDD p = R.createElement sizeDDCpt p []
sizeDDCpt :: R.Component SizeDDProps
sizeDDCpt = here.component "sizeDD" cpt
where
cpt {params: params /\ setParams} _ = do
cpt { params } _ = do
params' <- T.useLive T.unequal params
let { pageSize } = paramsState params'
pure $ H.span {} [
R2.select { className, defaultValue: show pageSize, on: {change} } sizes
]
where
{pageSize} = paramsState params
className = "form-control"
change e = do
let ps = string2PageSize $ R.unsafeEventValue e
setParams $ \p -> stateParams $ (paramsState p) { pageSize = ps }
T.modify (\p -> stateParams $ (paramsState p) { pageSize = ps }) params
sizes = map option pageSizes
option size = H.option {value} [H.text value]
where value = show size
......@@ -218,61 +226,72 @@ textDescription currPage pageSize totalRecords =
end = if end' > totalRecords then totalRecords else end'
msg = "Showing " <> show start <> " to " <> show end <> " of " <> show totalRecords
changePage :: Page -> R.State Params -> Effect Unit
changePage page (_ /\ setParams) =
setParams $ \p -> stateParams $ (paramsState p) { page = page }
pagination :: R.State Params -> Int -> R.Element
pagination p@(params /\ setParams) tp =
H.span {} $
[ H.text " ", prev, first, ldots]
<>
lnums
<>
[H.b {} [H.text $ " " <> show page <> " "]]
<>
rnums
<>
[ rdots, last, next ]
where
{page} = paramsState params
prev = if page == 1 then
H.text " Prev. "
else
changePageLink (page - 1) "Prev."
next = if page == tp then
H.text " Next "
else
changePageLink (page + 1) "Next"
first = if page == 1 then
H.text ""
else
changePageLink' 1
last = if page == tp then
H.text ""
else
changePageLink' tp
ldots = if page >= 5 then
H.text " ... "
changePage :: Page -> T.Box Params -> Effect Unit
changePage page params =
void $ T.modify (\p -> stateParams $ (paramsState p) { page = page }) params
type PaginationProps =
( params :: T.Box Params
, totalPages :: Int )
pagination :: R2.Leaf PaginationProps
pagination props = R.createElement paginationCpt props []
paginationCpt :: R.Component PaginationProps
paginationCpt = here.component "pagination" cpt
where
cpt { params, totalPages } _ = do
params' <- T.useLive T.unequal params
let { page } = paramsState params'
prev = if page == 1 then
H.text " Prev. "
else
H.text ""
rdots = if page + 3 < tp then
H.text " ... "
changePageLink (page - 1) "Prev."
next = if page == totalPages then
H.text " Next "
else
H.text ""
lnums = map changePageLink' $ A.filter (1 < _) [page - 2, page - 1]
rnums = map changePageLink' $ A.filter (tp > _) [page + 1, page + 2]
changePageLink :: Int -> String -> R.Element
changePageLink i s =
H.span {}
[ H.text " "
, effectLink (changePage i p) s
, H.text " "
]
changePageLink (page + 1) "Next"
first = if page == 1 then
H.text ""
else
changePageLink' 1
last = if page == totalPages then
H.text ""
else
changePageLink' totalPages
ldots = if page >= 5 then
H.text " ... "
else
H.text ""
rdots = if page + 3 < totalPages then
H.text " ... "
else
H.text ""
lnums = map changePageLink' $ A.filter (1 < _) [page - 2, page - 1]
rnums = map changePageLink' $ A.filter (totalPages > _) [page + 1, page + 2]
pure $ H.span {} $
[ H.text " ", prev, first, ldots]
<>
lnums
<>
[H.b {} [H.text $ " " <> show page <> " "]]
<>
rnums
<>
[ rdots, last, next ]
where
changePageLink :: Int -> String -> R.Element
changePageLink i s =
H.span {}
[ H.text " "
, effectLink (changePage i params) s
, H.text " "
]
changePageLink' :: Int -> R.Element
changePageLink' i = changePageLink i (show i)
changePageLink' :: Int -> R.Element
changePageLink' i = changePageLink i (show i)
data PageSizes = PS10 | PS20 | PS50 | PS100 | PS200
......
module Gargantext.Components.Table.Types where
import Prelude (class Eq, class Show, (<>))
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe)
import Data.Sequence as Seq
import Reactix as R
import Toestand as T
import Prelude (class Eq, class Show, (<>))
import Gargantext.Components.Search (SearchType)
import Data.Generic.Rep (class Generic)
type Params = { limit :: Int
, offset :: Int
......@@ -37,7 +40,7 @@ type Props =
( syncResetButton :: Array R.Element
, colNames :: Array ColumnName
, container :: Record TableContainerProps -> R.Element
, params :: R.State Params
, params :: T.Box Params
, rows :: Rows
, totalRecords :: Int
, wrapColElts :: ColumnName -> Array R.Element -> Array R.Element
......
......@@ -129,6 +129,6 @@ useCachedAPILoaderEffect { cacheEndpoint
if h == cacheReal then
pure hr'
else
throwError $ error $ "Fetched clean cache but hashes don't match"
throwError $ error $ "Fetched clean cache but hashes don't match: " <> h <> " != " <> cacheReal
liftEffect $ do
setState $ const $ Just $ handleResponse val
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