Commit 76e18024 authored by Abinaya Sudhir's avatar Abinaya Sudhir

pulled code

parents ac67045d dfb784a8
......@@ -30,6 +30,7 @@ import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, _render, cotransform, focus, foreach, modifyState, simpleSpec, withState)
import Unsafe.Coerce (unsafeCoerce)
import Landing as L
type State =
......@@ -61,7 +62,10 @@ data Action
| GO
performAction :: forall eff props. PerformAction (console :: CONSOLE, ajax :: AJAX,dom::DOM | eff) State props Action
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff ) State props Action
performAction NoOp _ _ = void do
modifyState id
......@@ -91,7 +95,8 @@ addcorpusviewSpec = simpleSpec performAction render
render :: Render State props Action
render dispatch _ state _ =
[
div [className "container"]
div [className "container"] [L.jumboTitle false]
, div [className "container"]
[
div [className "jumbotron"]
[ div [className "row"]
......
......@@ -51,9 +51,9 @@ type EchartsProps eff =
option :: Option, -- PropTypes.object.isRequired,
initOpts :: String, -- PropTypes.object,
notMerge :: Boolean,
lazyUpdate:: Boolean,
lazyUpdate :: Boolean,
loading :: Boolean,
optsLoading:: OptsLoading, -- PropTypes.object,
optsLoading :: OptsLoading, -- PropTypes.object,
onReady :: String, -- PropTypes.func,
resizable :: Boolean, -- PropTypes.bool,
onEvents :: String -- PropTypes.object
......@@ -63,7 +63,7 @@ type OptsLoading =
{ text :: String,
color :: Color, --- color
textColor :: Color, --color
maskColor:: Color, --color
maskColor :: Color, --color
zlevel :: Int
}
......@@ -80,11 +80,11 @@ type Option =
type DataZoom =
{"type":: String
, xAxisIndex:: Int
, filterMode:: String
, start:: Int
, end:: Int
{"type" :: String
, xAxisIndex :: Int
, filterMode :: String
, start :: Int
, end :: Int
}
type Grid =
......@@ -116,7 +116,7 @@ type Legend =
}
type Data =
{name :: String
{ name :: String
, icon :: String
, textStyle :: {}
}
......@@ -173,7 +173,7 @@ type AxisLabel =
type Series =
{name :: String
{ name :: String
, "type" :: String
, "data" :: Array Int
}
......@@ -373,16 +373,20 @@ yAxisIndex = unsafeMkProps "yAxisIndex"
-- , p''
-- ]
ex1 :: ReactElement
ex1 = echarts
histogram :: ReactElement
histogram = echarts
[ option
[ tooltip [trigger "axis"]
, grid [containLabel true]
, legend [data' ["Query A", "Query B", "Query C"]]
, legend [data' ["Map terms coverage", "Favorites", "All"]]
-- , legend [data' ["Map Terms coverage", "Favorites", "All"]]
, xAxis
[ type' "category"
, axisTick [alignWithLabel true]
, data' ["Jan", "Feb", "Mar", "Apr", "May", "Jun", "July", "Aug", "Sep", "Oct", "Nov", "Dec"]
, data' ["Jan" , "Feb", "Mar" , "Apr"
, "May", "Jun", "July", "Aug"
, "Sep", "Oct", "Nov" , "Dec"
]
]
, dataZoom [dz1,dz1,dz2,dz2]
, yAxis [ya1, ya2]
......@@ -408,22 +412,22 @@ dz2 = unsafeFromPropsArray
ya1 = unsafeFromPropsArray
[ type' "value"
, name "Publications (by year)"
, name "Score metric"
, min 0
, position "left"
, position "right"
, axisLabel [formatter "{value}"]
]
ya2 = unsafeFromPropsArray
[ type' "value"
, name "Score metric"
, name "Publications (by year)"
, min 0
, position "right"
, position "left"
, axisLabel [formatter "{value}"]
]
sd1 = unsafeFromPropsArray
[ name "Query A"
[ name "Map terms coverage"
, type' "line"
, label [normal[showp true, position "top"]]
, lineStyle [ normal
......@@ -432,26 +436,26 @@ sd1 = unsafeFromPropsArray
, shadowBlur 10
, shadowOffsetY 10
]]
, data' [1, 13, 37, 35, 15, 13, 25, 21, 6, 45, 32, 2]
, data' [95, 80, 75, 35, 30, 50, 70, 80, 95, 95, 95, 99]
]
sd2 = unsafeFromPropsArray
[ name "Query B"
sd3 = unsafeFromPropsArray
[ name "All"
, type' "bar"
, label [normal[showp true, position "top"]]
, yAxisIndex 1
, data' [22, 22, 23, 77, 24, 55, 55, 89, 98, 164, 106, 224]
, data' [201, 222, 223, 777, 244, 255, 555, 879, 938, 1364, 1806, 2324]
]
sd3 = unsafeFromPropsArray
[ name "Query C"
sd2 = unsafeFromPropsArray
[ name "Favorites"
, type' "bar"
, label [normal[showp true, position "top"]]
, yAxisIndex 1
, data' [201, 222, 223, 777, 244, 255, 555, 879, 938, 1364, 1806, 2324]
, data' [22, 22, 23, 77, 24, 55, 139, 350, 150, 164, 106, 224]
]
p'' :: ReactElement
p'' = p [] []
......@@ -2,7 +2,7 @@ module DocView where
import Data.Argonaut
import Chart (ex1, p'')
import Chart (histogram, p'')
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Cont.Trans (lift)
......@@ -26,8 +26,8 @@ import Partial.Unsafe (unsafePartial)
import Prelude (class Eq, class Ord, class Show, Unit, bind, map, not, pure, show, void, ($), (*), (+), (-), (/), (<), (<$>), (<>), (==), (>), (>=), (>>=))
import React (ReactElement)
import React as R
import React.DOM (a, b, b', br', div, h3, i, input, li, option, select, span, table, tbody, td, text, thead, tr, ul)
import React.DOM.Props (Props, _type, className, href, onChange, onClick, selected, value)
import React.DOM (a, b, b', br', div, h3, i, input, li, option, select, span, table, tbody, td, text, thead, th, tr, ul, nav)
import React.DOM.Props (Props, _type, className, href, onChange, onClick, selected, value, scope, _id, role, _data, aria)
import ReactDOM as RDOM
import Thermite (PerformAction, Render, Spec, cotransform, createReactSpec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
......@@ -62,9 +62,8 @@ newtype Response = Response
}
newtype Hyperdata = Hyperdata
{
title :: String
, abstract :: String
{ title :: String
, source :: String
}
type State = CorpusTableData
......@@ -79,8 +78,8 @@ instance decodeHyperdata :: DecodeJson Hyperdata where
decodeJson json = do
obj <- decodeJson json
title <- obj .? "title"
abstract <- obj .? "abstract"
pure $ Hyperdata { title,abstract }
source <- obj .? "source"
pure $ Hyperdata { title,source }
......@@ -112,56 +111,62 @@ toggleNode sid (NNode iid open name ary) =
toggleNode sid a = a
spec :: Spec _ State _ Action
spec = simpleSpec performAction render
where
render :: Render State _ Action
render dispatch _ state@(TableData d) _ =
[ div [className "container"]
[
div [className "jumbotron"]
[
div [className "row"]
[ div [className "row"]
[ div [className "col-md-3"]
[ br' []
, br' []
, div [className "tree"] [toHtml dispatch d.tree]
]
, div [className "col-md-9"]
[ nav []
[ div [className "nav nav-tabs", _id "nav-tab",role "tablist"]
[
br' []
a [ className "nav-item nav-link active"
, _id "nav-home-tab"
, _data {toggle : "tab"}
, href "#nav-home"
, role "tab"
, aria {controls : "nav-home"}
, aria {selected:true}] [ text "Documents"]
, a [className "nav-item nav-link",_id "nav-profile-tab", _data {toggle : "tab"},href "#nav-profile",role "tab",aria {controls : "nav-profile"},aria {selected:true}] [ text "Sources"]
,a [className "nav-item nav-link",_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "Authors"]
,a [className "nav-item nav-link",_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "Terms"]
,a [className "nav-item nav-link",_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "(+)"]
]
]
, br' []
, p''
, h3 [] [text "Chart Title"]
, ex1
, histogram
, p''
, div [] [b [] [text d.title]]
, div [] [ text "Search "
, br' []
, div [] [ b [] [text d.title]
, text " Filter "
, input [] []
]
, sizeDD d.pageSize dispatch
, br' []
, br' []
, textDescription d.currentPage d.pageSize d.totalRecords
, br' []
, br' []
, pagination dispatch d.totalPages d.currentPage
, br' []
, br' []
, table []
[thead [] [tr []
[ td [] [ b' [text "Date"]]
, td [] [ b' [text "Title"]]
, td [] [ b' [text "Source"]]
, td [] [ b' [text "Fav"]]
, td [] [ b' [text "Delete"]]
]]
, tbody [] $ map showRow d.rows
]
, table [ className "table"]
[thead [ className "thead-dark"]
[tr [] [ th [scope "col"] [ b' [text "Date"] ]
, th [scope "col"] [ b' [text "Title"] ]
, th [scope "col"] [ b' [text "Source"] ]
, th [scope "col"] [ b' [text "Favorite"]]
, th [scope "col"] [ b' [text "Delete"] ]
]
]
, tbody [] $ map showRow d.rows
]
]
]
]
......@@ -171,19 +176,13 @@ spec = simpleSpec performAction render
------------------------------------------------------------------------
-- Realistic Tree for the UI
urlFacetDoc :: String
urlFacetDoc = "http://localhost:8009/index.html#/docView"
myCorpus :: Int -> String -> NTree (Tuple String String)
myCorpus n name = NNode n false name
[ NLeaf (Tuple "Facets" urlFacetDoc)
, NLeaf (Tuple "Graph" urlFacetDoc)
, NLeaf (Tuple "Dashboard" urlFacetDoc)
[ NLeaf (Tuple "Facets" "#/docView")
, NLeaf (Tuple "Graph" "#/docView")
, NLeaf (Tuple "Dashboard" "#/userPage")
]
urlFacetAuth :: String
urlFacetAuth = urlFacetDoc
exampleTree :: NTree (Tuple String String)
exampleTree =
NNode 1 true "My gargantext"
......@@ -195,26 +194,29 @@ exampleTree =
]
]
------------------------------------------------------------------------
-- TODO
-- alignment to the right
nodeOptionsCorp = [ i [className "fab fa-whmcs" ] []]
nodeOptionsCorp activated = case activated of
true -> [ i [className "fab fa-whmcs" ] []]
false -> []
-- TODO
-- alignment to the right
-- on hover make other options available:
nodeOptionsView = [ i [className "fas fa-sync-alt" ] []
nodeOptionsView activated = case activated of
true -> [ i [className "fas fa-sync-alt" ] []
, i [className "fas fa-upload" ] []
, i [className "fas fa-share-alt"] []
]
false -> []
toHtml :: _ -> FTree -> ReactElement
toHtml d (NLeaf (Tuple name link)) =
li []
[ a [ href link]
( [ text (name <> " ")
] <> nodeOptionsView
] <> nodeOptionsView false
)
]
toHtml d (NNode id open name ary) =
......@@ -222,7 +224,7 @@ toHtml d (NNode id open name ary) =
[ li [] $
( [ a [onClick $ (\e-> d $ ToggleFolder id)] [i [fldr open] []]
, text $ " " <> name <> " "
] <> nodeOptionsCorp <>
] <> nodeOptionsCorp false <>
if open then
map (toHtml d) ary
else []
......@@ -249,7 +251,7 @@ performAction LoadData _ _ = void do
, url : ""
, date : res.created
, title : (\(Hyperdata r) -> r.title) res.hyperdata
, source : (\(Hyperdata r) -> r.abstract)res.hyperdata
, source : (\(Hyperdata r) -> r.source)res.hyperdata
, fav : res.favorite
}
......@@ -258,7 +260,11 @@ performAction (ToggleFolder i) _ _ = void (cotransform (\(TableData td) -> Table
changePageSize :: PageSizes -> CorpusTableData -> CorpusTableData
changePageSize ps (TableData td) = TableData $ td { pageSize = ps, totalPages = td.totalRecords / pageSizes2Int ps, currentPage = 1}
changePageSize ps (TableData td) =
TableData $ td { pageSize = ps
, totalPages = td.totalRecords / pageSizes2Int ps
, currentPage = 1
}
data PageSizes = PS10 | PS20 | PS50 | PS100
......@@ -332,7 +338,9 @@ pagination d tp cp
else
span []
[ text " "
, a [href "javascript:void()", onClick (\e -> d $ ChangePage $ cp - 1)] [text "Previous"]
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage $ cp - 1)
] [text "Previous"]
, text " "
]
next = if cp == tp then
......@@ -340,7 +348,9 @@ pagination d tp cp
else
span []
[ text " "
, a [href "javascript:void()", onClick (\e -> d $ ChangePage $ cp + 1)] [text "Next"]
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage $ cp + 1)
] [text "Next"]
, text " "
]
first = if cp == 1 then
......@@ -348,7 +358,9 @@ pagination d tp cp
else
span []
[ text " "
, a [href "javascript:void()", onClick (\e -> d $ ChangePage 1)] [text "1"]
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage 1)
] [text "1"]
, text " "
]
last = if cp == tp then
......@@ -356,7 +368,9 @@ pagination d tp cp
else
span []
[ text " "
, a [href "javascript:void()", onClick (\e -> d $ ChangePage tp)] [text $ show tp]
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage tp)
] [text $ show tp]
, text " "
]
ldots = if cp >= 5 then
......@@ -374,7 +388,9 @@ fnmid :: _ -> Int -> ReactElement
fnmid d i
= span []
[ text " "
, a [href "javascript:void()", onClick (\e -> d $ ChangePage i)] [text $ show i]
, a [ href "javascript:void()"
, onClick (\e -> d $ ChangePage i)
] [text $ show i]
, text " "
]
......@@ -387,7 +403,9 @@ greaterthan x y = x > y
newtype TableData a
= TableData
{ rows :: Array {row :: a, delete :: Boolean}
{ rows :: Array { row :: a
, delete :: Boolean
}
, totalPages :: Int
, currentPage :: Int
, pageSize :: PageSizes
......@@ -427,7 +445,7 @@ tdata = TableData
, currentPage : 1
, pageSize : PS10
, totalRecords : 100
, title : "Publications by title"
, title : "Documents"
, tree : exampleTree
}
......@@ -438,7 +456,7 @@ tdata' d = TableData
, currentPage : 1
, pageSize : PS10
, totalRecords : 100
, title : "Publications by title"
, title : "Documents"
, tree : exampleTree
}
......@@ -449,10 +467,13 @@ showRow {row : (Corpus c), delete} =
[ td [] [text c.date]
, td [] [text c.title]
, td [] [text c.source]
, td [] [text $ show c.fav]
, td [] [ input [ _type "checkbox"] []]
, td [] [div [className $ fa <> "fa-star"][]]
, td [] [input [ _type "checkbox"] []]
]
where
fa = case c.fav of
true -> "fas "
false -> "far "
......@@ -477,3 +498,6 @@ loadData = do
--liftEff $ log $ "GET /api response: " <> show a.response
let res = decodeJson a.response
pure res
......@@ -6,7 +6,8 @@ import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div)
import React.DOM (a, button, div, footer, h1, h3, hr, i, img, li, p, span, text, ul)
import React.DOM.Props (_data, _id, aria, className, href, onClick, role, src, style, tabIndex, target, title)
import React.DOM.Props (Props, _data, _id, aria, className, href, onClick, role, src, style, tabIndex, target, title)
import React (ReactElement)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, simpleSpec)
import Thermite as T
......@@ -49,162 +50,65 @@ performAction Login _ _ = void do
performAction SignUp _ _ = void do
T.modifyState \state -> state
loginSpec :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
loginSpec = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[
-- div [ _id "dafixedtop", className "navbar navbar-inverse navbar-fixed-top", role "navigation"]
-- [ div [className "container"]
-- [
-- div [ className "navbar-inner" ]
-- [ a [ className "navbar-brand logoSmall", href "/" ]
-- [ img [ src "images/logoSmall.png", title "Back to home." ]
-- []
-- ]
-- ]
-- , div [className "navbar-collapse collapse"]
-- [
-- ul [className "nav navbar-nav"]
-- [
-- ul [className "nav navbar-nav pull-left"] [
-- li [className "dropdown"]
-- [
-- a [
-- className "dropdown-toggle navbar-text", _data {toggle: "dropdown"}, href "#", role "button", title "Informations about Gargantext" ]
-- [ span [ aria {hidden : true}, className "glyphicon glyphicon-info-sign" ]
-- []
-- , text "Info"
-- , i [ className "caret" ]
-- []
-- ]
-- , ul [className "dropdown-menu"]
-- [ li []
-- [ a [tabIndex (-1), target "blank", title "Documentation and tutorials", href "https://iscpif.fr/gargantext/your-first-map/"]
-- [text "Documentation"]
-- ]
-- , li [className "divider"] []
-- , li []
-- [
-- a [ tabIndex (-1), target "blank", title "About", href "/about/", title "More informations about the project, its sponsors and its authors"]
-- [ text "About"]
-- ]
-- ]
-- ]
-- ]
-- ]
-- , ul [className "nav navbar-nav pull-right"]
-- [
-- li [className "dropdown"]
-- [
-- a [ className "dropdown-toggle navbar-text", _data {toggle : "dropdown"}, href "#", role "button", title "That is your username" ]
-- [ i [ className "" ]
-- []
-- , span [ aria {hidden : true}, className "glyphicon glyphicon-user", style {color:"white"} ]
-- []
-- , i [ className "caret" ]
-- []
-- ]
-- , ul [className "dropdown-menu"]
-- [
-- li []
-- [ a [tabIndex (-1), target "blank", title "Send us a message (bug, thanks, congrats...)", href "https://www.iscpif.fr/gargantext/feedback-and-bug-reports/"]
-- [
-- span [ className "glyphicon glyphicon-bullhorn" ,aria {hidden : true}] []
-- , text "Report Feedback"
-- ]
-- ]
-- , li [ className"divider"]
-- []
-- , li []
-- [ a [tabIndex (-1), href "/auth/login" ]
-- [ span [className "glyphicon glyphicon-log-in",aria {hidden : true}] []
-- , text "login"
-- ]
-- ]
-- ]
-- ]
-- ]
-- ]
-- ]
-- ]
div [className "container"]
[
div [className "jumbotron"]
[
div [className "row"]
[
div [className "col-md-8 content"]
[
h1 []
[ text "Gargantext" ]
, p []
[ text "Collaborative knowledge mapping experience" ]
-- TODO : put the login in top right page [#54]
, p []
[
-- a [ className "btn btn-primary btn-lg spacing-class ", onClick \_ -> dispatch $ Submit , title "Click and test by yourself" ]
-- [ span [ className "glyphicon glyphicon-hand-right" ]
-- []
-- , text " Login"
-- ]
---- TODO: login / sign up will not be mandatory any more (mandatory to save/share your research only)
---- TODO: ask for login or account creation after 5 mn when user is not logged and has made one search at least
-- , a [ className "btn btn-warning btn-lg spacing-class", href "https://iscpif.fr/services/applyforourservices/", target "blank", title "Fill the form to sign up" ]
-- [ span [ aria {hidden : true}, className "glyphicon glyphicon-hand-right" ]
-- []
-- , text "Sign Up"
-- ]
a [ className "btn btn-success btn-lg spacing-class", href "https://iscpif.fr/gargantext/your-first-map/", target "blank", title "Fill the form to sign up" ]
[ span [ aria {hidden : true}, className "glyphicon glyphicon-hand-right" ]
[]
, text " Get's started"
jumboTitle :: Boolean -> ReactElement
jumboTitle b = div jumbo
[ div [className "row" ]
[ div [className "col-md-8 content"]
[ h1 [] [ text "Gargantext"]
, p [] [ text "search map share" ]
, p [] [ a [ className "btn btn-success btn-lg spacing-class"
, href "https://iscpif.fr/gargantext/your-first-map/"
, target "blank"
, title "Your first map in less than 5 minutes"
]
[ span [ aria {hidden : true}
, className "glyphicon glyphicon-hand-right"
] []
, text " Documentation"
]
]
, span [ aria {hidden : true}, className "glyphicon glyphicon-warning-sign" ]
[]
, i []
[ text "Some features may not work without a javascript optimized browser (Chromium for instance). " ]
]
, div [className "col-md-2 content"]
[
p [ className "right" ]
, div [ className "col-md-2 content"]
[p [ className "right" ]
[ div [_id "logo-designed" ]
[ img [ src "images/logo.png", title "Logo designed by dacha and anoe" ]
[ img [ src "images/logo.png", title "Project hosted by CNRS (France, Europa, Solar System)" ]
[]
]
]
]
]
]
]
where
jumbo = case b of
true -> [className "jumbotron"]
false -> []
, div [className "container"]
[ div [className "row"]
imageEnter :: Props -> ReactElement
imageEnter action = div [className "row"]
[ div [className "col-md-offset-5 col-md-6 content"]
[ img [ src "images/Gargantextuel-212x300.jpg"
, title "Gargantextuel drawn by Cecile Meadel"
, _id "funnyimg"
, onClick \_ -> dispatch $ Enter , title "Click and test by yourself"
] []
, title "Click and test by yourself"
, action
]
[]
]
]
, div [ className "container" ]
[ div [ className "row" ]
home :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
home = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ div [ className "container" ] [ jumboTitle true ]
, div [ className "container" ] [ imageEnter (onClick \_ -> dispatch $ Enter)]
, div [ className "container" ] [ blocksRandomText ]
]
blocksRandomText :: ReactElement
blocksRandomText = div [ className "row" ]
[ div [ className "col-md-4 content" ]
[ h3 []
[ a [ href "#", title "Random sentences in Gargantua's Books chapters, historically true" ]
......@@ -245,28 +149,5 @@ loginSpec = simpleSpec performAction render
]
]
]
]
, div [className "container"]
[
hr [] []
, footer []
[ p []
[ text "Gargantext "
, span [className "glyphicon glyphicon-registration-mark" ]
[]
, text ", version 4.0"
, a [ href "http://www.cnrs.fr", target "blank", title "Institution that enables this project." ]
[ 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 "."
]
]
]
]
......@@ -26,6 +26,9 @@ import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
-- TODO: ask for login (modal) or account creation after 15 mn when user is not logged and has made one search at least
newtype State = State
{ username :: String
, password :: String
......@@ -49,7 +52,11 @@ data Action
| SetPassword String
performAction :: forall eff props. PerformAction (console :: CONSOLE, ajax :: AJAX,dom::DOM | eff) State props Action
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
......@@ -150,16 +157,14 @@ getDeviseID :: forall eff. Eff (dom :: DOM | eff) (Maybe String)
getDeviseID = do
w <- window
ls <- localStorage w
i <- getItem "token" ls
pure $ i
getItem "token" ls
setToken :: forall e . String -> Eff (dom :: DOM | e) Unit
setToken s = do
w <- window
ls <- localStorage w
liftEff $ setItem "token" s ls
pure unit
setItem "token" s ls
......
......@@ -3,25 +3,21 @@ module Navigation where
import DOM
import AddCorpusview as AC
import Control.Monad.Aff.Class (liftAff)
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Eff.Console (CONSOLE)
import Data.Either (Either(..))
import Data.Foldable (fold)
import Data.Lens (Lens', Prism', lens, over, prism)
import Data.Maybe (Maybe, Maybe(Nothing, Just))
import Data.Maybe (Maybe(Nothing, Just))
import Landing as L
import Login as LN
import Network.HTTP.Affjax (AJAX)
import PageRouter (Routes(..))
import Prelude hiding (div)
import Prelude (class Applicative, class Bind, Unit, bind, id, map, negate, pure, unit, void, ($), (<>))
import React (ReactElement)
import React.DOM (a, div, i, img, li, span, text, ul, map')
import React.DOM.Props (_data, _id, aria, className, href, role, src, style, tabIndex, target, title, onClick)
import React.DOM (a, div, img, li, span, text, ul, input, button, footer, p, hr, form)
import React.DOM.Props (_data, _id, aria, className, href, name, placeholder, _type, role, src, style, tabIndex, target, title)
import Thermite (PerformAction, Render, Spec, _render, defaultRender, focus, modifyState, simpleSpec, withState)
import DocView as DV
import Landing as Landing
import SearchForm as S
import UserPage as UP
......@@ -48,7 +44,6 @@ initAppState =
, userPage : UP.initialState
}
data Action
= Initialize
| LandingA L.Action
......@@ -60,7 +55,9 @@ data Action
| UserPageA UP.Action
performAction :: forall eff props. PerformAction (dom :: DOM |eff) AppState props Action
performAction :: forall eff props. PerformAction ( dom :: DOM
| eff
) AppState props Action
performAction (SetRoute route) _ _ = void do
modifyState $ _ {currentRoute = pure route}
......@@ -68,9 +65,8 @@ performAction _ _ _ = void do
modifyState id
---- Lens and Prism
_landingState:: Lens' AppState L.State
_landingState :: Lens' AppState L.State
_landingState = lens (\s -> s.landingState) (\s ss -> s{landingState = ss})
......@@ -81,8 +77,7 @@ _landingAction = prism LandingA \action ->
_-> Left action
_loginState:: Lens' AppState LN.State
_loginState :: Lens' AppState LN.State
_loginState = lens (\s -> s.loginState) (\s ss -> s{loginState = ss})
......@@ -93,7 +88,7 @@ _loginAction = prism LoginA \action ->
_-> Left action
_addCorpusState:: Lens' AppState AC.State
_addCorpusState :: Lens' AppState AC.State
_addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss})
......@@ -104,8 +99,7 @@ _addCorpusAction = prism AddCorpusA \action ->
_-> Left action
_docViewState:: Lens' AppState DV.State
_docViewState :: Lens' AppState DV.State
_docViewState = lens (\s -> s.docViewState) (\s ss -> s{docViewState = ss})
......@@ -116,7 +110,7 @@ _docViewAction = prism DocViewA \action ->
_-> Left action
_searchState:: Lens' AppState S.State
_searchState :: Lens' AppState S.State
_searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss})
......@@ -127,7 +121,7 @@ _searchAction = prism SearchA \action ->
_-> Left action
_userPageState:: Lens' AppState UP.State
_userPageState :: Lens' AppState UP.State
_userPageState = lens (\s -> s.userPage) (\s ss -> s{userPage = ss})
......@@ -147,9 +141,13 @@ pagesComponent s =
Nothing ->
selectSpec Home
where
selectSpec :: Routes -> Spec (ajax :: AJAX, console :: CONSOLE, dom :: DOM | eff) AppState props Action
selectSpec :: Routes -> Spec ( ajax :: AJAX
, console :: CONSOLE
, dom :: DOM
| eff
) AppState props Action
selectSpec Login = focus _loginState _loginAction LN.renderSpec
selectSpec Home = wrap $ focus _landingState _landingAction L.loginSpec
selectSpec Home = wrap $ focus _landingState _landingAction L.home
selectSpec AddCorpus = wrap $ focus _addCorpusState _addCorpusAction AC.addcorpusviewSpec
selectSpec DocView = wrap $ focus _docViewState _docViewAction DV.spec
selectSpec SearchView = wrap $ focus _searchState _searchAction S.searchSpec
......@@ -158,95 +156,81 @@ pagesComponent s =
routingSpec :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
routingSpec = simpleSpec performAction defaultRender
wrap :: forall eff props. Spec (E eff) AppState props Action -> Spec (E eff) AppState props Action
wrap spec =
fold
[ sidebarnavSpec
-- TODO Add Tree to the template
--, exampleTree'
, innerContainer $ spec
, footerLegalInfo
]
where
innerContainer :: Spec (E eff) AppState props Action -> Spec (E eff) AppState props Action
innerContainer = over _render \render d p s c ->
[ div [_id "page-wrapper"]
[
div[className "container-fluid"] (render d p s c)
div [className "container-fluid"] (render d p s c)
]
]
-- TODO Add Tree to the template
-- exampleTree' :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
-- exampleTree' = simpleSpec performAction render
-- where
-- render :: Render AppState props Action
-- render dispatch _ state _ = DV.toHtml dispatch DV.exampleTree
data LiNav = LiNav { title :: String
, href :: String
, icon :: String
, text :: String
}
liNav :: LiNav -> ReactElement
liNav (LiNav { title:tit
, href :h
, icon:i
, text: txt
}
) = li [] [ a [ tabIndex (-1)
, target "blank"
, title tit
, href h
]
[ span [ className i ] []
, text $ " " <> txt
sidebarnavSpec :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
sidebarnavSpec = simpleSpec performAction render
where
render :: Render AppState props Action
render dispatch _ state _ =
[ div [ _id "dafixedtop"
, className "navbar navbar-inverse navbar-fixed-top"
, role "navigation"
] [ div [className "container"]
[ div [ className "navbar-inner" ]
[ divLogo
, div [ className "collapse navbar-collapse"]
[ divDropdownLeft
, ul [className "nav navbar-nav"][text " XXXXXXXXXXXXXXXXXXX "]
, divSearchBar
, divDropdownRight
]
]
divLogo :: ReactElement
divLogo = div [ className "navbar-inner" ]
[ a [ className "navbar-brand logoSmall"
, href "/index.html"
]
[ img [ src "images/logoSmall.png"
, title "Back to home." ]
[]
]
]
--divDropdownLeft :: ReactElement
--divDropdownLeft = undefined
sidebarnavSpec :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
sidebarnavSpec = simpleSpec performAction render
where
render :: Render AppState props Action
render dispatch _ state _ =
[
div [ _id "dafixedtop"
, className "navbar navbar-inverse navbar-fixed-top"
, role "navigation"
divLogo :: ReactElement
divLogo = a [ className "navbar-brand logoSmall"
, href "/index.html"
] [ img [ src "images/logoSmall.png"
, title "Back to home."
] []
]
[ div [className "container"]
[ divLogo
-- divDropdownLeft
---------------------------------------------------------------------------
-- here is divDropDowLeft--------------------------------------------------
-- FIXME : divDropDownLeft and divDropDownRight seems to be intricated in dropdown?
---------------------------------------------------------------------------
, div [className "navbar-collapse collapse"]
[ ul [className "nav navbar-nav"]
divDropdownLeft :: ReactElement
divDropdownLeft = ul [className "nav navbar-nav"]
[ ul [className "nav navbar-nav pull-left"]
[ li [className "dropdown"]
[ a [ className "dropdown-toggle navbar-text"
, _data {toggle: "dropdown"}
, href "#", role "button"
, title "Informations about Gargantext"
]
[ span [ aria {hidden : true}
, title "About Gargantext"
][ span [ aria {hidden : true}
, className "glyphicon glyphicon-info-sign"
] []
, text " Info"
]
, ul [className "dropdown-menu"]
(( map liNav [ LiNav { title : "Documentation and tutorials"
(( map liNav [ LiNav { title : "Quick start, tutorials and methodology"
, href : "https://iscpif.fr/gargantext/your-first-map/"
, icon : "fas fa-book"
, text : "Documentation"
......@@ -256,7 +240,10 @@ sidebarnavSpec = simpleSpec performAction render
, icon : "glyphicon glyphicon-bullhorn"
, text : "Feedback"
}
, LiNav { title : "Interactive chat"
]
)
<> [li [className "divider"] []] <>
(map liNav [ LiNav { title : "Interactive chat"
, href : "https://chat.iscpif.fr/channel/gargantext"
, icon : "fab fa-rocketchat"
, text : "Chat"
......@@ -269,7 +256,7 @@ sidebarnavSpec = simpleSpec performAction render
]
)
<> [li [className "divider"] []] <>
[ liNav (LiNav { title : "About"
[ liNav (LiNav { title : "More about us (you)"
, href : "http://iscpif.fr"
, icon : "fas fa-question-circle"
, text : "About"
......@@ -280,10 +267,46 @@ sidebarnavSpec = simpleSpec performAction render
]
]
]
---------------------------------------------------------------------------
, divDropdownRight
data LiNav = LiNav { title :: String
, href :: String
, icon :: String
, text :: String
}
liNav :: LiNav -> ReactElement
liNav (LiNav { title:tit
, href :h
, icon:i
, text: txt
}
) = li [] [ a [ tabIndex (-1)
, target "blank"
, title tit
, href h
] [ span [ className i ] []
, text $ " " <> txt
]
]
-- TODO put the search form in the center of the navBar
divSearchBar :: ReactElement
divSearchBar = ul [ className "nav navbar-nav"]
[ div [className "navbar-form"]
[ input [ className "search-query"
, placeholder "Query, URL or FILE (works with Firefox or Chromium browsers)"
, _type "text"
, style { height: "35px"
, width : "450px"
-- , color: "white"
-- , background : "#A1C2D8"
}
] []
-- TODO add button in navbar (and "enter" execution)
-- , div [] [button [][]]
]
]
......@@ -298,6 +321,7 @@ divDropdownRight = ul [className "nav navbar-nav pull-right"]
, className "glyphicon glyphicon-log-in"
, href "#/login"
, style {color:"white"}
, title "Log in and save your time"
-- TODO hover: bold
]
-- TODO if logged in
......@@ -307,6 +331,36 @@ divDropdownRight = ul [className "nav navbar-nav pull-right"]
]
]
footerLegalInfo :: forall props eff. Spec (dom :: DOM |eff) AppState props Action
footerLegalInfo = simpleSpec performAction render
where
render :: Render AppState props 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 "."
]
]
layoutSpec :: forall eff props. Spec (E eff) AppState props Action
layoutSpec =
fold
......@@ -319,11 +373,14 @@ layoutSpec =
container = over _render \render d p s c ->
(render d p s c)
dispatchAction :: forall t115 t445 t447. Bind t445 => Applicative t445 => (Action -> t445 t447) -> t115 -> Routes -> t445 Unit
dispatchAction :: forall t115 t445 t447.
Bind t445 => Applicative t445 =>
(Action -> t445 t447) -> t115 -> Routes -> t445 Unit
dispatchAction dispatcher _ Home = do
_ <- dispatcher $ SetRoute $ Home
_ <- dispatcher $ LandingA $ L.NoOp
pure unit
dispatchAction dispatcher _ Login = do
_ <- dispatcher $ SetRoute $ Login
_ <- dispatcher $ LoginA $ LN.NoOp
......@@ -339,15 +396,16 @@ dispatchAction dispatcher _ DocView = do
_ <- dispatcher $ DocViewA $ DV.LoadData
pure unit
dispatchAction dispatcher _ SearchView = do
_ <- dispatcher $ SetRoute $ SearchView
_ <- dispatcher $ SearchA $ S.NoOp
pure unit
dispatchAction dispatcher _ UserPage = do
_ <- dispatcher $ SetRoute $ UserPage
_ <- dispatcher $ UserPageA $ UP.NoOp
pure unit
......@@ -53,7 +53,17 @@ routing =
home = Home <$ lit ""
route str = lit "" *> lit str
routeHandler :: forall e. (Maybe Routes -> Routes -> Eff ( dom :: DOM, console :: CONSOLE | e) Unit) -> Maybe Routes -> Routes -> Eff (dom :: DOM, console :: CONSOLE | e) Unit
routeHandler :: forall e. ( Maybe Routes -> Routes -> Eff
( dom :: DOM
, console :: CONSOLE
| e
) Unit
) -> Maybe Routes -> Routes -> Eff
( dom :: DOM
, console :: CONSOLE
| e
) Unit
routeHandler dispatchAction old new = do
liftEff $ log $ "change route : " <> show new
w <- window
......
......@@ -6,11 +6,12 @@ import Control.Monad.Cont.Trans (lift)
import DOM (DOM)
import Network.HTTP.Affjax (AJAX)
import Prelude hiding (div)
import React.DOM (br', button, div, h3, input, text)
import React.DOM.Props (_id, _type, className, name, onClick, onInput, placeholder, value)
import React.DOM (br', button, div, h3, input, text, i, span, img)
import React.DOM.Props (_id, _type, className, name, onClick, onInput, placeholder, value, aria, src, title)
import Routing.Hash.Aff (setHash)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
import Landing as L
type State =
{
......@@ -47,43 +48,41 @@ performAction GO _ _ = void do
unsafeEventValue :: forall event. event -> String
unsafeEventValue e = (unsafeCoerce e).target.value
-- TODO: case loggedIn of True -> Just Tree ; False -> Nothing
-- TODO: put the search form in the center of the page
searchSpec :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
searchSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
searchSpec = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[
div [className "container"]
[
div [className "jumbotron"]
[
div [className "row"]
[
div [className "col-md-10"]
[ div [className "container"] [L.jumboTitle false]
, div [className "container"]
[ div [className "jumbotron" ]
[ div [className "row" ]
[ div [className "col-md-10" ]
[ br' []
, br' []
, div [className "form-group"]
[
input [className "form-control",
_id "id_password",
name "query",
placeholder "Enter Query",
_type "text",
value state.query,
onInput \e -> dispatch (SetQuery (unsafeEventValue e))
, div [ className "form-group"]
[ input [ className "form-control"
, _id "id_password"
, name "query"
, placeholder "Query, URL or FILE (works best with Firefox or Chromium browsers)"
, _type "text"
, value state.query
, onInput \e -> dispatch (SetQuery (unsafeEventValue e))
] []
, br'[]
]
]
, div [className "col-md-2"]
, div [ className "col-md-2"]
[ br' []
, br' []
-- TODO put Gargantext logo as search button
, button [onClick \_ -> dispatch GO] [text "GO"]
]
, br' []
]
]
]
......
......@@ -8,33 +8,40 @@ import React.DOM (a, div, h3, h5, h6, i, img, li, nav, small, span, table, tbody
import React.DOM.Props (_data, _id, aria, className, href, role, scope, src)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import DocView as DV
type State = String
initialState :: State
initialState =""
initialState = ""
data Action
= NoOp
data Action = NoOp
performAction :: forall eff props. PerformAction (console :: CONSOLE, ajax :: AJAX,dom::DOM | eff) State props Action
performAction :: forall eff props. PerformAction ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
performAction NoOp _ _ = void do
modifyState id
userPageSpec :: forall props eff . Spec (console::CONSOLE, ajax::AJAX, dom::DOM | eff) State props Action
userPageSpec :: forall props eff . Spec ( console :: CONSOLE
, ajax :: AJAX
, dom :: DOM
| eff
) State props Action
userPageSpec = simpleSpec performAction render
where
render :: Render State props Action
render dispatch _ state _ =
[ div [className "container-fluid"]
[ -- TODO: div [className "tree"] [DV.toHtml dispatch d.tree]
div [className "container-fluid"]
[ div [className "row", _id "user-page-header"]
[ div [className "col-md-2"]
[ h3 [] [text "UserName"]
[ h3 [] [text "User Name"]
]
, div [className "col-md-8"] []
, div [className "col-md-2"]
......@@ -54,26 +61,21 @@ userPageSpec = simpleSpec performAction render
ul [className "list-group"]
[
li [className "list-group-item justify-content-between"]
[ span [] [text "fonction"]
, span [className "badge badge-default badge-pill"] [text "Ensignent checheur"]
[ span [] [text "Fonction"]
, span [className "badge badge-default badge-pill"] [text "Enseignant chercheur"]
]
, li [className "list-group-item justify-content-between"]
[ span [] [text "Entitte, service"]
, span [className "badge badge-default badge-pill"] [text "Mines Saint - Etinene SPIN -PTSI"]
[ span [] [text "Entité, service"]
, span [className "badge badge-default badge-pill"] [text "Mines Saint-Etienne SPIN -PTSI"]
]
, li [className "list-group-item justify-content-between"]
[ span [] [text "Telephone"]
, span [className "badge badge-default badge-pill"] [text "04 77 42 0070"]
]
, li [className "list-group-item justify-content-between"]
[ span [] [text "Telephone"]
, span [className "badge badge-default badge-pill"] [text "04 77 42 0070"]
[ span [] [text "Téléphone"]
, span [className "badge badge-default badge-pill"] [text "(+33) 04 77 42 0070"]
]
, li [className "list-group-item justify-content-between"]
[ span [] [text "courriel"]
, span [className "badge badge-default badge-pill"] [text "veronica@mines-stsi.fr"]
[ span [] [text "Courriel"]
, span [className "badge badge-default badge-pill"] [text "gargantua@rabelais.fr"]
]
, li [className "list-group-item justify-content-between"]
[ span [] [text "Bureau"]
......@@ -81,11 +83,11 @@ userPageSpec = simpleSpec performAction render
]
, li [className "list-group-item justify-content-between"]
[ span [] [text "Apellation"]
, span [className "badge badge-default badge-pill"] [text "Maitre de reherche (EPA)"]
, span [className "badge badge-default badge-pill"] [text "Maître de conférences (EPA)"]
]
, li [className "list-group-item justify-content-between"]
[ span [] [text "Lieu"]
, span [className "badge badge-default badge-pill"] [text "Saint -Etienne, 158 Cours Fauriel"]
, span [className "badge badge-default badge-pill"] [text "Saint-Etienne, 158 Cours Fauriel"]
]
]
......@@ -95,62 +97,73 @@ userPageSpec = simpleSpec performAction render
]
, div [className "row",_id "user-page-footer"]
[ div [className "col-md-12"]
[ nav []
[ div [className "nav nav-tabs", _id "nav-tab",role "tablist"]
[
a [className "nav-item nav-link active",_id "nav-home-tab", _data {toggle : "tab"},href "#nav-home",role "tab",aria {controls : "nav-home"},aria {selected:true}] [ text "Publications (12)"]
, a [className "nav-item nav-link",_id "nav-profile-tab", _data {toggle : "tab"},href "#nav-profile",role "tab",aria {controls : "nav-profile"},aria {selected:true}] [ text "Brevets (2)"]
,a [className "nav-item nav-link",_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "Projets IMT (5)"]
facets
]
]
, div [className "tab-content" , _id "nav-tabContent"]
[
div [className "tab-pane fade show active", role "tabpanel", aria {labelledby : "nav-home-tab"}, _id "nav-home"]
[
table [ className "table"]
[ thead [ className "thead-dark"]
[ tr []
[
th [ scope "col"]
[ text "Date"
]
, th [scope "col"]
[ text "Description"
]
, th [ scope "col"]
[ text "Projects"]
, th [ scope "col"]
[ text " Favorite"]
, th [scope "col"]
[text "Delete"]
facets = [ nav []
[ div [className "nav nav-tabs", _id "nav-tab",role "tablist"]
[ a [className "nav-item nav-link active",_id "nav-home-tab" , _data {toggle : "tab"},href "#nav-home" ,role "tab",aria {controls : "nav-home"} ,aria {selected:true}] [ text "Publications (12)"]
, a [className "nav-item nav-link" ,_id "nav-profile-tab", _data {toggle : "tab"},href "#nav-profile",role "tab",aria {controls : "nav-profile"},aria {selected:true}] [ text "Brevets (2)"]
, a [className "nav-item nav-link" ,_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "Projets (5)"]
, a [className "nav-item nav-link" ,_id "nav-contact-tab", _data {toggle : "tab"},href "#nav-contact",role "tab",aria {controls : "nav-contact"},aria {selected:true}] [ text "All (19)"]
]
]
, tbody []
[ tr []
[ td [] [ text "2012/03/06"]
, td [] [ text "USE OF ACOUSTIC TO DISCRIMINATE DAMAGE MODES IN COMPOSITE -ANTENNA - STRUCTURE DURING BUCKLING LOADING "]
, td [] [ text "ICEM15: 15TH INTERNATIONAL CONFERENCE ON EXPERIMENTAL MECHANICS"]
, td [] [ i [className "fas fa-star"] []]
, td [] [ text "delete"]
, div [className "tab-content" , _id "nav-tabContent"]
[
div [ className "tab-pane fade show active"
, role "tabpanel"
, aria {labelledby : "nav-home-tab"}
, _id "nav-home"
]
[ facetExample ]
, div [ className "tab-pane fade show"
, role "tabpanel"
, aria {labelledby : "nav-profile-tab"}
, _id "nav-profile"
]
[ ]
, div [ className "tab-pane fade show"
, role "tabpanel"
, aria {labelledby : "nav-contact-tab"}
, _id "nav-contact"
]
[ ]
]
, div [className "tab-pane fade show", role "tabpanel", aria {labelledby : "nav-profile-tab"}, _id "nav-profile"]
[
span [] [text "Lorizzle ipsum bling bling sit amizzle, consectetuer adipiscing elit. Nizzle sapien velizzle, bling bling volutpat, suscipit , gravida vel, arcu. Check it out hizzle that's the shizzle. We gonna chung erizzle. Fo izzle dolor fo turpis tempizzle tempor. Gangsta boom shackalack mofo et turpizzle. Sizzle izzle tortor. Pellentesque uhuh ... yih!"]
]
, div [className "tab-pane fade show", role "tabpanel", aria {labelledby : "nav-contact-tab"}, _id "nav-contact"]
[
span [] [text "Lorizzle ipsum bling bling sit amizzle, consectetuer adipiscing elit. Nizzle sapien velizzle, bling bling volutpat, suscipit , gravida vel, arcu. Check it out hizzle that's the shizzle. We gonna chung erizzle. Fo izzle dolor fo turpis tempizzle tempor. Gangsta boom shackalack mofo et turpizzle. Sizzle izzle tortor. Pellentesque uhuh ... yih!"]
]
facetExample = table [ className "table"]
[ thead [ className "thead-dark"]
[ tr []
[ th [ scope "col"] [ text "Date" ]
, th [ scope "col"] [ text "Description" ]
, th [ scope "col"] [ text "Projects" ]
, th [ scope "col"] [ text "Favorite" ]
, th [ scope "col"] [ text "Delete" ]
]
]
, tbody []
[ tr [] [ td [] [ text "2012/03/06"]
, td [] [ text "Big data and text mining"]
, td [] [ text "European funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Cryptography"]
, td [] [ text "French funds"]
, td [] [ text "True"]
, td [] [ text "False"]
]
, tr [] [ td [] [ text "2013/03/06"]
, td [] [ text "Artificial Intelligence"]
, td [] [ text "Not found"]
, td [] [ text "True"]
, td [] [ text "False"]
]
]
]
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