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

Codec.Xlsx.Types.ConditionalFormatting

Synopsis

Documentation

data CfRule Source #

This collection represents a description of a conditional formatting rule.

See 18.3.1.10 "cfRule (Conditional Formatting Rule)" (p. 1602)

Constructors

CfRule 

Fields

  • _cfrCondition :: Condition
     
  • _cfrDxfId :: Maybe Int

    This is an index to a dxf element in the Styles Part indicating which cell formatting to apply when the conditional formatting rule criteria is met.

  • _cfrPriority :: Int

    The priority of this conditional formatting rule. This value is used to determine which format should be evaluated and rendered. Lower numeric values are higher priority than higher numeric values, where 1 is the highest priority.

  • _cfrStopIfTrue :: Maybe Bool

    If this flag is set, no rules with lower priority shall be applied over this rule, when this rule evaluates to true.

Instances

Instances details
Eq CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

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

Ord CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep CfRule :: Type -> Type #

Methods

from :: CfRule -> Rep CfRule x #

to :: Rep CfRule x -> CfRule #

NFData CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: CfRule -> () #

FromXenoNode CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromCursor CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToElement CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep CfRule = D1 ('MetaData "CfRule" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "CfRule" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_cfrCondition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Condition) :*: S1 ('MetaSel ('Just "_cfrDxfId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "_cfrPriority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_cfrStopIfTrue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

newtype NStdDev Source #

The number of standard deviations to include above or below the average in the conditional formatting rule.

Constructors

NStdDev Int 

Instances

Instances details
Eq NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

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

Ord NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep NStdDev :: Type -> Type #

Methods

from :: NStdDev -> Rep NStdDev x #

to :: Rep NStdDev x -> NStdDev #

NFData NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: NStdDev -> () #

FromAttrBs NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromAttrVal NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

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

data Inclusion Source #

Flag indicating whether the aboveAverage and belowAverage criteria is inclusive of the average itself, or exclusive of that value.

Constructors

Inclusive 
Exclusive 

Instances

Instances details
Eq Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep Inclusion :: Type -> Type #

NFData Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: Inclusion -> () #

FromAttrBs Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromAttrVal Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep Inclusion = D1 ('MetaData "Inclusion" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "Inclusive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exclusive" 'PrefixI 'False) (U1 :: Type -> Type))

data CfValue Source #

Describes the values of the interpolation points in a color scale, data bar or icon set conditional formatting rules.

See 18.3.1.11 "cfvo (Conditional Format Value Object)" (p. 1604)

Instances

Instances details
Eq CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

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

Ord CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep CfValue :: Type -> Type #

Methods

from :: CfValue -> Rep CfValue x #

to :: Rep CfValue x -> CfValue #

NFData CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: CfValue -> () #

FromXenoNode CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromCursor CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToElement CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

data MinCfValue Source #

Constructors

CfvMin 
MinCfValue CfValue 

Instances

Instances details
Eq MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep MinCfValue :: Type -> Type #

NFData MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: MinCfValue -> () #

FromXenoNode MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromCursor MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToElement MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep MinCfValue = D1 ('MetaData "MinCfValue" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "CfvMin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MinCfValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CfValue)))

data MaxCfValue Source #

Constructors

CfvMax 
MaxCfValue CfValue 

Instances

Instances details
Eq MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep MaxCfValue :: Type -> Type #

NFData MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: MaxCfValue -> () #

FromXenoNode MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromCursor MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToElement MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep MaxCfValue = D1 ('MetaData "MaxCfValue" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "CfvMax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaxCfValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CfValue)))

data Condition Source #

Conditions which could be used for conditional formatting

See 18.18.12 "ST_CfType (Conditional Format Type)" (p. 2443)

Constructors

AboveAverage Inclusion (Maybe NStdDev)

This conditional formatting rule highlights cells that are above (or maybe equal to) the average for all values in the range.

BeginsWith Text

This conditional formatting rule highlights cells in the range that begin with the given text. Equivalent to using the LEFT() sheet function and comparing values.

BelowAverage Inclusion (Maybe NStdDev)

This conditional formatting rule highlights cells that are below the average for all values in the range.

BottomNPercent Int

This conditional formatting rule highlights cells whose values fall in the bottom N percent bracket.

BottomNValues Int

This conditional formatting rule highlights cells whose values fall in the bottom N bracket.

CellIs OperatorExpression

This conditional formatting rule compares a cell value to a formula calculated result, using an operator.

ColorScale2 MinCfValue Color MaxCfValue Color

This conditional formatting rule creates a gradated color scale on the cells with specified colors for specified minimum and maximum.

ColorScale3 MinCfValue Color CfValue Color MaxCfValue Color

This conditional formatting rule creates a gradated color scale on the cells with specified colors for specified minimum, midpoint and maximum.

ContainsBlanks

This conditional formatting rule highlights cells that are completely blank. Equivalent of using LEN(TRIM()). This means that if the cell contains only characters that TRIM() would remove, then it is considered blank. An empty cell is also considered blank.

ContainsErrors

This conditional formatting rule highlights cells with formula errors. Equivalent to using ISERROR() sheet function to determine if there is a formula error.

ContainsText Text

This conditional formatting rule highlights cells containing given text. Equivalent to using the SEARCH() sheet function to determine whether the cell contains the text.

DataBar DataBarOptions

This conditional formatting rule displays a gradated data bar in the range of cells.

DoesNotContainErrors

This conditional formatting rule highlights cells without formula errors. Equivalent to using ISERROR() sheet function to determine if there is a formula error.

DoesNotContainBlanks

This conditional formatting rule highlights cells that are not blank. Equivalent of using LEN(TRIM()). This means that if the cell contains only characters that TRIM() would remove, then it is considered blank. An empty cell is also considered blank.

DoesNotContainText Text

This conditional formatting rule highlights cells that do not contain given text. Equivalent to using the SEARCH() sheet function.

DuplicateValues

This conditional formatting rule highlights duplicated values.

EndsWith Text

This conditional formatting rule highlights cells ending with given text. Equivalent to using the RIGHT() sheet function and comparing values.

Expression Formula

This conditional formatting rule contains a formula to evaluate. When the formula result is true, the cell is highlighted.

IconSet IconSetOptions

This conditional formatting rule applies icons to cells according to their values.

InTimePeriod TimePeriod

This conditional formatting rule highlights cells containing dates in the specified time period. The underlying value of the cell is evaluated, therefore the cell does not need to be formatted as a date to be evaluated. For example, with a cell containing the value 38913 the conditional format shall be applied if the rule requires a value of 7142006.

TopNPercent Int

This conditional formatting rule highlights cells whose values fall in the top N percent bracket.

TopNValues Int

This conditional formatting rule highlights cells whose values fall in the top N bracket.

UniqueValues

This conditional formatting rule highlights unique values in the range.

Instances

Instances details
Eq Condition Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord Condition Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show Condition Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic Condition Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep Condition :: Type -> Type #

NFData Condition Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: Condition -> () #

type Rep Condition Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep Condition = D1 ('MetaData "Condition" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) ((((C1 ('MetaCons "AboveAverage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inclusion) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NStdDev))) :+: C1 ('MetaCons "BeginsWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "BelowAverage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inclusion) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NStdDev))) :+: (C1 ('MetaCons "BottomNPercent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "BottomNValues" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "CellIs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OperatorExpression)) :+: (C1 ('MetaCons "ColorScale2" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MinCfValue) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MaxCfValue) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color))) :+: C1 ('MetaCons "ColorScale3" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MinCfValue) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CfValue))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MaxCfValue) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)))))) :+: (C1 ('MetaCons "ContainsBlanks" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ContainsErrors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContainsText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))) :+: (((C1 ('MetaCons "DataBar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DataBarOptions)) :+: (C1 ('MetaCons "DoesNotContainErrors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoesNotContainBlanks" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DoesNotContainText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "DuplicateValues" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EndsWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) :+: ((C1 ('MetaCons "Expression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: (C1 ('MetaCons "IconSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IconSetOptions)) :+: C1 ('MetaCons "InTimePeriod" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimePeriod)))) :+: (C1 ('MetaCons "TopNPercent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "TopNValues" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "UniqueValues" 'PrefixI 'False) (U1 :: Type -> Type))))))

data OperatorExpression Source #

Logical operation used in CellIs condition

See 18.18.15 "ST_ConditionalFormattingOperator (Conditional Format Operators)" (p. 2446)

Constructors

OpBeginsWith Formula

'Begins with' operator

OpBetween Formula Formula

Between operator

OpContainsText Formula

Contains operator

OpEndsWith Formula

'Ends with' operator

OpEqual Formula

'Equal to' operator

OpGreaterThan Formula

'Greater than' operator

OpGreaterThanOrEqual Formula

'Greater than or equal to' operator

OpLessThan Formula

'Less than' operator

OpLessThanOrEqual Formula

'Less than or equal to' operator

OpNotBetween Formula Formula

'Not between' operator

OpNotContains Formula

'Does not contain' operator

OpNotEqual Formula

'Not equal to' operator

Instances

Instances details
Eq OperatorExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord OperatorExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show OperatorExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic OperatorExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep OperatorExpression :: Type -> Type #

NFData OperatorExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: OperatorExpression -> () #

type Rep OperatorExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep OperatorExpression = D1 ('MetaData "OperatorExpression" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (((C1 ('MetaCons "OpBeginsWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: (C1 ('MetaCons "OpBetween" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: C1 ('MetaCons "OpContainsText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)))) :+: (C1 ('MetaCons "OpEndsWith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: (C1 ('MetaCons "OpEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: C1 ('MetaCons "OpGreaterThan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula))))) :+: ((C1 ('MetaCons "OpGreaterThanOrEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: (C1 ('MetaCons "OpLessThan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: C1 ('MetaCons "OpLessThanOrEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)))) :+: (C1 ('MetaCons "OpNotBetween" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: (C1 ('MetaCons "OpNotContains" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: C1 ('MetaCons "OpNotEqual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula))))))

data TimePeriod Source #

Used in a "contains dates" conditional formatting rule. These are dynamic time periods, which change based on the date the conditional formatting is refreshed / applied.

See 18.18.82 "ST_TimePeriod (Time Period Types)" (p. 2508)

Constructors

PerLast7Days

A date in the last seven days.

PerLastMonth

A date occuring in the last calendar month.

PerLastWeek

A date occuring last week.

PerNextMonth

A date occuring in the next calendar month.

PerNextWeek

A date occuring next week.

PerThisMonth

A date occuring in this calendar month.

PerThisWeek

A date occuring this week.

PerToday

Today's date.

PerTomorrow

Tomorrow's date.

PerYesterday

Yesterday's date.

Instances

Instances details
Eq TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep TimePeriod :: Type -> Type #

NFData TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: TimePeriod -> () #

FromAttrBs TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromAttrVal TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep TimePeriod = D1 ('MetaData "TimePeriod" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (((C1 ('MetaCons "PerLast7Days" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PerLastMonth" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PerLastWeek" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PerNextMonth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PerNextWeek" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PerThisMonth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PerThisWeek" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PerToday" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PerTomorrow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PerYesterday" 'PrefixI 'False) (U1 :: Type -> Type)))))

data IconSetOptions Source #

Describes an icon set conditional formatting rule.

See 18.3.1.49 "iconSet (Icon Set)" (p. 1645)

Constructors

IconSetOptions 

Fields

Instances

Instances details
Eq IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep IconSetOptions :: Type -> Type #

Default IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

def :: IconSetOptions #

NFData IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: IconSetOptions -> () #

FromXenoNode IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromCursor IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToElement IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep IconSetOptions = D1 ('MetaData "IconSetOptions" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "IconSetOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_isoIconSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IconSetType) :*: S1 ('MetaSel ('Just "_isoValues") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CfValue])) :*: (S1 ('MetaSel ('Just "_isoReverse") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_isoShowValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data IconSetType Source #

Icon set type for conditional formatting. CfValue fields determine lower range bounds. I.e. IconSet3Signs (CfPercent 0) (CfPercent 33) (CfPercent 67) say that 1st icon will be shown for values ranging from 0 to 33 percents, 2nd for 33 to 67 percent and the 3rd one for values from 67 to 100 percent.

  1. 18.42 "ST_IconSetType (Icon Set Type)" (p. 2463)

Instances

Instances details
Eq IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep IconSetType :: Type -> Type #

NFData IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: IconSetType -> () #

FromAttrBs IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromAttrVal IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep IconSetType = D1 ('MetaData "IconSetType" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) ((((C1 ('MetaCons "IconSet3Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet3ArrowsGray" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IconSet3Flags" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet3Signs" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IconSet3Symbols" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet3Symbols2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IconSet3TrafficLights1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet3TrafficLights2" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "IconSet4Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet4ArrowsGray" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IconSet4Rating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet4RedToBlack" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IconSet4TrafficLights" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet5Arrows" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IconSet5ArrowsGray" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IconSet5Quarters" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IconSet5Rating" 'PrefixI 'False) (U1 :: Type -> Type))))))

data DataBarOptions Source #

Describes a data bar conditional formatting rule.

See 18.3.1.28 "dataBar (Data Bar)" (p. 1621)

Constructors

DataBarOptions 

Fields

Instances

Instances details
Eq DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Ord DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Show DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Generic DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Associated Types

type Rep DataBarOptions :: Type -> Type #

NFData DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

rnf :: DataBarOptions -> () #

FromXenoNode DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

FromCursor DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToElement DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

type Rep DataBarOptions = D1 ('MetaData "DataBarOptions" "Codec.Xlsx.Types.ConditionalFormatting" "xlsx-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" 'False) (C1 ('MetaCons "DataBarOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_dboMaxLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "_dboMinLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_dboShowValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "_dboMinimum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MinCfValue) :*: (S1 ('MetaSel ('Just "_dboMaximum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MaxCfValue) :*: S1 ('MetaSel ('Just "_dboColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Color)))))

Lenses

CfRule

IconSetOptions

DataBarOptions

Misc