Merge Tabs.{Sources,Authors,Terms} as Tabs.Ngrams

WIP: Extend the Table component, use it in NgramsTable
WIP: NgramsTable (plenty of TODO but it builds)
parent ca5fe2f6
......@@ -15,6 +15,14 @@ import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
type TableContainerProps =
{ pageSizeControl :: ReactElement
, pageSizeDescription :: ReactElement
, paginationLinks :: ReactElement
, tableHead :: ReactElement
, tableBody :: Array ReactElement
}
type Rows = Array { row :: Array ReactElement
, delete :: Boolean
}
......@@ -33,10 +41,10 @@ columnName (ColumnName c) = c
data OrderByDirection a = ASC a | DESC a
type Props' =
( title :: String
, colNames :: Array ColumnName
( colNames :: Array ColumnName
, totalRecords :: Int
, loadRows :: LoadRows
, container :: TableContainerProps -> Array ReactElement
)
type Props = Record Props'
......@@ -137,25 +145,35 @@ tableSpec = simpleSpec performAction render
_ -> [lnk (Just (ASC c)) (columnName c)]
render :: Render State Props Action
render dispatch {title, colNames, totalRecords}
render dispatch {container, colNames, totalRecords}
{pageSize, currentPage, orderBy, rows} _ =
let
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)
(maybe [] identity rows)
-- TODO display a loading spinner when rows == Nothing
-- instead of an empty list of results.
}
where
ps = pageSizes2Int pageSize
totalPages = (totalRecords / ps) + min 1 (totalRecords `mod` ps)
in
defaultContainer :: {title :: String} -> TableContainerProps -> Array ReactElement
defaultContainer {title} props =
[ div [className "row"]
[ div [className "col-md-1"] [b [] [text title]]
, div [className "col-md-2"] [sizeDD pageSize dispatch]
, div [className "col-md-3"] [textDescription currentPage pageSize totalRecords]
, div [className "col-md-3"] [pagination (dispatch <<< ChangePage) totalPages currentPage]
, div [className "col-md-2"] [props.pageSizeControl]
, div [className "col-md-3"] [props.pageSizeDescription]
, div [className "col-md-3"] []
]
, table [ className "table"]
[ thead [className "thead-dark"]
[tr [] (renderColHeader (dispatch <<< ChangeOrderBy) orderBy <$> colNames)]
, tbody [] $ map (tr [] <<< map (\c -> td [] [c]) <<< _.row)
(maybe [] identity rows)
-- TODO display a loading spinner when rows == Nothing
-- instead of an empty list of results.
[ thead [className "thead-dark"] [ props.tableHead ]
, tbody [] props.tableBody
]
]
......@@ -193,7 +211,7 @@ sizeDD ps d
textDescription :: Int -> PageSizes -> Int -> ReactElement
textDescription currPage pageSize totalRecords
= div [className "row1"]
[ div [className ""]
[ div [className ""] -- TODO or col-md-6 ?
[ text $ "Showing " <> show start <> " to " <> show end <> " of " <> show totalRecords ]
]
where
......
......@@ -252,7 +252,7 @@ instance decodeJsonLNode :: DecodeJson LNode where
, renameNodeValue : ""
}
instance decodeJsonFTree :: DecodeJson (NTree LNode) where
instance decodeJsonNTree :: DecodeJson a => DecodeJson (NTree a) where
decodeJson json = do
obj <- decodeJson json
node <- obj .? "node"
......
......@@ -18,6 +18,8 @@ import Data.Map as DM
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..))
import Gargantext.Types
endConfig :: EndConfig
endConfig = endConfig' V10
......@@ -113,6 +115,7 @@ toUrl e nt i = doUrl base path params
data NodeType = NodeUser
| Annuaire
| Tab TabType Offset Limit (Maybe OrderBy)
| Ngrams TabType (Maybe TermList)
| Corpus
| CorpusV3
| Dashboard
......@@ -157,6 +160,7 @@ instance showTabType :: Show TabType where
urlConfig :: NodeType -> Url
urlConfig Annuaire = show Annuaire
urlConfig nt@(Tab _ _ _ _) = show nt
urlConfig nt@(Ngrams _ _) = show nt
urlConfig Corpus = show Corpus
urlConfig CorpusV3 = show CorpusV3
urlConfig Dashboard = show Dashboard
......@@ -186,12 +190,21 @@ instance showNodeType :: Show NodeType where
<> "&limit=" <> show l <> os
where
os = maybe "" (\x -> "&order=" <> show x) s
show (Ngrams t listid) = "listGet?ngramsType=" <> show t <> listid'
where
listid' = maybe "" (\x -> "&list=" <> show x) listid
-- | TODO : where is the Read Class ?
-- NP: We don't need the Read class. Here are the encoding formats we need:
-- * JSON
-- * URL parts has in {To,From}HttpApiData but only for certain types
-- The Show class should only be used for dev.
-- instance readNodeType :: Read NodeType where
readNodeType :: String -> NodeType
readNodeType "NodeAnnuaire" = Annuaire
readNodeType "Tab" = (Tab TabDocs 0 0 Nothing)
readNodeType "Ngrams" = (Ngrams TabTerms Nothing)
readNodeType "NodeDashboard" = Dashboard
readNodeType "Document" = Url_Document
readNodeType "NodeFolder" = Folder
......
......@@ -92,7 +92,7 @@ loadedAnnuaireSpec = simpleSpec defaultPerformAction render
, br'
, Table.tableElt
{ loadRows
, title: "title" -- TODO
, container: Table.defaultContainer { title: "title" } -- TODO
, colNames:
Table.ColumnName <$>
[ ""
......
......@@ -3,7 +3,7 @@ module Gargantext.Pages.Corpus.Document where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.?), (.??), (:=), (~>))
import Data.Generic.Rep (class Generic)
import Data.Lens (Lens', Prism', lens, prism, (?~))
import Data.Lens (Lens', lens, (?~))
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..), maybe)
import Data.Either (Either(..))
......
......@@ -5,50 +5,26 @@ import Data.Lens (Prism', prism)
import Data.Either (Either(..))
import Gargantext.Pages.Corpus.Tabs.Documents as DV
import Gargantext.Pages.Corpus.Tabs.Sources as SV
import Gargantext.Pages.Corpus.Tabs.Authors as AV
import Gargantext.Pages.Corpus.Tabs.Terms as TV
import Gargantext.Pages.Corpus.Tabs.Trash as TT
import Gargantext.Pages.Corpus.Tabs.Ngrams as NG
import Gargantext.Components.Tab as Tab
data Action
= DocviewA DV.Action
| SourceviewA SV.Action
| AuthorviewA AV.Action
| TermsviewA TV.Action
| TrashviewA TT.Action
| TabViewA Tab.Action
= DocViewA DV.Action -- = Void
| NgramViewA NG.Action -- = Void
| TabViewA Tab.Action -- = ChangeTab which is only used locally
_docAction :: Prism' Action DV.Action
_docAction = prism DocviewA \ action ->
_docAction = prism DocViewA \ action ->
case action of
DocviewA laction -> Right laction
DocViewA laction -> Right laction
_-> Left action
_authorAction :: Prism' Action AV.Action
_authorAction = prism AuthorviewA \ action ->
_NgramViewA :: Prism' Action NG.Action
_NgramViewA = prism NgramViewA \ action ->
case action of
AuthorviewA laction -> Right laction
NgramViewA laction -> Right laction
_-> Left action
_sourceAction :: Prism' Action SV.Action
_sourceAction = prism SourceviewA \ action ->
case action of
SourceviewA laction -> Right laction
_-> Left action
_termsAction :: Prism' Action TV.Action
_termsAction = prism TermsviewA \ action ->
case action of
TermsviewA laction -> Right laction
_-> Left action
_trashAction :: Prism' Action TT.Action
_trashAction = prism TrashviewA \action ->
case action of
TrashviewA laction -> Right laction
_ -> Left action
_tabAction :: Prism' Action Tab.Action
_tabAction = prism TabViewA \ action ->
case action of
......
module Gargantext.Pages.Corpus.Tabs.Authors where
import Prelude hiding (div)
import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, simpleSpec)
type State = {}
initialState :: State
initialState = {}
type Action = Void
authorSpec :: Spec State {} Action
authorSpec = simpleSpec defaultPerformAction render
where
render :: Render State {} Action
render dispatch _ state _ = []
......@@ -125,7 +125,7 @@ layoutDocview = simpleSpec absurd render
, div [className "col-md-12"]
[ T.tableElt
{ loadRows
, title: "Documents"
, container: T.defaultContainer { title: "Documents" }
, colNames:
T.ColumnName <$>
[ ""
......
module Gargantext.Pages.Corpus.Tabs.Ngrams.NgramsTable where
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Array (filter, toUnfoldable)
import Data.Either (Either(..))
import Data.Newtype (class Newtype, unwrap)
import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Lens.Iso (re)
import Data.Lens.Iso.Newtype (_Newtype)
import Data.List (List)
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..), uncurry)
import Data.Void (Void)
import Data.Unit (Unit)
import Effect (Effect)
import Effect.Aff (Aff)
import React (ReactElement, ReactClass)
import React as React
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 Thermite (PerformAction, Spec, Render, _render, modifyState_, defaultPerformAction, focusState, hideState, simpleSpec, createClass)
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Types
import Gargantext.Components.Table as T
import Gargantext.Prelude
import Gargantext.Config
import Gargantext.Config.REST
import Gargantext.Components.Tree (NTree(..))
import Gargantext.Components.Loader as Loader
type NgramsTable = Array (NTree NgramsElement)
type State =
{ ngramsTable :: NgramsTable
, searchQuery :: String
, termListFilter :: Maybe TermList -- Nothing means all
, termTypeFilter :: Maybe TermType -- Nothing means all
}
initialState :: State
initialState = { ngramsTable: []
, searchQuery: ""
, termListFilter: Nothing
, termTypeFilter: Nothing
}
data Action
= SetTermListItem Int TermList
| SetTermListFilter (Maybe TermList)
| SetTermTypeFilter (Maybe TermType)
| SetSearchQuery String
type Dispatch = Action -> Effect Unit
performAction :: PerformAction State {} Action
performAction (SetTermListFilter c) _ _ = modifyState_ $ _ { termListFilter = c }
performAction (SetTermTypeFilter c) _ _ = modifyState_ $ _ { termTypeFilter = c }
performAction (SetSearchQuery s) _ _ = modifyState_ $ _ { searchQuery = s }
performAction (SetTermListItem _i _l) _ _ = pure unit -- TODO
tableContainer :: {searchQuery :: String, dispatch :: Dispatch} -> T.TableContainerProps -> Array ReactElement
tableContainer {searchQuery, dispatch} 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 :"1.5em"}]
[ span [className "needsaveicon glyphicon glyphicon-import"] []
, button [_id "ImportListOrSaveAll", className "btn btn-warning", style {fontSize : "120%"}]
[ text "Import a Termlist" ]
]
, div [className "col-md-4", style {marginTop : "37px"}]
[ input [ className "form-control "
, _id "id_password"
, name "search", placeholder "Search"
, _type "value"
, value searchQuery
, onInput \e -> dispatch (SetSearchQuery (unsafeEventValue e))
]
]
, div [_id "filter_terms", className "col-md-6", style{ marginTop : "2.1em",paddingLeft :"1em"}]
[ div [className "row", style {marginTop : "6px"}]
[ div [className "col-md-3"]
[ select [ _id "picklistmenu"
, className "form-control custom-select"
, onChange (\e -> dispatch (SetTermListFilter $ readTermList $ unsafeEventValue e))
] $ map optps1 termLists
]
, div [className "col-md-3"]
[ select [ _id "picktermtype"
, className "form-control custom-select"
, style {marginLeft : "1em"}
, onChange (\e -> dispatch (SetTermTypeFilter $ readTermType $ unsafeEventValue e))
] $ map optps1 termTypes
]
, div [className "col-md-3"] [ props.pageSizeControl ]
]
]
, div [className "col-md-6", style {marginTop : "24px", marginBottom : "14px"}]
[ props.pageSizeDescription
, props.paginationLinks
]
]
]
, div [ _id "terms_table", className "panel-body" ]
[ table [ className "table able table-bordered" ]
[ thead [ className "tableHeader table-bordered"] [props.tableHead]
, tbody [] props.tableBody
]
]
]
]
]
]
]
ngramsTableSpec'' = simpleSpec defaultPerformAction (\_ _ _ _ -> [])
ngramsTableSpec' :: Spec State {} Action
ngramsTableSpec' = simpleSpec performAction render
where
render :: Render State {} Action
render dispatch { {-path: nodeId, loaded-} } {searchQuery {- TODO more state -} } _ =
[ T.tableElt
{ loadRows
, container: tableContainer {searchQuery, dispatch}
, colNames:
T.ColumnName <$>
[ "Map"
, "Stop"
, "Terms"
, "Occurences (nb)"
]
, totalRecords: 10 -- TODO
}
]
where
loadRows {offset, limit, orderBy} = do
pure []
{-
_ <- logs "loading documents page"
res <- loadPage {nodeId,offset,limit,orderBy}
_ <- logs "OK: loading page documents."
pure $
(\(DocumentsView r) ->
{ row:
[ div [className $ fa r.fav <> "fa-star"] []
-- TODO show date: Year-Month-Day only
, text r.date
, a [ href (toUrl Front Url_Document r._id) ] [ text r.title ]
, text r.source
, input [ _type "checkbox"]
]
, delete: false
}) <$> res
fa true = "fas "
fa false = "far "
-}
newtype NgramsElement = NgramsElement
{ ngrams :: String
, list :: TermList
, occurrences :: Int
}
instance decodeJsonNgramsElement :: DecodeJson NgramsElement where
decodeJson json = do
obj <- decodeJson json
ngrams <- obj .? "ngrams"
list <- obj .? "list"
occurrences <- obj .? "occurrences"
pure $ NgramsElement {ngrams, list, occurrences}
getNgramsTable :: Int -> Aff NgramsTable
getNgramsTable = get <<< toUrl Back (Ngrams TabTerms Nothing)
ngramsLoaderClass :: ReactClass (Loader.Props Int NgramsTable)
ngramsLoaderClass = Loader.createLoaderClass "NgramsLoader" getNgramsTable
ngramsLoader :: Loader.Props Int NgramsTable -> ReactElement
ngramsLoader = React.createLeafElement ngramsLoaderClass
ngramsTableSpec :: Spec {} {nodeId :: Int} Void
ngramsTableSpec = simpleSpec defaultPerformAction render
where
render :: Render {} {nodeId :: Int} Void
render _ {nodeId} _ _ =
[ ngramsLoader { path: nodeId
, component: createClass "Layout" ngramsTableSpec'' initialState
} ]
renderNgramsItem :: { ngrams :: String
, occurrences :: Int
, termList :: TermList
, setTermList :: TermList -> Effect Unit
} -> Array (Array ReactElement)
renderNgramsItem { ngrams, occurrences, termList, setTermList } =
[ [ checkbox GraphTerm]
, [ checkbox StopTerm]
, [ span [termStyle termList] [text ngrams] ]
, [ text $ show occurrences ]
]
where
checkbox termList' =
input
[ _type "checkbox"
, className "checkbox"
, checked $ termList == termList'
-- , title "Mark as completed"
, onChange $ const $ setTermList termList
]
-- termStyle :: TermList -> {}
termStyle GraphTerm = style {color: "green"}
termStyle StopTerm = style {color: "red", textDecoration : "line-through"}
termStyle CandidateTerm = style {color: "black"}
optps1 :: forall a. Show a => { desc :: String, mval :: Maybe a } -> ReactElement
optps1 { desc, mval } = option [value val] [text desc]
where
val = maybe "" show mval
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
module Gargantext.Pages.Corpus.Tabs.Sources where
import Prelude hiding (div)
import React.DOM (h3, text)
import Thermite (Render, Spec, defaultPerformAction, simpleSpec)
type State = {}
initialState :: State
initialState = {}
type Action = Void
sourceSpec :: Spec State {} Action
sourceSpec = simpleSpec defaultPerformAction render
where
render :: Render State {} Action
render dispatch _ state _ = []
......@@ -6,14 +6,11 @@ import Data.List (fromFoldable)
import Data.Tuple (Tuple(..))
import Gargantext.Pages.Corpus.Tabs.Types (Props)
import Gargantext.Pages.Corpus.Tabs.States (State(), _doclens, _sourcelens, _authorlens, _termslens, _tablens, initialState, _trashlens)
import Gargantext.Pages.Corpus.Tabs.Actions (Action(), _docAction, _sourceAction, _authorAction, _termsAction, _tabAction, _trashAction)
import Gargantext.Pages.Corpus.Tabs.States (State(), _doclens, _ngramsView, _tablens, initialState)
import Gargantext.Pages.Corpus.Tabs.Actions (Action(), _docAction, _NgramViewA, _tabAction)
import Gargantext.Pages.Corpus.Tabs.Documents as DV
import Gargantext.Pages.Corpus.Tabs.Sources as SV
import Gargantext.Pages.Corpus.Tabs.Authors as AV
import Gargantext.Pages.Corpus.Tabs.Terms as TV
import Gargantext.Pages.Corpus.Tabs.Trash as TT
import Gargantext.Pages.Corpus.Tabs.Ngrams as NV
import Gargantext.Components.Tab as Tab
import Thermite (Spec, focus, hideState, cmapProps)
......@@ -33,20 +30,17 @@ statefulTabs =
docPageSpec :: Spec State Props Action
docPageSpec = focus _doclens _docAction DV.layoutDocview
ngramsViewSpec :: NV.Props -> Spec State Props Action
ngramsViewSpec props = cmapProps (const props) (focus _ngramsView _NgramViewA NV.ngramsSpec)
authorPageSpec :: Spec State Props Action
authorPageSpec = cmapProps (const {}) (focus _authorlens _authorAction AV.authorSpec)
-- <> docPageSpec
authorPageSpec = ngramsViewSpec {mode: NV.Authors}
sourcePageSpec :: Spec State Props Action
sourcePageSpec = cmapProps (const {}) (focus _sourcelens _sourceAction SV.sourceSpec)
-- <> docPageSpec
sourcePageSpec = ngramsViewSpec {mode: NV.Sources}
termsPageSpec :: Spec State Props Action
termsPageSpec = cmapProps (const {}) (focus _termslens _termsAction TV.termsSpec)
-- <> docPageSpec
termsPageSpec = ngramsViewSpec {mode: NV.Terms}
trashPageSpec :: Spec State Props Action
trashPageSpec = cmapProps (const {}) (focus _trashlens _trashAction TT.spec)
-- <> docPageSpec
trashPageSpec = ngramsViewSpec {mode: NV.Trash}
......@@ -2,46 +2,28 @@ module Gargantext.Pages.Corpus.Tabs.States where
import Data.Lens (Lens', lens)
import Gargantext.Pages.Corpus.Tabs.Documents as D
import Gargantext.Pages.Corpus.Tabs.Sources as S
import Gargantext.Pages.Corpus.Tabs.Authors as A
import Gargantext.Pages.Corpus.Tabs.Terms as T
import Gargantext.Pages.Corpus.Tabs.Trash as TT
import Gargantext.Pages.Corpus.Tabs.Ngrams as N
import Gargantext.Components.Tab as Tab
type State =
{ docsView :: D.State
, authorsView :: A.State
, sourcesView :: S.State
, termsView :: T.State
, trashView :: TT.State
, ngramsView :: N.State
, activeTab :: Int
}
initialState :: State
initialState =
{ docsView : {}
, authorsView : A.initialState
, sourcesView : S.initialState
, termsView : T.initialState
, trashView : TT.initialState
, ngramsView : N.initialState
, activeTab : 0
}
_doclens :: Lens' State D.State
_doclens = lens (\s -> s.docsView) (\s ss -> s {docsView = ss})
_authorlens :: Lens' State A.State
_authorlens = lens (\s -> s.authorsView) (\s ss -> s {authorsView = ss})
_sourcelens :: Lens' State S.State
_sourcelens = lens (\s -> s.sourcesView) (\s ss -> s {sourcesView = ss})
_termslens :: Lens' State T.State
_termslens = lens (\s -> s.termsView) (\s ss -> s {termsView = ss})
_trashlens :: Lens' State TT.State
_trashlens = lens (\s -> s.trashView) (\s ss -> s {trashView = ss})
_ngramsView :: Lens' State N.State
_ngramsView = lens (\s -> s.ngramsView) (\s ss -> s {ngramsView = ss})
_tablens :: Lens' State Tab.State
_tablens = lens (\s -> s.activeTab) (\s ss -> s {activeTab = ss})
module Gargantext.Pages.Corpus.Tabs.Terms where
import Data.Array (fold)
import Prelude hiding (div)
import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, simpleSpec)
type State = {}
initialState :: State
initialState = {}
type Action = Void
termsSpec :: Spec State {} Action
termsSpec = simpleSpec defaultPerformAction render
where
render :: Render State {} Action
render dispatch _ state _ = []
module Gargantext.Pages.Corpus.Tabs.Terms.NgramsItem where
import Prelude
import Data.Newtype (class Newtype, unwrap)
import Data.Lens.Iso (re)
import Data.Lens.Iso.Newtype (_Newtype)
import React (ReactElement)
import React.DOM (input, span, td, text, tr)
import React.DOM.Props (_type, checked, className, onChange, style, title)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec, hideState, focusState)
import Gargantext.Utils (getter, setter)
newtype State = State
{ term :: Term
}
derive instance newtypeState :: Newtype State _
initialState :: State
initialState = State {term : Term {id : 10, term : "hello", occurrence : 10, _type : None, children : []}}
newtype Term = Term {id :: Int, term :: String, occurrence :: Int, _type :: TermType, children :: Array Term}
derive instance newtypeTerm :: Newtype Term _
data TermType = MapTerm | StopTerm | None
derive instance eqTermType :: Eq TermType
instance showTermType :: Show TermType where
show MapTerm = "MapTerm"
show StopTerm = "StopTerm"
show None = "None"
data Action
= SetMap Boolean
| SetStop Boolean
ngramsItemSpec :: Spec {} {} Void
ngramsItemSpec = hideState (unwrap initialState) $
focusState (re _Newtype) $
simpleSpec performAction render
where
performAction :: PerformAction State {} Action
performAction (SetMap b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then MapTerm else None)}) s.term}
performAction (SetStop b) _ _ = void do
modifyState \(State s) -> State s {term = setter (_{_type = (if b then StopTerm else None)}) s.term}
render :: Render State {} Action
render dispatch _ (State state) _ =
[
tr []
[ td [] [ checkbox_map]
, td [] [ checkbox_stop]
, td [] [ dispTerm (getter _.term state.term) (getter _._type state.term) ]
, td [] [ text $ show $ getter _.occurrence state.term]
]
]
where
checkbox_map =
input [ _type "checkbox"
, className "checkbox"
, checked $ getter _._type state.term == MapTerm
, title "Mark as completed"
, onChange $ dispatch <<< ( const $ SetMap $ not (getter _._type state.term == MapTerm))
]
checkbox_stop =
input
[ _type "checkbox"
, className "checkbox"
, checked $ getter _._type state.term == StopTerm
, title "Mark as completed"
, onChange $ dispatch <<< ( const $ SetStop $ not (getter _._type state.term == StopTerm))
]
dispTerm :: String -> TermType -> ReactElement
dispTerm term MapTerm = span [style {color :"green"}] [text $ term]
dispTerm term StopTerm = span [style {color :"red", textDecoration : "line-through"}] [text $ term]
dispTerm term None = span [style {color :"black"}] [text term]
module Gargantext.Pages.Corpus.Tabs.Trash where
import Data.Array (fold)
import Prelude hiding (div)
import React.DOM (h3, text)
import Thermite (PerformAction, Render, Spec, defaultPerformAction, simpleSpec)
type State = {}
initialState :: State
initialState = {}
type Action = Void
spec :: Spec State {} Action
spec = simpleSpec defaultPerformAction render
where
render :: Render State {} Action
render dispatch _ state _ = []
......@@ -21,7 +21,7 @@ import Gargantext.Pages.Corpus as Corpus
import Gargantext.Pages.Corpus.Document as Annotation
import Gargantext.Pages.Corpus.Dashboard as Dsh
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Corpus.Tabs.Terms.NgramsTable as NG
import Gargantext.Pages.Corpus.Tabs.Ngrams.NgramsTable as NG
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _treeAction, _userPageAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
......@@ -65,7 +65,8 @@ pagesComponent s = case s.currentRoute of
selectSpec (Annuaire i) = layout0 $ cmapProps (const {annuaireId: i}) $ noState A.layout
selectSpec (UserPage i) = layout0 $ focus _userPageState _userPageAction C.layoutUser
-- To be removed
selectSpec NGramsTable = layout0 $ noState NG.ngramsTableSpec
selectSpec NGramsTable = layout0 $ cmapProps (const {nodeId: i}) $ noState NG.ngramsTableSpec
where i = 0 -- TODO
-- selectSpec _ = simpleSpec defaultPerformAction defaultRender
......
module Gargantext.Types where
import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Maybe (Maybe(..))
import Gargantext.Prelude
data TermType = MonoTerm | MultiTerm
derive instance eqTermType :: Eq TermType
instance showTermType :: Show TermType where
show MonoTerm = "MonoTerm"
show MultiTerm = "MultiTerm"
readTermType :: String -> Maybe TermType
readTermType "MonoTerm" = Just MonoTerm
readTermType "MultiTerm" = Just MultiTerm
readTermType _ = Nothing
termTypes :: Array { desc :: String, mval :: Maybe TermType }
termTypes = [ { desc: "All types", mval: Nothing }
, { desc: "One-word terms", mval: Just MonoTerm }
, { desc: "Multi-word terms", mval: Just MultiTerm }
]
data TermList = GraphTerm | StopTerm | CandidateTerm
derive instance eqTermList :: Eq TermList
instance decodeJsonTermList :: DecodeJson TermList where
decodeJson json = pure GraphTerm -- TODO
type ListTypeId = Int
listTypeId :: TermList -> ListTypeId
listTypeId GraphTerm = 1
listTypeId StopTerm = 2
listTypeId CandidateTerm = 3
instance showTermList :: Show TermList where
show GraphTerm = "Graph"
show StopTerm = "Stop"
show CandidateTerm = "Candidate"
readTermList :: String -> Maybe TermList
readTermList "Graph" = Just GraphTerm
readTermList "Stop" = Just StopTerm
readTermList "Candidate" = Just CandidateTerm
readTermList _ = Nothing
termLists :: Array { desc :: String, mval :: Maybe TermList }
termLists = [ { desc: "All terms", mval: Nothing }
, { desc: "Graph terms", mval: Just GraphTerm }
, { desc: "Stop terms", mval: Just StopTerm }
, { desc: "Candidate terms", mval: Just CandidateTerm }
]
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