Unverified Commit ce5135f4 authored by Nicolas Pouillard's avatar Nicolas Pouillard

Merge branch 'ngrams-table' into delete-and-favorite-api

This is WIP in particular the missing function "dispatch2" in Documents.
parents 662c8d7b 8030266a
#!/bin/bash #!/bin/bash
rm -rf output bower_components node_modules rm -rf .psc-package output bower_components node_modules
./build ./build
module Gargantext.Components.Loader where module Gargantext.Components.Loader where
import Control.Monad.Cont.Trans (lift)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Either (Either(..))
import Data.Traversable (traverse_)
import React as React import React as React
import React (ReactClass) import React (ReactClass, Children)
import Gargantext.Prelude import Gargantext.Prelude
import Effect.Aff (Aff, launchAff, launchAff_, makeAff, nonCanceler, killFiber) import Effect (Effect)
import Effect.Exception (error) import Effect.Aff (Aff)
type InnerProps a b = import Thermite (Render, PerformAction, simpleSpec, modifyState_, createReactSpec)
{ path :: a
, loaded :: Maybe b data Action path = ForceReload | SetPath path
, children :: React.Children
type InnerProps path loaded =
{ path :: path
, loaded :: Maybe loaded
, dispatch :: Action path -> Effect Unit
, children :: Children
} }
type Props a b = { path :: a type PropsRow path loaded row =
, component :: ReactClass (InnerProps a b) ( path :: path
} , component :: ReactClass (InnerProps path loaded)
| row
)
type Props path loaded = Record (PropsRow path loaded (children :: Children))
type Props' path loaded = Record (PropsRow path loaded ())
type State path loaded = { currentPath :: path, loaded :: Maybe loaded }
createLoaderClass' :: forall path loaded props
. Eq path
=> String
-> (path -> Aff loaded)
-> Render (State path loaded) {path :: path | props} (Action path)
-> ReactClass { path :: path, children :: Children | props }
createLoaderClass' name loader render =
React.component name
(\this -> do
s <- spec this
pure { state: s.state
, render: s.render
, componentDidMount: dispatcher this ForceReload
})
where
initialState {path} = {currentPath: path, loaded: Nothing}
performAction :: PerformAction (State path loaded) {path :: path | props} (Action path)
performAction ForceReload _ {currentPath} = do
loaded <- lift $ loader currentPath
modifyState_ $ _ { loaded = Just loaded }
performAction (SetPath newPath) _ {currentPath} =
when (newPath /= currentPath) $ do
loaded <- lift $ loader newPath
modifyState_ $ _ { currentPath = newPath, loaded = Just loaded }
{spec, dispatcher} = createReactSpec (simpleSpec performAction render) initialState
createLoaderClass :: forall path loaded
. Eq path
=> String
-> (path -> Aff loaded)
-> ReactClass (Record (PropsRow path loaded (children :: Children)))
createLoaderClass name loader =
createLoaderClass' name loader render
where
render :: Render (State path loaded) (Props' path loaded) (Action path)
render dispatch {component} {currentPath, loaded} c =
[React.createElement component {path: currentPath, loaded, dispatch} c]
createLoaderClass :: forall a b {-
createLoaderClass :: forall path loaded
. String . String
-> (a -> Aff b) -> (path -> Aff loaded)
-> ReactClass (Props a b) -> ReactClass (Props path loaded)
createLoaderClass name loader = React.component name mk createLoaderClass name loader = React.component name mk
where where
mk this = mk this =
...@@ -49,3 +102,4 @@ createLoaderClass name loader = React.component name mk ...@@ -49,3 +102,4 @@ createLoaderClass name loader = React.component name mk
{loaded} <- React.getState this {loaded} <- React.getState this
pure $ React.createElement component {path, loaded} [] pure $ React.createElement component {path, loaded} []
} }
-}
module Gargantext.Components.Table where module Gargantext.Components.Table where
import Control.Monad.Cont.Trans (lift)
import Data.Array (filter) import Data.Array (filter)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Class (liftEffect)
import React as React
import React (ReactElement, ReactClass, Children, createElement) 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 (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, style) import React.DOM.Props (className, href, onChange, onClick, scope, selected, value, style)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec, createReactSpec, StateCoTransformer) import Thermite (PerformAction, Render, Spec, modifyState_, simpleSpec, StateCoTransformer, createClass)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -29,7 +27,7 @@ type Rows = Array { row :: Array ReactElement ...@@ -29,7 +27,7 @@ type Rows = Array { row :: Array ReactElement
type OrderBy = Maybe (OrderByDirection ColumnName) type OrderBy = Maybe (OrderByDirection ColumnName)
type LoadRows = { offset :: Int, limit :: Int, orderBy :: OrderBy } -> Aff Rows type Params = { offset :: Int, limit :: Int, orderBy :: OrderBy }
newtype ColumnName = ColumnName String newtype ColumnName = ColumnName String
...@@ -40,32 +38,34 @@ columnName (ColumnName c) = c ...@@ -40,32 +38,34 @@ columnName (ColumnName c) = c
data OrderByDirection a = ASC a | DESC a data OrderByDirection a = ASC a | DESC a
derive instance eqOrderByDirection :: Eq a => Eq (OrderByDirection a)
type Props' = type Props' =
( colNames :: Array ColumnName ( colNames :: Array ColumnName
, totalRecords :: Int , totalRecords :: Int
, loadRows :: LoadRows , setParams :: Params -> Effect Unit
, rows :: Rows
, container :: TableContainerProps -> Array ReactElement , container :: TableContainerProps -> Array ReactElement
) )
type Props = Record Props' type Props = Record Props'
type State = type State =
{ rows :: Maybe Rows { currentPage :: Int
, currentPage :: Int
, pageSize :: PageSizes , pageSize :: PageSizes
, orderBy :: OrderBy , orderBy :: OrderBy
--, tree :: FTree
} }
initialState :: State initialState :: State
initialState = initialState =
{ rows : Nothing { currentPage : 1
, currentPage : 1
, pageSize : PS10 , pageSize : PS10
, orderBy : Nothing , orderBy : Nothing
--, tree : exampleTree
} }
initialParams :: Params
initialParams = stateParams initialState
data Action data Action
= ChangePageSize PageSizes = ChangePageSize PageSizes
| ChangePage Int | ChangePage Int
...@@ -118,9 +118,9 @@ tableSpec :: Spec State Props Action ...@@ -118,9 +118,9 @@ tableSpec :: Spec State Props Action
tableSpec = simpleSpec performAction render tableSpec = simpleSpec performAction render
where where
modifyStateAndReload :: (State -> State) -> Props -> State -> StateCoTransformer State Unit modifyStateAndReload :: (State -> State) -> Props -> State -> StateCoTransformer State Unit
modifyStateAndReload f {loadRows} state = do modifyStateAndReload f {setParams} state = do
void $ modifyState f modifyState_ f
loadAndSetRows {loadRows} $ f state liftEffect $ setParams $ stateParams $ f state
performAction :: PerformAction State Props Action performAction :: PerformAction State Props Action
performAction (ChangePageSize ps) = performAction (ChangePageSize ps) =
...@@ -145,8 +145,8 @@ tableSpec = simpleSpec performAction render ...@@ -145,8 +145,8 @@ tableSpec = simpleSpec performAction render
_ -> [lnk (Just (ASC c)) (columnName c)] _ -> [lnk (Just (ASC c)) (columnName c)]
render :: Render State Props Action render :: Render State Props Action
render dispatch {container, colNames, totalRecords} render dispatch {container, colNames, totalRecords, rows}
{pageSize, currentPage, orderBy, rows} _ = {pageSize, currentPage, orderBy} _ =
container container
{ pageSizeControl: sizeDD pageSize dispatch { pageSizeControl: sizeDD pageSize dispatch
, pageSizeDescription: textDescription currentPage pageSize totalRecords , pageSizeDescription: textDescription currentPage pageSize totalRecords
...@@ -154,10 +154,7 @@ tableSpec = simpleSpec performAction render ...@@ -154,10 +154,7 @@ tableSpec = simpleSpec performAction render
, tableHead: , tableHead:
tr [] (renderColHeader (dispatch <<< ChangeOrderBy) orderBy <$> colNames) tr [] (renderColHeader (dispatch <<< ChangeOrderBy) orderBy <$> colNames)
, tableBody: , tableBody:
map (tr [] <<< map (\c -> td [] [c]) <<< _.row) map (tr [] <<< map (\c -> td [] [c]) <<< _.row) rows
(maybe [] identity rows)
-- TODO display a loading spinner when rows == Nothing
-- instead of an empty list of results.
} }
where where
ps = pageSizes2Int pageSize ps = pageSizes2Int pageSize
...@@ -169,7 +166,7 @@ defaultContainer {title} props = ...@@ -169,7 +166,7 @@ defaultContainer {title} props =
[ div [className "col-md-1"] [b [] [text title]] [ div [className "col-md-1"] [b [] [text title]]
, div [className "col-md-2"] [props.pageSizeControl] , div [className "col-md-2"] [props.pageSizeControl]
, div [className "col-md-3"] [props.pageSizeDescription] , div [className "col-md-3"] [props.pageSizeDescription]
, div [className "col-md-3"] [] , div [className "col-md-3"] [props.paginationLinks]
] ]
, table [ className "table"] , table [ className "table"]
[ thead [className "thead-dark"] [ props.tableHead ] [ thead [className "thead-dark"] [ props.tableHead ]
...@@ -177,26 +174,14 @@ defaultContainer {title} props = ...@@ -177,26 +174,14 @@ defaultContainer {title} props =
] ]
] ]
loadAndSetRows :: {loadRows :: LoadRows} -> State -> StateCoTransformer State Unit stateParams :: State -> Params
loadAndSetRows {loadRows} {pageSize, currentPage, orderBy} = do stateParams {pageSize, currentPage, orderBy} = {offset, limit, orderBy}
let limit = pageSizes2Int pageSize where
offset = limit * (currentPage - 1) limit = pageSizes2Int pageSize
rows <- lift $ loadRows {offset, limit, orderBy} offset = limit * (currentPage - 1)
void $ modifyState (_ { rows = Just rows })
tableClass :: ReactClass {children :: Children | Props'} tableClass :: ReactClass {children :: Children | Props'}
tableClass = tableClass = createClass "Table" tableSpec (const initialState)
React.component "Table"
(\this -> do
{state, render} <- spec this
pure { state, render
, componentDidMount: do
{loadRows} <- React.getProps this
state' <- React.getState this
dispatcher' this $ loadAndSetRows {loadRows} state'
})
where
{ spec, dispatcher' } = createReactSpec tableSpec initialState
tableElt :: Props -> ReactElement tableElt :: Props -> ReactElement
tableElt props = createElement tableClass props [] tableElt props = createElement tableClass props []
...@@ -220,10 +205,7 @@ textDescription currPage pageSize totalRecords ...@@ -220,10 +205,7 @@ textDescription currPage pageSize totalRecords
end = if end' > totalRecords then totalRecords else end' end = if end' > totalRecords then totalRecords else end'
effectLink :: Effect Unit -> String -> ReactElement effectLink :: Effect Unit -> String -> ReactElement
effectLink eff msg = effectLink eff msg = a [onClick $ const eff] [text msg]
a [ href "javascript:void()"
, onClick (const eff)
] [text msg]
pagination :: ChangePageAction -> Int -> Int -> ReactElement pagination :: ChangePageAction -> Int -> Int -> ReactElement
pagination changePage tp cp pagination changePage tp cp
......
...@@ -5,10 +5,12 @@ import Data.Lens (Prism', prism) ...@@ -5,10 +5,12 @@ import Data.Lens (Prism', prism)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import React as React import React as React
import React (ReactClass, ReactElement) import React (ReactClass, ReactElement, Children)
import React.DOM (a, br', div, input, p, text) import React.DOM (a, br', div, input, p, text)
import React.DOM.Props (href) import React.DOM.Props (href)
import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Thermite ( Render, Spec import Thermite ( Render, Spec
, createClass, simpleSpec, defaultPerformAction , createClass, simpleSpec, defaultPerformAction
) )
...@@ -16,15 +18,17 @@ import Thermite ( Render, Spec ...@@ -16,15 +18,17 @@ import Thermite ( Render, Spec
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Loader as Loader import Gargantext.Components.Loader as Loader
import Gargantext.Components.Loader (createLoaderClass)
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table as Table import Gargantext.Components.Table as T
import Gargantext.Config (toUrl, NodeType(..), TabType(..), End(..)) import Gargantext.Config (toUrl, NodeType(..), TabType(..), End(..))
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import Gargantext.Pages.Annuaire.User.Contacts.Types (Contact(..), HyperData(..)) import Gargantext.Pages.Annuaire.User.Contacts.Types (Contact(..), HyperData(..))
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
type Props = {path :: Int, loaded :: Maybe AnnuaireInfo } type Props =
{ path :: Int
, loaded :: Maybe AnnuaireInfo
, dispatch :: Loader.Action Int -> Effect Unit }
data Action data Action
= TabsA Tab.Action = TabsA Tab.Action
...@@ -71,7 +75,7 @@ layout = simpleSpec defaultPerformAction render ...@@ -71,7 +75,7 @@ layout = simpleSpec defaultPerformAction render
render _ {annuaireId} _ _ = render _ {annuaireId} _ _ =
[ annuaireLoader [ annuaireLoader
{ path: annuaireId { path: annuaireId
, component: createClass "LoadedAnnuaire" loadedAnnuaireSpec {} , component: createClass "LoadedAnnuaire" loadedAnnuaireSpec (const {})
} ] } ]
loadedAnnuaireSpec :: Spec {} Props Void loadedAnnuaireSpec :: Spec {} Props Void
...@@ -79,8 +83,8 @@ loadedAnnuaireSpec = simpleSpec defaultPerformAction render ...@@ -79,8 +83,8 @@ loadedAnnuaireSpec = simpleSpec defaultPerformAction render
where where
render :: Render {} Props Void render :: Render {} Props Void
render _ {loaded: Nothing} _ _ = [] render _ {loaded: Nothing} _ _ = []
render _ {path, loaded: Just (AnnuaireInfo {name, date})} _ _ = render _ {path: nodeId, loaded: Just (annuaireInfo@AnnuaireInfo {name, date})} _ _ =
Table.renderTableHeaderLayout T.renderTableHeaderLayout
{ title: name { title: name
, desc: name , desc: name
, query: "" , query: ""
...@@ -90,25 +94,54 @@ loadedAnnuaireSpec = simpleSpec defaultPerformAction render ...@@ -90,25 +94,54 @@ loadedAnnuaireSpec = simpleSpec defaultPerformAction render
[ p [] [] [ p [] []
, div [] [ text " Filter ", input []] , div [] [ text " Filter ", input []]
, br' , br'
, Table.tableElt , pageLoader
{ loadRows { path: initialPageParams nodeId
, container: Table.defaultContainer { title: "title" } -- TODO , annuaireInfo
, colNames: }
Table.ColumnName <$> ]
type PageParams = {nodeId :: Int, params :: T.Params}
initialPageParams :: Int -> PageParams
initialPageParams nodeId = {nodeId, params: T.initialParams}
type PageLoaderProps =
{ path :: PageParams
, annuaireInfo :: AnnuaireInfo
}
renderPage :: forall props path.
Render (Loader.State {nodeId :: Int | path} AnnuaireTable)
{annuaireInfo :: AnnuaireInfo | props}
(Loader.Action PageParams)
renderPage _ _ {loaded: Nothing} _ = [] -- TODO loading spinner
renderPage dispatch {annuaireInfo}
{ currentPath: {nodeId}
, loaded: Just (AnnuaireTable {annuaireTable: res})
} _ =
[ T.tableElt
{ rows
, setParams: \params -> liftEffect $ dispatch (Loader.SetPath {nodeId, params})
, container: T.defaultContainer { title: "Annuaire" } -- TODO
, colNames:
T.ColumnName <$>
[ "" [ ""
, "Name" , "Name"
, "Role" , "Role"
, "Service" , "Service"
, "Company" , "Company"
] ]
, totalRecords: 47361 -- TODO , totalRecords: 47361 -- TODO
} }
] ]
where where
annuaireId = path rows = (\c -> {row: renderContactCells c, delete: false}) <$> res
loadRows {offset, limit, orderBy} = do -- TODO use offset, limit, orderBy
(AnnuaireTable {annuaireTable: rows}) <- getTable annuaireId pageLoaderClass :: ReactClass { path :: PageParams, annuaireInfo :: AnnuaireInfo, children :: Children }
pure $ (\c -> {row: renderContactCells c, delete: false}) <$> rows pageLoaderClass = Loader.createLoaderClass' "AnnuairePageLoader" loadPage renderPage
pageLoader :: PageLoaderProps -> ReactElement
pageLoader props = React.createElement pageLoaderClass props []
renderContactCells :: Contact -> Array ReactElement renderContactCells :: Contact -> Array ReactElement
renderContactCells (Contact { id, hyperdata : HyperData contact }) = renderContactCells (Contact { id, hyperdata : HyperData contact }) =
...@@ -168,15 +201,17 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where ...@@ -168,15 +201,17 @@ instance decodeAnnuaireTable :: DecodeJson AnnuaireTable where
rows <- decodeJson json rows <- decodeJson json
pure $ AnnuaireTable { annuaireTable : rows} pure $ AnnuaireTable { annuaireTable : rows}
------------------------------------------------------------------------ ------------------------------------------------------------------------
getTable :: Int -> Aff AnnuaireTable loadPage :: PageParams -> Aff AnnuaireTable
getTable id = get $ toUrl Back (Tab TabDocs 0 10 Nothing) id loadPage {nodeId, params} = get $ toUrl Back (Tab TabDocs 0 10 Nothing) nodeId
-- TODO Tab TabDocs is not the right API call
-- TODO params, see loadPage in Documents
getAnnuaireInfo :: Int -> Aff AnnuaireInfo getAnnuaireInfo :: Int -> Aff AnnuaireInfo
getAnnuaireInfo id = get $ toUrl Back Node id getAnnuaireInfo id = get $ toUrl Back Node id
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
annuaireLoaderClass :: ReactClass (Loader.Props Int AnnuaireInfo) annuaireLoaderClass :: ReactClass (Loader.Props Int AnnuaireInfo)
annuaireLoaderClass = createLoaderClass "AnnuaireLoader" getAnnuaireInfo annuaireLoaderClass = Loader.createLoaderClass "AnnuaireLoader" getAnnuaireInfo
annuaireLoader :: Loader.Props Int AnnuaireInfo -> ReactElement annuaireLoader :: Loader.Props' Int AnnuaireInfo -> ReactElement
annuaireLoader = React.createLeafElement annuaireLoaderClass annuaireLoader props = React.createElement annuaireLoaderClass props []
...@@ -28,9 +28,9 @@ type Props = Tabs.Props ...@@ -28,9 +28,9 @@ type Props = Tabs.Props
type State = { tabsView :: Tabs.State type State = { tabsView :: Tabs.State
} }
initialState :: State initialState :: Props -> State
initialState = { tabsView : Tabs.initialState initialState _props =
} { tabsView : Tabs.initialState {} }
------------------------------------------------------------------------ ------------------------------------------------------------------------
_tabsView :: forall a b. Lens' { tabsView :: a | b } a _tabsView :: forall a b. Lens' { tabsView :: a | b } a
...@@ -87,5 +87,5 @@ getCorpus = get <<< toUrl Back Corpus ...@@ -87,5 +87,5 @@ getCorpus = get <<< toUrl Back Corpus
corpusLoaderClass :: ReactClass (Loader.Props Int (NodePoly CorpusInfo)) corpusLoaderClass :: ReactClass (Loader.Props Int (NodePoly CorpusInfo))
corpusLoaderClass = createLoaderClass "CorpusLoader" getCorpus corpusLoaderClass = createLoaderClass "CorpusLoader" getCorpus
corpusLoader :: Loader.Props Int (NodePoly CorpusInfo) -> ReactElement corpusLoader :: Loader.Props' Int (NodePoly CorpusInfo) -> ReactElement
corpusLoader = React.createLeafElement corpusLoaderClass corpusLoader props = React.createElement corpusLoaderClass props []
...@@ -26,8 +26,8 @@ type State = ...@@ -26,8 +26,8 @@ type State =
, inputValue :: String , inputValue :: String
} }
initialState :: State initialState :: {} -> State
initialState = initialState {} =
{ document : Nothing { document : Nothing
, inputValue : "" , inputValue : ""
} }
......
module Gargantext.Pages.Corpus.Tabs.Documents where module Gargantext.Pages.Corpus.Tabs.Documents where
import Gargantext.Prelude import Data.Array (take, drop)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.?), (:=), (~>))
import Affjax (defaultRequest, request) import Affjax (defaultRequest, request)
import Affjax.RequestBody (RequestBody(..)) import Affjax.RequestBody (RequestBody(..))
...@@ -13,13 +14,23 @@ import Data.Either (Either(..)) ...@@ -13,13 +14,23 @@ import Data.Either (Either(..))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Data.HTTP.Method (Method(..)) import Data.HTTP.Method (Method(..))
import Data.List (List)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log) import React as React
import React (ReactClass, ReactElement, Children)
import React.DOM (a, br', div, input, p, text)
import React.DOM.Props (_type, className, href, style, placeholder, name)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
------------------------------------------------------------------------
import Gargantext.Prelude
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) import Gargantext.Components.Charts.Options.ECharts (chart)
import Gargantext.Components.Loader as Loader
import Gargantext.Components.Table as T
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Config (NodeType(..), TabType(..), toUrl, End(..), OrderBy(..)) import Gargantext.Config (NodeType(..), TabType(..), toUrl, End(..), OrderBy(..))
...@@ -63,19 +74,19 @@ performAction (SendFavorites nid) {path : nodeId} _ = void $ do ...@@ -63,19 +74,19 @@ performAction (SendFavorites nid) {path : nodeId} _ = void $ do
s' <- lift $ favorites nid (FavoriteQuery {favorites : [nid]}) s' <- lift $ favorites nid (FavoriteQuery {favorites : [nid]})
case s' of case s' of
Left err -> do Left err -> do
_ <- liftEffect $ log err logs err
modifyState identity modifyState identity
Right d -> modifyState identity Right d -> modifyState identity
--TODO add array of delete rows here --TODO add array of delete rows here
performAction (DeleteDocuments nid) _ s = void $ do performAction (DeleteDocuments nid) _ s = void $ do
_ <- liftEffect $ log $ show nid logs $ show nid
modifyState \state -> state {deleteRowId = ( cons nid s.deleteRowId), deleteRows = true} modifyState \state -> state {deleteRowId = ( cons nid s.deleteRowId), deleteRows = true}
performAction Trash {path:nodeId} state = void $ do performAction Trash {path:nodeId} state = void $ do
s' <- lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents : state.deleteRowId}) s' <- lift $ deleteDocuments nodeId (DeleteDocumentQuery {documents : state.deleteRowId})
case s' of case s' of
Left err -> do Left err -> do
_ <- liftEffect $ log err logs err
modifyState identity modifyState identity
Right d -> modifyState identity Right d -> modifyState identity
...@@ -166,7 +177,7 @@ layoutDocview :: Spec State Props Action ...@@ -166,7 +177,7 @@ layoutDocview :: Spec State Props Action
layoutDocview = simpleSpec performAction render layoutDocview = simpleSpec performAction render
where where
render :: Render State Props Action render :: Render State Props Action
render dispatch {path: nodeId, loaded} _ s = render dispatch {path: nodeId, loaded: corpusInfo} _ _ =
[ p [] [] [ p [] []
, div [ style {textAlign : "center"}] [input [placeholder "Filter here"]] , div [ style {textAlign : "center"}] [input [placeholder "Filter here"]]
, br' , br'
...@@ -174,23 +185,9 @@ layoutDocview = simpleSpec performAction render ...@@ -174,23 +185,9 @@ layoutDocview = simpleSpec performAction render
[ div [className "row"] [ div [className "row"]
[ chart globalPublis [ chart globalPublis
, div [className "col-md-12"] , div [className "col-md-12"]
[ T.tableElt [ pageLoader
{ loadRows { path: initialPageParams nodeId
, container: T.defaultContainer { title: "Documents" } , corpusInfo
, colNames:
T.ColumnName <$>
[ ""
, "Date"
, "Title"
, "Source"
, "Delete"
]
, totalRecords: maybe 47361 -- TODO
identity
((\(NodePoly n) -> n.hyperdata)
>>>
(\(CorpusInfo c) -> c.totalRecords)
<$> loaded)
} }
] ]
, div [className "col-md-12"] , div [className "col-md-12"]
...@@ -206,42 +203,17 @@ layoutDocview = simpleSpec performAction render ...@@ -206,42 +203,17 @@ layoutDocview = simpleSpec performAction render
] ]
] ]
] ]
where
loadRows {offset, limit, orderBy} = do
_ <- logs "loading documents page"
res <- loadPage {nodeId,offset,limit,orderBy}
_ <- logs "OK: loading page documents."
pure $
(\(DocumentsView r) ->
{ row:
[ div []
[ a [className $ fa r.fav <> "fa-star" ,onClick $ (\_-> dispatch $ (SendFavorites r._id))] []
]
-- TODO show date: Year-Month-Day only
, if (r.delete) then
div [ style {textDecoration : "line-through"}][text r.date]
else
div [ ][text r.date]
, if (r.delete) then
a [ href (toUrl Front Url_Document r._id), style {textDecoration : "line-through"} ] [ text r.title ]
else
a [ href (toUrl Front Url_Document r._id) ] [ text r.title ]
, if (r.delete) then
div [style {textDecoration : "line-through"}] [ text r.source]
else
div [] [ text r.source]
, input [ _type "checkbox", onClick $ (\_ -> dispatch $ (DeleteDocuments r._id))]
]
, delete: true
}) <$> res
fa true = "fas "
fa false = "far "
mock :: Boolean mock :: Boolean
mock = false mock = false
loadPage :: {nodeId :: Int, limit :: Int, offset :: Int, orderBy :: T.OrderBy} -> Aff (Array DocumentsView) type PageParams = {nodeId :: Int, params :: T.Params}
loadPage {nodeId, limit, offset, orderBy} = do
initialPageParams :: Int -> PageParams
initialPageParams nodeId = {nodeId, params: T.initialParams}
loadPage :: PageParams -> Aff (Array DocumentsView)
loadPage {nodeId, params: {limit, offset, orderBy}} = do
logs "loading documents page: loadPage with Offset and limit" logs "loading documents page: loadPage with Offset and limit"
--res <- get $ toUrl Back (Children Url_Document offset limit) nodeId --res <- get $ toUrl Back (Children Url_Document offset limit) nodeId
res <- get $ toUrl Back (Tab TabDocs offset limit (convOrderBy <$> orderBy)) nodeId res <- get $ toUrl Back (Tab TabDocs offset limit (convOrderBy <$> orderBy)) nodeId
...@@ -270,6 +242,69 @@ loadPage {nodeId, limit, offset, orderBy} = do ...@@ -270,6 +242,69 @@ loadPage {nodeId, limit, offset, orderBy} = do
convOrderBy _ = DateAsc -- TODO convOrderBy _ = DateAsc -- TODO
type PageLoaderProps =
{ path :: PageParams
, corpusInfo :: Maybe (NodePoly CorpusInfo)
}
renderPage :: forall props path.
Render (Loader.State {nodeId :: Int | path} (Array DocumentsView))
{corpusInfo :: Maybe (NodePoly CorpusInfo) | props}
(Loader.Action PageParams)
renderPage _ _ {loaded: Nothing} _ = [] -- TODO loading spinner
renderPage dispatch {corpusInfo} {currentPath: {nodeId}, loaded: Just res} _ =
[ T.tableElt
{ rows
, setParams: \params -> liftEffect $ dispatch (Loader.SetPath {nodeId, params})
, container: T.defaultContainer { title: "Documents" }
, colNames:
T.ColumnName <$>
[ ""
, "Date"
, "Title"
, "Source"
, "Delete"
]
, totalRecords: maybe 47361 -- TODO
identity
((\(NodePoly n) -> n.hyperdata)
>>>
(\(CorpusInfo c) -> c.totalRecords)
<$> corpusInfo)
}
]
where
dispatch2 _ = logs "TODO dispatch2"
fa true = "fas "
fa false = "far "
rows = (\(DocumentsView r) ->
{ row:
[ div []
[ a [className $ fa r.fav <> "fa-star" ,onClick $ (\_-> dispatch2 $ (SendFavorites r._id))] []
]
-- TODO show date: Year-Month-Day only
, if (r.delete) then
div [ style {textDecoration : "line-through"}][text r.date]
else
div [ ][text r.date]
, if (r.delete) then
a [ href (toUrl Front Url_Document r._id), style {textDecoration : "line-through"} ] [ text r.title ]
else
a [ href (toUrl Front Url_Document r._id) ] [ text r.title ]
, if (r.delete) then
div [style {textDecoration : "line-through"}] [ text r.source]
else
div [] [ text r.source]
, input [ _type "checkbox", onClick $ (\_ -> dispatch2 $ (DeleteDocuments r._id))]
]
, delete: true
}) <$> res
pageLoaderClass :: ReactClass { path :: PageParams, corpusInfo :: Maybe (NodePoly CorpusInfo), children :: Children }
pageLoaderClass = Loader.createLoaderClass' "PageLoader" loadPage renderPage
pageLoader :: PageLoaderProps -> ReactElement
pageLoader props = React.createElement pageLoaderClass props []
--------------------------------------------------------- ---------------------------------------------------------
sampleData' :: DocumentsView sampleData' :: DocumentsView
...@@ -335,14 +370,15 @@ favorites nodeId reqbody= do ...@@ -335,14 +370,15 @@ favorites nodeId reqbody= do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
let obj = decodeJson json let obj = decodeJson json
pure obj pure obj
deleteFavorites :: Int -> FavoriteQuery -> Aff (Either String (Array Int)) deleteFavorites :: Int -> FavoriteQuery -> Aff (Either String (Array Int))
deleteFavorites nodeId reqbody= do deleteFavorites nodeId reqbody = do
-- TODO use Config.REST.delete
res <- request $ defaultRequest res <- request $ defaultRequest
{ url = "http://localhost:8008/api/v1.0/node/"<>show nodeId<>"/favorites" { url = "http://localhost:8008/api/v1.0/node/"<>show nodeId<>"/favorites"
, responseFormat = ResponseFormat.json , responseFormat = ResponseFormat.json
...@@ -352,7 +388,7 @@ deleteFavorites nodeId reqbody= do ...@@ -352,7 +388,7 @@ deleteFavorites nodeId reqbody= do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
let obj = decodeJson json let obj = decodeJson json
...@@ -362,6 +398,7 @@ deleteFavorites nodeId reqbody= do ...@@ -362,6 +398,7 @@ deleteFavorites nodeId reqbody= do
deleteDocuments :: Int -> DeleteDocumentQuery -> Aff (Either String Unit) deleteDocuments :: Int -> DeleteDocumentQuery -> Aff (Either String Unit)
deleteDocuments nodeId reqbody= do deleteDocuments nodeId reqbody= do
-- TODO use Config.REST.delete
res <- request $ defaultRequest res <- request $ defaultRequest
{ url = "http://localhost:8008/api/v1.0/annuaire/"<>show nodeId <>"/documents" { url = "http://localhost:8008/api/v1.0/annuaire/"<>show nodeId <>"/documents"
, responseFormat = ResponseFormat.json , responseFormat = ResponseFormat.json
...@@ -371,7 +408,7 @@ deleteDocuments nodeId reqbody= do ...@@ -371,7 +408,7 @@ deleteDocuments nodeId reqbody= do
} }
case res.body of case res.body of
Left err -> do Left err -> do
_ <- liftEffect $ log $ printResponseFormatError err logs $ printResponseFormatError err
pure $ Left $ printResponseFormatError err pure $ Left $ printResponseFormatError err
Right json -> do Right json -> do
-- let obj = decodeJson json -- let obj = decodeJson json
......
...@@ -20,7 +20,7 @@ import Data.Void (Void) ...@@ -20,7 +20,7 @@ import Data.Void (Void)
import Data.Unit (Unit) import Data.Unit (Unit)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import React (ReactElement, ReactClass) import React (ReactElement, ReactClass, Children)
import React as React import React as React
import React.DOM hiding (style, map) import React.DOM hiding (style, map)
import React.DOM.Props (_id, _type, checked, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value) import React.DOM.Props (_id, _type, checked, className, href, name, onChange, onClick, onInput, placeholder, scope, selected, style, value)
...@@ -38,8 +38,11 @@ import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..), PropsRow) ...@@ -38,8 +38,11 @@ import Gargantext.Pages.Corpus.Tabs.Types (CorpusInfo(..), PropsRow)
type Props = { mode :: Mode | PropsRow } type Props = { mode :: Mode | PropsRow }
type Props' = { path :: Int type PageParams = {nodeId :: Int, params :: T.Params}
type Props' = { path :: PageParams
, loaded :: Maybe NgramsTable , loaded :: Maybe NgramsTable
, dispatch :: Loader.Action PageParams -> Effect Unit
} }
type NgramsTerm = String type NgramsTerm = String
...@@ -173,12 +176,13 @@ type State = ...@@ -173,12 +176,13 @@ type State =
, termTypeFilter :: Maybe TermType -- Nothing means all , termTypeFilter :: Maybe TermType -- Nothing means all
} }
initialState :: State initialState :: forall props. props -> State
initialState = { ngramsTablePatch: mempty initialState _ =
, searchQuery: "" { ngramsTablePatch: mempty
, termListFilter: Nothing , searchQuery: ""
, termTypeFilter: Nothing , termListFilter: Nothing
} , termTypeFilter: Nothing
}
data Action data Action
= SetTermListItem NgramsTerm (Replace TermList) = SetTermListItem NgramsTerm (Replace TermList)
...@@ -281,10 +285,13 @@ ngramsTableSpec' = simpleSpec performAction render ...@@ -281,10 +285,13 @@ ngramsTableSpec' = simpleSpec performAction render
-- patch the root of the child to be equal to the root of the parent. -- patch the root of the child to be equal to the root of the parent.
render :: Render State Props' Action render :: Render State Props' Action
render dispatch {path: nodeId, loaded: initTable} render dispatch { path: {nodeId}
{ngramsTablePatch, searchQuery {- TODO more state -} } _ = , loaded: initTable
, dispatch: loaderDispatch }
{ ngramsTablePatch, searchQuery } _children =
[ T.tableElt [ T.tableElt
{ loadRows { rows
, setParams: \params -> loaderDispatch (Loader.SetPath {nodeId, params})
, container: tableContainer {searchQuery, dispatch} , container: tableContainer {searchQuery, dispatch}
, colNames: , colNames:
T.ColumnName <$> T.ColumnName <$>
...@@ -293,37 +300,48 @@ ngramsTableSpec' = simpleSpec performAction render ...@@ -293,37 +300,48 @@ ngramsTableSpec' = simpleSpec performAction render
, "Terms" , "Terms"
, "Occurences (nb)" , "Occurences (nb)"
] ]
, totalRecords: 10 -- TODO , totalRecords: 47361 -- TODO
} }
] ]
where where
loadRows {offset, limit, orderBy} = rows =
case applyNgramsTablePatch ngramsTablePatch <$> initTable of case applyNgramsTablePatch ngramsTablePatch <$> initTable of
Nothing -> pure [] -- or an error Nothing -> [] -- or an error
Just (NgramsTable table) -> Just (NgramsTable table) ->
pure $ convertRow <$> Map.toUnfoldable (Map.filter isRoot table) convertRow <$> Map.toUnfoldable (Map.filter isRoot table)
isRoot (NgramsElement e) = e.root == Nothing isRoot (NgramsElement e) = e.root == Nothing
convertRow (Tuple ngrams (NgramsElement { occurrences, list })) = convertRow (Tuple ngrams (NgramsElement { occurrences, list })) =
{ row: { row:
let let
setTermList Keep = do setTermList Keep = do
logs "setTermList Keep" logs "setTermList Keep"
pure unit pure unit
setTermList rep@(Replace {old,new}) = do setTermList rep@(Replace {old,new}) = do
logs $ Tuple "setTermList" (Tuple old new) logs $ Tuple "setTermList" (Tuple old new)
dispatch $ SetTermListItem ngrams rep in dispatch $ SetTermListItem ngrams rep in
renderNgramsItem { ngrams, occurrences, termList: list, setTermList } renderNgramsItem { ngrams, occurrences, termList: list, setTermList }
, delete: false , delete: false
} }
initialPageParams :: Int -> PageParams
initialPageParams nodeId = {nodeId, params: T.initialParams}
type PageLoaderProps =
{ path :: PageParams
--, corpusInfo :: Maybe (NodePoly CorpusInfo)
}
getNgramsTable :: Int -> Aff NgramsTable getNgramsTable :: Int -> Aff NgramsTable
getNgramsTable = get <<< toUrl Back (Ngrams TabTerms Nothing) getNgramsTable = get <<< toUrl Back (Ngrams TabTerms Nothing)
ngramsLoaderClass :: ReactClass (Loader.Props Int NgramsTable) loadPage :: PageParams -> Aff NgramsTable
ngramsLoaderClass = Loader.createLoaderClass "NgramsLoader" getNgramsTable loadPage {nodeId} = getNgramsTable nodeId -- TODO this ignores params
ngramsLoaderClass :: ReactClass (Loader.Props PageParams NgramsTable)
ngramsLoaderClass = Loader.createLoaderClass "NgramsLoader" loadPage
ngramsLoader :: Loader.Props Int NgramsTable -> ReactElement ngramsLoader :: Loader.Props' PageParams NgramsTable -> ReactElement
ngramsLoader = React.createLeafElement ngramsLoaderClass ngramsLoader props = React.createElement ngramsLoaderClass props []
ngramsTableSpec :: Spec {} Props Void ngramsTableSpec :: Spec {} Props Void
ngramsTableSpec = simpleSpec defaultPerformAction render ngramsTableSpec = simpleSpec defaultPerformAction render
...@@ -331,7 +349,7 @@ ngramsTableSpec = simpleSpec defaultPerformAction render ...@@ -331,7 +349,7 @@ ngramsTableSpec = simpleSpec defaultPerformAction render
render :: Render {} Props Void render :: Render {} Props Void
render _ {path: nodeId} _ _ = render _ {path: nodeId} _ _ =
-- TODO: ignored mode, ignored loaded: corpusInfo -- TODO: ignored mode, ignored loaded: corpusInfo
[ ngramsLoader { path: nodeId [ ngramsLoader { path: initialPageParams nodeId
, component: createClass "Layout" ngramsTableSpec' initialState , component: createClass "Layout" ngramsTableSpec' initialState
} ] } ]
......
...@@ -15,8 +15,8 @@ import Gargantext.Components.Tab as Tab ...@@ -15,8 +15,8 @@ import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus, hideState, cmapProps) import Thermite (Spec, focus, hideState, cmapProps)
pureTabs :: Spec {} Props Void -- pureTabs :: Spec {} Props Void
pureTabs = hideState initialState statefulTabs -- pureTabs = hideState initialState statefulTabs
statefulTabs :: Spec State Props Action statefulTabs :: Spec State Props Action
statefulTabs = statefulTabs =
...@@ -32,7 +32,7 @@ docPageSpec = focus _doclens _docAction DV.layoutDocview ...@@ -32,7 +32,7 @@ docPageSpec = focus _doclens _docAction DV.layoutDocview
ngramsViewSpec :: {mode :: NV.Mode} -> Spec State Props Action ngramsViewSpec :: {mode :: NV.Mode} -> Spec State Props Action
ngramsViewSpec {mode} = ngramsViewSpec {mode} =
cmapProps (\{loaded, path} -> {mode,loaded,path}) cmapProps (\{loaded, path, dispatch} -> {mode,loaded,path, dispatch})
(focus _ngramsView _NgramViewA NV.ngramsTableSpec) (focus _ngramsView _NgramViewA NV.ngramsTableSpec)
authorPageSpec :: Spec State Props Action authorPageSpec :: Spec State Props Action
......
...@@ -12,9 +12,8 @@ type State = ...@@ -12,9 +12,8 @@ type State =
, activeTab :: Int , activeTab :: Int
} }
initialState :: {} -> State
initialState :: State initialState _ =
initialState =
{ docsView : { docsView :
{ documents : D.sampleData' { documents : D.sampleData'
, deleteRows : false , deleteRows : false
......
...@@ -2,9 +2,11 @@ module Gargantext.Pages.Corpus.Tabs.Types where ...@@ -2,9 +2,11 @@ module Gargantext.Pages.Corpus.Tabs.Types where
import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??)) import Data.Argonaut (class DecodeJson, decodeJson, (.?), (.??))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect (Effect)
-------------------------------------------------------- --------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Loader as Loader
newtype CorpusInfo = CorpusInfo { title :: String newtype CorpusInfo = CorpusInfo { title :: String
, desc :: String , desc :: String
...@@ -43,7 +45,11 @@ instance decodeCorpusInfo :: DecodeJson CorpusInfo where ...@@ -43,7 +45,11 @@ instance decodeCorpusInfo :: DecodeJson CorpusInfo where
pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords} pure $ CorpusInfo {title, desc, query, authors, chart, totalRecords}
-- TODO type Props = {nodeId :: Int, info :: Maybe (NodePoly CorpusInfo) } -- TODO type Props = {nodeId :: Int, info :: Maybe (NodePoly CorpusInfo) }
type PropsRow = (path :: Int, loaded :: Maybe (NodePoly CorpusInfo)) type PropsRow =
( path :: Int
, loaded :: Maybe (NodePoly CorpusInfo)
, dispatch :: Loader.Action Int -> Effect Unit
)
type Props = Record PropsRow type Props = Record PropsRow
-- TODO include Gargantext.Pages.Corpus.Tabs.States -- TODO include Gargantext.Pages.Corpus.Tabs.States
......
...@@ -26,7 +26,7 @@ landingData FR = Fr.landingData ...@@ -26,7 +26,7 @@ landingData FR = Fr.landingData
landingData EN = En.landingData landingData EN = En.landingData
layoutLanding :: Lang -> Spec {} {} Void layoutLanding :: Lang -> Spec {} {} Void
layoutLanding = hideState (unwrap initialState) layoutLanding = hideState (const $ unwrap initialState)
<<< focusState (re _Newtype) <<< focusState (re _Newtype)
<<< layoutLanding' <<< landingData <<< layoutLanding' <<< landingData
......
...@@ -36,7 +36,7 @@ initAppState = ...@@ -36,7 +36,7 @@ initAppState =
, addCorpusState : AC.initialState , addCorpusState : AC.initialState
, searchState : S.initialState , searchState : S.initialState
, userPageState : C.initialState , userPageState : C.initialState
, documentState : D.initialState , documentState : D.initialState {}
, ntreeState : Tree.exampleTree , ntreeState : Tree.exampleTree
, search : "" , search : ""
, showLogin : false , showLogin : false
......
...@@ -24,7 +24,7 @@ setUnsafeComponentWillMount = unsafeSet "unsafeComponentWillMount" ...@@ -24,7 +24,7 @@ setUnsafeComponentWillMount = unsafeSet "unsafeComponentWillMount"
main :: Effect Unit main :: Effect Unit
main = do main = do
case T.createReactSpec layoutSpec initAppState of case T.createReactSpec layoutSpec (const initAppState) of
{ spec, dispatcher } -> void $ do { spec, dispatcher } -> void $ do
let setRouting this = void $ do let setRouting this = void $ do
matches routing (routeHandler (dispatchAction (dispatcher this))) matches routing (routeHandler (dispatchAction (dispatcher this)))
......
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