xlsx-0.8.2: Simple and incomplete Excel file parser/writer

Safe HaskellNone
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
Eq ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ChartSpace :: Type -> Type #

NFData ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ChartSpace -> () #

FromCursor ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToElement ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToDocument ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

type Rep ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

newtype ChartTitle Source #

Chart title

TODO: layout, overlay, spPr, txPr, extLst

Constructors

ChartTitle (Maybe TextBody) 
Instances
Eq ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ChartTitle :: Type -> Type #

NFData ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ChartTitle -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DispBlanksAs :: Type -> Type #

NFData DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DispBlanksAs -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

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

Show Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

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 #

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 -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep LegendPos :: Type -> Type #

NFData LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: LegendPos -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

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

Show Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

showsPrec :: Int -> Chart -> ShowS #

show :: Chart -> String #

showList :: [Chart] -> ShowS #

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 #

NFData Chart Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: Chart -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ChartGrouping :: Type -> Type #

NFData ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ChartGrouping -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep BarChartGrouping :: Type -> Type #

NFData BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: BarChartGrouping -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep BarDirection :: Type -> Type #

NFData BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: BarDirection -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ScatterStyle :: Type -> Type #

NFData ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ScatterStyle -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic DataPoint Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataPoint :: Type -> Type #

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 -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

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

Show Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

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 #

NFData Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: Series -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep LineSeries :: Type -> Type #

NFData LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: LineSeries -> () #

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

data AreaSeries Source #

A series on an area chart

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

See CT_AreaSer (p. 4065)

Instances
Eq AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep AreaSeries :: Type -> Type #

NFData AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: AreaSeries -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep BarSeries :: Type -> Type #

NFData BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: BarSeries -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep PieSeries :: Type -> Type #

NFData PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: PieSeries -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep ScatterSeries :: Type -> Type #

NFData ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: ScatterSeries -> () #

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

data DataMarker Source #

Constructors

DataMarker 

Fields

Instances
Eq DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataMarker :: Type -> Type #

NFData DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DataMarker -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataMarkerSymbol :: Type -> Type #

NFData DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DataMarkerSymbol -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Generic DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Associated Types

type Rep DataLblProps :: Type -> Type #

NFData DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: DataLblProps -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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
Eq TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Show TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

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 #

NFData TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

rnf :: TickMark -> () #

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-0.8.2-8DMKXE4frdJ3Wwt78d3mZG" 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