xlsx-1.1.2.1: Simple and incomplete Excel file parser/writer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Codec.Xlsx.Types.Drawing.Chart

Synopsis

Documentation

data ChartSpace Source #

Main Chart holder, combines TODO: title, autoTitleDeleted, pivotFmts view3D, floor, sideWall, backWall, showDLblsOverMax, extLst

Instances

Instances details
Generic ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ChartSpace :: Type -> Type #

Show ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ChartSpace -> () #

Eq ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToDocument ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ChartSpace = D1 ('MetaData "ChartSpace" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "ChartSpace" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_chspTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChartTitle)) :*: S1 ('MetaSel ('Just "_chspCharts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Chart])) :*: (S1 ('MetaSel ('Just "_chspLegend") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Legend)) :*: (S1 ('MetaSel ('Just "_chspPlotVisOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_chspDispBlanksAs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DispBlanksAs))))))

newtype ChartTitle Source #

Chart title

TODO: layout, overlay, spPr, txPr, extLst

Constructors

ChartTitle (Maybe TextBody) 

Instances

Instances details
Generic ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ChartTitle :: Type -> Type #

Show ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ChartTitle -> () #

Eq ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ChartTitle = D1 ('MetaData "ChartTitle" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "ChartTitle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TextBody))))

data DispBlanksAs Source #

This simple type specifies the possible ways to display blanks.

See 21.2.3.10 "ST_DispBlanksAs (Display Blanks As)" (p. 3444)

Constructors

DispBlanksAsGap

Specifies that blank values shall be left as a gap.

DispBlanksAsSpan

Specifies that blank values shall be spanned with a line.

DispBlanksAsZero

Specifies that blank values shall be treated as zero.

Instances

Instances details
Generic DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DispBlanksAs :: Type -> Type #

Show DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DispBlanksAs -> () #

Eq DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromAttrVal DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DispBlanksAs = D1 ('MetaData "DispBlanksAs" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "DispBlanksAsGap" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DispBlanksAsSpan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DispBlanksAsZero" 'PrefixI 'False) (U1 :: Type -> Type)))

data Legend Source #

Instances

Instances details
Generic Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep Legend :: Type -> Type #

Methods

from :: Legend -> Rep Legend x #

to :: Rep Legend x -> Legend #

Show Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Default Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

def :: Legend #

NFData Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: Legend -> () #

Eq Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

(==) :: Legend -> Legend -> Bool #

(/=) :: Legend -> Legend -> Bool #

FromCursor Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep Legend = D1 ('MetaData "Legend" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "Legend" 'PrefixI 'True) (S1 ('MetaSel ('Just "_legendPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LegendPos)) :*: S1 ('MetaSel ('Just "_legendOverlay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

data LegendPos Source #

Constructors

LegendBottom

b (Bottom) Specifies that the legend shall be drawn at the bottom of the chart.

LegendLeft

l (Left) Specifies that the legend shall be drawn at the left of the chart.

LegendRight

r (Right) Specifies that the legend shall be drawn at the right of the chart.

LegendTop

t (Top) Specifies that the legend shall be drawn at the top of the chart.

LegendTopRight

tr (Top Right) Specifies that the legend shall be drawn at the top right of the chart.

Instances

Instances details
Generic LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep LegendPos :: Type -> Type #

Show LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: LegendPos -> () #

Eq LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromAttrVal LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep LegendPos = D1 ('MetaData "LegendPos" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "LegendBottom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LegendLeft" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LegendRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LegendTop" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LegendTopRight" 'PrefixI 'False) (U1 :: Type -> Type))))

data Chart Source #

Specific Chart TODO: area3DChart, line3DChart, stockChart, radarChart, pie3DChart, doughnutChart, bar3DChart, ofPieChart, surfaceChart, surface3DChart, bubbleChart

Constructors

LineChart 

Fields

AreaChart 
BarChart 
PieChart 

Fields

ScatterChart 

Instances

Instances details
Generic Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep Chart :: Type -> Type #

Methods

from :: Chart -> Rep Chart x #

to :: Rep Chart x -> Chart #

Show Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

showsPrec :: Int -> Chart -> ShowS #

show :: Chart -> String #

showList :: [Chart] -> ShowS #

NFData Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: Chart -> () #

Eq Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

(==) :: Chart -> Chart -> Bool #

(/=) :: Chart -> Chart -> Bool #

type Rep Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep Chart = D1 ('MetaData "Chart" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "LineChart" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_lnchGrouping") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChartGrouping) :*: S1 ('MetaSel ('Just "_lnchSeries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LineSeries])) :*: (S1 ('MetaSel ('Just "_lnchMarker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_lnchSmooth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :+: C1 ('MetaCons "AreaChart" 'PrefixI 'True) (S1 ('MetaSel ('Just "_archGrouping") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChartGrouping)) :*: S1 ('MetaSel ('Just "_archSeries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AreaSeries]))) :+: (C1 ('MetaCons "BarChart" 'PrefixI 'True) (S1 ('MetaSel ('Just "_brchDirection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BarDirection) :*: (S1 ('MetaSel ('Just "_brchGrouping") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BarChartGrouping)) :*: S1 ('MetaSel ('Just "_brchSeries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BarSeries]))) :+: (C1 ('MetaCons "PieChart" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pichSeries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PieSeries])) :+: C1 ('MetaCons "ScatterChart" 'PrefixI 'True) (S1 ('MetaSel ('Just "_scchStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScatterStyle) :*: S1 ('MetaSel ('Just "_scchSeries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ScatterSeries])))))

data ChartGrouping Source #

Possible groupings for a chart

See 21.2.3.17 "ST_Grouping (Grouping)" (p. 3446)

Constructors

PercentStackedGrouping

(100% Stacked) Specifies that the chart series are drawn next to each other along the value axis and scaled to total 100%.

StackedGrouping

(Stacked) Specifies that the chart series are drawn next to each other on the value axis.

StandardGrouping

(Standard) Specifies that the chart series are drawn on the value axis.

Instances

Instances details
Generic ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ChartGrouping :: Type -> Type #

Show ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ChartGrouping -> () #

Eq ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromAttrVal ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ChartGrouping = D1 ('MetaData "ChartGrouping" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "PercentStackedGrouping" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StackedGrouping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StandardGrouping" 'PrefixI 'False) (U1 :: Type -> Type)))

data BarChartGrouping Source #

Possible groupings for a bar chart

See 21.2.3.4 "ST_BarGrouping (Bar Grouping)" (p. 3441)

Constructors

BarClusteredGrouping

Specifies that the chart series are drawn next to each other along the category axis.

BarPercentStackedGrouping

(100% Stacked) Specifies that the chart series are drawn next to each other along the value axis and scaled to total 100%.

BarStackedGrouping

(Stacked) Specifies that the chart series are drawn next to each other on the value axis.

BarStandardGrouping

(Standard) Specifies that the chart series are drawn on the value axis.

Instances

Instances details
Generic BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep BarChartGrouping :: Type -> Type #

Show BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: BarChartGrouping -> () #

Eq BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromAttrVal BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep BarChartGrouping = D1 ('MetaData "BarChartGrouping" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "BarClusteredGrouping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BarPercentStackedGrouping" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BarStackedGrouping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BarStandardGrouping" 'PrefixI 'False) (U1 :: Type -> Type)))

data BarDirection Source #

Possible directions for a bar chart

See 21.2.3.3 "ST_BarDir (Bar Direction)" (p. 3441)

Instances

Instances details
Generic BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep BarDirection :: Type -> Type #

Show BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: BarDirection -> () #

Eq BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromAttrVal BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep BarDirection = D1 ('MetaData "BarDirection" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "DirectionBar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirectionColumn" 'PrefixI 'False) (U1 :: Type -> Type))

data ScatterStyle Source #

Possible styles of scatter chart

Note: It appears that even for ScatterMarker style Exel draws a line between chart points if otline fill for _scserShared isn't set to so it's not quite clear how could Excel use this property

See 21.2.3.40 "ST_ScatterStyle (Scatter Style)" (p. 3455)

Instances

Instances details
Generic ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ScatterStyle :: Type -> Type #

Show ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ScatterStyle -> () #

Eq ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromAttrVal ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ScatterStyle = D1 ('MetaData "ScatterStyle" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "ScatterNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ScatterLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScatterLineMarker" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ScatterMarker" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ScatterSmooth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScatterSmoothMarker" 'PrefixI 'False) (U1 :: Type -> Type))))

data DataPoint Source #

Single data point options

TODO: invertIfNegative, bubble3D, explosion, pictureOptions, extLst

See 21.2.2.52 "dPt (Data Point)" (p. 3384)

Instances

Instances details
Generic DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataPoint :: Type -> Type #

Show DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Default DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

def :: DataPoint #

NFData DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DataPoint -> () #

Eq DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataPoint = D1 ('MetaData "DataPoint" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "DataPoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "_dpMarker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataMarker)) :*: S1 ('MetaSel ('Just "_dpShapeProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ShapeProperties))))

data Series Source #

Specifies common series options TODO: spPr

See EG_SerShared (p. 4063)

Constructors

Series 

Fields

Instances

Instances details
Generic Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep Series :: Type -> Type #

Methods

from :: Series -> Rep Series x #

to :: Rep Series x -> Series #

Show Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: Series -> () #

Eq Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

(==) :: Series -> Series -> Bool #

(/=) :: Series -> Series -> Bool #

FromCursor Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep Series = D1 ('MetaData "Series" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "Series" 'PrefixI 'True) (S1 ('MetaSel ('Just "_serTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Formula)) :*: S1 ('MetaSel ('Just "_serShapeProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ShapeProperties))))

data LineSeries Source #

A series on a line chart

TODO: dPt, trendline, errBars, cat, extLst

See CT_LineSer (p. 4064)

Constructors

LineSeries 

Fields

Instances

Instances details
Generic LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep LineSeries :: Type -> Type #

Show LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: LineSeries -> () #

Eq LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep LineSeries = D1 ('MetaData "LineSeries" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "LineSeries" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_lnserShared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Series) :*: S1 ('MetaSel ('Just "_lnserMarker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataMarker))) :*: (S1 ('MetaSel ('Just "_lnserDataLblProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataLblProps)) :*: (S1 ('MetaSel ('Just "_lnserVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Formula)) :*: S1 ('MetaSel ('Just "_lnserSmooth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

data AreaSeries Source #

A series on an area chart

TODO: pictureOptions, dPt, trendline, errBars, cat, extLst

See CT_AreaSer (p. 4065)

Instances

Instances details
Generic AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep AreaSeries :: Type -> Type #

Show AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: AreaSeries -> () #

Eq AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep AreaSeries = D1 ('MetaData "AreaSeries" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "AreaSeries" 'PrefixI 'True) (S1 ('MetaSel ('Just "_arserShared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Series) :*: (S1 ('MetaSel ('Just "_arserDataLblProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataLblProps)) :*: S1 ('MetaSel ('Just "_arserVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Formula)))))

data BarSeries Source #

A series on a bar chart

TODO: invertIfNegative, pictureOptions, dPt, trendline, errBars, cat, shape, extLst

See CT_BarSer (p. 4064)

Instances

Instances details
Generic BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep BarSeries :: Type -> Type #

Show BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: BarSeries -> () #

Eq BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep BarSeries = D1 ('MetaData "BarSeries" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "BarSeries" 'PrefixI 'True) (S1 ('MetaSel ('Just "_brserShared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Series) :*: (S1 ('MetaSel ('Just "_brserDataLblProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataLblProps)) :*: S1 ('MetaSel ('Just "_brserVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Formula)))))

data PieSeries Source #

A series on a pie chart

TODO: explosion, cat, extLst

See CT_PieSer (p. 4065)

Constructors

PieSeries 

Fields

Instances

Instances details
Generic PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep PieSeries :: Type -> Type #

Show PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: PieSeries -> () #

Eq PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep PieSeries = D1 ('MetaData "PieSeries" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "PieSeries" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_piserShared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Series) :*: S1 ('MetaSel ('Just "_piserDataPoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataPoint])) :*: (S1 ('MetaSel ('Just "_piserDataLblProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataLblProps)) :*: S1 ('MetaSel ('Just "_piserVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Formula)))))

data ScatterSeries Source #

A series on a scatter chart

TODO: dPt, trendline, errBars, smooth, extLst

See CT_ScatterSer (p. 4064)

Instances

Instances details
Generic ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ScatterSeries :: Type -> Type #

Show ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ScatterSeries -> () #

Eq ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ScatterSeries = D1 ('MetaData "ScatterSeries" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "ScatterSeries" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_scserShared") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Series) :*: (S1 ('MetaSel ('Just "_scserMarker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataMarker)) :*: S1 ('MetaSel ('Just "_scserDataLblProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataLblProps)))) :*: (S1 ('MetaSel ('Just "_scserXVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Formula)) :*: (S1 ('MetaSel ('Just "_scserYVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Formula)) :*: S1 ('MetaSel ('Just "_scserSmooth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

data DataMarker Source #

Constructors

DataMarker 

Fields

Instances

Instances details
Generic DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataMarker :: Type -> Type #

Show DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DataMarker -> () #

Eq DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataMarker = D1 ('MetaData "DataMarker" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "DataMarker" 'PrefixI 'True) (S1 ('MetaSel ('Just "_dmrkSymbol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DataMarkerSymbol)) :*: S1 ('MetaSel ('Just "_dmrkSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

data DataMarkerSymbol Source #

Instances

Instances details
Generic DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataMarkerSymbol :: Type -> Type #

Show DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DataMarkerSymbol -> () #

Eq DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromAttrVal DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataMarkerSymbol = D1 ('MetaData "DataMarkerSymbol" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (((C1 ('MetaCons "DataMarkerCircle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataMarkerDash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataMarkerDiamond" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DataMarkerDot" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataMarkerNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataMarkerPicture" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DataMarkerPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataMarkerSquare" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataMarkerStar" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DataMarkerTriangle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataMarkerX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataMarkerAuto" 'PrefixI 'False) (U1 :: Type -> Type)))))

data DataLblProps Source #

Settings for the data labels for an entire series or the entire chart

TODO: numFmt, spPr, txPr, dLblPos, showBubbleSize, separator, showLeaderLines, leaderLines See 21.2.2.49 "dLbls (Data Labels)" (p. 3384)

Instances

Instances details
Generic DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataLblProps :: Type -> Type #

Show DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DataLblProps -> () #

Eq DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

FromCursor DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep DataLblProps = D1 ('MetaData "DataLblProps" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "DataLblProps" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_dlblShowLegendKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_dlblShowVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "_dlblShowCatName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "_dlblShowSerName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_dlblShowPercent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

data TickMark Source #

Specifies the possible positions for tick marks.

Constructors

TickMarkCross

(Cross) Specifies the tick marks shall cross the axis.

TickMarkIn

(Inside) Specifies the tick marks shall be inside the plot area.

TickMarkNone

(None) Specifies there shall be no tick marks.

TickMarkOut

(Outside) Specifies the tick marks shall be outside the plot area.

Instances

Instances details
Generic TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep TickMark :: Type -> Type #

Methods

from :: TickMark -> Rep TickMark x #

to :: Rep TickMark x -> TickMark #

Show TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

NFData TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: TickMark -> () #

Eq TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep TickMark = D1 ('MetaData "TickMark" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "TickMarkCross" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TickMarkIn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TickMarkNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TickMarkOut" 'PrefixI 'False) (U1 :: Type -> Type)))

c_ :: Text -> Name Source #

Add chart namespace to name