Basic support for orderBy in Table and corpus docs tab

parent b1aa2fd1
......@@ -19,11 +19,22 @@ type Rows = Array { row :: Array ReactElement
, delete :: Boolean
}
type LoadRows = { offset :: Int, limit :: Int } -> Aff Rows
type OrderBy = Maybe (OrderByDirection ColumnName)
type LoadRows = { offset :: Int, limit :: Int, orderBy :: OrderBy } -> Aff Rows
newtype ColumnName = ColumnName String
derive instance eqColumnName :: Eq ColumnName
columnName :: ColumnName -> String
columnName (ColumnName c) = c
data OrderByDirection a = ASC a | DESC a
type Props' =
( title :: String
, colNames :: Array String
, colNames :: Array ColumnName
, totalRecords :: Int
, loadRows :: LoadRows
)
......@@ -34,6 +45,7 @@ type State =
{ rows :: Maybe Rows
, currentPage :: Int
, pageSize :: PageSizes
, orderBy :: OrderBy
--, tree :: FTree
}
......@@ -42,12 +54,14 @@ initialState =
{ rows : Nothing
, currentPage : 1
, pageSize : PS10
, orderBy : Nothing
--, tree : exampleTree
}
data Action
= ChangePageSize PageSizes
| ChangePage Int
| ChangeOrderBy OrderBy
type ChangePageAction = Int -> Effect Unit
......@@ -105,10 +119,26 @@ tableSpec = simpleSpec performAction render
modifyStateAndReload $ changePageSize ps
performAction (ChangePage p) =
modifyStateAndReload $ _ { currentPage = p }
performAction (ChangeOrderBy mc) =
modifyStateAndReload $ _ { orderBy = mc }
renderColHeader :: (OrderBy -> Effect Unit)
-> OrderBy
-> ColumnName -> ReactElement
renderColHeader changeOrderBy currentOrderBy c =
th [scope "col"] [ b' cs ]
where
lnk mc = effectLink (changeOrderBy mc)
cs :: Array ReactElement
cs =
case currentOrderBy of
Just (ASC d) | c == d -> [lnk (Just (DESC c)) "ASC ", lnk Nothing (columnName c)]
Just (DESC d) | c == d -> [lnk (Just (ASC c)) "DESC ", lnk Nothing (columnName c)]
_ -> [lnk (Just (ASC c)) (columnName c)]
render :: Render State Props Action
render dispatch {title, colNames, totalRecords}
{pageSize, currentPage, rows} _ =
{pageSize, currentPage, orderBy, rows} _ =
let
ps = pageSizes2Int pageSize
totalPages = (totalRecords / ps) + min 1 (totalRecords `mod` ps)
......@@ -121,7 +151,7 @@ tableSpec = simpleSpec performAction render
]
, table [ className "table"]
[ thead [className "thead-dark"]
[tr [] ((\colName -> th [scope "col"] [ b' [text colName]]) <$> colNames)]
[tr [] (renderColHeader (dispatch <<< ChangeOrderBy) orderBy <$> colNames)]
, tbody [] $ map (tr [] <<< map (\c -> td [] [c]) <<< _.row)
(maybe [] identity rows)
-- TODO display a loading spinner when rows == Nothing
......@@ -130,10 +160,10 @@ tableSpec = simpleSpec performAction render
]
loadAndSetRows :: {loadRows :: LoadRows} -> State -> StateCoTransformer State Unit
loadAndSetRows {loadRows} {pageSize, currentPage} = do
loadAndSetRows {loadRows} {pageSize, currentPage, orderBy} = do
let limit = pageSizes2Int pageSize
offset = limit * (currentPage - 1)
rows <- lift $ loadRows {offset, limit}
rows <- lift $ loadRows {offset, limit, orderBy}
void $ modifyState (_ { rows = Just rows })
tableClass :: ReactClass {children :: Children | Props'}
......@@ -171,6 +201,12 @@ textDescription currPage pageSize totalRecords
end' = currPage * pageSizes2Int pageSize
end = if end' > totalRecords then totalRecords else end'
effectLink :: Effect Unit -> String -> ReactElement
effectLink eff msg =
a [ href "javascript:void()"
, onClick (const eff)
] [text msg]
pagination :: ChangePageAction -> Int -> Int -> ReactElement
pagination changePage tp cp
= span [] $
......@@ -186,44 +222,20 @@ pagination changePage tp cp
where
prev = if cp == 1 then
text " Previous "
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> changePage $ cp - 1)
] [text "Previous"]
, text " "
]
else
changePageLink (cp - 1) "Previous"
next = if cp == tp then
text " Next "
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> changePage $ cp + 1)
] [text "Next"]
, text " "
]
else
changePageLink (cp + 1) "Next"
first = if cp == 1 then
text ""
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> changePage 1)
] [text "1"]
, text " "
]
else
changePageLink' 1
last = if cp == tp then
text ""
else
span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> changePage tp)
] [text $ show tp]
, text " "
]
changePageLink' tp
ldots = if cp >= 5 then
text " ... "
else
......@@ -232,18 +244,18 @@ pagination changePage tp cp
text " ... "
else
text ""
lnums = map (\i -> fnmid changePage i) $ filter (1 < _) [cp - 2, cp - 1]
rnums = map (\i -> fnmid changePage i) $ filter (tp > _) [cp + 1, cp + 2]
lnums = map changePageLink' $ filter (1 < _) [cp - 2, cp - 1]
rnums = map changePageLink' $ filter (tp > _) [cp + 1, cp + 2]
fnmid :: ChangePageAction -> Int -> ReactElement
fnmid changePage i
= span []
[ text " "
, a [ href "javascript:void()"
, onClick (\e -> changePage i)
] [text $ show i]
, text " "
]
changePageLink :: Int -> String -> ReactElement
changePageLink i s = span []
[ text " "
, effectLink (changePage i) s
, text " "
]
changePageLink' :: Int -> ReactElement
changePageLink' i = changePageLink i (show i)
data PageSizes = PS10 | PS20 | PS50 | PS100
......
......@@ -11,9 +11,11 @@ module Gargantext.Config where
import Prelude
import Data.Argonaut (class DecodeJson, decodeJson)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Map (Map)
import Data.Map as DM
import Data.Maybe (maybe)
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..))
endConfig :: EndConfig
......@@ -98,7 +100,7 @@ endPathUrl Back c nt i = pathUrl c.back nt i
endPathUrl Front c nt i = pathUrl c.front nt i
pathUrl :: Config -> NodeType -> Id -> UrlPath
pathUrl c nt@(Tab _ _ _) i = pathUrl c Node i <> "/" <> show nt
pathUrl c nt@(Tab _ _ _ _) i = pathUrl c Node i <> "/" <> show nt
pathUrl c nt i = c.prePath <> urlConfig nt <> "/" <> show i
------------------------------------------------------------
toUrl :: End -> NodeType -> Id -> Url
......@@ -110,7 +112,7 @@ toUrl e nt i = doUrl base path params
------------------------------------------------------------
data NodeType = NodeUser
| Annuaire
| Tab TabType Offset Limit
| Tab TabType Offset Limit (Maybe OrderBy)
| Corpus
| CorpusV3
| Dashboard
......@@ -126,6 +128,14 @@ type Id = Int
type Limit = Int
type Offset = Int
data OrderBy = DateAsc | DateDesc
| TitleAsc | TitleDesc
| FavDesc | FavAsc
derive instance genericOrderBy :: Generic OrderBy _
instance showOrderBy :: Show OrderBy where
show = genericShow
------------------------------------------------------------
data ApiVersion = V10 | V11
......@@ -146,7 +156,7 @@ instance showTabType :: Show TabType where
------------------------------------------------------------
urlConfig :: NodeType -> Url
urlConfig Annuaire = show Annuaire
urlConfig nt@(Tab _ _ _) = show nt
urlConfig nt@(Tab _ _ _ _) = show nt
urlConfig Corpus = show Corpus
urlConfig CorpusV3 = show CorpusV3
urlConfig Dashboard = show Dashboard
......@@ -172,13 +182,16 @@ instance showNodeType :: Show NodeType where
show Node = "node"
show NodeUser = "user"
show Tree = "tree"
show (Tab t o l) = "table?view=" <> show t <> "&offset=" <> show o <> "&limit=" <> show l <> "&order=DateAsc"
show (Tab t o l s) = "table?view=" <> show t <> "&offset=" <> show o
<> "&limit=" <> show l <> os
where
os = maybe "" (\x -> "&order=" <> show x) s
-- | TODO : where is the Read Class ?
-- instance readNodeType :: Read NodeType where
readNodeType :: String -> NodeType
readNodeType "NodeAnnuaire" = Annuaire
readNodeType "Tab" = (Tab TabDocs 0 0)
readNodeType "Tab" = (Tab TabDocs 0 0 Nothing)
readNodeType "NodeDashboard" = Dashboard
readNodeType "Document" = Url_Document
readNodeType "NodeFolder" = Folder
......
......@@ -94,6 +94,7 @@ loadedAnnuaireSpec = simpleSpec defaultPerformAction render
{ loadRows
, title: "title" -- TODO
, colNames:
Table.ColumnName <$>
[ ""
, "Name"
, "Role"
......@@ -105,7 +106,7 @@ loadedAnnuaireSpec = simpleSpec defaultPerformAction render
]
where
annuaireId = path
loadRows {offset, limit} = do -- TODO use offset and limit
loadRows {offset, limit, orderBy} = do -- TODO use offset, limit, orderBy
(AnnuaireTable {annuaireTable: rows}) <- getTable annuaireId
pure $ (\c -> {row: renderContactCells c, delete: false}) <$> rows
......@@ -168,7 +169,7 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
pure $ AnnuaireTable { annuaireTable : rows}
------------------------------------------------------------------------
getTable :: Int -> Aff AnnuaireTable
getTable id = get $ toUrl Back (Tab TabDocs 0 10) id
getTable id = get $ toUrl Back (Tab TabDocs 0 10 Nothing) id
getAnnuaireInfo :: Int -> Aff AnnuaireInfo
getAnnuaireInfo id = get $ toUrl Back Node id
......
......@@ -13,7 +13,7 @@ import React.DOM.Props (_type, className, href)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (NodeType(..), TabType(..), toUrl, End(..))
import Gargantext.Config (NodeType(..), TabType(..), toUrl, End(..), OrderBy(..))
import Gargantext.Config.REST (get, post)
import Gargantext.Utils.DecodeMaybe ((.|))
import Gargantext.Components.Charts.Options.ECharts (chart)
......@@ -115,7 +115,7 @@ layoutDocview :: Spec {} Props Void
layoutDocview = simpleSpec absurd render
where
render :: Render {} Props Void
render dispatch {path, loaded} _ _ =
render dispatch {path: nodeId, loaded} _ _ =
[ div [className "container1"]
[ div [className "row"]
[ chart globalPublis
......@@ -127,6 +127,7 @@ layoutDocview = simpleSpec absurd render
{ loadRows
, title: "Documents"
, colNames:
T.ColumnName <$>
[ ""
, "Date"
, "Title"
......@@ -145,9 +146,9 @@ layoutDocview = simpleSpec absurd render
]
]
where
loadRows {offset, limit} = do
loadRows {offset, limit, orderBy} = do
_ <- logs "loading documents page"
res <- loadPage {nodeId: path,offset,limit}
res <- loadPage {nodeId,offset,limit,orderBy}
_ <- logs "OK: loading page documents."
pure $
(\(DocumentsView r) ->
......@@ -167,11 +168,11 @@ layoutDocview = simpleSpec absurd render
mock :: Boolean
mock = false
loadPage :: {nodeId :: Int, limit :: Int, offset :: Int} -> Aff (Array DocumentsView)
loadPage {nodeId, limit, offset} = do
loadPage :: {nodeId :: Int, limit :: Int, offset :: Int, orderBy :: T.OrderBy} -> Aff (Array DocumentsView)
loadPage {nodeId, limit, offset, orderBy} = do
logs "loading documents page: loadPage with Offset and limit"
--res <- get $ toUrl Back (Children Url_Document offset limit) nodeId
res <- get $ toUrl Back (Tab TabDocs offset limit ) nodeId
res <- get $ toUrl Back (Tab TabDocs offset limit (convOrderBy <$> orderBy)) nodeId
let docs = res2corpus <$> res
_ <- logs "Ok: loading page documents"
_ <- logs $ map show docs
......@@ -189,6 +190,12 @@ loadPage {nodeId, limit, offset} = do
, fav : r.favorite
, ngramCount : r.ngramCount
}
convOrderBy (T.ASC (T.ColumnName "Date")) = DateAsc
convOrderBy (T.DESC (T.ColumnName "Date")) = DateDesc
convOrderBy (T.ASC (T.ColumnName "Title")) = TitleAsc
convOrderBy (T.DESC (T.ColumnName "Title")) = TitleDesc
convOrderBy _ = DateAsc -- TODO
---------------------------------------------------------
......
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