Commit 729f7840 authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev-doc-table-columns' into dev

parents 88cdabd4 74638ba3
......@@ -22,15 +22,17 @@ import Data.Set (Set)
import Data.Set as Set
import Data.Int (fromString)
import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..))
import Data.Tuple (Tuple(..), fst)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Event as DE
import Effect (Effect)
import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import Effect.Uncurried (EffectFn1, mkEffectFn1)
import React as React
import React (ReactClass, ReactElement, Children)
import Reactix as R
import Reactix.SyntheticEvent as RE
import Reactix.DOM.HTML as H
import Unsafe.Coerce (unsafeCoerce)
------------------------------------------------------------------------
......@@ -76,6 +78,7 @@ type Props =
, tabType :: TabType
, listId :: Int
, corpusId :: Maybe Int
, showSearch :: Boolean
-- ^ tabType is not ideal here since it is too much entangled with tabs and
-- ngramtable. Let's see how this evolves.
}
......@@ -86,12 +89,11 @@ type PageLoaderProps =
, tabType :: TabType
, listId :: Int
, corpusId :: Maybe Int
, mQuery :: MQuery
, query :: Query
}
type DocumentIdsDeleted = Set Int
type LocalCategories = Map Int Category
type MQuery = Maybe String
type Query = String
_documentIdsDeleted = prop (SProxy :: SProxy "documentIdsDeleted")
_localCategories = prop (SProxy :: SProxy "localCategories")
......@@ -162,30 +164,23 @@ docViewSpec p = R.createElement el p []
where
el = R.hooksComponent "DocView" cpt
cpt p _children = do
documentIdsDeleted <- R.useState' (mempty :: DocumentIdsDeleted)
localCategories <- R.useState' (mempty :: LocalCategories)
mQuery <- R.useState' (Nothing :: MQuery)
query <- R.useState' ("" :: Query)
tableParams <- R.useState' T.initialParams
pure $ layoutDocview documentIdsDeleted localCategories mQuery tableParams p
pure $ layoutDocview query tableParams p
-- | Main layout of the Documents Tab of a Corpus
layoutDocview :: R.State DocumentIdsDeleted -> R.State LocalCategories -> R.State MQuery -> R.State T.Params -> Props -> R.Element
layoutDocview documentIdsDeleted@(_ /\ setDocumentIdsDeleted) localCategories (mQuery /\ setMQuery) tableParams@(params /\ _) p = R.createElement el p []
layoutDocview :: R.State Query -> R.State T.Params -> Props -> R.Element
layoutDocview query tableParams@(params /\ _) p = R.createElement el p []
where
el = R.hooksComponent "LayoutDocView" cpt
cpt {nodeId, tabType, listId, corpusId, totalRecords, chart} _children = do
cpt {nodeId, tabType, listId, corpusId, totalRecords, chart, showSearch} _children = do
pure $ H.div {className: "container1"}
[ H.div {className: "row"}
[ chart
, H.div {}
[ H.input { type: "text"
, onChange: onChangeQuery
, placeholder: maybe "" identity mQuery}
]
, if showSearch then searchBar query else H.div {} []
, H.div {className: "col-md-12"}
[ pageLoader localCategories tableParams {nodeId, totalRecords, tabType, listId, corpusId, mQuery}
]
[ pageLoader 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"}
......@@ -197,12 +192,46 @@ layoutDocview documentIdsDeleted@(_ /\ setDocumentIdsDeleted) localCategories (m
]
]
]
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)
searchBar :: R.State Query -> R.Element
searchBar (query /\ setQuery) = R.createElement el {} []
where
el = R.hooksComponent "SearchBar" cpt
cpt {} _children = do
queryText <- R.useState' query
pure $ H.div {className: "row"}
[ H.div {className: "col col-md-3 form-group"}
[ H.input { type: "text"
, className: "form-control"
, on: {change: onSearchChange queryText, keyUp: onSearchKeyup queryText}
, placeholder: query}
]
, H.div {className: "col col-md-1"}
[ H.button { type: "submit"
, className: "btn btn-default"
, on: {click: onSearchClick queryText}}
[ H.text "Search" ]
]
]
onSearchChange :: forall e. R.State Query -> e -> Effect Unit
onSearchChange (_ /\ setQueryText) = \e ->
setQueryText $ const $ R2.unsafeEventValue e
onSearchKeyup :: R.State Query -> DE.KeyboardEvent -> Effect Unit
onSearchKeyup (queryText /\ _) = \e ->
if DE.key e == "Enter" then
setQuery $ const queryText
else
pure $ unit
onSearchClick :: forall e. R.State Query -> e -> Effect Unit
onSearchClick (queryText /\ _) = \e ->
setQuery $ const queryText
mock :: Boolean
mock = false
......@@ -211,20 +240,20 @@ type PageParams = { nodeId :: Int
, listId :: Int
, corpusId :: Maybe Int
, tabType :: TabType
, mQuery :: Maybe String
, query :: Query
, params :: T.Params}
loadPage :: PageParams -> Aff (Array DocumentsView)
loadPage {nodeId, tabType, mQuery, listId, corpusId, params: {limit, offset, orderBy}} = do
loadPage {nodeId, tabType, query, listId, corpusId, params: {limit, offset, orderBy}} = do
logs "loading documents page: loadPage with Offset and limit"
-- res <- get $ toUrl Back (Tab tabType offset limit (convOrderBy <$> orderBy)) (Just nodeId)
let url = (toUrl Back Node (Just nodeId)) <> "/table"
res <- post url $ TabPostQuery {
offset
, limit
, orderBy: convOrderBy <$> orderBy
, orderBy: convOrderBy orderBy
, tabType
, mQuery
, query
}
let docs = res2corpus <$> res
pure $
......@@ -241,17 +270,17 @@ loadPage {nodeId, tabType, mQuery, listId, corpusId, params: {limit, offset, ord
, category : r.category
, ngramCount : r.ngramCount
}
convOrderBy (T.ASC (T.ColumnName "Date")) = DateAsc
convOrderBy (T.DESC (T.ColumnName "Date")) = DateDesc
convOrderBy (T.ASC (T.ColumnName "Title")) = TitleAsc
convOrderBy (T.DESC (T.ColumnName "Title")) = TitleDesc
convOrderBy (T.ASC (T.ColumnName "Source")) = SourceAsc
convOrderBy (T.DESC (T.ColumnName "Source")) = SourceDesc
convOrderBy (Just (T.ASC (T.ColumnName "Date"))) = DateAsc
convOrderBy (Just (T.DESC (T.ColumnName "Date"))) = DateDesc
convOrderBy (Just (T.ASC (T.ColumnName "Title"))) = TitleAsc
convOrderBy (Just (T.DESC (T.ColumnName "Title"))) = TitleDesc
convOrderBy (Just (T.ASC (T.ColumnName "Source"))) = SourceAsc
convOrderBy (Just (T.DESC (T.ColumnName "Source"))) = SourceDesc
convOrderBy _ = DateAsc -- TODO
renderPage :: R.State LocalCategories -> R.State T.Params -> PageLoaderProps -> Array DocumentsView -> R.Element
renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res = R.createElement el p []
renderPage :: R.State T.Params -> PageLoaderProps -> Array DocumentsView -> R.Element
renderPage (_ /\ setTableParams) p res = R.createElement el p []
where
el = R.hooksComponent "RenderPage" cpt
......@@ -259,14 +288,15 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res =
gi _ = "glyphicon glyphicon-star-empty"
trashStyle Trash = {textDecoration: "line-through"}
trashStyle _ = {textDecoration: "none"}
getCategory {_id, category} = maybe category identity (localCategories ^. at _id)
corpusDocument (Just corpusId) = Router.CorpusDocument corpusId
corpusDocument _ = Router.Document
cpt {nodeId, corpusId, listId} _children = do
localCategories <- R.useState' (mempty :: LocalCategories)
pure $ R2.buff $ T.tableElt
{ rows
-- , setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, tabType, listId, corpusId, params, mQuery})
{ rows: rows localCategories
-- , setParams: \params -> liftEffect $ loaderDispatch (Loader.SetPath {nodeId, tabType, listId, corpusId, params, query})
, setParams: \params -> setTableParams $ const params
, container: T.defaultContainer { title: "Documents" }
, colNames:
......@@ -281,19 +311,20 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res =
, totalRecords: 1000 -- TODO
}
where
rows = (\(DocumentsView r) ->
let cat = getCategory r
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
, onClick: onClick Favorite r._id cat
, on: {click: onClick localCategories Favorite r._id cat}
} []
]
, H.input { type: "checkbox"
, checked: isDel
, onClick: onClick Trash r._id cat
, 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) ]
......@@ -305,18 +336,18 @@ renderPage (localCategories /\ setLocalCategories) (_ /\ setTableParams) p res =
]
, delete: true
}) <$> res
onClick catType nid cat = mkEffectFn1 $ \_-> do
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}
pageLoader :: R.State LocalCategories -> R.State T.Params -> PageLoaderProps -> R.Element
pageLoader localCategories tableParams@(pageParams /\ _) p = R.createElement el p []
pageLoader :: R.State T.Params -> PageLoaderProps -> R.Element
pageLoader 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
cpt p@{nodeId, listId, corpusId, tabType, query} _children = do
useLoader {nodeId, listId, corpusId, tabType, query, params: pageParams} loadPage $ \{loaded} ->
renderPage tableParams p loaded
---------------------------------------------------------
sampleData' :: DocumentsView
......@@ -389,6 +420,3 @@ toggleSet :: forall a. Ord a => a -> Set a -> Set a
toggleSet a s
| Set.member a s = Set.delete a s
| otherwise = Set.insert a s
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
......@@ -22,6 +22,7 @@ import Gargantext.Config (toUrl, Path(..), End(..))
import Gargantext.Config.REST (post)
import Gargantext.Components.Modals.Modal (modalHide)
import Gargantext.Components.Login.Types
import Gargantext.Utils.Reactix as R2
-- TODO: ask for login (modal) or account creation after 15 mn when user
-- is not logged and has made one search at least
......@@ -128,10 +129,10 @@ renderSpec = simpleSpec performAction render
, div [className "form-group"]
[ p [] [text state.errorMessage]
, input [className "form-control", _id "id_username",maxLength "254", name "username", placeholder "username", _type "text",value state.username, onInput \e -> dispatch (SetUserName (unsafeEventValue e))]
, input [className "form-control", _id "id_username",maxLength "254", name "username", placeholder "username", _type "text",value state.username, onInput \e -> dispatch (SetUserName $ R2.unsafeEventValue e)]
]
, div [className "form-group"]
[ input [className "form-control", _id "id_password", name "password", placeholder "password", _type "password",value state.password,onInput \e -> dispatch (SetPassword (unsafeEventValue e))]
[ input [className "form-control", _id "id_password", name "password", placeholder "password", _type "password",value state.password,onInput \e -> dispatch (SetPassword $ R2.unsafeEventValue e)]
, div [className "clearfix"] []
]
, div [className "center"]
......@@ -186,10 +187,6 @@ renderSpec = simpleSpec performAction render
-- ]
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
getAuthData :: Effect (Maybe AuthData)
getAuthData = do
w <- window
......
......@@ -40,6 +40,7 @@ import Gargantext.Components.Table as T
import Gargantext.Prelude
import Gargantext.Components.Loader as Loader
import Gargantext.Components.NgramsTable.Core
import Gargantext.Utils.Reactix as R2
type State =
CoreState
......@@ -119,7 +120,7 @@ tableContainer { pageParams
, name "search", placeholder "Search"
, _type "value"
, value pageParams.searchQuery
, onInput \e -> setSearchQuery (unsafeEventValue e)
, onInput \e -> setSearchQuery (R2.unsafeEventValue e)
]
, div [] (
if A.null props.tableBody && pageParams.searchQuery /= "" then [
......@@ -134,7 +135,7 @@ tableContainer { pageParams
[ select [ _id "picklistmenu"
, className "form-control custom-select"
, value (maybe "" show pageParams.termListFilter)
, onChange (\e -> setTermListFilter $ readTermList $ unsafeEventValue e)
, onChange (\e -> setTermListFilter $ readTermList $ R2.unsafeEventValue e)
] $ map optps1 termLists
]
]
......@@ -143,7 +144,7 @@ tableContainer { pageParams
[ select [ _id "picktermtype"
, className "form-control custom-select"
, value (maybe "" show pageParams.termSizeFilter)
, onChange (\e -> setTermSizeFilter $ readTermSize $ unsafeEventValue e)
, onChange (\e -> setTermSizeFilter $ readTermSize $ R2.unsafeEventValue e)
] $ map optps1 termSizes
]
]
......@@ -420,6 +421,3 @@ optps1 :: forall a. Show a => { desc :: String, mval :: Maybe a } -> ReactElemen
optps1 { desc, mval } = option [value val] [text desc]
where
val = maybe "" show mval
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
......@@ -14,6 +14,7 @@ import Thermite (PerformAction, Render, Spec, modifyState_, simpleSpec, StateCoT
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Utils.Reactix as R2
type TableContainerProps =
{ pageSizeControl :: ReactElement
......@@ -218,7 +219,7 @@ sizeDD :: PageSizes -> (Action -> Effect Unit) -> ReactElement
sizeDD ps d
= span []
[ select [ className "form-control"
, onChange (\e -> d (ChangePageSize $ string2PageSize $ (unsafeCoerce e).target.value))
, onChange (\e -> d (ChangePageSize $ string2PageSize $ R2.unsafeEventValue e))
] $ map (optps ps) aryPS
]
......
......@@ -695,6 +695,3 @@ uploadFile id fileType (UploadFileContents fileContents) = postWwwUrlencoded url
fnTransform :: LNode -> FTree
fnTransform n = NTree n []
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
......@@ -142,9 +142,9 @@ showTabType' (TabPairing t) = show t
data TabPostQuery = TabPostQuery {
offset :: Int
, limit :: Int
, orderBy :: Maybe OrderBy
, orderBy :: OrderBy
, tabType :: TabType
, mQuery :: Maybe String
, query :: String
}
instance encodeJsonTabPostQuery :: EncodeJson TabPostQuery where
......@@ -153,7 +153,7 @@ instance encodeJsonTabPostQuery :: EncodeJson TabPostQuery where
~> "offset" := post.offset
~> "limit" := post.limit
~> "orderBy" := show post.orderBy
~> "query" := post.mQuery
~> "query" := post.query
~> jsonEmptyObject
pathUrl :: Config -> Path -> Maybe Id -> UrlPath
......
......@@ -78,7 +78,9 @@ statefulTabs =
, tabType: TabPairing TabDocs
, totalRecords: 4736
, listId: defaultListId
, corpusId: Nothing}
, corpusId: Nothing
, showSearch: true
}
ngramsViewSpec :: {mode :: Mode} -> Spec Tab.State Props Tab.Action
ngramsViewSpec {mode} =
......
......@@ -419,7 +419,7 @@ specOld = fold [treespec treeSpec, graphspec $ simpleSpec performAction render']
Nothing ->
simpleSpec defaultPerformAction defaultRender
Just treeId ->
(cmapProps (const {root: treeId, mCurrentRoute: Nothing}) (noState Tree.treeview))
cmapProps (const {root: treeId, mCurrentRoute: Nothing}) $ noState $ Tree.treeview
render' :: Render State {} Action
......
......@@ -5,8 +5,10 @@ import Data.Lens (over)
import Data.Maybe (Maybe(Nothing, Just))
import Effect (Effect)
import React (ReactElement)
import React.DOM (a, button, div, footer, hr', img, li, p, span, text, ul)
import React.DOM.Props (_data, _id, aria, className, href, onClick, role, src, style, tabIndex, target, title, height, width)
import React.DOM (button, div, text)
import React.DOM.Props (_id, className, onClick, role, style)
import Reactix as R
import Reactix.DOM.HTML as H
import Thermite (Render, Spec, _render, defaultPerformAction, defaultRender, focus, simpleSpec, withState, noState, cmapProps)
-- import Unsafe.Coerce (unsafeCoerce)
......@@ -31,7 +33,7 @@ import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Specs.SearchBar as SB
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _graphExplorerState, _loginState, _searchState)
import Gargantext.Router (Routes(..))
import Gargantext.Utils.Reactix (scuff)
import Gargantext.Utils.Reactix as R2
layoutSpec :: Spec AppState {} Action
layoutSpec =
......@@ -83,7 +85,7 @@ layout0 layout =
fold
[ searchBar
, outerLayout
, layoutFooter
, noState layoutFooter
]
where
outerLayout1 = simpleSpec defaultPerformAction defaultRender
......@@ -94,7 +96,7 @@ layout0 layout =
withState \st ->
case st.loginState.authData of
Just (AuthData {tree_id}) ->
ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute}) as
ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute}) $ noState $ Tree.treeview
Nothing ->
outerLayout1
, rs bs
......@@ -111,8 +113,6 @@ layout0 layout =
] (render d p s c) ]
cont = over _render \render d p s c -> [ div [className "row" ] (render d p s c) ]
as = noState Tree.treeview
bs = innerLayout $ layout
innerLayout :: Spec AppState {} Action
......@@ -132,7 +132,7 @@ layout1 layout =
[ searchBar
, layout
-- , outerLayout
, layoutFooter
, noState layoutFooter
]
where
outerLayout1 = simpleSpec defaultPerformAction defaultRender
......@@ -142,7 +142,7 @@ layout1 layout =
[ withState \st ->
case st.loginState.authData of
Just (AuthData {tree_id}) ->
ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute}) as
ls $ cmapProps (const {root: tree_id, mCurrentRoute: st.currentRoute}) $ noState $ Tree.treeview
Nothing ->
outerLayout1
, rs bs
......@@ -156,8 +156,6 @@ layout1 layout =
rs = over _render \render d p s c -> [ div [if (s.showTree) then className "col-md-10" else className "col-md-12"] (render d p s c) ]
cont = over _render \render d p s c -> [ div [className "row" ] (render d p s c) ]
as = noState Tree.treeview
bs = innerLayout $ layout
innerLayout :: Spec AppState {} Action
......@@ -180,29 +178,29 @@ searchBar = simpleSpec defaultPerformAction render
] [ div [className "container-fluid"
]
[ div [ className "navbar-inner" ]
[ divLogo
[ R2.scuff divLogo
, div [ className "collapse navbar-collapse"
]
$ [ divDropdownLeft ]
<> [ scuff (SB.searchBar SB.defaultProps) ]
<> [ divDropdownRight d s ]
$ [ R2.scuff divDropdownLeft ]
<> [ R2.scuff (SB.searchBar SB.defaultProps) ]
<> [ R2.scuff $ divDropdownRight d s ]
]
]
]
]
divLogo :: ReactElement
divLogo = a [ className "navbar-brand logoSmall"
, href "#/"
] [ img [ src "images/logoSmall.png"
, title "Back to home."
, width "30"
, height "28"
]
]
divLogo :: R.Element
divLogo = H.a { className: "navbar-brand logoSmall"
, href: "#/"
} [ H.img { src: "images/logoSmall.png"
, title: "Back to home."
, width: "30"
, height: "28"
}
]
divDropdownLeft :: ReactElement
divDropdownLeft :: R.Element
divDropdownLeft = divDropdownLeft' (LiNav { title : "About Gargantext"
, href : "#"
, icon : "glyphicon glyphicon-info-sign"
......@@ -210,32 +208,33 @@ divDropdownLeft = divDropdownLeft' (LiNav { title : "About Gargantext"
}
)
divDropdownLeft' :: LiNav -> ReactElement
divDropdownLeft' mb = ul [className "nav navbar-nav"]
[ ul [className "nav navbar-nav pull-left"]
[ li [className "dropdown"]
[ menuButton mb
, menuElements'
]
]
]
divDropdownLeft' :: LiNav -> R.Element
divDropdownLeft' mb = H.ul {className: "nav navbar-nav"}
[ H.ul {className: "nav navbar-nav pull-left"}
[ H.li {className: "dropdown"}
[ menuButton mb
, menuElements'
]
]
]
menuButton :: LiNav -> ReactElement
menuButton :: LiNav -> R.Element
menuButton (LiNav { title : title'
, href : href'
, icon : icon'
, text : text'
}) = a [ className "dropdown-toggle navbar-text"
, _data {toggle: "dropdown"}
, href href', role "button"
, title title'
][ span [ aria {hidden : true}
, className icon'
] []
, text (" " <> text')
]
menuElements' :: ReactElement
}) = H.a { className: "dropdown-toggle navbar-text"
, data: {toggle: "dropdown"}
, href: href'
, role: "button"
, title: title'
} [ H.span { aria: {hidden : true}
, className: icon'
} []
, H.text (" " <> text')
]
menuElements' :: R.Element
menuElements' = menuElements-- title, icon, text
[ -- ===========================================================
[ LiNav { title : "Quick start, tutorials and methodology"
......@@ -271,14 +270,14 @@ menuElements' = menuElements-- title, icon, text
] -- ===========================================================
-- | Menu in the sidebar, syntactic sugar
menuElements :: Array (Array LiNav) -> ReactElement
menuElements :: Array (Array LiNav) -> R.Element
menuElements ns = dropDown $ intercalate divider $ map (map liNav) ns
where
dropDown :: Array ReactElement -> ReactElement
dropDown = ul [className "dropdown-menu"]
dropDown :: Array R.Element -> R.Element
dropDown = H.ul {className: "dropdown-menu"}
divider :: Array ReactElement
divider = [li [className "divider"] []]
divider :: Array R.Element
divider = [H.li {className: "divider"} []]
-- | surgar for target : "blank"
--data LiNav_ = LiNav_ { title :: String
......@@ -294,77 +293,78 @@ data LiNav = LiNav { title :: String
, text :: String
}
liNav :: LiNav -> ReactElement
liNav :: LiNav -> R.Element
liNav (LiNav { title : title'
, href : href'
, icon : icon'
, text : text'
}
) = li [] [ a [ tabIndex (-1)
, target "blank"
, title title'
, href href'
] [ span [ className icon' ] []
, text $ " " <> text'
]
]
) = H.li {} [ H.a { tabIndex: (-1)
, target: "blank"
, title: title'
, href: href'
} [ H.span { className: icon' } []
, H.text $ " " <> text'
]
]
logLinks :: (Action -> Effect Unit) -> AppState -> ReactElement
logLinks :: (Action -> Effect Unit) -> AppState -> R.Element
logLinks d s = case s.loginState.authData of
Nothing -> loginLink
Just _ -> logoutLink
where
loginLink =
a [ aria {hidden : true}
, className "glyphicon glyphicon-log-in"
, onClick $ \e -> d ShowLogin
, style {color:"white"}
, title "Log in and save your time"
-- TODO hover: bold
]
[text " Login / Signup"]
H.a { aria: {hidden : true}
, className: "glyphicon glyphicon-log-in"
, on: {click: \e -> d ShowLogin}
, style: {color:"white"}
, title: "Log in and save your time"
-- TODO hover: bold
}
[H.text " Login / Signup"]
-- TODO dropdown to logout
logoutLink =
a [ aria {hidden : true}
, className "glyphicon glyphicon-log-out"
, onClick $ \e -> d Logout
, style {color:"white"}
, title "Log out" -- TODO
-- TODO hover: bold
]
[text " Logout"]
H.a { aria: {hidden : true}
, className: "glyphicon glyphicon-log-out"
, on: {click: \e -> d Logout}
, style: {color:"white"}
, title: "Log out" -- TODO
-- TODO hover: bold
}
[H.text " Logout"]
divDropdownRight :: (Action -> Effect Unit) -> AppState -> ReactElement
divDropdownRight :: (Action -> Effect Unit) -> AppState -> R.Element
divDropdownRight d s =
ul [className "nav navbar-nav pull-right"]
[ li [className "dropdown"]
[ logLinks d s ]
]
H.ul {className: "nav navbar-nav pull-right"}
[ H.li {className: "dropdown"}
[ logLinks d s ]
]
layoutFooter :: Spec AppState {} Action
layoutFooter = simpleSpec performAction render
layoutFooter :: Spec {} {} Void
layoutFooter = R2.elSpec $ R.hooksComponent "LayoutFooter" cpt
where
render :: Render AppState {} Action
render dispatch _ state _ = [div [ className "container" ] [ hr', footerLegalInfo']]
where
footerLegalInfo' = footer [] [ p [] [ text "Gargantext "
, span [className "glyphicon glyphicon-registration-mark" ] []
, text ", version 4.0"
, a [ href "http://www.cnrs.fr"
, target "blank"
, title "Project hosted by CNRS."
]
[ text ", Copyrights "
, span [ className "glyphicon glyphicon-copyright-mark" ] []
, text " CNRS 2017-Present"
]
, a [ href "http://gitlab.iscpif.fr/humanities/gargantext/blob/stable/LICENSE"
, target "blank"
, title "Legal instructions of the project."
]
[ text ", Licences aGPLV3 and CECILL variant Affero compliant" ]
, text "."
]
]
cpt {} _children = do
pure $ H.div { className: "container" } [ H.hr {}, footerLegalInfo']
footerLegalInfo' = H.footer {}
[ H.p {} [ H.text "Gargantext "
, H.span {className: "glyphicon glyphicon-registration-mark"} []
, H.text ", version 4.0"
, H.a { href: "http://www.cnrs.fr"
, target: "blank"
, title: "Project hosted by CNRS."
}
[ H.text ", Copyrights "
, H.span { className: "glyphicon glyphicon-copyright-mark" } []
, H.text " CNRS 2017-Present"
]
, H.a { href: "http://gitlab.iscpif.fr/humanities/gargantext/blob/stable/LICENSE"
, target: "blank"
, title: "Legal instructions of the project."
}
[ H.text ", Licences aGPLV3 and CECILL variant Affero compliant" ]
, H.text "."
]
]
......@@ -7,7 +7,8 @@ import React.DOM (br', button, div, input, text)
import React.DOM.Props (_id, _type, className, name, onClick, onInput, placeholder, value)
import Routing.Hash (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Utils.Reactix as R2
type State =
{
......@@ -26,20 +27,16 @@ data Action
= GO
| SetQuery String
performAction :: PerformAction State {} Action
performAction (SetQuery q) _ _ = void do
modifyState $ _ { query = q }
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
performAction GO _ _ = void do
liftEffect $ setHash "/addCorpus"
searchSpec :: Spec State {} Action
searchSpec = simpleSpec performAction render
where
performAction :: PerformAction State {} Action
performAction (SetQuery q) _ _ = void do
modifyState $ _ { query = q }
performAction GO _ _ = void do
liftEffect $ setHash "/addCorpus"
render :: Render State {} Action
render dispatch _ state _ =
[ div [className "container1"] []
......@@ -56,7 +53,7 @@ searchSpec = simpleSpec performAction render
, placeholder "Query, URL or FILE (works best with Firefox or Chromium browsers)"
, _type "text"
, value state.query
, onInput \e -> dispatch (SetQuery (unsafeEventValue e))
, onInput \e -> dispatch (SetQuery (R2.unsafeEventValue e))
]
, br'
]
......
......@@ -89,6 +89,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: true
}
params TabMoreLikeFav = {
nodeId: corpusId
......@@ -98,6 +99,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: false
}
params TabMoreLikeTrash = {
nodeId: corpusId
......@@ -107,6 +109,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737
, listId: defaultListId
, corpusId: Just corpusId
, showSearch: false
}
params TabTrash = {
nodeId: corpusId
......@@ -116,6 +119,7 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737
, listId: defaultListId
, corpusId: Nothing
, showSearch: true
}
-- DUMMY
params _ = {
......@@ -126,4 +130,5 @@ docViewSpec tst = R2.elSpec $ R.hooksComponent "DocViewSpecWithCorpus" cpt
, totalRecords: 4737
, listId: defaultListId
, corpusId: Nothing
, showSearch: true
}
......@@ -89,3 +89,7 @@ select = createDOMElement "select"
effToggler :: forall e. R.State Boolean -> EffectFn1 e Unit
effToggler (value /\ setValue) = mkEffectFn1 $ \e -> setValue $ const $ not value
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
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