xlsx-0.7.1: 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 # 
Show ChartSpace Source # 
Generic ChartSpace Source # 

Associated Types

type Rep ChartSpace :: * -> * #

NFData ChartSpace Source # 

Methods

rnf :: ChartSpace -> () #

FromCursor ChartSpace Source # 
ToElement ChartSpace Source # 
ToDocument ChartSpace Source # 
type Rep ChartSpace Source # 

newtype ChartTitle Source #

Chart title

TODO: layout, overlay, spPr, txPr, extLst

Constructors

ChartTitle (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 # 
Show DispBlanksAs Source # 
Generic DispBlanksAs Source # 

Associated Types

type Rep DispBlanksAs :: * -> * #

NFData DispBlanksAs Source # 

Methods

rnf :: DispBlanksAs -> () #

FromAttrVal DispBlanksAs Source # 
ToAttrVal DispBlanksAs Source # 
type Rep DispBlanksAs Source # 
type Rep DispBlanksAs = D1 * (MetaData "DispBlanksAs" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * (C1 * (MetaCons "DispBlanksAsGap" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DispBlanksAsSpan" PrefixI False) (U1 *)) (C1 * (MetaCons "DispBlanksAsZero" PrefixI False) (U1 *))))

data Legend Source #

Instances

Eq Legend Source # 

Methods

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

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

Show Legend Source # 
Generic Legend Source # 

Associated Types

type Rep Legend :: * -> * #

Methods

from :: Legend -> Rep Legend x #

to :: Rep Legend x -> Legend #

Default Legend Source # 

Methods

def :: Legend #

NFData Legend Source # 

Methods

rnf :: Legend -> () #

FromCursor Legend Source # 
ToElement Legend Source # 
type Rep Legend Source # 
type Rep Legend = D1 * (MetaData "Legend" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) (C1 * (MetaCons "Legend" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_legendPos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LegendPos))) (S1 * (MetaSel (Just Symbol "_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 # 
Show LegendPos Source # 
Generic LegendPos Source # 

Associated Types

type Rep LegendPos :: * -> * #

NFData LegendPos Source # 

Methods

rnf :: LegendPos -> () #

FromAttrVal LegendPos Source # 
ToAttrVal LegendPos Source # 
type Rep LegendPos Source # 
type Rep LegendPos = D1 * (MetaData "LegendPos" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LegendBottom" PrefixI False) (U1 *)) (C1 * (MetaCons "LegendLeft" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LegendRight" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LegendTop" PrefixI False) (U1 *)) (C1 * (MetaCons "LegendTopRight" PrefixI False) (U1 *)))))

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 # 

Methods

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

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

Show Chart Source # 

Methods

showsPrec :: Int -> Chart -> ShowS #

show :: Chart -> String #

showList :: [Chart] -> ShowS #

Generic Chart Source # 

Associated Types

type Rep Chart :: * -> * #

Methods

from :: Chart -> Rep Chart x #

to :: Rep Chart x -> Chart #

NFData Chart Source # 

Methods

rnf :: Chart -> () #

type Rep Chart Source # 
type Rep Chart = D1 * (MetaData "Chart" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LineChart" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lnchGrouping") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ChartGrouping)) (S1 * (MetaSel (Just Symbol "_lnchSeries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LineSeries]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lnchMarker") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_lnchSmooth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool)))))) (C1 * (MetaCons "AreaChart" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_archGrouping") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe ChartGrouping))) (S1 * (MetaSel (Just Symbol "_archSeries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [AreaSeries]))))) ((:+:) * (C1 * (MetaCons "BarChart" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_brchDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BarDirection)) ((:*:) * (S1 * (MetaSel (Just Symbol "_brchGrouping") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BarChartGrouping))) (S1 * (MetaSel (Just Symbol "_brchSeries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [BarSeries]))))) ((:+:) * (C1 * (MetaCons "PieChart" PrefixI True) (S1 * (MetaSel (Just Symbol "_pichSeries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [PieSeries]))) (C1 * (MetaCons "ScatterChart" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_scchStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ScatterStyle)) (S1 * (MetaSel (Just Symbol "_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 # 
Show ChartGrouping Source # 
Generic ChartGrouping Source # 

Associated Types

type Rep ChartGrouping :: * -> * #

NFData ChartGrouping Source # 

Methods

rnf :: ChartGrouping -> () #

FromAttrVal ChartGrouping Source # 
ToAttrVal ChartGrouping Source # 
type Rep ChartGrouping Source # 
type Rep ChartGrouping = D1 * (MetaData "ChartGrouping" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * (C1 * (MetaCons "PercentStackedGrouping" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StackedGrouping" PrefixI False) (U1 *)) (C1 * (MetaCons "StandardGrouping" PrefixI False) (U1 *))))

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 # 
Show BarChartGrouping Source # 
Generic BarChartGrouping Source # 
NFData BarChartGrouping Source # 

Methods

rnf :: BarChartGrouping -> () #

FromAttrVal BarChartGrouping Source # 
ToAttrVal BarChartGrouping Source # 
type Rep BarChartGrouping Source # 
type Rep BarChartGrouping = D1 * (MetaData "BarChartGrouping" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * ((:+:) * (C1 * (MetaCons "BarClusteredGrouping" PrefixI False) (U1 *)) (C1 * (MetaCons "BarPercentStackedGrouping" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BarStackedGrouping" PrefixI False) (U1 *)) (C1 * (MetaCons "BarStandardGrouping" PrefixI False) (U1 *))))

data BarDirection Source #

Possible directions for a bar chart

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

Instances

Eq BarDirection Source # 
Show BarDirection Source # 
Generic BarDirection Source # 

Associated Types

type Rep BarDirection :: * -> * #

NFData BarDirection Source # 

Methods

rnf :: BarDirection -> () #

FromAttrVal BarDirection Source # 
ToAttrVal BarDirection Source # 
type Rep BarDirection Source # 
type Rep BarDirection = D1 * (MetaData "BarDirection" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * (C1 * (MetaCons "DirectionBar" PrefixI False) (U1 *)) (C1 * (MetaCons "DirectionColumn" PrefixI False) (U1 *)))

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 # 
Show ScatterStyle Source # 
Generic ScatterStyle Source # 

Associated Types

type Rep ScatterStyle :: * -> * #

NFData ScatterStyle Source # 

Methods

rnf :: ScatterStyle -> () #

FromAttrVal ScatterStyle Source # 
ToAttrVal ScatterStyle Source # 
type Rep ScatterStyle Source # 
type Rep ScatterStyle = D1 * (MetaData "ScatterStyle" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ScatterNone" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ScatterLine" PrefixI False) (U1 *)) (C1 * (MetaCons "ScatterLineMarker" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ScatterMarker" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ScatterSmooth" PrefixI False) (U1 *)) (C1 * (MetaCons "ScatterSmoothMarker" PrefixI False) (U1 *)))))

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 # 
Show DataPoint Source # 
Generic DataPoint Source # 

Associated Types

type Rep DataPoint :: * -> * #

Default DataPoint Source # 

Methods

def :: DataPoint #

NFData DataPoint Source # 

Methods

rnf :: DataPoint -> () #

FromCursor DataPoint Source # 
type Rep DataPoint Source # 
type Rep DataPoint = D1 * (MetaData "DataPoint" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) (C1 * (MetaCons "DataPoint" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_dpMarker") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe DataMarker))) (S1 * (MetaSel (Just Symbol "_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 # 

Methods

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

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

Show Series Source # 
Generic Series Source # 

Associated Types

type Rep Series :: * -> * #

Methods

from :: Series -> Rep Series x #

to :: Rep Series x -> Series #

NFData Series Source # 

Methods

rnf :: Series -> () #

FromCursor Series Source # 
ToElement Series Source # 
type Rep Series Source # 
type Rep Series = D1 * (MetaData "Series" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) (C1 * (MetaCons "Series" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_serTx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Formula))) (S1 * (MetaSel (Just Symbol "_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 # 
Show LineSeries Source # 
Generic LineSeries Source # 

Associated Types

type Rep LineSeries :: * -> * #

NFData LineSeries Source # 

Methods

rnf :: LineSeries -> () #

FromCursor LineSeries Source # 
ToElement LineSeries Source # 
type Rep LineSeries Source # 

data AreaSeries Source #

A series on an area chart

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

See CT_AreaSer (p. 4065)

data BarSeries Source #

A series on a bar chart

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

See CT_BarSer (p. 4064)

data PieSeries Source #

A series on a pie chart

TODO: explosion, cat, extLst

See CT_PieSer (p. 4065)

Constructors

PieSeries 

Fields

data ScatterSeries Source #

A series on a scatter chart

TODO: dPt, trendline, errBars, smooth, extLst

See CT_ScatterSer (p. 4064)

Instances

Eq ScatterSeries Source # 
Show ScatterSeries Source # 
Generic ScatterSeries Source # 

Associated Types

type Rep ScatterSeries :: * -> * #

NFData ScatterSeries Source # 

Methods

rnf :: ScatterSeries -> () #

FromCursor ScatterSeries Source # 
ToElement ScatterSeries Source # 
type Rep ScatterSeries Source # 

data DataMarker Source #

Constructors

DataMarker 

Fields

data DataMarkerSymbol Source #

Instances

Eq DataMarkerSymbol Source # 
Show DataMarkerSymbol Source # 
Generic DataMarkerSymbol Source # 
NFData DataMarkerSymbol Source # 

Methods

rnf :: DataMarkerSymbol -> () #

FromAttrVal DataMarkerSymbol Source # 
ToAttrVal DataMarkerSymbol Source # 
type Rep DataMarkerSymbol Source # 
type Rep DataMarkerSymbol = D1 * (MetaData "DataMarkerSymbol" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "DataMarkerCircle" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DataMarkerDash" PrefixI False) (U1 *)) (C1 * (MetaCons "DataMarkerDiamond" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "DataMarkerDot" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DataMarkerNone" PrefixI False) (U1 *)) (C1 * (MetaCons "DataMarkerPicture" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "DataMarkerPlus" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DataMarkerSquare" PrefixI False) (U1 *)) (C1 * (MetaCons "DataMarkerStar" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "DataMarkerTriangle" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "DataMarkerX" PrefixI False) (U1 *)) (C1 * (MetaCons "DataMarkerAuto" PrefixI False) (U1 *))))))

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 # 
Show DataLblProps Source # 
Generic DataLblProps Source # 

Associated Types

type Rep DataLblProps :: * -> * #

NFData DataLblProps Source # 

Methods

rnf :: DataLblProps -> () #

FromCursor DataLblProps Source # 
ToElement DataLblProps Source # 
type Rep DataLblProps Source # 
type Rep DataLblProps = D1 * (MetaData "DataLblProps" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) (C1 * (MetaCons "DataLblProps" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dlblShowLegendKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_dlblShowVal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dlblShowCatName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_dlblShowSerName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_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 # 
Show TickMark Source # 
Generic TickMark Source # 

Associated Types

type Rep TickMark :: * -> * #

Methods

from :: TickMark -> Rep TickMark x #

to :: Rep TickMark x -> TickMark #

NFData TickMark Source # 

Methods

rnf :: TickMark -> () #

ToAttrVal TickMark Source # 
type Rep TickMark Source # 
type Rep TickMark = D1 * (MetaData "TickMark" "Codec.Xlsx.Types.Drawing.Chart" "xlsx-0.7.1-H5qFfXMGxrd2oSXq37XqR1" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TickMarkCross" PrefixI False) (U1 *)) (C1 * (MetaCons "TickMarkIn" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TickMarkNone" PrefixI False) (U1 *)) (C1 * (MetaCons "TickMarkOut" PrefixI False) (U1 *))))

c_ :: Text -> Name Source #

Add chart namespace to name