Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Xlsx = Xlsx {}
- newtype Styles = Styles {}
- newtype DefinedNames = DefinedNames [(Text, Maybe Text, Text)]
- data ColumnsProperties = ColumnsProperties {}
- data PageSetup = PageSetup {
- _pageSetupBlackAndWhite :: Maybe Bool
- _pageSetupCellComments :: Maybe CellComments
- _pageSetupCopies :: Maybe Int
- _pageSetupDraft :: Maybe Bool
- _pageSetupErrors :: Maybe PrintErrors
- _pageSetupFirstPageNumber :: Maybe Int
- _pageSetupFitToHeight :: Maybe Int
- _pageSetupFitToWidth :: Maybe Int
- _pageSetupHorizontalDpi :: Maybe Int
- _pageSetupId :: Maybe Text
- _pageSetupOrientation :: Maybe Orientation
- _pageSetupPageOrder :: Maybe PageOrder
- _pageSetupPaperHeight :: Maybe Text
- _pageSetupPaperSize :: Maybe PaperSize
- _pageSetupPaperWidth :: Maybe Text
- _pageSetupScale :: Maybe Int
- _pageSetupUseFirstPageNumber :: Maybe Bool
- _pageSetupUsePrinterDefaults :: Maybe Bool
- _pageSetupVerticalDpi :: Maybe Int
- data Worksheet = Worksheet {
- _wsColumnsProperties :: [ColumnsProperties]
- _wsRowPropertiesMap :: Map RowIndex RowProperties
- _wsCells :: CellMap
- _wsDrawing :: Maybe Drawing
- _wsMerges :: [Range]
- _wsSheetViews :: Maybe [SheetView]
- _wsPageSetup :: Maybe PageSetup
- _wsConditionalFormattings :: Map SqRef ConditionalFormatting
- _wsDataValidations :: Map SqRef DataValidation
- _wsPivotTables :: [PivotTable]
- _wsAutoFilter :: Maybe AutoFilter
- _wsTables :: [Table]
- _wsProtection :: Maybe SheetProtection
- _wsSharedFormulas :: Map SharedFormulaIndex SharedFormulaOptions
- _wsState :: SheetState
- data SheetState
- = Visible
- | Hidden
- | VeryHidden
- type CellMap = Map (RowIndex, ColumnIndex) Cell
- data CellValue
- data CellFormula = CellFormula {}
- data FormulaExpression
- newtype SharedFormulaIndex = SharedFormulaIndex Int
- data SharedFormulaOptions = SharedFormulaOptions {}
- data Cell = Cell {}
- data RowHeight
- data RowProperties = RowProps {}
- xlSheets :: Lens' Xlsx [(Text, Worksheet)]
- xlStyles :: Lens' Xlsx Styles
- xlDefinedNames :: Lens' Xlsx DefinedNames
- xlCustomProperties :: Lens' Xlsx (Map Text Variant)
- xlDateBase :: Lens' Xlsx DateBase
- wsColumnsProperties :: Lens' Worksheet [ColumnsProperties]
- wsRowPropertiesMap :: Lens' Worksheet (Map RowIndex RowProperties)
- wsCells :: Lens' Worksheet CellMap
- wsDrawing :: Lens' Worksheet (Maybe Drawing)
- wsMerges :: Lens' Worksheet [Range]
- wsSheetViews :: Lens' Worksheet (Maybe [SheetView])
- wsPageSetup :: Lens' Worksheet (Maybe PageSetup)
- wsConditionalFormattings :: Lens' Worksheet (Map SqRef ConditionalFormatting)
- wsDataValidations :: Lens' Worksheet (Map SqRef DataValidation)
- wsPivotTables :: Lens' Worksheet [PivotTable]
- wsAutoFilter :: Lens' Worksheet (Maybe AutoFilter)
- wsTables :: Lens' Worksheet [Table]
- wsProtection :: Lens' Worksheet (Maybe SheetProtection)
- wsSharedFormulas :: Lens' Worksheet (Map SharedFormulaIndex SharedFormulaOptions)
- wsState :: Lens' Worksheet SheetState
- cellValue :: Lens' Cell (Maybe CellValue)
- cellStyle :: Lens' Cell (Maybe Int)
- cellComment :: Lens' Cell (Maybe Comment)
- cellFormula :: Lens' Cell (Maybe CellFormula)
- rowHeightLens :: Lens' RowProperties (Maybe RowHeight)
- _CustomHeight :: Prism' RowHeight Double
- _AutomaticHeight :: Prism' RowHeight Double
- emptyStyles :: Styles
- renderStyleSheet :: StyleSheet -> Styles
- parseStyleSheet :: Styles -> Either SomeException StyleSheet
- simpleCellFormula :: Text -> CellFormula
- sharedFormulaByIndex :: SharedFormulaIndex -> CellFormula
- def :: Default a => a
- toRows :: CellMap -> [(RowIndex, [(ColumnIndex, Cell)])]
- fromRows :: [(RowIndex, [(ColumnIndex, Cell)])] -> CellMap
- module Codec.Xlsx.Types.Variant
- module Codec.Xlsx.Types.Table
- module Codec.Xlsx.Types.StyleSheet
- module Codec.Xlsx.Types.SheetViews
- module Codec.Xlsx.Types.RichText
- module Codec.Xlsx.Types.Protection
- module Codec.Xlsx.Types.PivotTable
- module Codec.Xlsx.Types.PageSetup
- module Codec.Xlsx.Types.Drawing.Common
- module Codec.Xlsx.Types.Drawing.Chart
- module Codec.Xlsx.Types.Drawing
- module Codec.Xlsx.Types.DataValidation
- module Codec.Xlsx.Types.ConditionalFormatting
- module Codec.Xlsx.Types.Common
- module Codec.Xlsx.Types.Comment
- module Codec.Xlsx.Types.AutoFilter
The main types
Structured representation of Xlsx file (currently a subset of its contents)
Xlsx | |
|
Instances
Generic Xlsx Source # | |
Show Xlsx Source # | |
Default Xlsx Source # | |
Defined in Codec.Xlsx.Types | |
NFData Xlsx Source # | |
Defined in Codec.Xlsx.Types | |
Eq Xlsx Source # | |
type Rep Xlsx Source # | |
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))))) |
Raw worksheet styles, for structured implementation see StyleSheet
and functions in Codec.Xlsx.Types.StyleSheet
Instances
Generic Styles Source # | |
Show Styles Source # | |
NFData Styles Source # | |
Defined in Codec.Xlsx.Types | |
Eq Styles Source # | |
type Rep Styles Source # | |
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.
DefinedNames [(Text, Maybe Text, Text)] |
Instances
Generic DefinedNames Source # | |
Defined in Codec.Xlsx.Types type Rep DefinedNames :: Type -> Type # from :: DefinedNames -> Rep DefinedNames x # to :: Rep DefinedNames x -> DefinedNames # | |
Show DefinedNames Source # | |
Defined in Codec.Xlsx.Types showsPrec :: Int -> DefinedNames -> ShowS # show :: DefinedNames -> String # showList :: [DefinedNames] -> ShowS # | |
Default DefinedNames Source # | |
Defined in Codec.Xlsx.Types def :: DefinedNames # | |
NFData DefinedNames Source # | |
Defined in Codec.Xlsx.Types rnf :: DefinedNames -> () # | |
Eq DefinedNames Source # | |
Defined in Codec.Xlsx.Types (==) :: DefinedNames -> DefinedNames -> Bool # (/=) :: DefinedNames -> DefinedNames -> Bool # | |
type Rep DefinedNames Source # | |
Defined in Codec.Xlsx.Types |
data ColumnsProperties Source #
Column range (from cwMin to cwMax) properties
ColumnsProperties | |
|
Instances
PageSetup | |
|
Instances
Xlsx worksheet
Worksheet | |
|
Instances
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.
Visible | state="visible" |
Hidden | state="hidden" |
VeryHidden | state="veryHidden" |
Instances
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'
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
data CellFormula Source #
Formula for the cell.
TODO: array, dataTable formula types support
See 18.3.1.40 "f (Formula)" (p. 1636)
CellFormula | |
|
Instances
data FormulaExpression Source #
formula type with type-specific options
Instances
newtype SharedFormulaIndex Source #
index of shared formula in worksheet's wsSharedFormulas
property
Instances
data SharedFormulaOptions Source #
Instances
Currently cell details include cell values, style ids and cell
formulas (inline strings from <is>
subelements are ignored)
Instances
Generic Cell Source # | |
Show Cell Source # | |
Default Cell Source # | |
Defined in Codec.Xlsx.Types.Cell | |
NFData Cell Source # | |
Defined in Codec.Xlsx.Types.Cell | |
Eq Cell Source # | |
type Rep Cell Source # | |
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))))) |
Height of a row in points (1/72in)
CustomHeight !Double | Row height is set by the user |
AutomaticHeight !Double | Row height is set automatically by the program |
Instances
Generic RowHeight Source # | |
Read RowHeight Source # | |
Show RowHeight Source # | |
NFData RowHeight Source # | |
Defined in Codec.Xlsx.Types | |
Eq RowHeight Source # | |
Ord RowHeight Source # | |
Defined in Codec.Xlsx.Types | |
type Rep RowHeight Source # | |
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
Instances
Lenses
Workbook
Worksheet
Cells
cellFormula :: Lens' Cell (Maybe CellFormula) Source #
Row properties
Style helpers
emptyStyles :: Styles Source #
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
simpleCellFormula :: Text -> CellFormula Source #
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
module Codec.Xlsx.Types.Variant
module Codec.Xlsx.Types.Table
module Codec.Xlsx.Types.StyleSheet
module Codec.Xlsx.Types.SheetViews
module Codec.Xlsx.Types.RichText
module Codec.Xlsx.Types.Protection
module Codec.Xlsx.Types.PivotTable
module Codec.Xlsx.Types.PageSetup
module Codec.Xlsx.Types.Drawing
module Codec.Xlsx.Types.Common
module Codec.Xlsx.Types.Comment
module Codec.Xlsx.Types.AutoFilter