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

Safe HaskellNone
LanguageHaskell2010

Codec.Xlsx.Types.StyleSheet

Contents

Description

Support for writing (but not reading) style sheets

Synopsis

The main two types

data StyleSheet Source #

StyleSheet for an XML document

Relevant parts of the EMCA standard (4th edition, part 1, http://www.ecma-international.org/publications/standards/Ecma-376.htm), page numbers refer to the page in the PDF rather than the page number as printed on the page):

  • Chapter 12, SpreadsheetML (p. 74) In particular Section 12.3.20, "Styles Part" (p. 104)
  • Chapter 18, "SpreadsheetML Reference Material" (p. 1528) In particular Section 18.8, Styles (p. 1754) and Section 18.8.39 "styleSheet" (Style Sheet)" (p. 1796); it is the latter section that specifies the top-level style sheet format.

TODO: the following child elements:

  • cellStyles
  • cellStyleXfs
  • colors
  • extLst
  • tableStyles

NOTE: You will probably want to base your style sheet on minimalStyleSheet. See also:

Constructors

StyleSheet 

Fields

  • _styleSheetBorders :: [Border]

    This element contains borders formatting information, specifying all border definitions for all cells in the workbook.

    Section 18.8.5, "borders (Borders)" (p. 1760)

  • _styleSheetCellXfs :: [CellXf]

    Cell formats

    This element contains the master formatting records (xf) which define the formatting applied to cells in this workbook. These records are the starting point for determining the formatting for a cell. Cells in the Sheet Part reference the xf records by zero-based index.

    Section 18.8.10, "cellXfs (Cell Formats)" (p. 1764)

  • _styleSheetFills :: [Fill]

    This element defines the cell fills portion of the Styles part, consisting of a sequence of fill records. A cell fill consists of a background color, foreground color, and pattern to be applied across the cell.

    Section 18.8.21, "fills (Fills)" (p. 1768)

  • _styleSheetFonts :: [Font]

    This element contains all font definitions for this workbook.

    Section 18.8.23 "fonts (Fonts)" (p. 1769)

  • _styleSheetDxfs :: [Dxf]

    Differential formatting

    This element contains the master differential formatting records (dxf's) which define formatting for all non-cell formatting in this workbook. Whereas xf records fully specify a particular aspect of formatting (e.g., cell borders) by referencing those formatting definitions elsewhere in the Styles part, dxf records specify incremental (or differential) aspects of formatting directly inline within the dxf element. The dxf formatting is to be applied on top of or in addition to any formatting already present on the object using the dxf record.

    Section 18.8.15, "dxfs (Formats)" (p. 1765)

  • _styleSheetNumFmts :: Map Int FormatCode

    Number formats

    This element contains custom number formats defined in this style sheet

    Section 18.8.31, "numFmts (Number Formats)" (p. 1784)

Instances

Eq StyleSheet Source # 
Ord StyleSheet Source # 
Show StyleSheet Source # 
Generic StyleSheet Source # 

Associated Types

type Rep StyleSheet :: * -> * #

Default StyleSheet Source # 

Methods

def :: StyleSheet #

NFData StyleSheet Source # 

Methods

rnf :: StyleSheet -> () #

FromCursor StyleSheet Source #

See CT_Stylesheet, p. 4482

ToElement StyleSheet Source #

See CT_Stylesheet, p. 4482

ToDocument StyleSheet Source # 
type Rep StyleSheet Source # 
type Rep StyleSheet = D1 * (MetaData "StyleSheet" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "StyleSheet" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_styleSheetBorders") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Border])) ((:*:) * (S1 * (MetaSel (Just Symbol "_styleSheetCellXfs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [CellXf])) (S1 * (MetaSel (Just Symbol "_styleSheetFills") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Fill])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_styleSheetFonts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Font])) ((:*:) * (S1 * (MetaSel (Just Symbol "_styleSheetDxfs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Dxf])) (S1 * (MetaSel (Just Symbol "_styleSheetNumFmts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map Int FormatCode)))))))

data CellXf Source #

Cell formatting

TODO: The extLst field is currently unsupported.

Section 18.8.45 "xf (Format)" (p. 1800)

Constructors

CellXf 

Fields

  • _cellXfApplyAlignment :: Maybe Bool

    A boolean value indicating whether the alignment formatting specified for this xf should be applied.

  • _cellXfApplyBorder :: Maybe Bool

    A boolean value indicating whether the border formatting specified for this xf should be applied.

  • _cellXfApplyFill :: Maybe Bool

    A boolean value indicating whether the fill formatting specified for this xf should be applied.

  • _cellXfApplyFont :: Maybe Bool

    A boolean value indicating whether the font formatting specified for this xf should be applied.

  • _cellXfApplyNumberFormat :: Maybe Bool

    A boolean value indicating whether the number formatting specified for this xf should be applied.

  • _cellXfApplyProtection :: Maybe Bool

    A boolean value indicating whether the protection formatting specified for this xf should be applied.

  • _cellXfBorderId :: Maybe Int

    Zero-based index of the border record used by this cell format.

    (18.18.2, p. 2437).

  • _cellXfFillId :: Maybe Int

    Zero-based index of the fill record used by this cell format.

    (18.18.30, p. 2455)

  • _cellXfFontId :: Maybe Int

    Zero-based index of the font record used by this cell format.

    An integer that represents a zero based index into the styleSheetFonts collection in the style sheet (18.18.32, p. 2456).

  • _cellXfNumFmtId :: Maybe Int

    Id of the number format (numFmt) record used by this cell format.

    This simple type defines the identifier to a style sheet number format entry in CT_NumFmts. Number formats are written to the styles part (18.18.47, p. 2468). See also 18.8.31 (p. 1784) for more information on number formats.

  • _cellXfPivotButton :: Maybe Bool

    A boolean value indicating whether the cell rendering includes a pivot table dropdown button.

  • _cellXfQuotePrefix :: Maybe Bool

    A boolean value indicating whether the text string in a cell should be prefixed by a single quote mark (e.g., 'text). In these cases, the quote is not stored in the Shared Strings Part.

  • _cellXfId :: Maybe Int

    For xf records contained in cellXfs this is the zero-based index of an xf record contained in cellStyleXfs corresponding to the cell style applied to the cell.

    Not present for xf records contained in cellStyleXfs.

    Used by xf records and cellStyle records to reference xf records defined in the cellStyleXfs collection. (18.18.10, p. 2442) TODO: the cellStyleXfs field of a style sheet not currently implemented.

  • _cellXfAlignment :: Maybe Alignment

    Formatting information pertaining to text alignment in cells. There are a variety of choices for how text is aligned both horizontally and vertically, as well as indentation settings, and so on.

  • _cellXfProtection :: Maybe Protection

    Contains protection properties associated with the cell. Each cell has protection properties that can be set. The cell protection properties do not take effect unless the sheet has been protected.

Instances

Eq CellXf Source # 

Methods

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

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

Ord CellXf Source # 
Show CellXf Source # 
Generic CellXf Source # 

Associated Types

type Rep CellXf :: * -> * #

Methods

from :: CellXf -> Rep CellXf x #

to :: Rep CellXf x -> CellXf #

Default CellXf Source # 

Methods

def :: CellXf #

NFData CellXf Source # 

Methods

rnf :: CellXf -> () #

FromCursor CellXf Source #

See CT_Xf, p. 4486

ToElement CellXf Source #

See CT_Xf, p. 4486

type Rep CellXf Source # 
type Rep CellXf = D1 * (MetaData "CellXf" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "CellXf" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfApplyAlignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfApplyBorder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_cellXfApplyFill") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfApplyFont") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_cellXfApplyNumberFormat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfApplyProtection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_cellXfBorderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfFillId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_cellXfFontId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfNumFmtId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_cellXfPivotButton") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfQuotePrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_cellXfId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cellXfAlignment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Alignment))) (S1 * (MetaSel (Just Symbol "_cellXfProtection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Protection))))))))

minimalStyleSheet :: StyleSheet Source #

Minimal style sheet

Excel expects some minimal definitions in the stylesheet; you probably want to define your own stylesheets based on this one.

This more-or-less follows the recommendations at http://stackoverflow.com/questions/26050708/minimal-style-sheet-for-excel-open-xml-with-dates, but with some additions based on experimental evidence.

Supporting record types

data Alignment Source #

Alignment

See 18.8.1 "alignment (Alignment)" (p. 1754)

Constructors

Alignment 

Fields

Instances

Eq Alignment Source # 
Ord Alignment Source # 
Show Alignment Source # 
Generic Alignment Source # 

Associated Types

type Rep Alignment :: * -> * #

Default Alignment Source # 

Methods

def :: Alignment #

NFData Alignment Source # 

Methods

rnf :: Alignment -> () #

FromCursor Alignment Source #

See CT_CellAlignment, p. 4482

ToElement Alignment Source #

See CT_CellAlignment, p. 4482

type Rep Alignment Source # 

data Border Source #

Expresses a single set of cell border formats (left, right, top, bottom, diagonal). Color is optional. When missing, automatic is implied.

See 18.8.4 "border (Border)" (p. 1759)

Constructors

Border 

Fields

Instances

Eq Border Source # 

Methods

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

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

Ord Border Source # 
Show Border Source # 
Generic Border Source # 

Associated Types

type Rep Border :: * -> * #

Methods

from :: Border -> Rep Border x #

to :: Rep Border x -> Border #

Default Border Source # 

Methods

def :: Border #

NFData Border Source # 

Methods

rnf :: Border -> () #

FromCursor Border Source #

See CT_Border, p. 4483

ToElement Border Source #

See CT_Border, p. 4483

type Rep Border Source # 
type Rep Border = D1 * (MetaData "Border" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "Border" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_borderDiagonalDown") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_borderDiagonalUp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_borderOutline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_borderBottom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "_borderDiagonal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))) (S1 * (MetaSel (Just Symbol "_borderEnd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_borderHorizontal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "_borderLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))) (S1 * (MetaSel (Just Symbol "_borderRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_borderStart") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))) ((:*:) * (S1 * (MetaSel (Just Symbol "_borderTop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))) (S1 * (MetaSel (Just Symbol "_borderVertical") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BorderStyle))))))))

data BorderStyle Source #

Border style See CT_BorderPr (p. 3934)

Instances

Eq BorderStyle Source # 
Ord BorderStyle Source # 
Show BorderStyle Source # 
Generic BorderStyle Source # 

Associated Types

type Rep BorderStyle :: * -> * #

Default BorderStyle Source # 

Methods

def :: BorderStyle #

NFData BorderStyle Source # 

Methods

rnf :: BorderStyle -> () #

FromCursor BorderStyle Source # 
ToElement BorderStyle Source #

See CT_BorderPr, p. 4483

type Rep BorderStyle Source # 
type Rep BorderStyle = D1 * (MetaData "BorderStyle" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "BorderStyle" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_borderStyleColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "_borderStyleLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe LineStyle)))))

data Color Source #

One of the colors associated with the data bar or color scale.

The indexed attribute (used for backwards compatibility only) is not modelled here.

See 18.3.1.15 "color (Data Bar Color)" (p. 1608)

Constructors

Color 

Fields

  • _colorAutomatic :: Maybe Bool

    A boolean value indicating the color is automatic and system color dependent.

  • _colorARGB :: Maybe Text

    Standard Alpha Red Green Blue color value (ARGB).

    This simple type's contents have a length of exactly 8 hexadecimal digit(s); see "18.18.86 ST_UnsignedIntHex (Hex Unsigned Integer)" (p. 2511).

  • _colorTheme :: Maybe Int

    A zero-based index into the clrScheme collection (20.1.6.2), referencing a particular sysClr or srgbClr value expressed in the Theme part.

  • _colorTint :: Maybe Double

    Specifies the tint value applied to the color.

    If tint is supplied, then it is applied to the RGB value of the color to determine the final color applied.

    The tint value is stored as a double from -1.0 .. 1.0, where -1.0 means 100% darken and 1.0 means 100% lighten. Also, 0.0 means no change.

Instances

Eq Color Source # 

Methods

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

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

Ord Color Source # 

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 

Associated Types

type Rep Color :: * -> * #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

Default Color Source # 

Methods

def :: Color #

NFData Color Source # 

Methods

rnf :: Color -> () #

FromXenoNode Color Source # 
FromCursor Color Source #

See CT_Color, p. 4484

Methods

fromCursor :: Cursor -> [Color] Source #

ToElement Color Source #

See CT_Color, p. 4484

type Rep Color Source # 

data Dxf Source #

A single dxf record, expressing incremental formatting to be applied.

Section 18.8.14, "dxf (Formatting)" (p. 1765)

Constructors

Dxf 

Fields

Instances

Eq Dxf Source # 

Methods

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

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

Ord Dxf Source # 

Methods

compare :: Dxf -> Dxf -> Ordering #

(<) :: Dxf -> Dxf -> Bool #

(<=) :: Dxf -> Dxf -> Bool #

(>) :: Dxf -> Dxf -> Bool #

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

max :: Dxf -> Dxf -> Dxf #

min :: Dxf -> Dxf -> Dxf #

Show Dxf Source # 

Methods

showsPrec :: Int -> Dxf -> ShowS #

show :: Dxf -> String #

showList :: [Dxf] -> ShowS #

Generic Dxf Source # 

Associated Types

type Rep Dxf :: * -> * #

Methods

from :: Dxf -> Rep Dxf x #

to :: Rep Dxf x -> Dxf #

Default Dxf Source # 

Methods

def :: Dxf #

NFData Dxf Source # 

Methods

rnf :: Dxf -> () #

FromCursor Dxf Source #

See CT_Dxf, p. 3937

Methods

fromCursor :: Cursor -> [Dxf] Source #

ToElement Dxf Source #

See CT_Dxf, p. 3937

Methods

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

type Rep Dxf Source # 

data Fill Source #

This element specifies fill formatting.

TODO: Gradient fills (18.8.4) are currently unsupported. If we add them, then the spec says (CT_Fill, p. 3935), _either_ a gradient _or_ a solid fill pattern should be specified.

Section 18.8.20, "fill (Fill)" (p. 1768)

Constructors

Fill 

Instances

Eq Fill Source # 

Methods

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

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

Ord Fill Source # 

Methods

compare :: Fill -> Fill -> Ordering #

(<) :: Fill -> Fill -> Bool #

(<=) :: Fill -> Fill -> Bool #

(>) :: Fill -> Fill -> Bool #

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

max :: Fill -> Fill -> Fill #

min :: Fill -> Fill -> Fill #

Show Fill Source # 

Methods

showsPrec :: Int -> Fill -> ShowS #

show :: Fill -> String #

showList :: [Fill] -> ShowS #

Generic Fill Source # 

Associated Types

type Rep Fill :: * -> * #

Methods

from :: Fill -> Rep Fill x #

to :: Rep Fill x -> Fill #

Default Fill Source # 

Methods

def :: Fill #

NFData Fill Source # 

Methods

rnf :: Fill -> () #

FromCursor Fill Source #

See CT_Fill, p. 4484

Methods

fromCursor :: Cursor -> [Fill] Source #

ToElement Fill Source #

See CT_Fill, p. 4484

Methods

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

type Rep Fill Source # 
type Rep Fill = D1 * (MetaData "Fill" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "Fill" PrefixI True) (S1 * (MetaSel (Just Symbol "_fillPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FillPattern))))

data FillPattern Source #

This element is used to specify cell fill information for pattern and solid color cell fills. For solid cell fills (no pattern), fgColor is used. For cell fills with patterns specified, then the cell fill color is specified by the bgColor element.

Section 18.8.32 "patternFill (Pattern)" (p. 1793)

Instances

Eq FillPattern Source # 
Ord FillPattern Source # 
Show FillPattern Source # 
Generic FillPattern Source # 

Associated Types

type Rep FillPattern :: * -> * #

Default FillPattern Source # 

Methods

def :: FillPattern #

NFData FillPattern Source # 

Methods

rnf :: FillPattern -> () #

FromCursor FillPattern Source #

See CT_PatternFill, p. 4484

ToElement FillPattern Source #

See CT_PatternFill, p. 4484

type Rep FillPattern Source # 
type Rep FillPattern = D1 * (MetaData "FillPattern" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "FillPattern" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_fillPatternBgColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fillPatternFgColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))) (S1 * (MetaSel (Just Symbol "_fillPatternType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe PatternType))))))

data Font Source #

This element defines the properties for one of the fonts used in this workbook.

Section 18.2.22 "font (Font)" (p. 1769)

Constructors

Font 

Fields

  • _fontBold :: Maybe Bool

    Displays characters in bold face font style.

  • _fontCharset :: Maybe Int

    This element defines the font character set of this font.

    This field is used in font creation and selection if a font of the given facename is not available on the system. Although it is not required to have around when resolving font facename, the information can be stored for when needed to help resolve which font face to use of all available fonts on a system.

    Charset represents the basic set of characters associated with a font (that it can display), and roughly corresponds to the ANSI codepage (8-bit or DBCS) of that character set used by a given language. Given more common use of Unicode where many fonts support more than one of the traditional charset categories, and the use of font linking, using charset to resolve font name is less and less common, but still can be useful.

    These are operating-system-dependent values.

    Section 18.4.1 "charset (Character Set)" provides some example values.

  • _fontColor :: Maybe Color

    Color

  • _fontCondense :: Maybe Bool

    Macintosh compatibility setting. Represents special word/character rendering on Macintosh, when this flag is set. The effect is to condense the text (squeeze it together). SpreadsheetML applications are not required to render according to this flag.

  • _fontExtend :: Maybe Bool

    This element specifies a compatibility setting used for previous spreadsheet applications, resulting in special word/character rendering on those legacy applications, when this flag is set. The effect extends or stretches out the text. SpreadsheetML applications are not required to render according to this flag.

  • _fontFamily :: Maybe FontFamily

    The font family this font belongs to. A font family is a set of fonts having common stroke width and serif characteristics. This is system level font information. The font name overrides when there are conflicting values.

  • _fontItalic :: Maybe Bool

    Displays characters in italic font style. The italic style is defined by the font at a system level and is not specified by ECMA-376.

  • _fontName :: Maybe Text

    This element specifies the face name of this font.

    A string representing the name of the font. If the font doesn't exist (because it isn't installed on the system), or the charset not supported by that font, then another font should be substituted.

    The string length for this attribute shall be 0 to 31 characters.

  • _fontOutline :: Maybe Bool

    This element displays only the inner and outer borders of each character. This is very similar to Bold in behavior.

  • _fontScheme :: Maybe FontScheme

    Defines the font scheme, if any, to which this font belongs. When a font definition is part of a theme definition, then the font is categorized as either a major or minor font scheme component. When a new theme is chosen, every font that is part of a theme definition is updated to use the new major or minor font definition for that theme. Usually major fonts are used for styles like headings, and minor fonts are used for body and paragraph text.

  • _fontShadow :: Maybe Bool

    Macintosh compatibility setting. Represents special word/character rendering on Macintosh, when this flag is set. The effect is to render a shadow behind, beneath and to the right of the text. SpreadsheetML applications are not required to render according to this flag.

  • _fontStrikeThrough :: Maybe Bool

    This element draws a strikethrough line through the horizontal middle of the text.

  • _fontSize :: Maybe Double

    This element represents the point size (1/72 of an inch) of the Latin and East Asian text.

  • _fontUnderline :: Maybe FontUnderline

    This element represents the underline formatting style.

  • _fontVertAlign :: Maybe FontVerticalAlignment

    This element adjusts the vertical position of the text relative to the text's default appearance for this run. It is used to get superscript or subscript texts, and shall reduce the font size (if a smaller size is available) accordingly.

Instances

Eq Font Source # 

Methods

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

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

Ord Font Source # 

Methods

compare :: Font -> Font -> Ordering #

(<) :: Font -> Font -> Bool #

(<=) :: Font -> Font -> Bool #

(>) :: Font -> Font -> Bool #

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

max :: Font -> Font -> Font #

min :: Font -> Font -> Font #

Show Font Source # 

Methods

showsPrec :: Int -> Font -> ShowS #

show :: Font -> String #

showList :: [Font] -> ShowS #

Generic Font Source # 

Associated Types

type Rep Font :: * -> * #

Methods

from :: Font -> Rep Font x #

to :: Rep Font x -> Font #

Default Font Source # 

Methods

def :: Font #

NFData Font Source # 

Methods

rnf :: Font -> () #

FromCursor Font Source #

See CT_Font, p. 4489

Methods

fromCursor :: Cursor -> [Font] Source #

ToElement Font Source #

See CT_Font, p. 4489

Methods

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

type Rep Font Source # 
type Rep Font = D1 * (MetaData "Font" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "Font" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fontBold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fontCharset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Int))) (S1 * (MetaSel (Just Symbol "_fontColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Color))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fontCondense") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_fontExtend") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontFamily))) (S1 * (MetaSel (Just Symbol "_fontItalic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fontName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_fontOutline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fontScheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontScheme))) (S1 * (MetaSel (Just Symbol "_fontShadow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_fontStrikeThrough") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_fontSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Double)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_fontUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontUnderline))) (S1 * (MetaSel (Just Symbol "_fontVertAlign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe FontVerticalAlignment))))))))

data NumberFormat Source #

This type gives a high-level version of representation of number format used in Format.

data NumFmt Source #

This element specifies number format properties which indicate how to format and render the numeric value of a cell.

Section 18.8.30 "numFmt (Number Format)" (p. 1777)

Constructors

NumFmt 

Instances

Eq NumFmt Source # 

Methods

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

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

Ord NumFmt Source # 
Show NumFmt Source # 
Generic NumFmt Source # 

Associated Types

type Rep NumFmt :: * -> * #

Methods

from :: NumFmt -> Rep NumFmt x #

to :: Rep NumFmt x -> NumFmt #

NFData NumFmt Source # 

Methods

rnf :: NumFmt -> () #

FromCursor NumFmt Source #

See CT_NumFmt, p. 3936

ToElement NumFmt Source #

See CT_NumFmt, p. 3936

type Rep NumFmt Source # 
type Rep NumFmt = D1 * (MetaData "NumFmt" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "NumFmt" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_numFmtId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "_numFmtCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FormatCode))))

data ImpliedNumberFormat Source #

Implied number formats

Note: This only implements the predefined values for 18.2.30 "All Languages", other built-in format ids (with id < firstUserNumFmtId) are stored in NfOtherBuiltin

Constructors

NfGeneral
0 General
NfZero
1 0
Nf2Decimal
2 0.00
NfMax3Decimal
3 #,##0
NfThousandSeparator2Decimal
4 #,##0.00
NfPercent
9 0%
NfPercent2Decimal
10 0.00%
NfExponent2Decimal
11 0.00E+00
NfSingleSpacedFraction
12 # ?/?
NfDoubleSpacedFraction
13 # ??/??
NfMmDdYy
14 mm-dd-yy
NfDMmmYy
15 d-mmm-yy
NfDMmm
16 d-mmm
NfMmmYy
17 mmm-yy
NfHMm12Hr
18 h:mm AM/PM
NfHMmSs12Hr
19 h:mm:ss AM/PM
NfHMm
20 h:mm
NfHMmSs
21 h:mm:ss
NfMdyHMm
22 m/d/yy h:mm
NfThousandsNegativeParens
37 #,##0 ;(#,##0)
NfThousandsNegativeRed
38 #,##0 ;[Red](#,##0)
NfThousands2DecimalNegativeParens
39 #,##0.00;(#,##0.00)
NfThousands2DecimalNegativeRed
40 #,##0.00;[Red](#,##0.00)
NfMmSs
45 mm:ss
NfOptHMmSs
46 [h]:mm:ss
NfMmSs1Decimal
47 mmss.0
NfExponent1Decimal
48 ##0.0E+0
NfTextPlaceHolder
49 @
NfOtherImplied Int

other (non local-neutral?) built-in format (id < 164)

Instances

Eq ImpliedNumberFormat Source # 
Ord ImpliedNumberFormat Source # 
Show ImpliedNumberFormat Source # 
Generic ImpliedNumberFormat Source # 
NFData ImpliedNumberFormat Source # 

Methods

rnf :: ImpliedNumberFormat -> () #

type Rep ImpliedNumberFormat Source # 
type Rep ImpliedNumberFormat = D1 * (MetaData "ImpliedNumberFormat" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NfGeneral" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NfZero" PrefixI False) (U1 *)) (C1 * (MetaCons "Nf2Decimal" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NfMax3Decimal" PrefixI False) (U1 *)) (C1 * (MetaCons "NfThousandSeparator2Decimal" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NfPercent" PrefixI False) (U1 *)) (C1 * (MetaCons "NfPercent2Decimal" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "NfExponent2Decimal" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NfSingleSpacedFraction" PrefixI False) (U1 *)) (C1 * (MetaCons "NfDoubleSpacedFraction" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NfMmDdYy" PrefixI False) (U1 *)) (C1 * (MetaCons "NfDMmmYy" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NfDMmm" PrefixI False) (U1 *)) (C1 * (MetaCons "NfMmmYy" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NfHMm12Hr" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NfHMmSs12Hr" PrefixI False) (U1 *)) (C1 * (MetaCons "NfHMm" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NfHMmSs" PrefixI False) (U1 *)) (C1 * (MetaCons "NfMdyHMm" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NfThousandsNegativeParens" PrefixI False) (U1 *)) (C1 * (MetaCons "NfThousandsNegativeRed" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "NfThousands2DecimalNegativeParens" PrefixI False) (U1 *)) (C1 * (MetaCons "NfThousands2DecimalNegativeRed" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NfMmSs" PrefixI False) (U1 *)) (C1 * (MetaCons "NfOptHMmSs" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NfMmSs1Decimal" PrefixI False) (U1 *)) (C1 * (MetaCons "NfExponent1Decimal" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NfTextPlaceHolder" PrefixI False) (U1 *)) (C1 * (MetaCons "NfOtherImplied" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))))

type FormatCode = Text Source #

A number format code.

Section 18.8.30, "numFmt (Number Format)" (p. 1777)

data Protection Source #

Protection properties

Contains protection properties associated with the cell. Each cell has protection properties that can be set. The cell protection properties do not take effect unless the sheet has been protected.

Section 18.8.33, "protection (Protection Properties)", p. 1793

Instances

Eq Protection Source # 
Ord Protection Source # 
Show Protection Source # 
Generic Protection Source # 

Associated Types

type Rep Protection :: * -> * #

Default Protection Source # 

Methods

def :: Protection #

NFData Protection Source # 

Methods

rnf :: Protection -> () #

FromCursor Protection Source #

See CT_CellProtection, p. 4484

ToElement Protection Source #

See CT_CellProtection, p. 4484

type Rep Protection Source # 
type Rep Protection = D1 * (MetaData "Protection" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) (C1 * (MetaCons "Protection" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_protectionHidden") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_protectionLocked") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Bool)))))

Supporting enumerations

data CellHorizontalAlignment Source #

Horizontal alignment in cells

See 18.18.40 "ST_HorizontalAlignment (Horizontal Alignment Type)" (p. 2459)

Instances

Eq CellHorizontalAlignment Source # 
Ord CellHorizontalAlignment Source # 
Show CellHorizontalAlignment Source # 
Generic CellHorizontalAlignment Source # 
NFData CellHorizontalAlignment Source # 

Methods

rnf :: CellHorizontalAlignment -> () #

FromAttrVal CellHorizontalAlignment Source # 
ToAttrVal CellHorizontalAlignment Source # 
type Rep CellHorizontalAlignment Source # 
type Rep CellHorizontalAlignment = D1 * (MetaData "CellHorizontalAlignment" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "CellHorizontalAlignmentCenter" PrefixI False) (U1 *)) (C1 * (MetaCons "CellHorizontalAlignmentCenterContinuous" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CellHorizontalAlignmentDistributed" PrefixI False) (U1 *)) (C1 * (MetaCons "CellHorizontalAlignmentFill" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CellHorizontalAlignmentGeneral" PrefixI False) (U1 *)) (C1 * (MetaCons "CellHorizontalAlignmentJustify" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CellHorizontalAlignmentLeft" PrefixI False) (U1 *)) (C1 * (MetaCons "CellHorizontalAlignmentRight" PrefixI False) (U1 *)))))

data CellVerticalAlignment Source #

Vertical alignment in cells

See 18.18.88 "ST_VerticalAlignment (Vertical Alignment Types)" (p. 2512)

Instances

Eq CellVerticalAlignment Source # 
Ord CellVerticalAlignment Source # 
Show CellVerticalAlignment Source # 
Generic CellVerticalAlignment Source # 
NFData CellVerticalAlignment Source # 

Methods

rnf :: CellVerticalAlignment -> () #

FromAttrVal CellVerticalAlignment Source # 
ToAttrVal CellVerticalAlignment Source # 
type Rep CellVerticalAlignment Source # 
type Rep CellVerticalAlignment = D1 * (MetaData "CellVerticalAlignment" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * ((:+:) * (C1 * (MetaCons "CellVerticalAlignmentBottom" PrefixI False) (U1 *)) (C1 * (MetaCons "CellVerticalAlignmentCenter" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CellVerticalAlignmentDistributed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CellVerticalAlignmentJustify" PrefixI False) (U1 *)) (C1 * (MetaCons "CellVerticalAlignmentTop" PrefixI False) (U1 *)))))

data FontFamily Source #

Font family

See 18.8.18 "family (Font Family)" (p. 1766) and 17.18.30 "ST_FontFamily (Font Family Value)" (p. 1388)

Constructors

FontFamilyNotApplicable

Family is not applicable

FontFamilyRoman

Proportional font with serifs

FontFamilySwiss

Proportional font without serifs

FontFamilyModern

Monospace font with or without serifs

FontFamilyScript

Script font designed to mimic the appearance of handwriting

FontFamilyDecorative

Novelty font

Instances

Eq FontFamily Source # 
Ord FontFamily Source # 
Show FontFamily Source # 
Generic FontFamily Source # 

Associated Types

type Rep FontFamily :: * -> * #

NFData FontFamily Source # 

Methods

rnf :: FontFamily -> () #

FromAttrBs FontFamily Source # 
FromAttrVal FontFamily Source #

See 18.18.94 "ST_FontFamily (Font Family)" (p. 2517)

ToAttrVal FontFamily Source # 
type Rep FontFamily Source # 
type Rep FontFamily = D1 * (MetaData "FontFamily" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * ((:+:) * (C1 * (MetaCons "FontFamilyNotApplicable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FontFamilyRoman" PrefixI False) (U1 *)) (C1 * (MetaCons "FontFamilySwiss" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "FontFamilyModern" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FontFamilyScript" PrefixI False) (U1 *)) (C1 * (MetaCons "FontFamilyDecorative" PrefixI False) (U1 *)))))

data FontScheme Source #

Font scheme

See 18.18.33 "ST_FontScheme (Font scheme Styles)" (p. 2456)

Constructors

FontSchemeMajor

This font is the major font for this theme.

FontSchemeMinor

This font is the minor font for this theme.

FontSchemeNone

This font is not a theme font.

data FontUnderline Source #

Font underline property

See 18.4.13 "u (Underline)", p 1728

Instances

Eq FontUnderline Source # 
Ord FontUnderline Source # 
Show FontUnderline Source # 
Generic FontUnderline Source # 

Associated Types

type Rep FontUnderline :: * -> * #

NFData FontUnderline Source # 

Methods

rnf :: FontUnderline -> () #

FromAttrBs FontUnderline Source # 
FromAttrVal FontUnderline Source # 
ToAttrVal FontUnderline Source # 
type Rep FontUnderline Source # 
type Rep FontUnderline = D1 * (MetaData "FontUnderline" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * ((:+:) * (C1 * (MetaCons "FontUnderlineSingle" PrefixI False) (U1 *)) (C1 * (MetaCons "FontUnderlineDouble" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "FontUnderlineSingleAccounting" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FontUnderlineDoubleAccounting" PrefixI False) (U1 *)) (C1 * (MetaCons "FontUnderlineNone" PrefixI False) (U1 *)))))

data FontVerticalAlignment Source #

Vertical alignment

See 22.9.2.17 "ST_VerticalAlignRun (Vertical Positioning Location)" (p. 3794)

Instances

Eq FontVerticalAlignment Source # 
Ord FontVerticalAlignment Source # 
Show FontVerticalAlignment Source # 
Generic FontVerticalAlignment Source # 
NFData FontVerticalAlignment Source # 

Methods

rnf :: FontVerticalAlignment -> () #

FromAttrBs FontVerticalAlignment Source # 
FromAttrVal FontVerticalAlignment Source # 
ToAttrVal FontVerticalAlignment Source # 
type Rep FontVerticalAlignment Source # 
type Rep FontVerticalAlignment = D1 * (MetaData "FontVerticalAlignment" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * (C1 * (MetaCons "FontVerticalAlignmentBaseline" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "FontVerticalAlignmentSubscript" PrefixI False) (U1 *)) (C1 * (MetaCons "FontVerticalAlignmentSuperscript" PrefixI False) (U1 *))))

data LineStyle Source #

Instances

Eq LineStyle Source # 
Ord LineStyle Source # 
Show LineStyle Source # 
Generic LineStyle Source # 

Associated Types

type Rep LineStyle :: * -> * #

NFData LineStyle Source # 

Methods

rnf :: LineStyle -> () #

FromAttrVal LineStyle Source # 
ToAttrVal LineStyle Source # 
type Rep LineStyle Source # 
type Rep LineStyle = D1 * (MetaData "LineStyle" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "LineStyleDashDot" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LineStyleDashDotDot" PrefixI False) (U1 *)) (C1 * (MetaCons "LineStyleDashed" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "LineStyleDotted" PrefixI False) (U1 *)) (C1 * (MetaCons "LineStyleDouble" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LineStyleHair" PrefixI False) (U1 *)) (C1 * (MetaCons "LineStyleMedium" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "LineStyleMediumDashDot" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LineStyleMediumDashDotDot" PrefixI False) (U1 *)) (C1 * (MetaCons "LineStyleMediumDashed" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "LineStyleNone" PrefixI False) (U1 *)) (C1 * (MetaCons "LineStyleSlantDashDot" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LineStyleThick" PrefixI False) (U1 *)) (C1 * (MetaCons "LineStyleThin" PrefixI False) (U1 *))))))

data PatternType Source #

Indicates the style of fill pattern being used for a cell format.

Section 18.18.55 "ST_PatternType (Pattern Type)" (p. 2472)

Instances

Eq PatternType Source # 
Ord PatternType Source # 
Show PatternType Source # 
Generic PatternType Source # 

Associated Types

type Rep PatternType :: * -> * #

NFData PatternType Source # 

Methods

rnf :: PatternType -> () #

FromAttrVal PatternType Source # 
ToAttrVal PatternType Source # 
type Rep PatternType Source # 
type Rep PatternType = D1 * (MetaData "PatternType" "Codec.Xlsx.Types.StyleSheet" "xlsx-0.7.2-Bllq6ZS7v593hEJpIAxkWW" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PatternTypeDarkDown" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeDarkGray" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PatternTypeDarkGrid" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeDarkHorizontal" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "PatternTypeDarkTrellis" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeDarkUp" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PatternTypeDarkVertical" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PatternTypeGray0625" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeGray125" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PatternTypeLightDown" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeLightGray" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PatternTypeLightGrid" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PatternTypeLightHorizontal" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeLightTrellis" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "PatternTypeLightUp" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeLightVertical" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PatternTypeMediumGray" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PatternTypeNone" PrefixI False) (U1 *)) (C1 * (MetaCons "PatternTypeSolid" PrefixI False) (U1 *)))))))

data ReadingOrder Source #

Reading order

See 18.8.1 "alignment (Alignment)" (p. 1754, esp. p. 1755)

Lenses

StyleSheet

CellXf

Dxf

Alignment

Border

BorderStyle

Color

Fill

FillPattern

Font

Protection

Helpers

Number formats

fmtDecimals :: Int -> NumberFormat Source #

Basic number format with predefined number of decimals as format code of number format in xlsx should be less than 255 characters number of decimals shouldn't be more than 253

fmtDecimalsZeroes :: Int -> NumberFormat Source #

Basic number format with predefined number of decimals. Works like fmtDecimals with the only difference that extra zeroes are displayed when number of digits after the point is less than the number of digits specified in the format