xlsx-1.1.0.1: Simple and incomplete Excel file parser/writer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Codec.Xlsx.Types

Synopsis

The main types

data Xlsx Source #

Structured representation of Xlsx file (currently a subset of its contents)

Constructors

Xlsx 

Fields

Instances

Instances details
Generic Xlsx Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep Xlsx :: Type -> Type #

Methods

from :: Xlsx -> Rep Xlsx x #

to :: Rep Xlsx x -> Xlsx #

Show Xlsx Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

showsPrec :: Int -> Xlsx -> ShowS #

show :: Xlsx -> String #

showList :: [Xlsx] -> ShowS #

Default Xlsx Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

def :: Xlsx #

NFData Xlsx Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: Xlsx -> () #

Eq Xlsx Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

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

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

type Rep Xlsx Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep Xlsx = D1 ('MetaData "Xlsx" "Codec.Xlsx.Types" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Xlsx" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_xlSheets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Worksheet)]) :*: S1 ('MetaSel ('Just "_xlStyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Styles)) :*: (S1 ('MetaSel ('Just "_xlDefinedNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DefinedNames) :*: (S1 ('MetaSel ('Just "_xlCustomProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Variant)) :*: S1 ('MetaSel ('Just "_xlDateBase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DateBase)))))

newtype Styles Source #

Raw worksheet styles, for structured implementation see StyleSheet and functions in Codec.Xlsx.Types.StyleSheet

Constructors

Styles 

Fields

Instances

Instances details
Generic Styles Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep Styles :: Type -> Type #

Methods

from :: Styles -> Rep Styles x #

to :: Rep Styles x -> Styles #

Show Styles Source # 
Instance details

Defined in Codec.Xlsx.Types

NFData Styles Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: Styles -> () #

Eq Styles Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

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

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

type Rep Styles Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep Styles = D1 ('MetaData "Styles" "Codec.Xlsx.Types" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'True) (C1 ('MetaCons "Styles" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype DefinedNames Source #

Defined names

Each defined name consists of a name, an optional local sheet ID, and a value.

This element defines the collection of defined names for this workbook. Defined names are descriptive names to represent cells, ranges of cells, formulas, or constant values. Defined names can be used to represent a range on any worksheet.

Excel also defines a number of reserved names with a special interpretation:

  • _xlnm.Print_Area specifies the workbook's print area. Example value: SheetName!$A:$A,SheetName!$1:$4
  • _xlnm.Print_Titles specifies the row(s) or column(s) to repeat at the top of each printed page.
  • _xlnm.Sheet_Title:refers to a sheet title.

and others. See Section 18.2.6, "definedNames (Defined Names)" (p. 1728) of the spec (second edition).

NOTE: Right now this is only a minimal implementation of defined names.

Constructors

DefinedNames [(Text, Maybe Text, Text)] 

Instances

Instances details
Generic DefinedNames Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep DefinedNames :: Type -> Type #

Show DefinedNames Source # 
Instance details

Defined in Codec.Xlsx.Types

Default DefinedNames Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

def :: DefinedNames #

NFData DefinedNames Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: DefinedNames -> () #

Eq DefinedNames Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep DefinedNames Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep DefinedNames = D1 ('MetaData "DefinedNames" "Codec.Xlsx.Types" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'True) (C1 ('MetaCons "DefinedNames" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Maybe Text, Text)])))

data ColumnsProperties Source #

Column range (from cwMin to cwMax) properties

Constructors

ColumnsProperties 

Fields

  • cpMin :: Int

    First column affected by this ColumnWidth record.

  • cpMax :: Int

    Last column affected by this ColumnWidth record.

  • cpWidth :: Maybe Double

    Column width measured as the number of characters of the maximum digit width of the numbers 0, 1, 2, ..., 9 as rendered in the normal style's font.

    See longer description in Section 18.3.1.13 "col (Column Width & Formatting)" (p. 1605)

  • cpStyle :: Maybe Int

    Default style for the affected column(s). Affects cells not yet allocated in the column(s). In other words, this style applies to new columns.

  • cpHidden :: Bool

    Flag indicating if the affected column(s) are hidden on this worksheet.

  • cpCollapsed :: Bool

    Flag indicating if the outlining of the affected column(s) is in the collapsed state.

  • cpBestFit :: Bool

    Flag indicating if the specified column(s) is set to 'best fit'.

Instances

Instances details
Generic ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep ColumnsProperties :: Type -> Type #

Show ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

NFData ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: ColumnsProperties -> () #

Eq ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

FromCursor ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

FromXenoNode ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

ToElement ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

data PageSetup Source #

Constructors

PageSetup 

Fields

Instances

Instances details
Generic PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

Associated Types

type Rep PageSetup :: Type -> Type #

Show PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

Default PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

Methods

def :: PageSetup #

NFData PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

Methods

rnf :: PageSetup -> () #

Eq PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

Ord PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

FromCursor PageSetup Source #

See CT_PageSetup, p. 3922

Instance details

Defined in Codec.Xlsx.Types.PageSetup

FromXenoNode PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

ToElement PageSetup Source #

See CT_PageSetup, p. 3922

Instance details

Defined in Codec.Xlsx.Types.PageSetup

type Rep PageSetup Source # 
Instance details

Defined in Codec.Xlsx.Types.PageSetup

type Rep PageSetup = D1 ('MetaData "PageSetup" "Codec.Xlsx.Types.PageSetup" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "PageSetup" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "_pageSetupBlackAndWhite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_pageSetupCellComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CellComments))) :*: (S1 ('MetaSel ('Just "_pageSetupCopies") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "_pageSetupDraft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "_pageSetupErrors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PrintErrors)) :*: S1 ('MetaSel ('Just "_pageSetupFirstPageNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "_pageSetupFitToHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "_pageSetupFitToWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "_pageSetupHorizontalDpi") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))) :*: (((S1 ('MetaSel ('Just "_pageSetupId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_pageSetupOrientation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Orientation))) :*: (S1 ('MetaSel ('Just "_pageSetupPageOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PageOrder)) :*: (S1 ('MetaSel ('Just "_pageSetupPaperHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_pageSetupPaperSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PaperSize))))) :*: ((S1 ('MetaSel ('Just "_pageSetupPaperWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "_pageSetupScale") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "_pageSetupUseFirstPageNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "_pageSetupUsePrinterDefaults") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "_pageSetupVerticalDpi") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))))))

data Worksheet Source #

Xlsx worksheet

Instances

Instances details
Generic Worksheet Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep Worksheet :: Type -> Type #

Show Worksheet Source # 
Instance details

Defined in Codec.Xlsx.Types

Default Worksheet Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

def :: Worksheet #

NFData Worksheet Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: Worksheet -> () #

Eq Worksheet Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep Worksheet Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep Worksheet = D1 ('MetaData "Worksheet" "Codec.Xlsx.Types" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Worksheet" 'PrefixI 'True) (((S1 ('MetaSel ('Just "_wsColumnsProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ColumnsProperties]) :*: (S1 ('MetaSel ('Just "_wsRowPropertiesMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map RowIndex RowProperties)) :*: S1 ('MetaSel ('Just "_wsCells") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CellMap))) :*: ((S1 ('MetaSel ('Just "_wsDrawing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Drawing)) :*: S1 ('MetaSel ('Just "_wsMerges") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Range])) :*: (S1 ('MetaSel ('Just "_wsSheetViews") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [SheetView])) :*: S1 ('MetaSel ('Just "_wsPageSetup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PageSetup))))) :*: (((S1 ('MetaSel ('Just "_wsConditionalFormattings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map SqRef ConditionalFormatting)) :*: S1 ('MetaSel ('Just "_wsDataValidations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map SqRef DataValidation))) :*: (S1 ('MetaSel ('Just "_wsPivotTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PivotTable]) :*: S1 ('MetaSel ('Just "_wsAutoFilter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AutoFilter)))) :*: ((S1 ('MetaSel ('Just "_wsTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Table]) :*: S1 ('MetaSel ('Just "_wsProtection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SheetProtection))) :*: (S1 ('MetaSel ('Just "_wsSharedFormulas") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map SharedFormulaIndex SharedFormulaOptions)) :*: S1 ('MetaSel ('Just "_wsState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SheetState))))))

data SheetState Source #

Sheet visibility state cf. Ecma Office Open XML Part 1: 18.18.68 ST_SheetState (Sheet Visibility Types) * "visible" Indicates the sheet is visible (default) * "hidden" Indicates the workbook window is hidden, but can be shown by the user via the user interface. * "veryHidden" Indicates the sheet is hidden and cannot be shown in the user interface (UI). This state is only available programmatically.

Constructors

Visible

state="visible"

Hidden

state="hidden"

VeryHidden

state="veryHidden"

Instances

Instances details
Generic SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep SheetState :: Type -> Type #

Show SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

Default SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

def :: SheetState #

NFData SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: SheetState -> () #

Eq SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

FromAttrVal SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

FromAttrBs SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

ToAttrVal SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep SheetState Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep SheetState = D1 ('MetaData "SheetState" "Codec.Xlsx.Types" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Visible" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Hidden" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VeryHidden" 'PrefixI 'False) (U1 :: Type -> Type)))

type CellMap = Map (RowIndex, ColumnIndex) Cell Source #

Map containing cell values which are indexed by row and column if you need to use more traditional (x,y) indexing please you could use corresponding accessors from 'Lens'

data CellValue Source #

Cell values include text, numbers and booleans, standard includes date format also but actually dates are represented by numbers with a date format assigned to a cell containing it Specification (ECMA-376): - 18.3.1.4 c (Cell) - 18.18.11 ST_CellType (Cell Type)

Instances

Instances details
Generic CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep CellValue :: Type -> Type #

Show CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: CellValue -> () #

Eq CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

data CellFormula Source #

Formula for the cell.

TODO: array, dataTable formula types support

See 18.3.1.40 "f (Formula)" (p. 1636)

Constructors

CellFormula 

Fields

Instances

Instances details
Generic CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep CellFormula :: Type -> Type #

Show CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

NFData CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: CellFormula -> () #

Eq CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

ToElement CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep CellFormula = D1 ('MetaData "CellFormula" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "CellFormula" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cellfExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormulaExpression) :*: (S1 ('MetaSel ('Just "_cellfAssignsToName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_cellfCalculate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data FormulaExpression Source #

formula type with type-specific options

Instances

Instances details
Generic FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep FormulaExpression :: Type -> Type #

Show FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

NFData FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: FormulaExpression -> () #

Eq FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep FormulaExpression = D1 ('MetaData "FormulaExpression" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "NormalFormula" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: C1 ('MetaCons "SharedFormula" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SharedFormulaIndex)))

newtype SharedFormulaIndex Source #

index of shared formula in worksheet's wsSharedFormulas property

Constructors

SharedFormulaIndex Int 

Instances

Instances details
Generic SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep SharedFormulaIndex :: Type -> Type #

Show SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

NFData SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: SharedFormulaIndex -> () #

Eq SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Ord SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

FromAttrVal SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

FromAttrBs SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

ToAttrVal SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep SharedFormulaIndex = D1 ('MetaData "SharedFormulaIndex" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'True) (C1 ('MetaCons "SharedFormulaIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Cell Source #

Currently cell details include cell values, style ids and cell formulas (inline strings from <is> subelements are ignored)

Instances

Instances details
Generic Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep Cell :: Type -> Type #

Methods

from :: Cell -> Rep Cell x #

to :: Rep Cell x -> Cell #

Show Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Default Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

def :: Cell #

NFData Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: Cell -> () #

Eq Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

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

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

type Rep Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep Cell = D1 ('MetaData "Cell" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Cell" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_cellStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "_cellValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CellValue))) :*: (S1 ('MetaSel ('Just "_cellComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Comment)) :*: S1 ('MetaSel ('Just "_cellFormula") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CellFormula)))))

data RowHeight Source #

Height of a row in points (1/72in)

Constructors

CustomHeight !Double

Row height is set by the user

AutomaticHeight !Double

Row height is set automatically by the program

Instances

Instances details
Generic RowHeight Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep RowHeight :: Type -> Type #

Read RowHeight Source # 
Instance details

Defined in Codec.Xlsx.Types

Show RowHeight Source # 
Instance details

Defined in Codec.Xlsx.Types

NFData RowHeight Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: RowHeight -> () #

Eq RowHeight Source # 
Instance details

Defined in Codec.Xlsx.Types

Ord RowHeight Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep RowHeight Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep RowHeight = D1 ('MetaData "RowHeight" "Codec.Xlsx.Types" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "CustomHeight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "AutomaticHeight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)))

data RowProperties Source #

Properties of a row. See §18.3.1.73 "row (Row)" for more details

Constructors

RowProps 

Fields

Instances

Instances details
Generic RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Associated Types

type Rep RowProperties :: Type -> Type #

Read RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Show RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Default RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

def :: RowProperties #

NFData RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

rnf :: RowProperties -> () #

Eq RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Ord RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep RowProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

type Rep RowProperties = D1 ('MetaData "RowProperties" "Codec.Xlsx.Types" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "RowProps" 'PrefixI 'True) (S1 ('MetaSel ('Just "rowHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RowHeight)) :*: (S1 ('MetaSel ('Just "rowStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "rowHidden") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

Lenses

Workbook

Worksheet

Cells

Row properties

Style helpers

renderStyleSheet :: StyleSheet -> Styles Source #

Render StyleSheet

This is used to render a structured StyleSheet into a raw XML Styles document. Actually replacing Styles with StyleSheet would mean we would need to write a parser for StyleSheet as well (and would moreover require that we support the full style sheet specification, which is still quite a bit of work).

parseStyleSheet :: Styles -> Either SomeException StyleSheet Source #

Parse StyleSheet

This is used to parse raw Styles into structured StyleSheet currently not all of the style sheet specification is supported so parser (and the data model) is to be completed

Misc

def :: Default a => a #

The default value for this type.

toRows :: CellMap -> [(RowIndex, [(ColumnIndex, Cell)])] Source #

converts cells mapped by (row, column) into rows which contain row index and cells as pairs of column indices and cell values