Commit 033c721e authored by Mael NICOLAS's avatar Mael NICOLAS

Refactor, separe in files

parent ce9e14d5
module Charts.Color where
import Prelude ((<<<))
import CSS (Color, toHexString)
newtype ChartColor = ChartColor String
renderChartColor :: Color -> ChartColor
renderChartColor = ChartColor <<< toHexString
module Charts.ECharts where module Charts.ECharts where
import Charts.Types import Data.Either (Either(..))
import Data.Either
import CSS (Color, black, blue, blueviolet, bolder, borderColor, fontWeight, green, italic, toHexString, turquoise, violet, white, yellow, yellowgreen)
import CSS.Common (class Bottom, normal)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Prelude (show, ($)) import Prelude (($))
import Charts.Type (Data, DataZoom, Echarts, Legend, Option, Series, TextStyle, Title, Tooltip, XAxis, YAxis)
import Charts.Color (renderChartColor)
import Charts.Font (renderChartFontStyle, renderChartFontWeight)
import Charts.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition)
import CSS (black, blue, white, yellow)
import CSS.Common (normal)
import React as R import React as R
import React.DOM (p) import React.DOM (p)
import React.DOM.Props (Props)
foreign import eChartsClass :: forall props. R.ReactClass props foreign import eChartsClass :: forall props. R.ReactClass props
foreign import eChartsClass2 :: R.ReactClass Echarts foreign import eChartsClass2 :: R.ReactClass Echarts
...@@ -125,14 +128,14 @@ title = ...@@ -125,14 +128,14 @@ title =
,itemGap: 0.0 ,itemGap: 0.0
,zlevel: 2.0 ,zlevel: 2.0
,z: 2.0 ,z: 2.0
,left: renderRelativePosition (Relative Center) ,left: relativePosition (Relative Center)
,top: renderRelativePosition (Relative Middle) ,top: relativePosition (Relative Middle)
,right: renderNumber 60.0 ,right: numberPosition 60.0
,bottom: renderPercentage 40.0 ,bottom: percentPosition 40.0
,backgroundColor: renderChartColor black ,backgroundColor: renderChartColor black
,borderColor: renderChartColor black ,borderColor: renderChartColor black
,borderWidth: 0.0 ,borderWidth: 0.0
,borderRadius: Left 20.0 ,borderRadius: 20.0
,shadowBlur: 0.0 ,shadowBlur: 0.0
,shadowColor: renderChartColor black ,shadowColor: renderChartColor black
,shadowOffsetX: 0.0 ,shadowOffsetX: 0.0
...@@ -147,11 +150,11 @@ textStyle2 = ...@@ -147,11 +150,11 @@ textStyle2 =
,fontWeight: renderChartFontWeight normal ,fontWeight: renderChartFontWeight normal
,fontFamily: "sans-serif" ,fontFamily: "sans-serif"
,fontSize: 12 ,fontSize: 12
,align: renderRelativePosition $ Relative RightPos ,align: relativePosition $ Relative RightPos
,verticalAlign: renderRelativePosition $ Relative Bottom ,verticalAlign: relativePosition $ Relative Bottom
,lineHeight: renderPercentage 0.0 ,lineHeight: percentPosition 0.0
,width: renderPercentage 100.0 ,width: percentPosition 100.0
,height: renderPercentage 100.0 ,height: percentPosition 100.0
,textBorderColor: renderChartColor blue ,textBorderColor: renderChartColor blue
,textBorderWidth: 5.0 ,textBorderWidth: 5.0
,textShadowColor: renderChartColor black ,textShadowColor: renderChartColor black
...@@ -169,11 +172,11 @@ textStyle = ...@@ -169,11 +172,11 @@ textStyle =
,fontWeight: renderChartFontWeight normal ,fontWeight: renderChartFontWeight normal
,fontFamily: "sans-serif" ,fontFamily: "sans-serif"
,fontSize: 12 ,fontSize: 12
,align: renderRelativePosition $ Relative LeftPos ,align: relativePosition $ Relative LeftPos
,verticalAlign: renderRelativePosition $ Relative Top ,verticalAlign: relativePosition $ Relative Top
,lineHeight: renderPercentage 0.0 ,lineHeight: percentPosition 0.0
,width: renderPercentage 100.0 ,width: percentPosition 100.0
,height: renderPercentage 100.0 ,height: percentPosition 100.0
,textBorderColor: renderChartColor blue ,textBorderColor: renderChartColor blue
,textBorderWidth: 5.0 ,textBorderWidth: 5.0
,textShadowColor: renderChartColor black ,textShadowColor: renderChartColor black
......
module Charts.Font where
import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..))
newtype ChartFontStyle = ChartFontStyle String
renderChartFontStyle :: FontStyle -> ChartFontStyle
renderChartFontStyle (FontStyle (Value (Plain "italic"))) = ChartFontStyle "italic"
renderChartFontStyle (FontStyle (Value (Plain "oblique"))) = ChartFontStyle "oblique"
renderChartFontStyle _ = ChartFontStyle "normal"
newtype ChartFontWeight = ChartFontWeight String
renderChartFontWeight :: FontWeight -> ChartFontWeight
renderChartFontWeight (FontWeight (Value (Plain "bold"))) = ChartFontWeight "bold"
renderChartFontWeight (FontWeight (Value (Plain "bolder"))) = ChartFontWeight "bolder"
renderChartFontWeight (FontWeight (Value (Plain "lighter"))) = ChartFontWeight "lighter"
renderChartFontWeight _ = ChartFontWeight "normal"
module Charts.Position where
import Prelude (class Show, show, ($), (<>))
import Unsafe.Coerce (unsafeCoerce)
-- | The type `Position` is made to render a css position.
-- | It should be either a `Number`, a `"Number%"` or a `Position` type (`TopRelativePosition` for exemple)
-- | To construct such a type you will have to use one of the smart constructor
foreign import data Position :: Type -> Type
-- | Smart constructor to build a JS Number
numberPosition :: forall r. Number -> Position r
numberPosition = unsafeCoerce
-- | Smart constructor to build a JS Percent
percentPosition :: forall r. Number -> Position r
percentPosition n = unsafeCoerce $ (show n) <> "%"
-- | Smart constructor to build a JS String giving position's detail ("top", "left", ...)
relativePosition :: forall a. Show a => Align a -> Position a
relativePosition (Auto) = unsafeCoerce "auto"
relativePosition (Relative r) = unsafeCoerce $ show r
data Align p = Auto | Relative p
data TopRelativePosition = Top | Middle | Bottom
instance showTopRelativePosition :: Show TopRelativePosition
where show (Top) = "top"
show (Middle) = "middle"
show (Bottom) = "bottom"
data LeftRelativePosition = LeftPos | Center | RightPos
instance showLeftRelativePosition :: Show LeftRelativePosition
where show (LeftPos) = "left"
show (Center) = "center"
show (RightPos) = "right"
module Charts.Types where module Charts.Type where
import Unsafe.Coerce import Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
import Charts.Font
import CSS (Color, FontStyle(..), FontWeight(..), Prefixed(..), Value(..), toHexString) import Charts.Color (ChartColor)
import CSS (Color)
import Data.Either (Either) import Data.Either (Either)
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Prelude ((<>), class Show, show, ($), Unit, (<<<)) import Prelude (Unit, (<<<))
type NumberOrArray = Either Number (Array Number)
data TopRelativePosition = Top | Middle | Bottom
instance showTopRelativePosition :: Show TopRelativePosition
where show (Top) = "top"
show (Middle) = "middle"
show (Bottom) = "bottom"
data LeftRelativePosition = LeftPos | Center | RightPos
instance showLeftRelativePosition :: Show LeftRelativePosition
where show (LeftPos) = "left"
show (Center) = "center"
show (RightPos) = "right"
data Align p = Auto | Relative p
newtype ChartAlign = ChartAlign String newtype ChartAlign = ChartAlign String
newtype ChartColor = ChartColor String
renderChartColor :: Color -> ChartColor
renderChartColor = ChartColor <<< toHexString
newtype ChartFontStyle = ChartFontStyle String
renderChartFontStyle :: FontStyle -> ChartFontStyle
renderChartFontStyle (FontStyle (Value (Plain "italic"))) = ChartFontStyle "italic"
renderChartFontStyle (FontStyle (Value (Plain "oblique"))) = ChartFontStyle "oblique"
renderChartFontStyle _ = ChartFontStyle "normal"
newtype ChartFontWeight = ChartFontWeight String
renderChartFontWeight :: FontWeight -> ChartFontWeight
renderChartFontWeight (FontWeight (Value (Plain "bold"))) = ChartFontWeight "bold"
renderChartFontWeight (FontWeight (Value (Plain "bolder"))) = ChartFontWeight "bolder"
renderChartFontWeight (FontWeight (Value (Plain "lighter"))) = ChartFontWeight "lighter"
renderChartFontWeight _ = ChartFontWeight "normal"
foreign import data Position :: Type -> Type
renderNumber :: forall r. Number -> Position r
renderNumber = unsafeCoerce
renderPercentage :: forall r. Number -> Position r
renderPercentage n = unsafeCoerce $ (show n) <> "%"
renderRelativePosition :: forall a. Show a => Align a -> Position a
renderRelativePosition (Auto) = unsafeCoerce "auto"
renderRelativePosition (Relative r) = unsafeCoerce $ show r
type Echarts = type Echarts =
{ className :: Maybe String, { className :: Maybe String,
style :: Maybe String, -- objealect-black-altdarkmincnaquadahherry-blossomect, style :: Maybe String, -- objealect-black-altdarkmincnaquadahherry-blossomect,
...@@ -107,7 +61,7 @@ type Title = ...@@ -107,7 +61,7 @@ type Title =
, backgroundColor :: ChartColor -- default 'transparent'' , backgroundColor :: ChartColor -- default 'transparent''
, borderColor :: ChartColor -- default '#ccc' , borderColor :: ChartColor -- default '#ccc'
, borderWidth :: Number -- default '1' , borderWidth :: Number -- default '1'
, borderRadius :: NumberOrArray -- default 0; data NumberOrArray = Number | Array Number , borderRadius :: Number -- default 0; data NumberOrArray = Number | Array Number
, shadowBlur :: Number , shadowBlur :: Number
, shadowColor :: ChartColor , shadowColor :: ChartColor
, shadowOffsetX :: Number , shadowOffsetX :: Number
......
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