Commit 9dd3448b authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DASHBOARD] refactored + design - real data.

parent a117110b
This source diff could not be displayed because it is too large. You can view the blob instead.
module Dashboard where
import Charts.ECharts
import DOM (DOM)
import Data.Unit (Unit)
import Prelude (pure, unit)
import React.DOM (div, h1, text, title)
import React.DOM.Props (className)
import Thermite (PerformAction, Render, Spec, simpleSpec)
type State = Unit
data Action = None
initialState :: State
initialState = unit
performAction :: forall eff props. PerformAction (dom :: DOM | eff) State props Action
performAction _ _ _ = pure unit
render :: forall props. Render State props Action
render dispatch _ state _ = [
h1 [] [text "IMT DashBoard"]
, histogram1
, div [className "row"] [
div [className "col-md-4 content"] [histogram2]
, div [className "col-md-4 content"] [histogram3]
, div [className "col-md-4 content"] [histogram4]
]
]
layoutDashboard :: forall props eff. Spec (dom :: DOM | eff) State props Action
layoutDashboard = simpleSpec performAction render
......@@ -3,7 +3,7 @@ module DocView where
import Data.Argonaut
import Data.Generic (class Generic, gShow)
import Chart (histogram2, p'')
import Gargantext.Chart (histogram2, p'')
import Control.Monad.Eff.Class (liftEff)
import Control.Monad.Aff (Aff, attempt)
import Control.Monad.Aff.Class (liftAff)
......@@ -187,7 +187,7 @@ performAction LoadData _ _ = void do
loadPage :: forall eff. Aff (ajax :: AJAX, console :: CONSOLE | eff) (Either String CorpusTableData)
loadPage = do
res <- get "http://localhost:8008/corpus/472764/facet/documents/table"
res <- get "http://localhost:8008/corpus/472764/facet/documents/table?offset=0&limit=10"
case res of
Left err -> do
_ <- liftEff $ log $ show err
......
module Chart where
module Gargantext.Chart where
import Prelude (($), (<<<), (<$>))
......
module Charts.Color
(
ChartColor(),
chartColor
module Gargantext.Charts.Color
( ChartColor()
, chartColor
, transparent
) where
import Prelude ((<<<))
import CSS (Color, toHexString)
import Color (rgba)
newtype ChartColor = ChartColor String
transparent :: Color
transparent = rgba 255 255 255 0.0
chartColor :: Color -> ChartColor
chartColor = ChartColor <<< toHexString
module Charts.Data where
module Gargantext.Charts.Data where
import Charts.Font (TextStyle, Icon)
import Gargantext.Charts.Font (TextStyle, Icon)
import Prelude ((<<<))
import Unsafe.Coerce (unsafeCoerce)
......
module Charts.ECharts where
module Gargantext.Charts.ECharts where
import Prelude (($), map, class Show, show, (<<<), (==))
import Data.Array (length)
import CSS (black, blue, italic, violet, white, yellow)
import CSS.Common (normal)
import Charts.Series
import Charts.Data
import Charts.Color (chartColor)
import Charts.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon)
import Charts.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient)
import Charts.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition)
import Charts.Type (DataZoom, Echarts, Legend, Option, Title, Tooltip, XAxis, YAxis)
import Gargantext.Charts.Series
import Gargantext.Charts.Data
import Gargantext.Charts.Color (chartColor, transparent)
import Gargantext.Charts.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon)
import Gargantext.Charts.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient)
import Gargantext.Charts.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition)
import Gargantext.Charts.Type (DataZoom, Echarts, Legend, Option, Title, Tooltip, XAxis, YAxis)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Prelude (($))
import React as R
import React.DOM (p)
foreign import eChartsClass :: R.ReactClass Echarts
chart :: Options -> R.ReactElement
chart = echarts <<< chartWith <<< opts
chartWith :: Option -> Echarts
chartWith opts = { className: Nothing
, style: Nothing
, theme: Nothing
, group: Nothing
, option: opts
, initOpts: Nothing
, notMerge: Nothing
, lazyUpdate: Nothing
, loading: Nothing
, optsLoading: Nothing
, onReady: Nothing
, resizable: Nothing
, onEvents: Nothing
}
echarts :: forall eff. Echarts -> R.ReactElement
echarts chart = R.createElementDynamic eChartsClass chart []
type MainTitle = String
type SubTitle = String
title :: MainTitle -> SubTitle -> Title
title mainTitle subTitle =
{
id: ""
,show: true
,text: mainTitle
,link: ""
,target: "blank"
,textStyle: textStyle
,subtext: subTitle
,sublink: ""
,subtarget: "blank"
,subtextStyle: textStyle2
,padding: 10.0
,itemGap: 0.0
,zlevel: 2.0
,z: 2.0
,left: relativePosition (Relative LeftPos)
,top: relativePosition (Relative Top)
,right: numberPosition 60.0
,bottom: percentPosition 40.0
,backgroundColor: chartColor transparent
,borderColor: chartColor transparent
,borderWidth: 0.0
,borderRadius: 0.0
,shadowBlur: 0.0
,shadowColor: chartColor transparent
,shadowOffsetX: 0.0
,shadowOffsetY: 0.0
}
legend :: Legend
legend =
{
......@@ -58,50 +113,16 @@ data2 = {name: "Favorites", icon: icon $ Shape Circle, textStyle: textStyle'}
data3 :: DataN
data3 = {name: "Test", icon: icon $ Shape Diamond, textStyle: textStyle'}
xAxis' :: XAxis
xAxis' =
{
"data": [xData1, xData2, xData3]
, "type": "category"
, axisTick: {alignWithLabel: true}
, show: true
}
xAxis'' :: XAxis
xAxis'' =
{
"data": [xData1, xData2, xData3, xData4, xData5]
, "type": "category"
, axisTick: {alignWithLabel: true}
, show: true
}
xAxisVoid :: XAxis
xAxisVoid =
{
"data": []
xAxis :: Array String -> XAxis
xAxis xs = { "data": xData xs
, "type": "category"
, axisTick: {alignWithLabel: true}
, show: false
, show: if (length xs == 0) then false else true
}
where
xData :: Array String -> Array DataV
xData xs = map (\x -> {value : x, textStyle : textStyle'}) xs
xData1 :: DataV
xData1 = {value: "Jan", textStyle: textStyle'}
xData2 :: DataV
xData2 = {value: "Feb", textStyle: textStyle'}
xData3 :: DataV
xData3 = {value: "Mar", textStyle: textStyle'}
xData4 :: DataV
xData4 = {value: "Apr", textStyle: textStyle'}
xData5 :: DataV
xData5 = {value: "May", textStyle: textStyle'}
xDataVoid :: DataV
xDataVoid = {value: "", textStyle: textStyle'}
yDataVoid :: YAxis
yDataVoid =
......@@ -120,7 +141,7 @@ yData1 =
"type": "value"
, name: "data"
, min: 0
, position: "right"
, position: "left"
, axisLabel: {formatter: "{value}"}
, show: true
}
......@@ -132,45 +153,69 @@ tooltip' =
, formatter: Nothing
}
seriesBar :: Series
seriesBar =
{
name: "Big Bar Data"
, "type": seriesType Bar
, "data": [{name: "Test1", value: 12.0},
{name: "Test2", value: 20.0},
{name: "Test4", value: 35.0},
{name: "Test5", value: 2.0},
{name: "Test3", value: 32.0}
]
series :: SeriesShape -> SeriesName -> Array DataS -> Series
series sh name ss = { name: name
, "type": seriesType sh
, "data": ss
}
seriesHBar :: Series
seriesHBar =
{
name: "Funnel Data"
, "type": seriesType Funnel
, "data": [{name: "Test1", value: 60.0},
{name: "Test2", value: 100.0},
{name: "Test4", value: 40.0},
{name: "Test5", value: 65.0},
{name: "Test3", value: 32.0}
]
data YAxisFormat = YAxisFormat { position :: String
, visible :: Boolean
}
seriesLine :: Series
seriesLine =
{
name: "Line Data"
, "type": seriesType Line
, "data": [{name: "Test1", value: 50.0},
{name: "Test2", value: 45.0},
{name: "Test3", value: 65.0},
{name: "Test4", value: 15.0},
{name: "Test5", value: 83.0}
]
data Options = Options { mainTitle :: MainTitle
, subTitle :: SubTitle
, xAxis :: XAxis
, yAxis :: Array Series
, yAxisFormat :: YAxisFormat
, addZoom :: Boolean
}
opts :: Options -> Option
opts (Options { mainTitle : mainTitle
, subTitle : subTitle
, xAxis : xs
, yAxis : ss
, yAxisFormat : (YAxisFormat { position : position
, visible : visible
})
, addZoom : addZoom}) =
{ title: title mainTitle subTitle
, legend : legend
, tooltip: { trigger: "axis"
, formatter: Nothing
}
, grid : {containLabel: true}
, xAxis : xs
, series : ss
, yAxis : { "type": "value"
, name: "data"
, min: 0
, position: position
, axisLabel: {formatter: "{value}"}
, show: visible
}
,dataZoom: if addZoom then [zoom Slider, zoom Inside] else []
}
data Zoom = Slider | Inside
instance showZoom :: Show Zoom where
show Slider = "slider"
show Inside = "inside"
zoom :: Zoom -> DataZoom
zoom z = {
"type": show z
,xAxisIndex: 0
,filterMode: "empty"
,start: 0
,end: 100
}
seriesPie :: Series
seriesPie =
{
......@@ -184,98 +229,7 @@ seriesPie =
]
}
seriesWave :: Series
seriesWave =
{
name: "Bar Data"
, "type": seriesType Bar
, "data": [{name: "val1", value: 50.0},
{name: "val2", value: 20.0},
{name: "val5", value: 100.0}]
}
optLineBar :: Option
optLineBar =
{
title: title
,legend: legend
,tooltip: tooltip'
,grid: {containLabel: true}
,xAxis: xAxis''
,yAxis: yData1
,series: [seriesBar, seriesLine]
,dataZoom: [dz1', dz1', dz2', dz2']
}
optSunburst :: Option
optSunburst =
{
title: title
,legend: legend
,tooltip: tooltip'
,grid: {containLabel: true}
,xAxis: xAxisVoid
,yAxis: yDataVoid
,series: [seriesPie]
,dataZoom: []
}
optHBar :: Option
optHBar =
{
title: title
,legend: legend
,tooltip: tooltip'
,grid: {containLabel: true}
,xAxis: xAxisVoid
,yAxis: yDataVoid
,series: [seriesHBar]
,dataZoom: []
}
optWave :: Option
optWave =
{
title: title
,legend: legend
,tooltip: tooltip'
,grid: {containLabel: true}
,xAxis: xAxis'
,yAxis: yData1
,series: [seriesWave]
,dataZoom: []
}
title :: Title
title =
{
id: ""
,show: true
,text: "Awesome Title"
,link: ""
,target: "blank"
,textStyle: textStyle
,subtext: "Awesome Subtitle"
,sublink: ""
,subtarget: "blank"
,subtextStyle: textStyle2
,padding: 10.0
,itemGap: 0.0
,zlevel: 2.0
,z: 2.0
,left: relativePosition (Relative LeftPos)
,top: relativePosition (Relative Top)
,right: numberPosition 60.0
,bottom: percentPosition 40.0
,backgroundColor: chartColor white
,borderColor: chartColor black
,borderWidth: 0.0
,borderRadius: 20.0
,shadowBlur: 0.0
,shadowColor: chartColor black
,shadowOffsetX: 0.0
,shadowOffsetY: 0.0
}
textStyle2 :: TextStyle
textStyle2 =
......@@ -284,14 +238,14 @@ textStyle2 =
,fontStyle: chartFontStyle italic
,fontWeight: chartFontWeight normal
,fontFamily: "sans-serif"
,fontSize: 15
,fontSize: 12
,align: relativePosition $ Relative RightPos
,verticalAlign: relativePosition $ Relative Bottom
,lineHeight: percentPosition 0.0
,width: percentPosition 100.0
,height: percentPosition 100.0
,textBorderColor: chartColor black
,textBorderWidth: 1.0
,textBorderWidth: 0.0
,textShadowColor: chartColor black
,textShadowBlur: chartColor black
,textShadowOffsetX: 0.0
......@@ -305,7 +259,7 @@ textStyle' =
,fontStyle: chartFontStyle normal
,fontWeight: chartFontWeight normal
,fontFamily: "sans-serif"
,fontSize: 12
,fontSize: 15
,align: relativePosition $ Relative LeftPos
,verticalAlign: relativePosition $ Relative Top
,lineHeight: percentPosition 0.0
......@@ -326,7 +280,7 @@ textStyle =
,fontStyle: chartFontStyle normal
,fontWeight: chartFontWeight normal
,fontFamily: "sans-serif"
,fontSize: 12
,fontSize: 20
,align: relativePosition $ Relative LeftPos
,verticalAlign: relativePosition $ Relative Top
,lineHeight: percentPosition 0.0
......@@ -340,138 +294,4 @@ textStyle =
,textShadowOffsetY: 0.0
}
charts1 :: Echarts
charts1 =
{
className: Nothing
,style: Nothing
,theme: Nothing
,group: Nothing
,option: optLineBar
,initOpts: Nothing
,notMerge: Nothing
,lazyUpdate: Nothing
,loading: Nothing
,optsLoading: Nothing
,onReady: Nothing
,resizable: Nothing
,onEvents: Nothing
}
charts2 :: Echarts
charts2 =
{
className: Nothing
,style: Nothing
,theme: Nothing
,group: Nothing
,option: optHBar
,initOpts: Nothing
,notMerge: Nothing
,lazyUpdate: Nothing
,loading: Nothing
,optsLoading: Nothing
,onReady: Nothing
,resizable: Nothing
,onEvents: Nothing
}
charts3 :: Echarts
charts3 =
{
className: Nothing
,style: Nothing
,theme: Nothing
,group: Nothing
,option: optWave
,initOpts: Nothing
,notMerge: Nothing
,lazyUpdate: Nothing
,loading: Nothing
,optsLoading: Nothing
,onReady: Nothing
,resizable: Nothing
,onEvents: Nothing
}
charts4 :: Echarts
charts4 =
{
className: Nothing
,style: Nothing
,theme: Nothing
,group: Nothing
,option: optSunburst
,initOpts: Nothing
,notMerge: Nothing
,lazyUpdate: Nothing
,loading: Nothing
,optsLoading: Nothing
,onReady: Nothing
,resizable: Nothing
,onEvents: Nothing
}
histogram1 :: R.ReactElement
histogram1 = echarts charts1
histogram2 :: R.ReactElement
histogram2 = echarts charts2
histogram3 :: R.ReactElement
histogram3 = echarts charts3
histogram4 :: R.ReactElement
histogram4 = echarts charts4
{-
histogram :: R.ReactElement
histogram = echarts
[ option
[ tooltip [trigger "axis"]
, grid [containLabel true]
, legend [data' ["TEST MUDADA", "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"
]
]
, dataZoom' [dz1', dz1', dz2', dz2']
, yAxis [ya1, ya2]
, series [sd1, sd2, sd3]
]
j ]
type DataZoom =
{"type" :: String
, xAxisIndex :: Int
, filterMode :: String
, start :: Int
, end :: Int
}
-}
dz1' :: DataZoom
dz1' = {
"type": "slider"
,xAxisIndex: 0
,filterMode: "empty"
,start: 0
,end: 100
}
dz2' :: DataZoom
dz2' = {
"type": "inside"
,xAxisIndex: 0
,filterMode: "empty"
,start: 0
,end: 100
}
p'' :: R.ReactElement
p'' = p [] []
module Charts.Font
module Gargantext.Charts.Font
(
TextStyle,
ChartFontStyle(),
......@@ -13,8 +13,8 @@ module Charts.Font
) where
import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..))
import Charts.Color (ChartColor)
import Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
import Gargantext.Charts.Color (ChartColor)
import Gargantext.Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
import Data.Generic (class Generic, gShow)
import Data.String (toLower)
import Prelude (Unit, ($), (<<<), (<>))
......
module Charts.Legend
module Gargantext.Charts.Legend
(
LegendType(..),
PlainOrScroll(..),
......
module Charts.Position
module Gargantext.Charts.Position
(
Position(),
numberPosition,
......
module Charts.Series where
module Gargantext.Charts.Series where
import Charts.Data (DataS)
import Gargantext.Charts.Data (DataS)
import Prelude (class Show, show, (<<<))
newtype SeriesType = SeriesType String
type SeriesName = String
data SeriesShape = Line
| Bar | PictorialBar
| Pie
......
module Charts.Type where
module Gargantext.Charts.Type where
import Charts.Font
import Gargantext.Charts.Font
import CSS (Color)
import Charts.Series
import Charts.Data
import Charts.Color (ChartColor(..))
import Charts.Font (Icon, icon, TextStyle)
import Charts.Legend (LegendType, SelectedMode, selectedMode, Orient)
import Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
import Gargantext.Charts.Series
import Gargantext.Charts.Data
import Gargantext.Charts.Color (ChartColor(..))
import Gargantext.Charts.Font (Icon, icon, TextStyle)
import Gargantext.Charts.Legend (LegendType, SelectedMode, selectedMode, Orient)
import Gargantext.Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
import Data.Either (Either)
import Data.Maybe (Maybe)
import Prelude (Unit, (<<<))
......
module Gargantext.Dashboard where
import Prelude (($), (<>), show, pure, unit, map)
import Gargantext.Charts.ECharts
import Gargantext.Charts.Series
import DOM (DOM)
import Data.Unit (Unit)
import React.DOM (div, h1, text, title)
import React.DOM.Props (className)
import Thermite (PerformAction, Render, Spec, simpleSpec)
type State = Unit
data Action = None
initialState :: State
initialState = unit
performAction :: forall eff props. PerformAction (dom :: DOM | eff) State props Action
performAction _ _ _ = pure unit
render :: forall props. Render State props Action
render dispatch _ state _ = [
h1 [] [text "IMT DashBoard"]
, div [className "row"] [ div [className "col-md-9 content"] [chart globalPublis]
, div [className "col-md-3 content"] [chart naturePublis]
]
, chart distriBySchool
, div [className "row"] (map (\school -> div [className "col-md-4 content"] [chart $ focus school])
[ "Telecom Paris Sud", "Telecom Bretagne", "Telecom ParisTech"]
)
]
where
globalPublis :: Options
globalPublis = (Options { mainTitle : "Global Scientific Publications"
, subTitle : "Distribution of scientific publications by IMT's Schools over time"
, xAxis : xAxis ["Jan", "Feb", "Mar", "Apr", "May"]
, yAxis : [series Bar "Number of publication of IMT / year" [ {name: "Test1", value: 12.0}
, {name: "Test2", value: 20.0}
, {name: "Test4", value: 35.0}
, {name: "Test5", value: 2.0}
, {name: "Test3", value: 32.0}
]
]
, yAxisFormat : (YAxisFormat { position : "left"
, visible : true
})
, addZoom : true
})
distriBySchool :: Options
distriBySchool = Options { mainTitle : "School production in 2018"
, subTitle : "Distribution by school"
, xAxis : xAxis []
, yAxis : [ series Pie "Pie data" [{name: "Sud Paris", value: 50.0},
{name: "Eurecom", value: 45.0},
{name: "Telecom ParisTech", value: 65.0},
{name: "Telecom Bretagne", value: 15.0},
{name: "Telecom Saint-Etienne", value: 23.0}
]
]
, yAxisFormat : (YAxisFormat { position : ""
, visible : false
})
, addZoom : false
}
focus :: String -> Options
focus school = Options { mainTitle : ("Focus " <> school)
, subTitle : "Total scientific publications"
, xAxis : xAxis ["Jan", "Feb", "Mar"]
, yAxis : [series Bar "Bar Data" [ {name: "val1", value: 50.0}
, {name: "val2", value: 20.0}
, {name: "val5", value: 100.0}
]
]
, yAxisFormat : (YAxisFormat { position : "left"
, visible : true
})
, addZoom : false
}
naturePublis :: Options
naturePublis = Options { mainTitle : "Nature of publications"
, subTitle : "Distribution by type"
, xAxis : xAxis []
, yAxis : [series Funnel "Funnel Data" [ {name: "Articles", value: 60.0}
, {name: "Reports", value: 100.0}
, {name: "Patents", value: 40.0}
, {name: "Books", value: 65.0}
]
]
, yAxisFormat : (YAxisFormat { position : "left"
, visible : false
})
, addZoom : false
}
layoutDashboard :: forall props eff. Spec (dom :: DOM | eff) State props Action
layoutDashboard = simpleSpec performAction render
......@@ -38,7 +38,7 @@ import Thermite (PerformAction, Render, Spec, _render, cotransform, defaultPerfo
import Unsafe.Coerce (unsafeCoerce)
import UserPage as UP
import NgramsTable as NG
import Dashboard as Dsh
import Gargantext.Dashboard as Dsh
import Graph as GE
......@@ -109,7 +109,6 @@ data Action
| NgramsA NG.Action
performAction :: forall eff props. PerformAction ( dom :: DOM
, ajax :: AJAX
, console :: CONSOLE
......
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