Commit 6cf771f9 authored by James Laver's avatar James Laver

Refactor table components to use reactix

parent 6213f074
......@@ -18,12 +18,13 @@ import Data.Tuple.Nested ((/\))
import DOM.Simple.Event as DE
import Effect (Effect)
import Effect.Aff (Aff, launchAff)
import Effect.Uncurried (mkEffectFn1)
import Effect.Class (liftEffect)
import Effect.Uncurried (EffectFn1, mkEffectFn1)
import Reactix as R
import Reactix.DOM.HTML as H
------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType, TabPostQuery(..), toUrl, endConfigStateful, toLink)
import Gargantext.Config (Ends, NodeType(..), OrderBy(..), BackendRoute(..), TabType, TabPostQuery(..), url)
import Gargantext.Config.REST (get, put, post, deleteWithBody, delete)
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Search.Types (Category(..), CategoryQuery(..), favCategory, trashCategory, decodeCategory, putCategories)
......@@ -38,25 +39,25 @@ type NodeID = Int
type TotalRecords = Int
type Props =
{ nodeId :: Int
( nodeId :: Int
, totalRecords :: Int
, chart :: R.Element
, tabType :: TabType
, listId :: Int
, corpusId :: Maybe Int
, showSearch :: Boolean
, ends :: Ends )
-- ^ 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. )
type PageLoaderProps =
{ nodeId :: Int
( nodeId :: Int
, totalRecords :: Int
, tabType :: TabType
, listId :: Int
, corpusId :: Maybe Int
, query :: Query
}
)
type LocalCategories = Map Int Category
type Query = String
......@@ -119,18 +120,19 @@ instance decodeResponse :: DecodeJson Response where
pure $ Response { cid, category: decodeCategory favorite, ngramCount, hyperdata }
docViewSpec :: Props -> R.Element
docViewSpec p = R.createElement el p []
docView :: Record Props -> R.Element
docView p = R.createElement docViewCpt p []
docViewCpt :: R.Component Props
docViewCpt = R.hooksComponent "DocView" cpt
where
el = R.hooksComponent "DocView" cpt
cpt p _children = do
query <- R.useState' ("" :: Query)
tableParams <- R.useState' T.initialParams
pure $ layoutDocview query tableParams p
-- | Main layout of the Documents Tab of a Corpus
layoutDocview :: R.State Query -> R.State T.Params -> Props -> R.Element
layoutDocview :: R.State Query -> R.State T.Params -> Record Props -> R.Element
layoutDocview query tableParams@(params /\ _) p = R.createElement el p []
where
el = R.hooksComponent "LayoutDocView" cpt
......@@ -140,9 +142,13 @@ layoutDocview query tableParams@(params /\ _) p = R.createElement el p []
[ chart
, if showSearch then searchBar query else H.div {} []
, H.div {className: "col-md-12"}
[ pageLoader tableParams {nodeId, totalRecords, tabType, listId, corpusId, query: fst query} ]
[ pageLoader tableParams {nodeId, totalRecords, tabType, listId, corpusId, query: fst query} ] ] ]
onClickTrashAll nodeId = mkEffectFn1 $ \_ -> do
launchAff $ deleteAllDocuments p.ends nodeId
{-, H.div {className: "col-md-1 col-md-offset-11"}
[ pageLoader p.ends tableParams {nodeId, totalRecords, tabType, listId, corpusId, query: fst query} ]
, H.div {className: "col-md-1 col-md-offset-11"}
[ H.button { className: "btn"
, style: {backgroundColor: "peru", color : "white", border : "white"}
, onClick: onClickTrashAll nodeId
......@@ -152,11 +158,6 @@ layoutDocview query tableParams@(params /\ _) p = R.createElement el p []
]
]
-}
]
]
onClickTrashAll nodeId = mkEffectFn1 $ \_ -> do
launchAff $ deleteAllDocuments nodeId
searchBar :: R.State Query -> R.Element
searchBar (query /\ setQuery) = R.createElement el {} []
......@@ -210,12 +211,12 @@ type PageParams = { nodeId :: Int
, query :: Query
, params :: T.Params}
loadPage :: PageParams -> Aff (Array DocumentsView)
loadPage {nodeId, tabType, query, listId, corpusId, params: {limit, offset, orderBy}} = do
loadPage :: Ends -> PageParams -> Aff (Array DocumentsView)
loadPage ends {nodeId, tabType, query, listId, corpusId, params: {limit, offset, orderBy}} = do
logs "loading documents page: loadPage with Offset and limit"
-- res <- get $ toUrl endConfigStateful Back (Tab tabType offset limit (convOrderBy <$> orderBy)) (Just nodeId)
let url = (toUrl endConfigStateful Back Node (Just nodeId)) <> "/table"
res <- post url $ TabPostQuery {
let url2 = (url ends (NodeAPI Node (Just nodeId))) <> "/table"
res <- post url2 $ TabPostQuery {
offset
, limit
, orderBy: convOrderBy orderBy
......@@ -246,8 +247,8 @@ loadPage {nodeId, tabType, query, listId, corpusId, params: {limit, offset, orde
convOrderBy _ = DateAsc -- TODO
renderPage :: R.State T.Params -> PageLoaderProps -> Array DocumentsView -> R.Element
renderPage (tableParams /\ setTableParams) p res = R.createElement el p []
renderPage :: Ends -> R.State T.Params -> Record PageLoaderProps -> Array DocumentsView -> R.Element
renderPage ends (_ /\ setTableParams) p res = R.createElement el p []
where
el = R.hooksComponent "RenderPage" cpt
......@@ -260,61 +261,46 @@ renderPage (tableParams /\ setTableParams) p res = R.createElement el p []
cpt {nodeId, corpusId, listId, totalRecords} _children = do
localCategories <- R.useState' (mempty :: LocalCategories)
pure $ R2.buff $ T.tableEltWithInitialState
(T.paramsState tableParams)
pure $ T.table
{ rows: rows localCategories
-- , setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, tabType, listId, corpusId, params, query})
, setParams: setTableParams <<< const
, container: T.defaultContainer { title: "Documents" }
, colNames:
T.ColumnName <$>
[ "Favorites"
, "Trash"
, "Date"
, "Title"
, "Source"
]
, colNames
, totalRecords
}
where
colNames = T.ColumnName <$> [ "Map", "Stop", "Date", "Title", "Source"]
getCategory (localCategories /\ _) {_id, category} = maybe category identity (localCategories ^. at _id)
rows localCategories = (\(DocumentsView r) ->
let cat = getCategory localCategories r
isDel = Trash == cat in
{ row: map R2.scuff $ [
H.div {}
[ H.a { className: gi cat
, style: trashStyle cat
, on: {click: onClick localCategories Favorite r._id cat}
} []
rows localCategories = row <$> res
where
row (DocumentsView r) =
{ row:
[ H.div {} [ H.a { className, style, on: {click: click Favorite} } [] ]
, H.input { type: "checkbox", checked, on: {click: click Trash} }
-- TODO show date: Year-Month-Day only
, H.div { style } [ R2.showText r.date ]
, H.div { style } [ H.text r.source ]
]
, H.input { type: "checkbox"
, defaultChecked: isDel
, on: {click: onClick localCategories Trash r._id cat}
}
-- TODO show date: Year-Month-Day only
, H.div { style: trashStyle cat } [ H.text (show r.date) ]
, H.a { href: toLink $ (corpusDocument corpusId) listId r._id
, style: trashStyle cat
, target: "_blank"
} [ H.text r.title ]
, H.div { style: trashStyle cat} [ H.text r.source ]
]
, delete: true
}) <$> res
, delete: true }
where
cat = getCategory localCategories r
click cat2 = onClick localCategories cat2 r._id cat
checked = Trash == cat
style = trashStyle cat
className = gi cat
onClick (_ /\ setLocalCategories) catType nid cat = \_-> do
let newCat = if (catType == Favorite) then (favCategory cat) else (trashCategory cat)
setLocalCategories $ insert nid newCat
void $ launchAff $ putCategories nodeId $ CategoryQuery {nodeIds: [nid], category: newCat}
void $ launchAff $ putCategories ends nodeId $ CategoryQuery {nodeIds: [nid], category: newCat}
pageLoader :: R.State T.Params -> PageLoaderProps -> R.Element
pageLoader tableParams@(pageParams /\ _) p = R.createElement el p []
pageLoader :: Ends -> R.State T.Params -> Record PageLoaderProps -> R.Element
pageLoader ends tableParams@(pageParams /\ _) p = R.createElement el p []
where
el = R.hooksComponent "PageLoader" cpt
cpt p@{nodeId, listId, corpusId, tabType, query} _children = do
useLoader {nodeId, listId, corpusId, tabType, query, params: pageParams} loadPage $ \{loaded} ->
renderPage tableParams p loaded
useLoader {nodeId, listId, corpusId, tabType, query, params: pageParams} (loadPage ends) $
\loaded -> renderPage ends tableParams p loaded
---------------------------------------------------------
sampleData' :: DocumentsView
......@@ -358,7 +344,6 @@ searchResults :: SearchQuery -> Aff Int
searchResults squery = post "http://localhost:8008/count" unit
-- TODO
newtype CategoryQuery = CategoryQuery {
nodeIds :: Array Int
, category :: Category
......@@ -376,11 +361,11 @@ categoryUrl nodeId = toUrl endConfigStateful Back Node (Just nodeId) <> "/catego
putCategories :: Int -> CategoryQuery -> Aff (Array Int)
putCategories nodeId = put $ categoryUrl nodeId
documentsUrl :: Int -> String
documentsUrl nodeId = toUrl endConfigStateful Back Node (Just nodeId) <> "/documents"
documentsUrl :: Ends -> Int -> String
documentsUrl ends nodeId = url ends (NodeAPI Node (Just nodeId)) <> "/documents"
deleteAllDocuments :: Int -> Aff (Array Int)
deleteAllDocuments nodeId = delete $ documentsUrl nodeId
deleteAllDocuments :: Ends -> Int -> Aff (Array Int)
deleteAllDocuments ends = delete <<< documentsUrl ends
-- TODO: not optimal but Data.Set lacks some function (Set.alter)
toggleSet :: forall a. Ord a => a -> Set a -> Set a
......
-- TODO: this module should replace DocsTable
-- However the fix for favorites in commit 91cb6bd9906e128b3129b1db01ef6ef5ae13f7f8
-- However the fix for favorites in commit 91cb6bd9906e128b3129b1db01ef6ef5ae13f7f8
-- has not been ported to this module yet.
module Gargantext.Components.FacetsTable where
......@@ -12,24 +12,25 @@ import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..))
import Data.Set (Set)
import Data.Set as Set
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff)
import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect)
import React as React
import React (ReactClass, ReactElement, Children)
import Reactix as R
import Reactix.DOM.HTML as H
------------------------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType, toUrl, endConfigStateful)
import Gargantext.Config (Ends, NodeType(..), OrderBy(..), NodePath(..), BackendRoute(..), TabType, url)
import Gargantext.Config.REST (put, post, deleteWithBody)
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Search.Types (Category(..), CategoryQuery(..), favCategory, decodeCategory, putCategories)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Search.Types (Category(..), CategoryQuery(..), favCategory, trashCategory, decodeCategory, putCategories)
import Gargantext.Components.Table as T
import Gargantext.Router as Router
import Gargantext.Utils (toggleSet)
import Gargantext.Utils.DecodeMaybe ((.|))
import React.DOM (a, br', button, div, i, input, p, text, span)
import React.DOM.Props (_type, className, href, onClick, style, checked, target)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState_, simpleSpec, hideState)
import Gargantext.Utils.Reactix as R2
------------------------------------------------------------------------
type NodeID = Int
......@@ -40,9 +41,7 @@ type TotalRecords = Int
-- This searches for documents with "machine learning" or "artificial intelligence"
type TextQuery = Array (Array String)
newtype SearchQuery = SearchQuery
{ query :: TextQuery
}
newtype SearchQuery = SearchQuery { query :: TextQuery }
instance encodeJsonSearchQuery :: EncodeJson SearchQuery where
encodeJson (SearchQuery post)
......@@ -58,51 +57,39 @@ instance decodeSearchResults :: DecodeJson SearchResults where
pure $ SearchResults {results}
type Props =
{ nodeId :: Int
( nodeId :: Int
, listId :: Int
, query :: TextQuery
, totalRecords :: Int
, chart :: ReactElement
, container :: T.TableContainerProps -> Array ReactElement
}
type State =
{ documentIdsToDelete :: Set Int
, documentIdsDeleted :: Set Int
}
, chart :: R.Element
, container :: Record T.TableContainerProps -> R.Element
, ends :: Ends
)
initialState :: State
initialState =
{ documentIdsToDelete: mempty
, documentIdsDeleted: mempty
}
-- | Tracks the ids of documents to delete and that have been deleted
type Deletions = { pending :: Set Int, deleted :: Set Int }
data Action
= MarkCategory Category (Array Int)
| ToggleDocumentToDelete Int
| TrashDocuments
initialDeletions :: Deletions
initialDeletions = { pending: mempty, deleted: mempty }
newtype Pair = Pair
{ id :: Int
, label :: String
}
newtype Pair = Pair { id :: Int, label :: String }
derive instance genericPair :: Generic Pair _
instance showPair :: Show Pair where
show = genericShow
newtype DocumentsView
= DocumentsView
{ id :: Int
, date :: String
, title :: String
, source :: String
, score :: Int
, pairs :: Array Pair
, delete :: Boolean
, category :: Category
}
newtype DocumentsView =
DocumentsView
{ id :: Int
, date :: String
, title :: String
, source :: String
, score :: Int
, pairs :: Array Pair
, delete :: Boolean
, category :: Category
}
derive instance genericDocumentsView :: Generic DocumentsView _
......@@ -120,7 +107,6 @@ newtype Response = Response
-- , pairs :: Array Pair
}
newtype Hyperdata = Hyperdata
{ title :: String
, source :: String
......@@ -133,7 +119,6 @@ newtype Hyperdata = Hyperdata
-- source <- obj .: "source"
-- pure $ Hyperdata { title,source }
instance decodePair :: DecodeJson Pair where
decodeJson json = do
obj <- decodeJson json
......@@ -172,252 +157,180 @@ instance decodeResponse :: DecodeJson Response where
let ngramCount = 1
pure $ Response { id, created, hyperdata, category: decodeCategory favorite, ngramCount}
-- | Filter
-- TODO: unused
filterSpec :: forall state props action. Spec state props action
filterSpec = simpleSpec defaultPerformAction render
where
render d p s c = [] {-[div [ className "col-md-2", style {textAlign : "center", marginLeft : "0px", paddingLeft : "0px"}] [ text " Filter "
, input [className "form-control", placeholder "Filter here"]
]]
-}
docViewSpec :: Spec {} Props Void
docViewSpec = hideState (const initialState) layoutDocviewGraph
-- | Main layout of the Documents Tab of a Corpus
layoutDocview :: Spec State Props Action
layoutDocview = simpleSpec performAction render
docView :: Record Props -> R.Element
docView props = R.createElement docViewCpt props []
docViewCpt :: R.Component Props
docViewCpt = R.hooksComponent "G.C.FacetsTable.DocView" cpt
where
performAction :: PerformAction State Props Action
performAction (MarkCategory category nids) {nodeId} _ =
void $ lift $ putCategories nodeId $ CategoryQuery {nodeIds: nids, category: favCategory category}
--TODO add array of delete rows here
performAction (ToggleDocumentToDelete nid) _ _ =
modifyState_ \state -> state {documentIdsToDelete = toggleSet nid state.documentIdsToDelete}
performAction TrashDocuments {nodeId} {documentIdsToDelete} = do
void $ lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents: Set.toUnfoldable documentIdsToDelete})
modifyState_ \{documentIdsToDelete, documentIdsDeleted} ->
{ documentIdsToDelete: mempty
, documentIdsDeleted: documentIdsDeleted <> documentIdsToDelete
}
render :: Render State Props Action
render dispatch {nodeId, listId, query, totalRecords, chart, container} deletionState _ =
[ {- br'
, div [ style {textAlign : "center"}] [ text " Filter "
, input [className "form-control", style {width : "120px", display : "inline-block"}, placeholder "Filter here"]
]
, p [] [text ""]
, br'
-}
div [className "container1"]
[ div [className "row"]
cpt {ends, nodeId, listId, query, totalRecords, chart, container} _ = do
deletions <- R.useState' initialDeletions
path <- R.useState' $ initialPagePath {nodeId, listId, query, ends}
pure $ H.div { className: "container1" }
[ H.div { className: "row" }
[ chart
, div [className "col-md-12"]
[ pageLoader
{ path: initialPageParams {nodeId, listId, query}
, totalRecords
, deletionState
, dispatch
, container
}
]
, div [className "col-md-12"]
[ button [ style {backgroundColor: "peru", padding : "9px", color : "white", border : "white", float: "right"}
, onClick $ (\_ -> dispatch TrashDocuments)
]
[ i [className "glyphitem glyphicon glyphicon-trash", style {marginRight : "9px"}] []
, text "Trash it !"
]
]
]
]
]
layoutDocviewGraph :: Spec State Props Action
layoutDocviewGraph = simpleSpec performAction render
, H.div { className: "col-md-12" }
[ pageLayout { deletions, totalRecords, container, ends, path } ]
, H.div { className: "col-md-12" }
[ H.button { style: buttonStyle, on: { click: trashClick deletions } }
[ H.i { className: "glyphitem glyphicon glyphicon-trash"
, style: { marginRight : "9px" }} []
, H.text "Delete document!" ] ] ] ]
where
buttonStyle =
{ backgroundColor: "peru", padding: "9px", color: "white"
, border: "white", float: "right" }
trashClick deletions _ = performDeletions ends nodeId deletions
performDeletions :: Ends -> Int -> R.State Deletions -> Effect Unit
performDeletions ends nodeId (deletions /\ setDeletions) =
launchAff_ call *> setDeletions del
where
performAction :: PerformAction State Props Action
performAction (MarkCategory category nids) {nodeId} _ =
void $ lift $ putCategories nodeId $ CategoryQuery {nodeIds: nids, category: favCategory category}
--TODO add array of delete rows here
performAction (ToggleDocumentToDelete nid) _ _ =
modifyState_ \state -> state {documentIdsToDelete = toggleSet nid state.documentIdsToDelete}
performAction TrashDocuments {nodeId} {documentIdsToDelete} = do
void $ lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents: Set.toUnfoldable documentIdsToDelete})
modifyState_ \{documentIdsToDelete, documentIdsDeleted} ->
{ documentIdsToDelete: mempty
, documentIdsDeleted: documentIdsDeleted <> documentIdsToDelete
}
render :: Render State Props Action
render dispatch {nodeId, listId, query, totalRecords, chart, container} deletionState _ =
[ br'
, p [] [text ""]
, br'
, div [className "container-fluid"]
[ div [className "row"]
[ chart
, div [className "col-md-12"]
[ pageLoader
{ path: initialPageParams {nodeId, listId, query}
, totalRecords
, deletionState
, dispatch
, container
}
, button [ style {backgroundColor: "peru", padding : "9px", color : "white", border : "white", float: "right"}
, onClick $ (\_ -> dispatch TrashDocuments)
]
[ i [className "glyphitem glyphicon glyphicon-trash", style {marginRight : "9px"}] []
, text "Trash it !"
]
]
]
]
]
type PageParams = {nodeId :: Int, listId :: Int, query :: TextQuery, params :: T.Params}
initialPageParams :: {nodeId :: Int, listId :: Int, query :: TextQuery} -> PageParams
initialPageParams {nodeId, listId, query} = {nodeId, listId, query, params: T.initialParams}
loadPage :: PageParams -> Aff (Array DocumentsView)
loadPage {nodeId, listId, query, params: {limit, offset, orderBy}} = do
q = {documents: Set.toUnfoldable deletions.pending}
call = deleteDocuments ends nodeId (DeleteDocumentQuery q)
del {pending, deleted} = {pending: mempty, deleted: deleted <> pending}
-- markCategory :: Ends -> NodeID -> _ -> Array NodeID -> Effect Unit
markCategory ends nodeId category nids =
void $ launchAff_ $putCategories ends nodeId (CategoryQuery q)
where -- TODO add array of delete rows here
q = {nodeIds: nids, category: favCategory category}
togglePendingDeletion :: R.State Deletions -> NodeID -> Effect Unit
togglePendingDeletion (_ /\ setDeletions) nid = setDeletions setter
where setter deletions@{pending} = deletions { pending = toggleSet nid pending }
docViewGraph :: Record Props -> R.Element
docViewGraph props = R.createElement docViewCpt props []
docViewGraphCpt :: R.Component Props
docViewGraphCpt = R.hooksComponent "FacetsDocViewGraph" cpt
where
cpt {ends, nodeId, listId, query, totalRecords, chart, container} _ = do
deletions <- R.useState' initialDeletions
let buttonStyle = { backgroundColor: "peru", padding : "9px"
, color : "white", border : "white", float: "right"}
let performClick = \_ -> performDeletions ends nodeId deletions
path <- R.useState' $ initialPagePath { nodeId, listId, query, ends }
pure $ R.fragment
[ H.br {}
, H.p {} [ H.text "" ]
, H.br {}
, H.div { className: "container-fluid" }
[ H.div { className: "row" }
[ chart
, H.div { className: "col-md-12" }
[ pageLayout { totalRecords, deletions, container, ends, path }
, H.button { style: buttonStyle, on: { click: performClick } }
[ H.i { className: "glyphitem glyphicon glyphicon-trash"
, style: { marginRight : "9px" } } []
, H.text "Delete document!" ] ] ] ] ]
type PagePath = {nodeId :: Int, listId :: Int, query :: TextQuery, params :: T.Params, ends :: Ends}
initialPagePath :: {ends :: Ends, nodeId :: Int, listId :: Int, query :: TextQuery} -> PagePath
initialPagePath {ends, nodeId, listId, query} = {ends, nodeId, listId, query, params: T.initialParams}
loadPage :: PagePath -> Aff (Array DocumentsView)
loadPage {ends, nodeId, listId, query, params: {limit, offset, orderBy}} = do
logs "loading documents page: loadPage with Offset and limit"
let url = toUrl endConfigStateful Back (Search { listId, offset, limit, orderBy: convOrderBy <$> orderBy }) (Just nodeId)
SearchResults res <- post url $ SearchQuery {query}
let url2 = url ends $ Search { listId, offset, limit, orderBy: convOrderBy <$> orderBy } (Just nodeId)
SearchResults res <- post url2 $ SearchQuery {query}
pure $ res2corpus <$> res.results
where
res2corpus :: Response -> DocumentsView
res2corpus (Response { id, created: date, ngramCount: score
, hyperdata: Hyperdata {title, source}
, category
}) =
DocumentsView
{ id
, date
, title
, source
, score
, pairs: []
, delete: false
, category
}
res2corpus (Response { id, created: date, ngramCount: score, category
, hyperdata: Hyperdata {title, source} }) =
DocumentsView { id, date, title, source, score, category, pairs: [], delete: false }
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 (T.ASC (T.ColumnName "Source")) = SourceAsc
convOrderBy (T.DESC (T.ColumnName "Source")) = SourceDesc
convOrderBy _ = DateAsc -- TODO
type PageLoaderProps row =
{ path :: PageParams
, totalRecords :: Int
, dispatch :: Action -> Effect Unit
, deletionState :: State
, container :: T.TableContainerProps -> Array ReactElement
| row
}
type PageLayoutProps =
( totalRecords :: Int
, deletions :: R.State Deletions
, container :: Record T.TableContainerProps -> R.Element
, ends :: Ends
, path :: R.State PagePath
)
type PageProps = ( documents :: Array DocumentsView | PageLayoutProps )
renderPage :: forall props path.
Render (Loader.State {nodeId :: Int, listId :: Int, query :: TextQuery | path} (Array DocumentsView))
{ totalRecords :: Int
, dispatch :: Action -> Effect Unit
, deletionState :: State
, container :: T.TableContainerProps -> Array ReactElement
| props
}
(Loader.Action PageParams)
renderPage _ _ {loaded: Nothing} _ = [] -- TODO loading spinner
renderPage loaderDispatch { totalRecords, dispatch, container
, deletionState: {documentIdsToDelete, documentIdsDeleted}}
{currentPath: {nodeId, listId, query}, loaded: Just res} _ =
[ T.tableElt
{ rows
, setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, listId, query, params})
, container
, colNames:
T.ColumnName <$>
[ ""
, "Date"
, "Title"
, "Source"
, "Authors"
, "Delete"
]
, totalRecords
}
]
-- | Loads and renders a page
pageLayout :: Record PageLayoutProps -> R.Element
pageLayout props = R.createElement pageLayoutCpt props []
pageLayoutCpt :: R.Component PageLayoutProps
pageLayoutCpt = R.hooksComponent "G.C.FacetsTable.PageLayout" cpt
where
cpt {totalRecords, deletions, container, ends, path} _ = do
useLoader (fst path) loadPage $ \documents ->
page {totalRecords, deletions, container, ends, path, documents}
page :: Record PageProps -> R.Element
page props = R.createElement pageCpt props []
pageCpt :: R.Component PageProps
pageCpt = R.staticComponent "G.C.FacetsTable.Page" cpt
where
-- TODO: how to interprete other scores?
gi Favorite = "glyphicon glyphicon-star-empty"
gi _ = "glyphicon glyphicon-star"
isChecked id = Set.member id documentIdsToDelete
isDeleted (DocumentsView {id}) = Set.member id documentIdsDeleted
pairUrl (Pair {id,label})
| id > 1 = [a [href (toUrl endConfigStateful Front NodeContact (Just id)), target "blank"] [text label]]
| otherwise = [text label]
comma = span [] [text ", "]
rows = (\(DocumentsView {id,score,title,source,date,pairs,delete,category}) ->
let
strikeIfDeleted
| delete = [style {textDecoration : "line-through"}]
| otherwise = []
in
{ row:
[ div []
[ a [ className $ gi category
, onClick $ const $ dispatch $ MarkCategory category [id]
] []
]
cpt {totalRecords, container, deletions, documents, ends, path: path@({nodeId, listId, query} /\ setPath)} _ = do
T.table { rows, container, colNames, totalRecords, setParams }
where
setParams params = setPath (_ {params = params})
colNames = T.ColumnName <$> [ "", "Date", "Title", "Source", "Authors", "Delete" ]
-- TODO: how to interprete other scores?
gi Favorite = "glyphicon glyphicon-star-empty"
gi _ = "glyphicon glyphicon-star"
isChecked id = Set.member id (fst deletions).pending
isDeleted (DocumentsView {id}) = Set.member id (fst deletions).deleted
pairUrl (Pair {id,label})
| id > 1 = H.a { href, target: "blank" } [ H.text label ]
where href = url ends $ NodePath NodeContact (Just id)
| otherwise = H.text label
comma = H.span {} [ H.text ", " ]
rows = row <$> filter (not <<< isDeleted) documents
where
row (DocumentsView {id,score,title,source,date,pairs,delete,category}) =
{ row:
[ H.div {}
[ H.a { className, on: {click: markClick} } []
-- TODO show date: Year-Month-Day only
, div strikeIfDeleted [text date]
, a (strikeIfDeleted <> [ href $ toLink endConfigStateful $ Router.Document listId id
, target "blank"])
[ text title ]
, div strikeIfDeleted [text source]
, div strikeIfDeleted $ intercalate [comma] $ pairUrl <$> pairs
, input [ _type "checkbox"
, checked (isChecked id)
, onClick $ const $ dispatch $ ToggleDocumentToDelete id]
]
, delete: true
}) <$> filter (not <<< isDeleted) res
pageLoaderClass :: ReactClass (PageLoaderProps (children :: Children))
pageLoaderClass = Loader.createLoaderClass' "PageLoader" loadPage renderPage
pageLoader :: PageLoaderProps () -> ReactElement
pageLoader props = React.createElement pageLoaderClass props []
, maybeStricken [ H.text date ]
, maybeStricken [ H.text source ]
-- , maybeStricken $ intercalate [comma] (pairUrl <$> pairs)
, H.input { type: "checkbox", checked: isChecked id, on: { click: toggleClick } }
] ]
, delete: true }
where
markClick _ = markCategory ends nodeId category [id]
toggleClick _ = togglePendingDeletion deletions id
className = gi category
maybeStricken
| delete = H.div { style: { textDecoration: "line-through" } }
| otherwise = H.div {}
---------------------------------------------------------
newtype DeleteDocumentQuery = DeleteDocumentQuery
{
documents :: Array Int
}
---------------------------------------------------------
newtype DeleteDocumentQuery = DeleteDocumentQuery { documents :: Array Int }
instance encodeJsonDDQuery :: EncodeJson DeleteDocumentQuery where
encodeJson (DeleteDocumentQuery post)
= "documents" := post.documents
~> jsonEmptyObject
encodeJson (DeleteDocumentQuery post) =
"documents" := post.documents ~> jsonEmptyObject
putFavorites :: Int -> FavoriteQuery -> Aff (Array Int)
putFavorites nodeId = put (toUrl endConfigStateful Back Node (Just nodeId) <> "/favorites")
putFavorites :: Ends -> Int -> FavoriteQuery -> Aff (Array Int)
putFavorites ends nodeId = put to
where to = url endst (NodeAPI Node (Just nodeId)) <> "/favorites"
deleteFavorites :: Int -> FavoriteQuery -> Aff (Array Int)
deleteFavorites nodeId = deleteWithBody (toUrl endConfigStateful Back Node (Just nodeId) <> "/favorites")
deleteFavorites nodeId = deleteWithBody to
where to = url ends (NodeAPI Node (Just nodeId)) <> "/favorites"
deleteDocuments :: Int -> DeleteDocumentQuery -> Aff (Array Int)
deleteDocuments nodeId = deleteWithBody (toUrl endConfigStateful Back Node (Just nodeId) <> "/documents")
deleteDocuments :: Ends -> Int -> DeleteDocumentQuery -> Aff (Array Int)
deleteDocuments ends nodeId = deleteWithBody to
where to = url ends (NodeAPI Node (Just nodeId)) <> "/documents"
module Gargantext.Components.NgramsTable
( Action
, MainNgramsTableProps
, initialState
, mainNgramsTableSpec
, ngramsTableClass
, ngramsTableSpec
, termStyle
)
where
module Gargantext.Components.NgramsTable where
import Data.Array as A
import Data.Lens (to, view, (%~), (.~), (^.), (^..))
......@@ -24,7 +15,10 @@ import Data.Monoid.Additive (Additive(..))
import Data.Ord.Down (Down(..))
import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..), snd)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
import React (ReactElement)
import React.DOM (a, button, div, h2, i, input, li, option, p, select, span, table, tbody, text, thead, ul)
import React.DOM.Props (_id, _type, checked, className, name, onChange, onClick, onInput, placeholder, style, value)
......@@ -32,11 +26,11 @@ import React.DOM.Props as DOM
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState_, simpleSpec, createClass)
import Gargantext.Types (TermList(..), readTermList, readTermSize, termLists, termSizes)
import Gargantext.Config (OrderBy(..), TabType, CTabNgramType(..))
import Gargantext.Config (Ends, OrderBy(..), TabType, CTabNgramType(..))
import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.Table as T
import Gargantext.Prelude
import Gargantext.Components.Loader as Loader
import Gargantext.Hooks.Loader (useLoader, useLoader2)
import Gargantext.Components.NgramsTable.Core
import Gargantext.Utils.Reactix as R2
......@@ -52,9 +46,8 @@ type State =
_ngramsChildren = prop (SProxy :: SProxy "ngramsChildren")
initialState :: forall props. { loaded :: VersionedNgramsTable | props }
-> State
initialState {loaded: Versioned {version}} =
initialState :: VersionedNgramsTable -> State
initialState (Versioned {version}) =
{ ngramsTablePatch: mempty
, ngramsVersion: version
, ngramsParent: Nothing
......@@ -78,86 +71,66 @@ data Action
type Dispatch = Action -> Effect Unit
type LoaderAction = Loader.Action PageParams
type LoaderDispatch = LoaderAction -> Effect Unit
tableContainer :: { pageParams :: PageParams
, dispatch :: Dispatch
, loaderDispatch :: LoaderDispatch
, setPath :: R2.Setter PageParams
, ngramsParent :: Maybe NgramsTerm
, ngramsChildren :: Map NgramsTerm Boolean
, ngramsTable :: NgramsTable
}
-> T.TableContainerProps -> Array ReactElement
-> Record T.TableContainerProps -> R.Element
tableContainer { pageParams
, dispatch
, loaderDispatch
, setPath
, ngramsParent
, ngramsChildren
, ngramsTable: ngramsTableCache
} props =
[ div [className "container-fluid"]
[ div [className "jumbotron1"]
[ div [className "row"]
[ div [className "panel panel-default"]
[ div [className "panel-heading"]
[ h2 [className "panel-title", style {textAlign : "center"}]
[ span [className "glyphicon glyphicon-hand-down"] []
, text "Extracted Terms"
]
, div [className "row"]
[
{-div [className "savediv pull-left col-md-2", style { marginTop :"35px"}]
[ button [_id "ImportListOrSaveAll", className "btn btn-warning", style {fontSize : "120%"}]
[ text "Import a Termlist" ]
]
,-}
div [className "col-md-3", style {marginTop : "6px"}]
[ input [ className "form-control "
, name "search", placeholder "Search"
, _type "value"
, value pageParams.searchQuery
, onInput \e -> setSearchQuery (R2.unsafeEventValue e)
]
, div [] (
if A.null props.tableBody && pageParams.searchQuery /= "" then [
button [ className "btn btn-primary"
, onClick $ const $ dispatch $ AddNewNgram pageParams.searchQuery
] [text $ "Add " <> pageParams.searchQuery]
] else []
)
]
, div [className "col-md-2", style {marginTop : "6px"}]
[ li [className " list-group-item"]
[ select [ _id "picklistmenu"
, className "form-control custom-select"
, value (maybe "" show pageParams.termListFilter)
, onChange (\e -> setTermListFilter $ readTermList $ R2.unsafeEventValue e)
] $ map optps1 termLists
]
]
, div [className "col-md-2", style {marginTop : "6px"}]
[ li [className "list-group-item"]
[ select [ _id "picktermtype"
, className "form-control custom-select"
, value (maybe "" show pageParams.termSizeFilter)
, onChange (\e -> setTermSizeFilter $ readTermSize $ R2.unsafeEventValue e)
] $ map optps1 termSizes
]
]
, div [className "col-md-4", style {marginTop : "6px", marginBottom : "1px"}]
[ li [className " list-group-item"] [ props.pageSizeDescription
, props.pageSizeControl
, text " items / "
, props.paginationLinks
]
--, li [className " list-group-item"] [ props.pageSizeControl ]
]
]
H.div {className: "container-fluid"}
[ H.div {className: "jumbotron1"}
[ H.div {className: "row"}
[ H.div {className: "panel panel-default"}
[ H.div {className: "panel-heading"}
[ H.h2 {className: "panel-title", style: {textAlign : "center"}}
[ H.span {className: "glyphicon glyphicon-hand-down"} []
, H.text "Extracted Terms"
]
, div [] (maybe [] (\ngrams ->
, H.div {className: "row"}
[ H.div {className: "col-md-3", style: {marginTop: "6px"}}
[ H.input { className: "form-control"
, name: "search"
, placeholder: "Search"
, type: "value"
, value: pageParams.searchQuery
, on: {input: \e -> setSearchQuery (R2.unsafeEventValue e)}}
, H.div {} (
if A.null props.tableBody && pageParams.searchQuery /= "" then [
H.button { className: "btn btn-primary"
, on: {click: const $ dispatch $ AddNewNgram pageParams.searchQuery}}
[ H.text ("Add " <> pageParams.searchQuery) ]
] else [])]
, H.div {className: "col-md-2", style: {marginTop : "6px"}}
[ H.li {className: " list-group-item"}
[ R2.select { id: "picklistmenu"
, className: "form-control custom-select"
, value: (maybe "" show pageParams.termListFilter)
, on: {change: (\e -> setTermListFilter $ readTermList $ R2.unsafeEventValue e)}}
(map optps1 termLists)]]
, H.div {className: "col-md-2", style: {marginTop : "6px"}}
[ H.li {className: "list-group-item"}
[ R2.select {id: "picktermtype"
, className: "form-control custom-select"
, value: (maybe "" show pageParams.termSizeFilter)
, on: {change: (\e -> setTermSizeFilter $ readTermSize $ R2.unsafeEventValue e)}}
(map optps1 termSizes)]]
, H.div {className: "col-md-4", style: {marginTop : "6px", marginBottom : "1px"}}
[ H.li {className: " list-group-item"}
[ props.pageSizeDescription
, props.pageSizeControl
, H.text " items / "
, props.paginationLinks]]]]
, H.div {}
(maybe [] (\ngrams ->
let
ngramsTable =
ngramsTableCache # at ngrams
......@@ -170,24 +143,17 @@ tableContainer { pageParams
ngramsClick _ = Nothing
ngramsEdit _ = Nothing
in
[ p[] [text $ "Editing " <> ngrams]
, renderNgramsTree { ngramsTable, ngrams, ngramsStyle: [], ngramsClick, ngramsEdit }
, button [className "btn btn-primary", onClick $ const $ dispatch $ AddTermChildren] [text "Save"]
, button [className "btn btn-secondary", onClick $ const $ dispatch $ SetParentResetChildren Nothing] [text "Cancel"]
[ H.p {} [H.text $ "Editing " <> ngrams]
, R2.buff $ renderNgramsTree { ngramsTable, ngrams, ngramsStyle: [], ngramsClick, ngramsEdit }
, H.button {className: "btn btn-primary", on: {click: (const $ dispatch $ AddTermChildren)}} [H.text "Save"]
, H.button {className: "btn btn-secondary", on: {click: (const $ dispatch $ SetParentResetChildren Nothing)}} [H.text "Cancel"]
]) ngramsParent)
, div [ _id "terms_table", className "panel-body" ]
[ table [ className "table able" ]
[ thead [ className "tableHeader"] [props.tableHead]
, tbody [] props.tableBody
]
]
]
]
]
]
]
, H.div {id: "terms_table", className: "panel-body"}
[ H.table {className: "table able"}
[ H.thead {className: "tableHeader"} [props.tableHead]
, H.tbody {} props.tableBody]]]]]]
where
setPageParams f = loaderDispatch $ Loader.SetPath $ f pageParams
setPageParams f = setPath (const $ f pageParams)
setSearchQuery x = setPageParams $ _ { searchQuery = x }
setTermListFilter x = setPageParams $ _ { termListFilter = x }
setTermSizeFilter x = setPageParams $ _ { termSizeFilter = x }
......@@ -196,21 +162,50 @@ toggleMap :: forall a. a -> Maybe a -> Maybe a
toggleMap _ (Just _) = Nothing
toggleMap b Nothing = Just b
ngramsTableSpec :: CTabNgramType -> Spec State LoadedNgramsTableProps Action
ngramsTableSpec ntype = simpleSpec performAction render
data Action'
= SetParentResetChildren' (Maybe NgramsTerm)
| ToggleChild' (Maybe NgramsTerm) NgramsTerm
| Refresh'
performNgramsAction :: State -> Action' -> State
performNgramsAction st (SetParentResetChildren' term) = st
performNgramsAction st (ToggleChild' b c) = st
performNgramsAction st Refresh' = st
useNgramsReducer :: State -> R.Hooks (R.Reducer State Action')
useNgramsReducer init = R.useReducer performNgramsAction identity init
type Props =
( ends :: Ends
, tabNgramType :: CTabNgramType
, path :: R.State PageParams
, versioned :: VersionedNgramsTable )
ngramsTable :: Record Props -> R.Element
ngramsTable props = R.createElement ngramsTableCpt props []
ngramsTableCpt :: R.Component Props
ngramsTableCpt = R.hooksComponent "G.C.NgramsTable.ngramsTable" cpt
where
cpt {versioned} _ = do
state <- useNgramsReducer (initialState versioned)
pure $ R.fragment []
ngramsTableSpec :: Ends -> CTabNgramType -> R2.Setter PageParams -> Spec State (Record LoadedNgramsTableProps) Action
ngramsTableSpec ends ntype setPath = simpleSpec performAction render
where
setParentResetChildren :: Maybe NgramsTerm -> State -> State
setParentResetChildren p = _ { ngramsParent = p, ngramsChildren = mempty }
performAction :: PerformAction State LoadedNgramsTableProps Action
performAction :: PerformAction State (Record LoadedNgramsTableProps) Action
performAction (SetParentResetChildren p) _ _ =
modifyState_ $ setParentResetChildren p
performAction (ToggleChild b c) _ _ =
modifyState_ $ _ngramsChildren <<< at c %~ toggleMap b
performAction Refresh {path: {nodeId, listIds, tabType}} {ngramsVersion} = do
commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: mempty})
commitPatch ends {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: mempty})
performAction (SetTermListItem n pl) {path: {nodeId, listIds, tabType}} {ngramsVersion} =
commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt})
commitPatch ends {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt})
where
pe = NgramsPatch { patch_list: pl, patch_children: mempty }
pt = singletonNgramsTablePatch ntype n pe
......@@ -223,94 +218,87 @@ ngramsTableSpec ntype = simpleSpec performAction render
, ngramsVersion
} = do
modifyState_ $ setParentResetChildren Nothing
commitPatch {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt})
commitPatch ends {nodeId, listIds, tabType} (Versioned {version: ngramsVersion, data: pt})
where
pc = patchSetFromMap ngramsChildren
pe = NgramsPatch { patch_list: mempty, patch_children: pc }
pt = singletonNgramsTablePatch ntype parent pe
performAction (AddNewNgram ngram) {path: {listIds, nodeId, tabType}} {ngramsVersion} =
commitPatch {listIds, nodeId, tabType} (Versioned {version: ngramsVersion, data: pt})
commitPatch ends {listIds, nodeId, tabType} (Versioned {version: ngramsVersion, data: pt})
where
pt = addNewNgram ntype ngram CandidateTerm
render :: Render State LoadedNgramsTableProps Action
render :: Render State (Record LoadedNgramsTableProps) Action
render dispatch { path: pageParams
, loaded: Versioned { data: initTable }
, dispatch: loaderDispatch }
, loaded: Versioned { data: initTable } }
{ ngramsTablePatch, ngramsParent, ngramsChildren }
_reactChildren =
[ autoUpdateElt { duration: 3000
, effect: dispatch Refresh
}
, T.tableElt
{ rows
, setParams
, container: tableContainer {pageParams, loaderDispatch, dispatch, ngramsParent, ngramsChildren, ngramsTable}
, colNames:
T.ColumnName <$>
[ "Map"
, "Stop"
, "Terms"
, "Score (Occurrences)" -- see convOrderBy
]
, totalRecords: 47361 -- TODO
}
[ autoUpdateElt { duration: 3000, effect: dispatch Refresh }
, R2.scuff $ T.table { rows, setParams, container, colNames, totalRecords}
]
where
setParams params =
loaderDispatch $ Loader.SetPath $ pageParams {params = params}
ngramsTable = applyNgramsTablePatch ngramsTablePatch initTable
orderWith =
case convOrderBy <$> pageParams.params.orderBy of
Just ScoreAsc -> A.sortWith \x -> (snd x) ^. _NgramsElement <<< _occurrences
Just ScoreDesc -> A.sortWith \x -> Down $ (snd x) ^. _NgramsElement <<< _occurrences
_ -> identity -- the server ordering is enough here
rows = convertRow <$> orderWith (addOcc <$> Map.toUnfoldable (Map.filter displayRow (ngramsTable ^. _NgramsTable)))
addOcc (Tuple ne ngramsElement) =
let Additive occurrences = sumOccurrences ngramsTable ngramsElement in
Tuple ne (ngramsElement # _NgramsElement <<< _occurrences .~ occurrences)
ngramsParentRoot :: Maybe String
ngramsParentRoot =
(\np -> ngramsTable ^. at np <<< _Just <<< _NgramsElement <<< _root) =<< ngramsParent
displayRow (NgramsElement {ngrams, root}) =
root == Nothing
-- ^ Display only nodes without parents
&& ngramsChildren ^. at ngrams /= Just true
-- ^ and which are not scheduled to be added already
&& Just ngrams /= ngramsParent
-- ^ and which are not our new parent
&& Just ngrams /= ngramsParentRoot
-- ^ and which are not the root of our new parent
|| -- Unless they are scheduled to be removed.
ngramsChildren ^. at ngrams == Just false
convertRow (Tuple ngrams ngramsElement) =
{ row: renderNgramsItem { ngramsTable, ngrams, ngramsParent, ngramsElement, dispatch}
, delete: false
}
ngramsTableClass :: CTabNgramType -> Loader.InnerClass PageParams VersionedNgramsTable
ngramsTableClass ct = createClass "NgramsTable" (ngramsTableSpec ct) initialState
where
totalRecords = 47361 -- TODO
colNames = T.ColumnName <$> ["Map", "Stop", "Terms", "Score (Occurrences)"] -- see convOrderBy
container = tableContainer {pageParams, setPath, dispatch, ngramsParent, ngramsChildren, ngramsTable}
setParams params = setPath $ const (pageParams {params = params})
ngramsTable = applyNgramsTablePatch ngramsTablePatch initTable
orderWith =
case convOrderBy <$> pageParams.params.orderBy of
Just ScoreAsc -> A.sortWith \x -> (snd x) ^. _NgramsElement <<< _occurrences
Just ScoreDesc -> A.sortWith \x -> Down $ (snd x) ^. _NgramsElement <<< _occurrences
_ -> identity -- the server ordering is enough here
rows = convertRow <$> orderWith (addOcc <$> Map.toUnfoldable (Map.filter displayRow (ngramsTable ^. _NgramsTable)))
addOcc (Tuple ne ngramsElement) =
let Additive occurrences = sumOccurrences ngramsTable ngramsElement in
Tuple ne (ngramsElement # _NgramsElement <<< _occurrences .~ occurrences)
ngramsParentRoot :: Maybe String
ngramsParentRoot =
(\np -> ngramsTable ^. at np <<< _Just <<< _NgramsElement <<< _root) =<< ngramsParent
displayRow (NgramsElement {ngrams, root}) =
root == Nothing
-- ^ Display only nodes without parents
&& ngramsChildren ^. at ngrams /= Just true
-- ^ and which are not scheduled to be added already
&& Just ngrams /= ngramsParent
-- ^ and which are not our new parent
&& Just ngrams /= ngramsParentRoot
-- ^ and which are not the root of our new parent
|| -- Unless they are scheduled to be removed.
ngramsChildren ^. at ngrams == Just false
convertRow (Tuple ngrams ngramsElement) =
{ row: R2.buff <$> renderNgramsItem { ngramsTable, ngrams, ngramsParent, ngramsElement, dispatch}
, delete: false
}
-- ngramsTableClass :: Ends -> CTabNgramType -> R2.Setter PageParams -> Loader.InnerClass PageParams (Versioned NgramsTable)
-- ngramsTableClass ends ct setPath = createClass "NgramsTable" (ngramsTableSpec ends ct setPath) initialState
-- ngramsTable' :: Ends -> CTabNgramType -> R2.Setter PageParams -> Record LoadedNgramsTableProps -> R.Element
-- ngramsTable' ends ct setPath props = R2.createElement' (ngramsTableClass ends ct setPath) props []
type MainNgramsTableProps =
{ nodeId :: Int
( nodeId :: Int
-- ^ This node can be a corpus or contact.
, defaultListId :: Int
, tabType :: TabType
}
, ends :: Ends
, tabNgramType :: CTabNgramType
)
mainNgramsTableSpec :: CTabNgramType -> Spec {} MainNgramsTableProps Void
mainNgramsTableSpec nt = simpleSpec defaultPerformAction render
where
render :: Render {} MainNgramsTableProps Void
render _ {nodeId, defaultListId, tabType} _ _ =
[ ngramsLoader
{ path: initialPageParams nodeId [defaultListId] tabType
, component: (ngramsTableClass nt)
} ]
mainNgramsTable :: Record MainNgramsTableProps -> R.Element
mainNgramsTable props = R.createElement mainNgramsTableCpt props []
mainNgramsTableCpt :: R.Component MainNgramsTableProps
mainNgramsTableCpt = R.hooksComponent "MainNgramsTable" cpt
where
cpt {nodeId, defaultListId, tabType, ends, tabNgramType} _ = do
path <- R.useState' $ initialPageParams ends nodeId [defaultListId] tabType
useLoader2 path (loadNgramsTable ends) $
\versioned -> ngramsTable {ends, tabNgramType, path, versioned}
type NgramsDepth = {ngrams :: NgramsTerm, depth :: Int}
type NgramsClick = NgramsDepth -> Maybe (Effect Unit)
......@@ -415,7 +403,6 @@ nextTermList GraphTerm = StopTerm
nextTermList StopTerm = CandidateTerm
nextTermList CandidateTerm = GraphTerm
optps1 :: forall a. Show a => { desc :: String, mval :: Maybe a } -> ReactElement
optps1 { desc, mval } = option [value val] [text desc]
where
val = maybe "" show mval
optps1 :: forall a. Show a => { desc :: String, mval :: Maybe a } -> R.Element
optps1 { desc, mval } = H.option {value} [H.text desc]
where value = maybe "" show mval
......@@ -86,7 +86,7 @@ import Partial.Unsafe (unsafePartial)
import Gargantext.Utils.KarpRabin (indicesOfAny)
import Gargantext.Types (TermList(..), TermSize)
import Gargantext.Config (toUrl, endConfigStateful, End(..), Path(..), TabType, OrderBy(..), CTabNgramType(..))
import Gargantext.Config (Ends, BackendRoute(..), TabType, OrderBy(..), CTabNgramType(..), url)
import Gargantext.Config.REST (get, put, post)
import Gargantext.Components.Table as T
import Gargantext.Prelude
......@@ -106,10 +106,11 @@ type PageParams =
, searchQuery :: String
, termListFilter :: Maybe TermList -- Nothing means all
, termSizeFilter :: Maybe TermSize -- Nothing means all
, ends :: Ends
)
initialPageParams :: Int -> Array Int -> TabType -> PageParams
initialPageParams nodeId listIds tabType =
initialPageParams :: Ends -> Int -> Array Int -> TabType -> PageParams
initialPageParams ends nodeId listIds tabType =
{ nodeId
, listIds
, params: T.initialParams
......@@ -117,6 +118,7 @@ initialPageParams nodeId listIds tabType =
, termSizeFilter: Nothing
, termListFilter: Just GraphTerm
, searchQuery: ""
, ends
}
type NgramsTerm = String
......@@ -561,47 +563,48 @@ type CoreState s =
| s
}
postNewNgrams :: forall s. Array NgramsTerm -> Maybe TermList -> CoreParams s -> Aff Unit
postNewNgrams newNgrams mayList {nodeId, listIds, tabType} =
postNewNgrams :: forall s. Ends -> Array NgramsTerm -> Maybe TermList -> CoreParams s -> Aff Unit
postNewNgrams ends newNgrams mayList {nodeId, listIds, tabType} =
when (not (A.null newNgrams)) $ do
(_ :: Array Unit) <- post (toUrl endConfigStateful Back (PutNgrams tabType (head listIds) mayList) $ Just nodeId) newNgrams
(_ :: Array Unit) <- post (url ends put) newNgrams
pure unit
where put = PutNgrams tabType (head listIds) mayList (Just nodeId)
postNewElems :: forall s. NewElems -> CoreParams s -> Aff Unit
postNewElems newElems params = void $ traverseWithIndex postNewElem newElems
postNewElems :: forall s. Ends -> NewElems -> CoreParams s -> Aff Unit
postNewElems ends newElems params = void $ traverseWithIndex postNewElem newElems
where
postNewElem ngrams list = postNewNgrams [ngrams] (Just list) params
postNewElem ngrams list = postNewNgrams ends [ngrams] (Just list) params
addNewNgram :: CTabNgramType -> NgramsTerm -> TermList -> NgramsTablePatch
addNewNgram ntype ngrams list = { ngramsPatches: mempty
, ngramsNewElems: Map.singleton (normNgram ntype ngrams) list }
putNgramsPatches :: {nodeId :: Int, listIds :: Array Int, tabType :: TabType} -> Versioned NgramsPatches -> Aff (Versioned NgramsPatches)
putNgramsPatches {nodeId, listIds, tabType} =
put (toUrl endConfigStateful Back (PutNgrams tabType (head listIds) Nothing) $ Just nodeId)
putNgramsPatches :: Ends -> {nodeId :: Int, listIds :: Array Int, tabType :: TabType} -> Versioned NgramsPatches -> Aff (Versioned NgramsPatches)
putNgramsPatches ends {nodeId, listIds, tabType} = put $ url ends putNgrams
where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId)
commitPatch :: forall s. {nodeId :: Int, listIds :: Array Int, tabType :: TabType}
commitPatch :: forall s. Ends -> {nodeId :: Int, listIds :: Array Int, tabType :: TabType}
-> Versioned NgramsTablePatch -> StateCoTransformer (CoreState s) Unit
commitPatch props (Versioned {version, data: tablePatch@{ngramsPatches, ngramsNewElems}}) = do
commitPatch ends props (Versioned {version, data: tablePatch@{ngramsPatches, ngramsNewElems}}) = do
let pt = Versioned { version, data: ngramsPatches }
lift $ postNewElems ngramsNewElems props
Versioned {version: newVersion, data: newPatch} <- lift $ putNgramsPatches props pt
lift $ postNewElems ends ngramsNewElems props
Versioned {version: newVersion, data: newPatch} <- lift $ putNgramsPatches ends props pt
modifyState_ $ \s ->
s { ngramsVersion = newVersion
, ngramsTablePatch = fromNgramsPatches newPatch <> tablePatch <> s.ngramsTablePatch
}
-- TODO: check that pt.version == s.ngramsTablePatch.version
loadNgramsTable :: PageParams -> Aff VersionedNgramsTable
loadNgramsTable { nodeId, listIds, termListFilter, termSizeFilter
, searchQuery, tabType, params: {offset, limit, orderBy}} =
get $ toUrl endConfigStateful Back
(GetNgrams { tabType, offset, limit, listIds
, orderBy: convOrderBy <$> orderBy
, termListFilter, termSizeFilter
, searchQuery
})
(Just nodeId)
loadNgramsTable :: Ends -> PageParams -> Aff VersionedNgramsTable
loadNgramsTable ends
{ nodeId, listIds, termListFilter, termSizeFilter
, searchQuery, tabType, params: {offset, limit, orderBy}}
= get $ url ends query
where query = GetNgrams { tabType, offset, limit, listIds
, orderBy: convOrderBy <$> orderBy
, termListFilter, termSizeFilter
, searchQuery } (Just nodeId)
convOrderBy :: T.OrderByDirection T.ColumnName -> OrderBy
convOrderBy (T.ASC (T.ColumnName "Score (Occurrences)")) = ScoreAsc
......@@ -609,10 +612,10 @@ convOrderBy (T.DESC (T.ColumnName "Score (Occurrences)")) = ScoreDesc
convOrderBy (T.ASC _) = TermAsc
convOrderBy (T.DESC _) = TermDesc
ngramsLoaderClass :: Loader.LoaderClass PageParams VersionedNgramsTable
ngramsLoaderClass = Loader.createLoaderClass "NgramsTableLoader" loadNgramsTable
ngramsLoaderClass :: Ends -> Loader.LoaderClass PageParams VersionedNgramsTable
ngramsLoaderClass ends = Loader.createLoaderClass "NgramsTableLoader" (loadNgramsTable ends)
ngramsLoader :: Loader.Props' PageParams VersionedNgramsTable -> ReactElement
ngramsLoader props = React.createElement ngramsLoaderClass props []
ngramsLoader :: Ends -> Loader.Props' PageParams VersionedNgramsTable -> ReactElement
ngramsLoader ends props = React.createElement (ngramsLoaderClass ends) props []
type LoadedNgramsTableProps = Loader.InnerProps PageParams VersionedNgramsTable ()
type LoadedNgramsTableProps = ( path :: PageParams, loaded :: VersionedNgramsTable )
......@@ -167,8 +167,8 @@ instance encodeJsonCategoryQuery :: EncodeJson CategoryQuery where
~> "ntc_category" := encodeJson post.category
~> jsonEmptyObject
categoryUrl :: Int -> String
categoryUrl nodeId = toUrl endConfigStateful Back Node (Just nodeId) <> "/category"
categoryUrl :: Ends -> Int -> String
categoryUrl ends nodeId = url ends (NodeAPI Node (Just nodeId)) <> "/category"
putCategories :: Int -> CategoryQuery -> Aff (Array Int)
putCategories nodeId = put $ categoryUrl nodeId
putCategories :: Ends -> Int -> CategoryQuery -> Aff (Array Int)
putCategories = put <<< categoryUrl
......@@ -7,25 +7,25 @@ import Data.Maybe (Maybe(..), maybe)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Utils.Reactix as R2
import React (ReactElement, ReactClass, Children, createElement)
import React.DOM (a, b, b', p, i, h3, hr, div, option, select, span, table, tbody, td, text, th, thead, tr)
import React.DOM.Props (className, href, onChange, onClick, scope, selected, value, defaultValue, style)
import Thermite (PerformAction, Render, Spec, modifyState_, simpleSpec, StateCoTransformer, createClass)
type TableContainerProps =
{ pageSizeControl :: ReactElement
, pageSizeDescription :: ReactElement
, paginationLinks :: ReactElement
, tableHead :: ReactElement
, tableBody :: Array ReactElement
}
( pageSizeControl :: R.Element
, pageSizeDescription :: R.Element
, paginationLinks :: R.Element
, tableHead :: R.Element
, tableBody :: Array R.Element
)
type Rows = Array { row :: Array ReactElement
, delete :: Boolean
}
type Row = { row :: Array R.Element, delete :: Boolean }
type Rows = Array Row
type OrderBy = Maybe (OrderByDirection ColumnName)
......@@ -52,250 +52,203 @@ instance showOrderByDirection :: Show a => Show (OrderByDirection a) where
derive instance eqOrderByDirection :: Eq a => Eq (OrderByDirection a)
type Props' =
type Props =
( colNames :: Array ColumnName
, totalRecords :: Int
, setParams :: Params -> Effect Unit
, rows :: Rows
, container :: TableContainerProps -> Array ReactElement
, container :: Record TableContainerProps -> R.Element
)
type Props = Record Props'
type State =
{ currentPage :: Int
, pageSize :: PageSizes
, orderBy :: OrderBy
{ page :: Int
, pageSize :: PageSizes
, orderBy :: OrderBy
}
initialState :: State
initialState =
{ currentPage : 1
, pageSize : PS10
, orderBy : Nothing
}
stateParams :: State -> Params
stateParams {pageSize, page, orderBy} = {offset, limit, orderBy}
where
limit = pageSizes2Int pageSize
offset = limit * (page - 1)
type TableHeaderLayoutProps =
( title :: String
, desc :: String
, query :: String
, date :: String
, user :: String
)
initialParams :: Params
initialParams = stateParams initialState
data Action
= ChangePageSize PageSizes
| ChangePage Int
| ChangeOrderBy OrderBy
type ChangePageAction = Int -> Effect Unit
-- | Action
-- ChangePageSize
changePageSize :: PageSizes -> State -> State
changePageSize ps td =
td { pageSize = ps
, currentPage = 1
}
-- TODO: Not sure this is the right place for this function.
renderTableHeaderLayout :: { title :: String
, desc :: String
, query :: String
, date :: String
, user :: String
} -> Array ReactElement
renderTableHeaderLayout {title, desc, query, date, user} =
[ div [className "row"]
[ div [className "col-md-3"] [ h3 [] [text title] ]
, div [className "col-md-9"] [ hr [style {height : "2px",backgroundColor : "black"}] ]
]
, div [className "row"] [ div [className "jumbotron1", style {padding : "12px 0px 20px 12px"}]
[ div [ className "col-md-8 content"]
[ p [] [ i [className "glyphicon glyphicon-globe"] []
, text $ " " <> desc
]
, p [] [ i [className "glyphicon glyphicon-zoom-in"] []
, text $ " " <> query
]
initialParams = stateParams {page: 1, pageSize: PS10, orderBy: Nothing}
-- TODO: Not sure this is the right place for this
tableHeaderLayout :: Record TableHeaderLayoutProps -> R.Element
tableHeaderLayout props = R.createElement tableHeaderLayoutCpt props []
tableHeaderLayoutCpt :: R.Component TableHeaderLayoutProps
tableHeaderLayoutCpt = R.staticComponent "TableHeaderLayout" cpt
where
cpt {title, desc, query, date, user} _ =
R.fragment
[ H.div {className: "row"}
[ H.div {className: "col-md-3"} [ H.h3 {} [H.text title] ]
, H.div {className: "col-md-9"}
[ H.hr {style: {height: "2px", backgroundColor: "black"}} ]
]
, H.div {className: "row"}
[ H.div {className: "jumbotron1", style: {padding: "12px 0px 20px 12px"}}
[ H.div {className: "col-md-8 content"}
[ H.p {}
[ H.i {className: "glyphicon glyphicon-globe"} []
, H.text $ " " <> desc
]
, H.p {}
[ H.i {className: "glyphicon glyphicon-zoom-in"} []
, H.text $ " " <> query
]
, div [ className "col-md-4 content"]
[ p [] [ i [className "glyphicon glyphicon-calendar"] []
, text $ " " <> date
]
, p [] [ i [className "glyphicon glyphicon-user"] []
, text $ " " <> user
]
]
, H.div {className: "col-md-4 content"}
[ H.p {}
[ H.i {className: "glyphicon glyphicon-calendar"} []
, H.text $ " " <> date
]
, H.p {}
[ H.i {className: "glyphicon glyphicon-user"} []
, H.text $ " " <> user
]
]
]
]
]
]
]
table :: Record Props -> R.Element
table props = R.createElement tableCpt props []
tableSpec :: Spec State Props Action
tableSpec = simpleSpec performAction render
tableCpt :: R.Component Props
tableCpt = R.hooksComponent "Table" cpt
where
modifyStateAndReload :: (State -> State) -> Props -> State -> StateCoTransformer State Unit
modifyStateAndReload f {setParams} state = do
--logs "modifyStateAndReload" -- TODO rename
modifyState_ f
liftEffect $ setParams $ stateParams $ f state
performAction :: PerformAction State Props Action
performAction (ChangePageSize ps) =
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 ]
cpt {container, colNames, totalRecords, rows, setParams} _ = do
(pageSize /\ setPageSize) <- R.useState' PS10
(page /\ setPage) <- R.useState' 1
(orderBy /\ setOrderBy) <- R.useState' Nothing
let state = {pageSize, orderBy, page}
let ps = pageSizes2Int pageSize
let totalPages = (totalRecords / ps) + min 1 (totalRecords `mod` ps)
R.useEffect1' state $ setParams (stateParams state)
pure $ container
{ pageSizeControl: sizeDD pageSize setPageSize
, pageSizeDescription: textDescription page pageSize totalRecords
, paginationLinks: pagination setPage totalPages page
, tableHead: H.tr {} (colHeader setOrderBy orderBy <$> colNames)
, tableBody: map (H.tr {} <<< map (\c -> H.td {} [c]) <<< _.row) rows
}
colHeader :: (R2.Setter OrderBy) -> OrderBy -> ColumnName -> R.Element
colHeader setOrderBy currentOrderBy c = H.th {scope: "col"} [ H.b {} cs ]
where
lnk mc = effectLink (changeOrderBy mc)
cs :: Array ReactElement
lnk mc = effectLink (setOrderBy (const mc))
cs :: Array R.Element
cs =
case currentOrderBy of
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)]
_ -> [lnk (Just (ASC c)) (columnName c)]
render :: Render State Props Action
render dispatch {container, colNames, totalRecords, rows}
{pageSize, currentPage, orderBy} _ =
container
{ pageSizeControl: sizeDD pageSize dispatch
, pageSizeDescription: textDescription currentPage pageSize totalRecords
, paginationLinks: pagination (dispatch <<< ChangePage) totalPages currentPage
, tableHead:
tr [] (renderColHeader (dispatch <<< ChangeOrderBy) orderBy <$> colNames)
, tableBody:
map (tr [] <<< map (\c -> td [] [c]) <<< _.row) rows
}
where
ps = pageSizes2Int pageSize
totalPages = (totalRecords / ps) + min 1 (totalRecords `mod` ps)
defaultContainer :: {title :: String} -> TableContainerProps -> Array ReactElement
defaultContainer {title} props =
[ div [className "row"]
[ div [className "col-md-4"] [props.pageSizeDescription]
, div [className "col-md-4"] [props.paginationLinks]
, div [className "col-md-4"] [props.pageSizeControl]
defaultContainer :: {title :: String} -> Record TableContainerProps -> R.Element
defaultContainer {title} props = R.fragment
[ H.div {className: "row"}
[ H.div {className: "col-md-4"} [ props.pageSizeDescription ]
, H.div {className: "col-md-4"} [ props.paginationLinks ]
, H.div {className: "col-md-4"} [ props.pageSizeControl ]
]
, table [ className "table"]
[ thead [className "thead-dark"] [ props.tableHead ]
, tbody [] props.tableBody
, H.table {className: "table"}
[ H.thead {className: "thead-dark"} [ props.tableHead ]
, H.tbody {} props.tableBody
]
]
-- TODO: this needs to be in Gargantext.Pages.Corpus.Graph.Tabs
graphContainer :: {title :: String} -> TableContainerProps -> Array ReactElement
graphContainer :: {title :: String} -> Record TableContainerProps -> R.Element
graphContainer {title} props =
[ -- TODO title in tabs name (above)
table [ className "table"]
[ thead [className "thead-dark"] [ props.tableHead ]
, tbody [] props.tableBody
]
-- TODO title in tabs name (above)
H.table {className: "table"}
[ H.thead {className: "thead-dark"} [ props.tableHead ]
, H.tbody {} props.tableBody
]
-- TODO better rendering of the paginationLinks
-- , props.pageSizeControl
-- , props.pageSizeDescription
-- , props.paginationLinks
]
stateParams :: State -> Params
stateParams {pageSize, currentPage, orderBy} = {offset, limit, orderBy}
sizeDD :: PageSizes -> R2.Setter PageSizes -> R.Element
sizeDD ps setPageSize = H.span {} [ R2.select { className, on: {change} } sizes ]
where
limit = pageSizes2Int pageSize
offset = limit * (currentPage - 1)
className = "form-control"
change e = setPageSize $ const (string2PageSize $ R2.unsafeEventValue e)
sizes = map (optps ps) pageSizes
paramsState :: Params -> State
paramsState {offset, limit, orderBy} = {pageSize, currentPage, orderBy}
textDescription :: Int -> PageSizes -> Int -> R.Element
textDescription currPage pageSize totalRecords =
H.div {className: "row1"} [ H.div {className: ""} [ H.text msg ] ] -- TODO or col-md-6 ?
where
pageSize = string2PageSize $ show limit
currentPage = (offset / limit) + 1
tableClass :: ReactClass {children :: Children | Props'}
tableClass = createClass "Table" tableSpec (const initialState)
tableElt :: Props -> ReactElement
tableElt props = createElement tableClass props []
tableEltWithInitialState :: State -> Props -> ReactElement
tableEltWithInitialState state props = createElement tc props []
where
tc = createClass "Table" tableSpec (const state)
sizeDD :: PageSizes -> (Action -> Effect Unit) -> ReactElement
sizeDD ps d
= span []
[ select [ className "form-control"
, defaultValue $ show ps
, onChange $ \e -> d (ChangePageSize $ string2PageSize $ R2.unsafeEventValue e)
] $ map (optps ps) aryPS
]
textDescription :: Int -> PageSizes -> Int -> ReactElement
textDescription currPage pageSize totalRecords
= div [className "row1"]
[ div [className ""] -- TODO or col-md-6 ?
[ text $ "Showing " <> show start <> " to " <> show end <> " of " <> show totalRecords ]
]
where
start = (currPage - 1) * pageSizes2Int pageSize + 1
end' = currPage * pageSizes2Int pageSize
end = if end' > totalRecords then totalRecords else end'
effectLink :: Effect Unit -> String -> ReactElement
effectLink eff msg = a [onClick $ const eff] [text msg]
pagination :: ChangePageAction -> Int -> Int -> ReactElement
pagination changePage tp cp
= span [] $
[ text " ", prev, first, ldots]
start = (currPage - 1) * pageSizes2Int pageSize + 1
end' = currPage * pageSizes2Int pageSize
end = if end' > totalRecords then totalRecords else end'
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 changePage tp cp =
H.span {} $
[ H.text " ", prev, first, ldots]
<>
lnums
<>
[b' [text $ " " <> show cp <> " "]]
[H.b {} [H.text $ " " <> show cp <> " "]]
<>
rnums
<>
[ rdots, last, next ]
where
prev = if cp == 1 then
text " Prev. "
H.text " Prev. "
else
changePageLink (cp - 1) "Prev."
next = if cp == tp then
text " Next "
H.text " Next "
else
changePageLink (cp + 1) "Next"
first = if cp == 1 then
text ""
H.text ""
else
changePageLink' 1
last = if cp == tp then
text ""
H.text ""
else
changePageLink' tp
ldots = if cp >= 5 then
text " ... "
H.text " ... "
else
text ""
H.text ""
rdots = if cp + 3 < tp then
text " ... "
H.text " ... "
else
text ""
H.text ""
lnums = map changePageLink' $ filter (1 < _) [cp - 2, cp - 1]
rnums = map changePageLink' $ filter (tp > _) [cp + 1, cp + 2]
changePageLink :: Int -> String -> ReactElement
changePageLink i s = span []
[ text " "
, effectLink (changePage i) s
, text " "
changePageLink :: Int -> String -> R.Element
changePageLink i s =
H.span {}
[ H.text " "
, effectLink (changePage (const i)) s
, H.text " "
]
changePageLink' :: Int -> ReactElement
changePageLink' :: Int -> R.Element
changePageLink' i = changePageLink i (show i)
data PageSizes = PS10 | PS20 | PS50 | PS100 | PS200
......@@ -316,8 +269,8 @@ pageSizes2Int PS50 = 50
pageSizes2Int PS100 = 100
pageSizes2Int PS200 = 200
aryPS :: Array PageSizes
aryPS = [PS10, PS20, PS50, PS100, PS200]
pageSizes :: Array PageSizes
pageSizes = [PS10, PS20, PS50, PS100, PS200]
string2PageSize :: String -> PageSizes
string2PageSize "10" = PS10
......@@ -327,5 +280,5 @@ string2PageSize "100" = PS100
string2PageSize "200" = PS200
string2PageSize _ = PS10
optps :: PageSizes -> PageSizes -> ReactElement
optps cv val = option [ value $ show val ] [text $ show val]
optps :: PageSizes -> PageSizes -> R.Element
optps cv val = H.option {selected: (cv == val), value: show val} [R2.showText 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