xlsx-0.8.4: Simple and incomplete Excel file parser/writer
Safe HaskellNone
LanguageHaskell2010

Codec.Xlsx.Types.PivotTable

Synopsis

Documentation

data PivotTable Source #

Instances

Instances details
Eq PivotTable Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Show PivotTable Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Generic PivotTable Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Associated Types

type Rep PivotTable :: Type -> Type #

NFData PivotTable Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Methods

rnf :: PivotTable -> () #

type Rep PivotTable Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep PivotTable = D1 ('MetaData "PivotTable" "Codec.Xlsx.Types.PivotTable" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "PivotTable" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_pvtName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "_pvtDataCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_pvtRowFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PositionedField]))) :*: (S1 ('MetaSel ('Just "_pvtColumnFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PositionedField]) :*: (S1 ('MetaSel ('Just "_pvtDataFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DataField]) :*: S1 ('MetaSel ('Just "_pvtFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PivotFieldInfo])))) :*: ((S1 ('MetaSel ('Just "_pvtRowGrandTotals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_pvtColumnGrandTotals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_pvtOutline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "_pvtOutlineData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_pvtLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CellRef)) :*: (S1 ('MetaSel ('Just "_pvtSrcSheet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_pvtSrcRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))))))

newtype PivotFieldName Source #

Constructors

PivotFieldName Text 

Instances

Instances details
Eq PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Ord PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Show PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Generic PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Associated Types

type Rep PivotFieldName :: Type -> Type #

NFData PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Methods

rnf :: PivotFieldName -> () #

FromAttrVal PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

ToAttrVal PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep PivotFieldName = D1 ('MetaData "PivotFieldName" "Codec.Xlsx.Types.PivotTable" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'True) (C1 ('MetaCons "PivotFieldName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data PivotFieldInfo Source #

Instances

Instances details
Eq PivotFieldInfo Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Show PivotFieldInfo Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Generic PivotFieldInfo Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Associated Types

type Rep PivotFieldInfo :: Type -> Type #

NFData PivotFieldInfo Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Methods

rnf :: PivotFieldInfo -> () #

type Rep PivotFieldInfo Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep PivotFieldInfo = D1 ('MetaData "PivotFieldInfo" "Codec.Xlsx.Types.PivotTable" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "PivotFieldInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_pfiName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PivotFieldName)) :*: S1 ('MetaSel ('Just "_pfiOutline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_pfiSortType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldSortType) :*: S1 ('MetaSel ('Just "_pfiHiddenItems") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CellValue]))))

data FieldSortType Source #

Sort orders that can be applied to fields in a PivotTable

See 18.18.28 "ST_FieldSortType (Field Sort Type)" (p. 2454)

Instances

Instances details
Eq FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Ord FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Show FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Generic FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Associated Types

type Rep FieldSortType :: Type -> Type #

NFData FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Methods

rnf :: FieldSortType -> () #

FromAttrVal FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

ToAttrVal FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep FieldSortType = D1 ('MetaData "FieldSortType" "Codec.Xlsx.Types.PivotTable" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "FieldSortAscending" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FieldSortDescending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FieldSortManual" 'PrefixI 'False) (U1 :: Type -> Type)))

data PositionedField Source #

Instances

Instances details
Eq PositionedField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Ord PositionedField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Show PositionedField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Generic PositionedField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Associated Types

type Rep PositionedField :: Type -> Type #

NFData PositionedField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Methods

rnf :: PositionedField -> () #

type Rep PositionedField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep PositionedField = D1 ('MetaData "PositionedField" "Codec.Xlsx.Types.PivotTable" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "DataPosition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FieldPosition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PivotFieldName)))

data DataField Source #

Instances

Instances details
Eq DataField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Show DataField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Generic DataField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Associated Types

type Rep DataField :: Type -> Type #

NFData DataField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Methods

rnf :: DataField -> () #

type Rep DataField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep DataField = D1 ('MetaData "DataField" "Codec.Xlsx.Types.PivotTable" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "DataField" 'PrefixI 'True) (S1 ('MetaSel ('Just "_dfField") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PivotFieldName) :*: (S1 ('MetaSel ('Just "_dfName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_dfFunction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConsolidateFunction))))

data ConsolidateFunction Source #

Data consolidation functions specified by the user and used to consolidate ranges of data

See 18.18.17 "ST_DataConsolidateFunction (Data Consolidation Functions)" (p. 2447)

Constructors

ConsolidateAverage

The average of the values.

ConsolidateCount

The number of data values. The Count consolidation function works the same as the COUNTA worksheet function.

ConsolidateCountNums

The number of data values that are numbers. The Count Nums consolidation function works the same as the COUNT worksheet function.

ConsolidateMaximum

The largest value.

ConsolidateMinimum

The smallest value.

ConsolidateProduct

The product of the values.

ConsolidateStdDev

An estimate of the standard deviation of a population, where the sample is a subset of the entire population.

ConsolidateStdDevP

The standard deviation of a population, where the population is all of the data to be summarized.

ConsolidateSum

The sum of the values.

ConsolidateVariance

An estimate of the variance of a population, where the sample is a subset of the entire population.

ConsolidateVarP

The variance of a population, where the population is all of the data to be summarized.

Instances

Instances details
Eq ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Show ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Generic ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Associated Types

type Rep ConsolidateFunction :: Type -> Type #

NFData ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

Methods

rnf :: ConsolidateFunction -> () #

FromAttrVal ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

ToAttrVal ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

type Rep ConsolidateFunction = D1 ('MetaData "ConsolidateFunction" "Codec.Xlsx.Types.PivotTable" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (((C1 ('MetaCons "ConsolidateAverage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsolidateCount" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ConsolidateCountNums" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ConsolidateMaximum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsolidateMinimum" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ConsolidateProduct" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ConsolidateStdDev" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsolidateStdDevP" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ConsolidateSum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ConsolidateVariance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsolidateVarP" 'PrefixI 'False) (U1 :: Type -> Type)))))