Commit af59716b authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[DocsTable] refactor thermite -> reactix

parent a357a2d7
...@@ -16,30 +16,33 @@ import Data.HTTP.Method (Method(..)) ...@@ -16,30 +16,33 @@ import Data.HTTP.Method (Method(..))
import Data.Lens import Data.Lens
import Data.Lens.At (at) import Data.Lens.At (at)
import Data.Lens.Record (prop) import Data.Lens.Record (prop)
import Data.Map (Map) import Data.Map (Map, insert)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import Data.Int (fromString) import Data.Int (fromString)
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import React as React import React as React
import React (ReactClass, ReactElement, Children) import React (ReactClass, ReactElement, Children)
import Reactix as R
import Reactix.DOM.HTML as H
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
------------------------------------------------------------------------ ------------------------------------------------------------------------
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType, TabPostQuery(..), toUrl, toLink) import Gargantext.Config (End(..), NodeType(..), OrderBy(..), Path(..), TabType, TabPostQuery(..), toUrl, toLink)
import Gargantext.Config.REST (get, put, post, deleteWithBody, delete) import Gargantext.Config.REST (get, put, post, deleteWithBody, delete)
import Gargantext.Components.Loader as Loader import Gargantext.Components.Loader2 (useLoader)
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Utils.DecodeMaybe ((.|)) import Gargantext.Utils.DecodeMaybe ((.|))
import Gargantext.Router as R import Gargantext.Utils.Reactix as R2
import React.DOM (a, br', button, div, i, input, p, text) import Gargantext.Router as Router
import React.DOM.Props (_type, className, href, onClick, onChange, placeholder, style, checked, target)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState_, simpleSpec, hideState) import Thermite (PerformAction, Render, Spec, defaultPerformAction, modifyState_, simpleSpec, hideState)
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -77,26 +80,25 @@ type Props = ...@@ -77,26 +80,25 @@ type Props =
-- ngramtable. Let's see how this evolves. -- ngramtable. Let's see how this evolves.
} }
type State = type PageLoaderProps =
{ documentIdsDeleted :: Set Int { nodeId :: Int
, localCategories :: Map Int Category , totalRecords :: Int
, mQuery :: Maybe String , tabType :: TabType
, listId :: Int
, corpusId :: Maybe Int
, mQuery :: MQuery
} }
initialState :: State type DocumentIdsDeleted = Set Int
initialState = type LocalCategories = Map Int Category
{ documentIdsDeleted: mempty type MQuery = Maybe String
, localCategories: mempty
, mQuery: Nothing
}
_documentIdsDeleted = prop (SProxy :: SProxy "documentIdsDeleted") _documentIdsDeleted = prop (SProxy :: SProxy "documentIdsDeleted")
_localCategories = prop (SProxy :: SProxy "localCategories") _localCategories = prop (SProxy :: SProxy "localCategories")
data Action data Action
= MarkCategory Int Category = MarkCategory Int Category
| TrashAll
| ChangeQuery (Maybe String)
newtype DocumentsView newtype DocumentsView
= DocumentsView = DocumentsView
...@@ -155,64 +157,51 @@ instance decodeResponse :: DecodeJson Response where ...@@ -155,64 +157,51 @@ instance decodeResponse :: DecodeJson Response where
pure $ Response { cid, category: decodeCategory favorite, ngramCount, hyperdata } pure $ Response { cid, category: decodeCategory favorite, ngramCount, hyperdata }
docViewSpec :: Spec {} Props Void
-- | Filter docViewSpec = R2.elSpec $ R.hooksComponent "DocView" cpt
filterSpec :: forall state props action. Spec state props action
filterSpec = simpleSpec defaultPerformAction render
where where
render d p s c = [] cpt p _children = do
documentIdsDeleted <- R.useState' (mempty :: DocumentIdsDeleted)
localCategories <- R.useState' (mempty :: LocalCategories)
mQuery <- R.useState' (Nothing :: MQuery)
tableParams <- R.useState' T.initialParams
docViewSpec :: Spec {} Props Void pure $ layoutDocview documentIdsDeleted localCategories mQuery tableParams p
docViewSpec = hideState (const initialState) layoutDocview
-- | Main layout of the Documents Tab of a Corpus -- | Main layout of the Documents Tab of a Corpus
layoutDocview :: Spec State Props Action layoutDocview :: R.State DocumentIdsDeleted -> R.State LocalCategories -> R.State MQuery -> R.State T.Params -> Props -> R.Element
layoutDocview = simpleSpec performAction render layoutDocview documentIdsDeleted@(_ /\ setDocumentIdsDeleted) localCategories (mQuery /\ setMQuery) tableParams@(params /\ _) p = R.createElement el p []
where where
performAction :: PerformAction State Props Action el = R.hooksComponent "LayoutDocView" cpt
performAction (MarkCategory nid cat) {nodeId} _ = do cpt {nodeId, tabType, listId, corpusId, totalRecords, chart} _children = do
modifyState_ $ _localCategories <<< at nid ?~ cat pure $ H.div {className: "container1"}
void $ lift $ putCategories nodeId $ CategoryQuery {nodeIds: [nid], category: cat} [ H.div {className: "row"}
performAction TrashAll {nodeId} {documentIdsDeleted} = do [ R2.buff chart
ids <- lift $ deleteAllDocuments nodeId , H.div {}
modifyState_ $ _ {documentIdsDeleted = Set.union documentIdsDeleted $ Set.fromFoldable ids} [ H.input { type: "text"
performAction (ChangeQuery mQuery) _ _ = do , onChange: onChangeQuery
modifyState_ $ _ {mQuery = mQuery} , placeholder: maybe "" identity mQuery}
render :: Render State Props Action
render dispatch {nodeId, tabType, listId, corpusId, totalRecords, chart} state@{mQuery} _ =
[
div [className "container1"]
[ div [className "row"]
[ chart
, div []
[
input [ _type "text"
, onChange $ \e -> dispatch $ ChangeQuery $ if (unsafeEventValue e) == "" then Nothing else Just $ unsafeEventValue e
, placeholder $ maybe "" identity mQuery]
] ]
, div [className "col-md-12"] , H.div {className: "col-md-12"}
[ pageLoader [ pageLoader localCategories tableParams {nodeId, totalRecords, tabType, listId, corpusId, mQuery}
{ path: initialPageParams {nodeId, tabType, listId, corpusId, mQuery} ]
, listId , H.div {className: "col-md-1 col-md-offset-11"}
, corpusId [ H.button { className: "btn"
, totalRecords , style: {backgroundColor: "peru", color : "white", border : "white"}
, state , onClick: onClickTrashAll nodeId
, dispatch }
} [ H.i {className: "glyphitem glyphicon glyphicon-trash"} []
, H.text "Trash all"
]
] ]
, div [className "col-md-1 col-md-offset-11"]
[ button [ className "btn"
, style {backgroundColor: "peru", color : "white", border : "white"}
, onClick $ (\_ -> dispatch TrashAll)
]
[ i [className "glyphitem glyphicon glyphicon-trash"] []
, text "Trash all"
]
]
] ]
] ]
] onChangeQuery = mkEffectFn1 $ \e -> do
setMQuery $ const $ if (unsafeEventValue e) == "" then Nothing else Just $ unsafeEventValue e
onClickTrashAll nodeId = mkEffectFn1 $ \_ -> do
launchAff $ deleteAllDocuments nodeId
-- TODO
-- setDocumentIdsDeleted $ \dids -> Set.union dids (Set.fromFoldable ids)
mock :: Boolean mock :: Boolean
mock = false mock = false
...@@ -224,10 +213,6 @@ type PageParams = { nodeId :: Int ...@@ -224,10 +213,6 @@ type PageParams = { nodeId :: Int
, mQuery :: Maybe String , mQuery :: Maybe String
, params :: T.Params} , params :: T.Params}
initialPageParams :: {nodeId :: Int, listId :: Int, corpusId :: Maybe Int, tabType :: TabType, mQuery :: Maybe String} -> PageParams
initialPageParams {nodeId, listId, corpusId, tabType, mQuery} =
{nodeId, tabType, mQuery, listId, corpusId, params: T.initialParams}
loadPage :: PageParams -> Aff (Array DocumentsView) loadPage :: PageParams -> Aff (Array DocumentsView)
loadPage {nodeId, tabType, mQuery, listId, corpusId, params: {limit, offset, orderBy}} = do loadPage {nodeId, tabType, mQuery, listId, corpusId, params: {limit, offset, orderBy}} = do
logs "loading documents page: loadPage with Offset and limit" logs "loading documents page: loadPage with Offset and limit"
...@@ -264,84 +249,73 @@ loadPage {nodeId, tabType, mQuery, listId, corpusId, params: {limit, offset, ord ...@@ -264,84 +249,73 @@ loadPage {nodeId, tabType, mQuery, listId, corpusId, params: {limit, offset, ord
convOrderBy _ = DateAsc -- TODO convOrderBy _ = DateAsc -- TODO
type PageLoaderProps row = renderPage :: R.State LocalCategories -> R.State T.Params -> PageLoaderProps -> Array DocumentsView -> R.Element
{ path :: PageParams renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res = R.createElement el p []
, totalRecords :: Int
, dispatch :: Action -> Effect Unit
, state :: State
, listId :: Int
, corpusId :: Maybe Int
| row
}
renderPage :: forall props path.
Render (Loader.State {nodeId :: Int, listId :: Int, corpusId :: Maybe Int, tabType :: TabType, mQuery :: Maybe String | path} (Array DocumentsView))
{ totalRecords :: Int
, dispatch :: Action -> Effect Unit
, state :: State
, listId :: Int
, corpusId :: Maybe Int
| props
}
(Loader.Action PageParams)
renderPage _ _ {loaded: Nothing} _ = [] -- TODO loading spinner
renderPage loaderDispatch { totalRecords, dispatch, listId, corpusId
, state: {documentIdsDeleted, localCategories}}
{currentPath: {nodeId, tabType, mQuery}, loaded: Just res} _ =
[
T.tableElt
{ rows
, setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, tabType, listId, corpusId, params, mQuery})
, container: T.defaultContainer { title: "Documents" }
, colNames:
T.ColumnName <$>
[ "Map"
, "Stop"
, "Date"
, "Title"
, "Source"
]
, totalRecords
}
]
where where
el = R.hooksComponent "RenderPage" cpt
gi Favorite = "glyphicon glyphicon-star" gi Favorite = "glyphicon glyphicon-star"
gi _ = "glyphicon glyphicon-star-empty" gi _ = "glyphicon glyphicon-star-empty"
trashStyle Trash = style {textDecoration: "line-through"} trashStyle Trash = {textDecoration: "line-through"}
trashStyle _ = style {textDecoration: "none"} trashStyle _ = {textDecoration: "none"}
getCategory {_id, category} = maybe category identity (localCategories ^. at _id) getCategory {_id, category} = maybe category identity (localCategories ^. at _id)
corpusDocument (Just corpusId) = R.CorpusDocument corpusId corpusDocument (Just corpusId) = Router.CorpusDocument corpusId
corpusDocument _ = R.Document corpusDocument _ = Router.Document
rows = (\(DocumentsView r) ->
let cat = getCategory r cpt {nodeId, corpusId, listId} _children = do
isDel = Trash == cat in pure $ R2.buff $ T.tableElt
{ row: { rows
[ div [] -- , setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, tabType, listId, corpusId, params, mQuery})
[ a [ className $ gi cat , setParams: \params -> setTableParams $ const params
, trashStyle cat , container: T.defaultContainer { title: "Documents" }
, onClick $ \_-> dispatch $ MarkCategory r._id $ favCategory cat , colNames:
] [] T.ColumnName <$>
] [ "Map"
, input [ _type "checkbox" , "Stop"
, checked isDel , "Date"
, onClick $ \_ -> dispatch $ MarkCategory r._id $ trashCategory cat , "Title"
] , "Source"
-- TODO show date: Year-Month-Day only ]
, div [ trashStyle cat ][text (show r.date)] -- , totalRecords
, a [ href (toLink $ (corpusDocument corpusId) listId r._id) , totalRecords: 1000 -- TODO
, trashStyle cat }
, target "_blank" where
] [ text r.title ] rows = (\(DocumentsView r) ->
, div [trashStyle cat] [ text r.source ] let cat = getCategory r
] isDel = Trash == cat in
, delete: true { row: map R2.scuff $ [
}) <$> res H.div {}
[ H.a { className: gi cat
pageLoaderClass :: ReactClass (PageLoaderProps (children :: Children)) , style: trashStyle cat
pageLoaderClass = Loader.createLoaderClass' "PageLoader" loadPage renderPage , onClick: onClick Favorite r._id cat
} []
pageLoader :: PageLoaderProps () -> ReactElement ]
pageLoader props = React.createElement pageLoaderClass props [] , H.input { type: "checkbox"
, checked: isDel
, onClick: onClick 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
onClick catType nid cat = mkEffectFn1 $ \_-> 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}
pageLoader :: R.State LocalCategories -> R.State T.Params -> PageLoaderProps -> R.Element
pageLoader localCategories tableParams@(pageParams /\ _) p = R.createElement el p []
where
el = R.hooksComponent "PageLoader" cpt
cpt p@{nodeId, listId, corpusId, tabType, mQuery} _children = do
useLoader {nodeId, listId, corpusId, tabType, mQuery, params: pageParams} loadPage $ \{loaded} ->
renderPage localCategories tableParams p loaded
--------------------------------------------------------- ---------------------------------------------------------
sampleData' :: DocumentsView sampleData' :: DocumentsView
......
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