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

Codec.Xlsx.Types.AutoFilter

Synopsis

Documentation

data FilterColumn Source #

The filterColumn collection identifies a particular column in the AutoFilter range and specifies filter information that has been applied to this column. If a column in the AutoFilter range has no criteria specified, then there is no corresponding filterColumn collection expressed for that column.

See 18.3.2.7 "filterColumn (AutoFilter Column)" (p. 1717)

Constructors

Filters FilterByBlank [FilterCriterion] 
ColorFilter ColorFilterOptions 
ACustomFilter CustomFilter 
CustomFiltersOr CustomFilter CustomFilter 
CustomFiltersAnd CustomFilter CustomFilter 
DynamicFilter DynFilterOptions 
IconFilter (Maybe Int) IconSetType

Specifies the icon set and particular icon within that set to filter by. Icon is specified using zero-based index of an icon in an icon set. Nothing means "no icon"

BottomNFilter EdgeFilterOptions

Specifies the bottom N (percent or number of items) to filter by

TopNFilter EdgeFilterOptions

Specifies the top N (percent or number of items) to filter by

Instances

Instances details
Eq FilterColumn Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show FilterColumn Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic FilterColumn Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep FilterColumn :: Type -> Type #

NFData FilterColumn Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: FilterColumn -> () #

FromXenoNode (Int, FilterColumn) Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep FilterColumn Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep FilterColumn = D1 ('MetaData "FilterColumn" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (((C1 ('MetaCons "Filters" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilterByBlank) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilterCriterion])) :+: C1 ('MetaCons "ColorFilter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColorFilterOptions))) :+: (C1 ('MetaCons "ACustomFilter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomFilter)) :+: C1 ('MetaCons "CustomFiltersOr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomFilter) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomFilter)))) :+: ((C1 ('MetaCons "CustomFiltersAnd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomFilter) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomFilter)) :+: C1 ('MetaCons "DynamicFilter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DynFilterOptions))) :+: (C1 ('MetaCons "IconFilter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IconSetType)) :+: (C1 ('MetaCons "BottomNFilter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EdgeFilterOptions)) :+: C1 ('MetaCons "TopNFilter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EdgeFilterOptions))))))

data FilterByBlank Source #

Instances

Instances details
Eq FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep FilterByBlank :: Type -> Type #

NFData FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: FilterByBlank -> () #

FromAttrBs FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

FromAttrVal FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

ToAttrVal FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep FilterByBlank = D1 ('MetaData "FilterByBlank" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (C1 ('MetaCons "FilterByBlank" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DontFilterByBlank" 'PrefixI 'False) (U1 :: Type -> Type))

data FilterCriterion Source #

Instances

Instances details
Eq FilterCriterion Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show FilterCriterion Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic FilterCriterion Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep FilterCriterion :: Type -> Type #

NFData FilterCriterion Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: FilterCriterion -> () #

FromXenoNode FilterCriterion Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

FromCursor FilterCriterion Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

fromCursor :: Cursor -> [FilterCriterion] Source #

type Rep FilterCriterion Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep FilterCriterion = D1 ('MetaData "FilterCriterion" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (C1 ('MetaCons "FilterValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "FilterDateGroup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DateGroup)))

data DateGroup Source #

Used to express a group of dates or times which are used in an AutoFilter criteria

Section 18.3.2.4 "dateGroupItem (Date Grouping)" (p. 1714)

Instances

Instances details
Eq DateGroup Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show DateGroup Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic DateGroup Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep DateGroup :: Type -> Type #

NFData DateGroup Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: DateGroup -> () #

type Rep DateGroup Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep DateGroup = D1 ('MetaData "DateGroup" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) ((C1 ('MetaCons "DateGroupByYear" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "DateGroupByMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "DateGroupByDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: (C1 ('MetaCons "DateGroupByHour" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "DateGroupByMinute" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) :+: C1 ('MetaCons "DateGroupBySecond" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))))

data CustomFilter Source #

Instances

Instances details
Eq CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep CustomFilter :: Type -> Type #

NFData CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: CustomFilter -> () #

FromXenoNode CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

ToElement CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

toElement :: Name -> CustomFilter -> Element Source #

type Rep CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep CustomFilter = D1 ('MetaData "CustomFilter" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (C1 ('MetaCons "CustomFilter" 'PrefixI 'True) (S1 ('MetaSel ('Just "cfltOperator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomFilterOperator) :*: S1 ('MetaSel ('Just "cfltValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data CustomFilterOperator Source #

Constructors

FltrEqual

Show results which are equal to criteria.

FltrGreaterThan

Show results which are greater than criteria.

FltrGreaterThanOrEqual

Show results which are greater than or equal to criteria.

FltrLessThan

Show results which are less than criteria.

FltrLessThanOrEqual

Show results which are less than or equal to criteria.

FltrNotEqual

Show results which are not equal to criteria.

Instances

Instances details
Eq CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep CustomFilterOperator :: Type -> Type #

NFData CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: CustomFilterOperator -> () #

FromAttrBs CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

FromAttrVal CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

ToAttrVal CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep CustomFilterOperator = D1 ('MetaData "CustomFilterOperator" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) ((C1 ('MetaCons "FltrEqual" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FltrGreaterThan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FltrGreaterThanOrEqual" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "FltrLessThan" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FltrLessThanOrEqual" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FltrNotEqual" 'PrefixI 'False) (U1 :: Type -> Type))))

data EdgeFilterOptions Source #

Constructors

EdgeFilterOptions 

Fields

  • _efoUsePercents :: Bool

    Flag indicating whether or not to filter by percent value of the column. A false value filters by number of items.

  • _efoVal :: Double

    Top or bottom value to use as the filter criteria. Example: "Filter by Top 10 Percent" or "Filter by Top 5 Items"

  • _efoFilterVal :: Maybe Double

    The actual cell value in the range which is used to perform the comparison for this filter.

Instances

Instances details
Eq EdgeFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show EdgeFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic EdgeFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep EdgeFilterOptions :: Type -> Type #

NFData EdgeFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: EdgeFilterOptions -> () #

type Rep EdgeFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep EdgeFilterOptions = D1 ('MetaData "EdgeFilterOptions" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (C1 ('MetaCons "EdgeFilterOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "_efoUsePercents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_efoVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "_efoFilterVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)))))

data ColorFilterOptions Source #

Specifies the color to filter by and whether to use the cell's fill or font color in the filter criteria. If the cell's font or fill color does not match the color specified in the criteria, the rows corresponding to those cells are hidden from view.

See 18.3.2.1 "colorFilter (Color Filter Criteria)" (p. 1712)

Constructors

ColorFilterOptions 

Fields

  • _cfoCellColor :: Bool

    Flag indicating whether or not to filter by the cell's fill color. True indicates to filter by cell fill. False indicates to filter by the cell's font color.

    For rich text in cells, if the color specified appears in the cell at all, it shall be included in the filter.

  • _cfoDxfId :: Maybe Int

    Id of differential format record (dxf) in the Styles Part (see _styleSheetDxfs) which expresses the color value to filter by.

Instances

Instances details
Eq ColorFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show ColorFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic ColorFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep ColorFilterOptions :: Type -> Type #

NFData ColorFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: ColorFilterOptions -> () #

ToElement ColorFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

toElement :: Name -> ColorFilterOptions -> Element Source #

type Rep ColorFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep ColorFilterOptions = D1 ('MetaData "ColorFilterOptions" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (C1 ('MetaCons "ColorFilterOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cfoCellColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_cfoDxfId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

data DynFilterOptions Source #

Specifies dynamic filter criteria. These criteria are considered dynamic because they can change, either with the data itself (e.g., "above average") or with the current system date (e.g., show values for "today"). For any cells whose values do not meet the specified criteria, the corresponding rows shall be hidden from view when the filter is applied.

_dfoMaxVal shall be required for DynFilterTday, DynFilterYesterday, DynFilterTomorrow, DynFilterNextWeek, DynFilterThisWeek, DynFilterLastWeek, DynFilterNextMonth, DynFilterThisMonth, DynFilterLastMonth, DynFilterNextQuarter, DynFilterThisQuarter, DynFilterLastQuarter, DynFilterNextYear, DynFilterThisYear, DynFilterLastYear, and 'DynFilterYearToDate.

The above criteria are based on a value range; that is, if today's date is September 22nd, then the range for thisWeek is the values greater than or equal to September 17 and less than September 24. In the thisWeek range, the lower value is expressed _dfoval. The higher value is expressed using _dfoMmaxVal.

These dynamic filters shall not require '_dfoVal or _dfoMaxVal: DynFilterQ1, DynFilterQ2, DynFilterQ3, DynFilterQ4, DynFilterM1, DynFilterM2, DynFilterM3, DynFilterM4, DynFilterM5, DynFilterM6, DynFilterM7, DynFilterM8, DynFilterM9, DynFilterM10, DynFilterM11 and DynFilterM12.

The above criteria shall not specify the range using valIso and maxValIso because Q1 always starts from M1 to M3, and M1 is always January.

These types of dynamic filters shall use valIso and shall not use _dfoMaxVal: DynFilterAboveAverage and DynFilterBelowAverage

Note: Specification lists valIso and maxIso to store datetime values but it appears that Excel doesn't use them and stored them as numeric values (as it does for datetimes in cell values)

See 18.3.2.5 "dynamicFilter (Dynamic Filter)" (p. 1715)

Constructors

DynFilterOptions 

Fields

Instances

Instances details
Eq DynFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show DynFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic DynFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep DynFilterOptions :: Type -> Type #

NFData DynFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: DynFilterOptions -> () #

ToElement DynFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

toElement :: Name -> DynFilterOptions -> Element Source #

type Rep DynFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep DynFilterOptions = D1 ('MetaData "DynFilterOptions" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (C1 ('MetaCons "DynFilterOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "_dfoType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DynFilterType) :*: (S1 ('MetaSel ('Just "_dfoVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)) :*: S1 ('MetaSel ('Just "_dfoMaxVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)))))

data DynFilterType Source #

Specifies concrete type of dynamic filter used

See 18.18.26 "ST_DynamicFilterType (Dynamic Filter)" (p. 2452)

Constructors

DynFilterAboveAverage

Shows values that are above average.

DynFilterBelowAverage

Shows values that are below average.

DynFilterLastMonth

Shows last month's dates.

DynFilterLastQuarter

Shows last calendar quarter's dates.

DynFilterLastWeek

Shows last week's dates, using Sunday as the first weekday.

DynFilterLastYear

Shows last year's dates.

DynFilterM1

Shows the dates that are in January, regardless of year.

DynFilterM10

Shows the dates that are in October, regardless of year.

DynFilterM11

Shows the dates that are in November, regardless of year.

DynFilterM12

Shows the dates that are in December, regardless of year.

DynFilterM2

Shows the dates that are in February, regardless of year.

DynFilterM3

Shows the dates that are in March, regardless of year.

DynFilterM4

Shows the dates that are in April, regardless of year.

DynFilterM5

Shows the dates that are in May, regardless of year.

DynFilterM6

Shows the dates that are in June, regardless of year.

DynFilterM7

Shows the dates that are in July, regardless of year.

DynFilterM8

Shows the dates that are in August, regardless of year.

DynFilterM9

Shows the dates that are in September, regardless of year.

DynFilterNextMonth

Shows next month's dates.

DynFilterNextQuarter

Shows next calendar quarter's dates.

DynFilterNextWeek

Shows next week's dates, using Sunday as the first weekday.

DynFilterNextYear

Shows next year's dates.

DynFilterNull

Common filter type not available.

DynFilterQ1

Shows the dates that are in the 1st calendar quarter, regardless of year.

DynFilterQ2

Shows the dates that are in the 2nd calendar quarter, regardless of year.

DynFilterQ3

Shows the dates that are in the 3rd calendar quarter, regardless of year.

DynFilterQ4

Shows the dates that are in the 4th calendar quarter, regardless of year.

DynFilterThisMonth

Shows this month's dates.

DynFilterThisQuarter

Shows this calendar quarter's dates.

DynFilterThisWeek

Shows this week's dates, using Sunday as the first weekday.

DynFilterThisYear

Shows this year's dates.

DynFilterToday

Shows today's dates.

DynFilterTomorrow

Shows tomorrow's dates.

DynFilterYearToDate

Shows the dates between the beginning of the year and today, inclusive.

DynFilterYesterday

Shows yesterday's dates.

Instances

Instances details
Eq DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep DynFilterType :: Type -> Type #

NFData DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: DynFilterType -> () #

FromAttrBs DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

FromAttrVal DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

ToAttrVal DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep DynFilterType = D1 ('MetaData "DynFilterType" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (((((C1 ('MetaCons "DynFilterAboveAverage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterBelowAverage" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterLastMonth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterLastQuarter" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DynFilterLastWeek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterLastYear" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterM1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterM10" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "DynFilterM11" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterM12" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterM2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterM3" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DynFilterM4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterM5" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterM6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DynFilterM7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterM8" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "DynFilterM9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterNextMonth" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterNextQuarter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterNextWeek" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DynFilterNextYear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterNull" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterQ1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DynFilterQ2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterQ3" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DynFilterQ4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterThisMonth" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterThisQuarter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterThisWeek" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DynFilterThisYear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterToday" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DynFilterTomorrow" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DynFilterYearToDate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DynFilterYesterday" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data AutoFilter Source #

AutoFilter temporarily hides rows based on a filter criteria, which is applied column by column to a table of datain the worksheet.

TODO: sortState, extList

See 18.3.1.2 "autoFilter (AutoFilter Settings)" (p. 1596)

Instances

Instances details
Eq AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Show AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Generic AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Associated Types

type Rep AutoFilter :: Type -> Type #

NFData AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

rnf :: AutoFilter -> () #

FromXenoNode AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Default AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

def :: AutoFilter #

FromCursor AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

fromCursor :: Cursor -> [AutoFilter] Source #

ToElement AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

toElement :: Name -> AutoFilter -> Element Source #

type Rep AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

type Rep AutoFilter = D1 ('MetaData "AutoFilter" "Codec.Xlsx.Types.AutoFilter" "xlsx-1.0.0.1-inplace" 'False) (C1 ('MetaCons "AutoFilter" 'PrefixI 'True) (S1 ('MetaSel ('Just "_afRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CellRef)) :*: S1 ('MetaSel ('Just "_afFilterColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Int FilterColumn))))