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.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
......@@ -26,13 +28,13 @@ data SeriesShape = Line
| ThemeRiver
instance showSeriesShape :: Show SeriesShape where
show Line = "line"
show Bar = "bar"
show Pie = "pie"
show Line = "line"
show Bar = "bar"
show Pie = "pie"
show Sunburst = "sunburst"
show Funnel = "funnel"
show Heatmap = "heatmap"
show _ = ""
show Funnel = "funnel"
show Heatmap = "heatmap"
show _ = ""
seriesType :: SeriesShape -> SeriesType
seriesType = SeriesType <<< show
......
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