diff --git a/src/Charts/Color.purs b/src/Charts/Color.purs
index 7f74823269871eeb88a7ef6369978fd5688c03c9..9a26069a0ec162b88e12a3ad2ff1197be4ff7501 100644
--- a/src/Charts/Color.purs
+++ b/src/Charts/Color.purs
@@ -2,7 +2,7 @@ module Charts.Color
        (
          ChartColor(),
          chartColor
-       )where
+       ) where
 
 import Prelude ((<<<))
 import CSS (Color, toHexString)
diff --git a/src/Charts/ECharts.purs b/src/Charts/ECharts.purs
index fafb999d346a87c35aceaed325959b21121e4ba3..8f26da0e09cf4d11cd5a54c14827fb2651d9699a 100644
--- a/src/Charts/ECharts.purs
+++ b/src/Charts/ECharts.purs
@@ -1,12 +1,14 @@
 module Charts.ECharts where
 
-import CSS (black, blue, white, yellow)
+
+import CSS (black, blue, italic, violet, white, yellow)
 import CSS.Common (normal)
+import Charts.Data
 import Charts.Color (chartColor)
-import Charts.Font (chartFontStyle, chartFontWeight)
-import Charts.Legend (legendType, LegendType, PlainOrScroll(..))
+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 (Data, DataZoom, Echarts, Legend, Option, Series, TextStyle, Title, Tooltip, XAxis, YAxis)
+import Charts.Type (DataZoom, Echarts, Legend, Option, Series, Title, Tooltip, XAxis, YAxis)
 import Data.Either (Either(..))
 import Data.Maybe (Maybe(..))
 import Prelude (($))
@@ -18,41 +20,42 @@ foreign import eChartsClass :: R.ReactClass Echarts
 echarts :: forall eff. Echarts -> R.ReactElement
 echarts chart = R.createElementDynamic eChartsClass chart []
 
-legend' :: Legend
-legend' =
+legend :: Legend
+legend =
   {
-    id: ""
+    id: "Muda"
    ,"type": legendType Plain
    , show: true
-   , zlevel: 40.0
-   , z: 40.0
-   , left: percentPosition 40.0
-   , top:  percentPosition 40.0
-   , right:  percentPosition 40.0
-   , bottom:  percentPosition 40.0
-   , width: percentPosition 40.0
-   , height: percentPosition 40.0
-   , orient: Nothing
-   , align: Nothing
-   , padding: Nothing
-   , itemGap: Nothing
-   , itemWidth: Nothing
-   , itemHeight: Nothing
+   , zlevel: 0.0
+   , z: 2.0
+   , left: relativePosition Auto
+   , top: relativePosition Auto
+   , right: relativePosition Auto
+   , bottom: relativePosition Auto
+   , width: relativePosition Auto
+   , height: relativePosition Auto
+   , orient: orient Horizontal
+   , align: relativePosition Auto
+   , padding: 5.0
+   , itemGap: 10.0
+   , itemWidth: 25.0
+   , itemHeight: 14.0
    , formatter: Nothing
-   , selectedMode: Nothing
-   , inactiveColor: Nothing
+   , selectedMode: selectedMode $ Bool true
+   , inactiveColor: chartColor violet
    , selected: Nothing
-   , "data": Nothing
+   , textStyle: textStyle
+   , "data": [data1]
   }
 
-data1 :: Data
-data1 = {name: "Map terms coverage", icon: Nothing, textStyle: Nothing}
+data1 :: DataN
+data1 = {name: "Map terms coverage", icon: icon $ Shape Circle, textStyle: textStyle'}
 
-data2 :: Data
-data2 = {name: "Favorites", icon: Nothing, textStyle: Nothing}
+data2 :: DataN
+data2 = {name: "Favorites", icon: icon $ Shape Circle, textStyle: textStyle'}
 
-data3 :: Data
-data3 = {name: "All", icon: Nothing, textStyle: Nothing}
+data3 :: DataN
+data3 = {name: "Test", icon: icon $ Shape Diamond, textStyle: textStyle'}
 
 xAxis' :: XAxis
 xAxis' =
@@ -62,14 +65,14 @@ xAxis' =
  , axisTick: {alignWithLabel: true}
  }
 
-xData1 :: Data
-xData1 = {name: "Jan", icon: Nothing, textStyle: Nothing}
+xData1 :: DataV
+xData1 = {value: "Jan", textStyle: textStyle'}
 
-xData2 :: Data
-xData2 = {name: "Feb", icon: Nothing, textStyle: Nothing}
+xData2 :: DataV
+xData2 = {value: "Feb", textStyle: textStyle'}
 
-xData3 :: Data
-xData3 = {name: "Mar", icon: Nothing, textStyle: Nothing}
+xData3 :: DataV
+xData3 = {value: "Mar", textStyle: textStyle'}
 
 yData1 :: YAxis
 yData1 =
@@ -101,7 +104,7 @@ opt :: Option
 opt =
   {
     title: title
-    ,legend: Nothing
+    ,legend: legend
     ,tooltip: tooltip'
     ,grid: {containLabel: true}
     ,xAxis: xAxis'
@@ -113,7 +116,7 @@ opt =
 title :: Title
 title =
   {
-    id: ""
+    id: "Muda"
    ,show: true
    ,text: "MudaTitre rpz les pyramides"
    ,link: "https://google.com"
@@ -127,8 +130,8 @@ title =
    ,itemGap: 0.0
    ,zlevel: 2.0
    ,z: 2.0
-   ,left: relativePosition (Relative Center)
-   ,top: relativePosition (Relative Middle)
+   ,left: relativePosition (Relative LeftPos)
+   ,top: relativePosition (Relative Top)
    ,right: numberPosition 60.0
    ,bottom: percentPosition 40.0
    ,backgroundColor: chartColor black
@@ -145,7 +148,7 @@ textStyle2 :: TextStyle
 textStyle2 =
   {
     color: chartColor yellow
-    ,fontStyle: chartFontStyle normal
+    ,fontStyle: chartFontStyle italic
     ,fontWeight: chartFontWeight normal
     ,fontFamily: "sans-serif"
     ,fontSize: 12
@@ -162,6 +165,26 @@ textStyle2 =
     ,textShadowOffsetY: 0.0
   }
 
+textStyle' :: TextStyle
+textStyle' =
+  {
+    color: chartColor violet
+    ,fontStyle: chartFontStyle normal
+    ,fontWeight: chartFontWeight normal
+    ,fontFamily: "sans-serif"
+    ,fontSize: 12
+    ,align: relativePosition $ Relative LeftPos
+    ,verticalAlign: relativePosition $ Relative Top
+    ,lineHeight: percentPosition 0.0
+    ,width: percentPosition 100.0
+    ,height: percentPosition 100.0
+    ,textBorderColor: chartColor black
+    ,textBorderWidth: 5.0
+    ,textShadowColor: chartColor black
+    ,textShadowBlur: chartColor black
+    ,textShadowOffsetX: 0.0
+    ,textShadowOffsetY: 0.0
+  }
 
 textStyle :: TextStyle
 textStyle =
diff --git a/src/Charts/Font.purs b/src/Charts/Font.purs
index 1f2e1313a7e6f82f93dbbba0b923b02059c892bd..9bc1d887f4b78b4884223deeaad170398b31b79f 100644
--- a/src/Charts/Font.purs
+++ b/src/Charts/Font.purs
@@ -1,12 +1,43 @@
 module Charts.Font
        (
+         TextStyle,
          ChartFontStyle(),
          chartFontStyle,
          ChartFontWeight(),
-         chartFontWeight
+         chartFontWeight,
+         Icon(),
+         ImageURL(..),
+         Shape(..),
+         IconOptions(..),
+         icon
        ) where
 
 import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..))
+import Charts.Color (ChartColor)
+import Charts.Position (LeftRelativePosition, Position, TopRelativePosition)
+import Data.Generic (class Generic, gShow)
+import Data.String (toLower)
+import Prelude (Unit, ($), (<<<), (<>))
+
+type TextStyle =
+  { color      :: ChartColor
+  , fontStyle  :: ChartFontStyle
+  , fontWeight :: ChartFontWeight
+  , fontFamily :: String
+  , fontSize   :: Int
+  , align      :: Position LeftRelativePosition
+  , verticalAlign :: Position TopRelativePosition
+  , lineHeight    :: Position Unit
+  , width         :: Position Unit
+  , height        :: Position Unit
+  , textBorderColor :: ChartColor
+  , textBorderWidth :: Number
+  , textShadowColor :: ChartColor
+  , textShadowBlur  :: ChartColor
+  , textShadowOffsetX :: Number
+  , textShadowOffsetY :: Number
+  }
+
 
 newtype ChartFontStyle = ChartFontStyle String
 
@@ -15,6 +46,7 @@ chartFontStyle (FontStyle (Value (Plain "italic"))) = ChartFontStyle "italic"
 chartFontStyle (FontStyle (Value (Plain "oblique"))) = ChartFontStyle "oblique"
 chartFontStyle _ = ChartFontStyle "normal"
 
+
 newtype ChartFontWeight = ChartFontWeight String
 
 chartFontWeight :: FontWeight -> ChartFontWeight
@@ -22,3 +54,17 @@ chartFontWeight (FontWeight (Value (Plain "bold"))) = ChartFontWeight "bold"
 chartFontWeight (FontWeight (Value (Plain "bolder"))) = ChartFontWeight "bolder"
 chartFontWeight (FontWeight (Value (Plain "lighter"))) = ChartFontWeight "lighter"
 chartFontWeight  _ = ChartFontWeight "normal"
+
+
+newtype Icon = Icon String
+
+newtype ImageURL = ImageURL String
+
+data Shape = Circle | Rect | RoundRect | Triangle | Diamond | Pin | Arrow
+derive instance genericShape :: Generic Shape
+
+data IconOptions = Shape Shape | Image ImageURL
+
+icon :: IconOptions -> Icon
+icon (Shape s) = Icon <<< toLower $ gShow s
+icon (Image (ImageURL url)) = Icon $ "image://" <> url
diff --git a/src/Charts/Legend.purs b/src/Charts/Legend.purs
index fa8f1cbdbe699902abdf3ed9cf4cc3ddf574d717..92df36112dea7540371b5fbe5a8ad90c55d60420 100644
--- a/src/Charts/Legend.purs
+++ b/src/Charts/Legend.purs
@@ -1,24 +1,30 @@
 module Charts.Legend
        (
-         LegendType(),
+         LegendType(..),
          PlainOrScroll(..),
          legendType,
          Orient(),
          Orientation(..),
-         orient
+         orient,
+         SelectedMode(),
+         LegendMode(..),
+         selectedMode
        ) where
 
 import Data.Generic (class Generic, gShow)
 import Data.String (toLower)
-import Prelude ((<<<))
+import Prelude (class Show, show, (<<<))
+import Unsafe.Coerce (unsafeCoerce)
 
 newtype LegendType = LegendType String
 
 data PlainOrScroll = Plain | Scroll
-derive instance genericPlainOrScroll :: Generic PlainOrScroll
+instance showPlainOrScroll :: Show PlainOrScroll where
+  show (Plain) = "plain"
+  show (Scroll) = "scroll"
 
 legendType :: PlainOrScroll -> LegendType
-legendType = LegendType <<< toLower <<< gShow
+legendType = LegendType <<< toLower <<< show
 
 
 newtype Orient = Orient String
@@ -28,3 +34,15 @@ derive instance genericOrientation :: Generic Orientation
 
 orient :: Orientation -> Orient
 orient = Orient <<< toLower <<< gShow
+
+
+foreign import data SelectedMode :: Type
+
+data LegendMode = Bool Boolean | Single | Multiple
+derive instance genericLegendMode :: Generic LegendMode
+
+selectedMode :: LegendMode -> SelectedMode
+selectedMode (Bool b) = unsafeCoerce b
+selectedMode (Single) = unsafeCoerce "single"
+selectedMode (Multiple) = unsafeCoerce "multiple"
+
diff --git a/src/Charts/Position.purs b/src/Charts/Position.purs
index 511fca1896f256d2fcf1613b27c485f6343e5e8f..ed5aaabb04ade606b252ed316a1f19e43b31a615 100644
--- a/src/Charts/Position.purs
+++ b/src/Charts/Position.purs
@@ -8,6 +8,7 @@ module Charts.Position
          TopRelativePosition(..),
          LeftRelativePosition(..)
        ) where
+
 import Prelude (class Show, show, ($), (<>))
 import Unsafe.Coerce (unsafeCoerce)
 
diff --git a/src/Charts/Type.purs b/src/Charts/Type.purs
index 97f4869a4b56dfbe3241547657afdf51f4c74ef0..a5298daa019eab9465d5a902dcfa748712182f46 100644
--- a/src/Charts/Type.purs
+++ b/src/Charts/Type.purs
@@ -3,8 +3,10 @@ module Charts.Type where
 import Charts.Font
 
 import CSS (Color)
-import Charts.Color (ChartColor)
-import Charts.Legend (LegendType)
+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 Data.Either (Either)
 import Data.Maybe (Maybe)
@@ -31,7 +33,7 @@ type Echarts =
 
 type Option =
   { title    :: Title
-  , legend   :: Maybe Legend
+  , legend   :: Legend
   , tooltip  :: Tooltip
   , grid     :: Grid
   , xAxis    :: XAxis
@@ -103,42 +105,18 @@ type Legend =
   , bottom :: Position Unit
   , width :: Position Unit
   , height :: Position Unit
-  , orient :: Maybe String
-  , align :: Maybe String
-  , padding :: Maybe Number
-  , itemGap :: Maybe Number
-  , itemWidth :: Maybe Number
-  , itemHeight :: Maybe Number
+  , orient :: Orient
+  , align :: Position LeftRelativePosition
+  , padding :: Number
+  , itemGap :: Number
+  , itemWidth :: Number
+  , itemHeight :: Number
   , formatter :: Maybe String
-  , selectedMode :: Maybe Boolean
-  , inactiveColor :: Maybe Color
+  , selectedMode :: SelectedMode
+  , inactiveColor :: ChartColor
   , selected :: Maybe String -- object
-  , "data" :: Maybe (Array Data)
-  }
-
-type Data =
-  { name      :: String
-  , icon      :: Maybe String
-  , textStyle :: Maybe {}
-  }
-
-type TextStyle =
-  { color      :: ChartColor
-  , fontStyle  :: ChartFontStyle
-  , fontWeight :: ChartFontWeight
-  , fontFamily :: String
-  , fontSize   :: Int
-  , align      :: Position LeftRelativePosition
-  , verticalAlign :: Position TopRelativePosition
-  , lineHeight    :: Position Unit
-  , width         :: Position Unit
-  , height        :: Position Unit
-  , textBorderColor :: ChartColor
-  , textBorderWidth :: Number
-  , textShadowColor :: ChartColor
-  , textShadowBlur  :: ChartColor
-  , textShadowOffsetX :: Number
-  , textShadowOffsetY :: Number
+  , textStyle :: TextStyle
+  , "data" :: Array DataN
   }
 
 type Tooltip =
@@ -147,7 +125,7 @@ type Tooltip =
   }
 
 type XAxis =
-  { "data"   :: Array Data
+  { "data"   :: Array DataV
   , "type"   :: String
   , axisTick :: AxisTick
   }