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

Codec.Xlsx.Writer.Internal

Synopsis

Rendering documents

class ToDocument a where Source #

Methods

toDocument :: a -> Document Source #

documentFromElement :: Text -> Element -> Document Source #

documentFromNsElement :: Text -> Text -> Element -> Document Source #

documentFromNsPrefElement :: Text -> Text -> Maybe Text -> Element -> Document Source #

Rendering elements

class ToElement a where Source #

Methods

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

Instances

Instances details
ToElement Protection Source #

See CT_CellProtection, p. 4484

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement NumFmt Source #

See CT_NumFmt, p. 3936

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement Dxf Source #

See CT_Dxf, p. 3937

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement Font Source #

See CT_Font, p. 4489

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement FillPattern Source #

See CT_PatternFill, p. 4484

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement Fill Source #

See CT_Fill, p. 4484

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement Color Source #

See CT_Color, p. 4484

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement BorderStyle Source #

See CT_BorderPr, p. 4483

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement Border Source #

See CT_Border, p. 4483

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement Alignment Source #

See CT_CellAlignment, p. 4482

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement CellXf Source #

See CT_Xf, p. 4486

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement StyleSheet Source #

See CT_Stylesheet, p. 4482

Instance details

Defined in Codec.Xlsx.Types.StyleSheet

Methods

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

ToElement RunProperties Source #

See CT_RPrElt, p. 3903

Instance details

Defined in Codec.Xlsx.Types.RichText

Methods

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

ToElement RichTextRun Source #

See CT_RElt, p. 3903

Instance details

Defined in Codec.Xlsx.Types.RichText

Methods

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

ToElement SheetProtection Source # 
Instance details

Defined in Codec.Xlsx.Types.Protection

Methods

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

ToElement PageSetup Source #

See CT_PageSetup, p. 3922

Instance details

Defined in Codec.Xlsx.Types.PageSetup

Methods

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

ToElement CustomProperty Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal.CustomProperties

Methods

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

ToElement CustomProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal.CustomProperties

Methods

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

ToElement Relationships Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal.Relationships

Methods

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

ToElement Relationship Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal.Relationships

Methods

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

ToElement LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

ToElement Formula Source #

See ST_Formula, p. 3873

Instance details

Defined in Codec.Xlsx.Types.Common

Methods

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

ToElement XlsxText Source #

See CT_Rst, p. 3903

Instance details

Defined in Codec.Xlsx.Types.Common

Methods

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

ToElement Pane Source #

See CT_Pane, p. 3913

Instance details

Defined in Codec.Xlsx.Types.SheetViews

Methods

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

ToElement Selection Source #

See CT_Selection, p. 3914

Instance details

Defined in Codec.Xlsx.Types.SheetViews

Methods

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

ToElement SheetView Source #

See CT_SheetView, p. 3913

Instance details

Defined in Codec.Xlsx.Types.SheetViews

Methods

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

ToElement CacheField Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable.Internal

Methods

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

ToElement DataLblProps Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement DataMarker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement ScatterSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement PieSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement BarSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement AreaSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement LineSeries Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement Series Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement Legend Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement ChartTitle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement ChartSpace Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

Methods

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

ToElement UnresolvedDrawing Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

Methods

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

ToElement NonVisualDrawingProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

Methods

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

ToElement GraphNonVisual Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

Methods

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

ToElement PicNonVisual Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

Methods

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

ToElement ClientData Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

Methods

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

ToElement Marker Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

Methods

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

ToElement DataValidation Source # 
Instance details

Defined in Codec.Xlsx.Types.DataValidation

Methods

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

ToElement DvPair Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal.DvPair

Methods

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

ToElement CfRule Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

ToElement DataBarOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

ToElement IconSetOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

ToElement MaxCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

ToElement MinCfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

ToElement CfValue Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

Methods

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

ToElement CfPair Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal.CfPair

Methods

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

ToElement CommentTable Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal.CommentTable

Methods

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

ToElement CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

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

ToElement AutoFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

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

ToElement DynFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

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

ToElement ColorFilterOptions Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

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

ToElement CustomFilter Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

Methods

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

ToElement ColumnsProperties Source # 
Instance details

Defined in Codec.Xlsx.Types

Methods

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

ToElement SharedStringTable Source #

See CT_Sst, p. 3902.

TODO: The count and uniqCount attributes are currently unsupported.

Instance details

Defined in Codec.Xlsx.Types.Internal.SharedStringTable

Methods

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

ToElement (BlipFillProperties RefId) Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

Methods

toElement :: Name -> BlipFillProperties RefId -> Element Source #

countedElementList :: Name -> [Element] -> Element Source #

nonEmptyCountedElementList :: Name -> [Element] -> Maybe Element Source #

elementList :: Name -> [(Name, Text)] -> [Element] -> Element Source #

elementListSimple :: Name -> [Element] -> Element Source #

nonEmptyElListSimple :: Name -> [Element] -> Maybe Element Source #

leafElement :: Name -> [(Name, Text)] -> Element Source #

emptyElement :: Name -> Element Source #

elementContent0 :: Name -> [(Name, Text)] -> Text -> Element Source #

elementContent :: Name -> Text -> Element Source #

elementContentPreserved :: Name -> Text -> Element Source #

elementValue :: ToAttrVal a => Name -> a -> Element Source #

elementValueDef :: (Eq a, ToAttrVal a) => Name -> a -> a -> Element Source #

Rendering attributes

class ToAttrVal a where Source #

Methods

toAttrVal :: a -> Text Source #

Instances

Instances details
ToAttrVal Bool Source # 
Instance details

Defined in Codec.Xlsx.Writer.Internal

Methods

toAttrVal :: Bool -> Text Source #

ToAttrVal Double Source # 
Instance details

Defined in Codec.Xlsx.Writer.Internal

ToAttrVal Int Source # 
Instance details

Defined in Codec.Xlsx.Writer.Internal

Methods

toAttrVal :: Int -> Text Source #

ToAttrVal Integer Source # 
Instance details

Defined in Codec.Xlsx.Writer.Internal

ToAttrVal String Source # 
Instance details

Defined in Codec.Xlsx.Writer.Internal

ToAttrVal Text Source # 
Instance details

Defined in Codec.Xlsx.Writer.Internal

Methods

toAttrVal :: Text -> Text Source #

ToAttrVal ReadingOrder Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal PatternType Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal LineStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal FontVerticalAlignment Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal FontUnderline Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal FontScheme Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal FontFamily Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal CellVerticalAlignment Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal CellHorizontalAlignment Source # 
Instance details

Defined in Codec.Xlsx.Types.StyleSheet

ToAttrVal LegacyPassword Source # 
Instance details

Defined in Codec.Xlsx.Types.Protection

ToAttrVal PaperSize Source #

See paperSize (attribute of pageSetup), p. 1659

Instance details

Defined in Codec.Xlsx.Types.PageSetup

ToAttrVal PageOrder Source #

See ST_PageOrder, p. 3923

Instance details

Defined in Codec.Xlsx.Types.PageSetup

ToAttrVal Orientation Source #

See ST_Orientation, p. 3923

Instance details

Defined in Codec.Xlsx.Types.PageSetup

ToAttrVal PrintErrors Source #

See ST_PrintError, p. 3923

Instance details

Defined in Codec.Xlsx.Types.PageSetup

ToAttrVal CellComments Source #

See ST_CellComments, p. 3923

Instance details

Defined in Codec.Xlsx.Types.PageSetup

ToAttrVal RefId Source # 
Instance details

Defined in Codec.Xlsx.Types.Internal

Methods

toAttrVal :: RefId -> Text Source #

ToAttrVal PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal Coordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

toAttrVal :: Angle -> Text Source #

ToAttrVal ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

ToAttrVal SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

toAttrVal :: SqRef -> Text Source #

ToAttrVal CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

ToAttrVal PaneState Source #

See ST_PaneState, p. 3929

Instance details

Defined in Codec.Xlsx.Types.SheetViews

ToAttrVal PaneType Source #

See ST_Pane, p. 3914

Instance details

Defined in Codec.Xlsx.Types.SheetViews

ToAttrVal SheetViewType Source #

See ST_SheetViewType, p. 3913

Instance details

Defined in Codec.Xlsx.Types.SheetViews

ToAttrVal ConsolidateFunction Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

ToAttrVal PivotFieldName Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

ToAttrVal FieldSortType Source # 
Instance details

Defined in Codec.Xlsx.Types.PivotTable

ToAttrVal TickMark Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal DataMarkerSymbol Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal ScatterStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal BarDirection Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal BarChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal ChartGrouping Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal LegendPos Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal DispBlanksAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Chart

ToAttrVal DrawingElementId Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

ToAttrVal EditAs Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing

ToAttrVal ErrorStyle Source # 
Instance details

Defined in Codec.Xlsx.Types.DataValidation

ToAttrVal ValidationType Source # 
Instance details

Defined in Codec.Xlsx.Types.DataValidation

ToAttrVal IconSetType Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal NStdDev Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal Inclusion Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal TimePeriod Source # 
Instance details

Defined in Codec.Xlsx.Types.ConditionalFormatting

ToAttrVal SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

ToAttrVal DynFilterType Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

ToAttrVal CustomFilterOperator Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

ToAttrVal FilterByBlank Source # 
Instance details

Defined in Codec.Xlsx.Types.AutoFilter

(.=) :: ToAttrVal a => Name -> a -> (Name, Text) Source #

(.=?) :: ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text) Source #

setAttr :: ToAttrVal a => Name -> a -> Element -> Element Source #

Dealing with namespaces

addNS :: Text -> Maybe Text -> Element -> Element Source #

Set the namespace for the entire document

This follows the same policy that the rest of the xlsx package uses.

mainNamespace :: Text Source #

The main namespace for Excel

Misc

txti :: Integral a => a -> Text Source #

justNonDef :: Eq a => a -> a -> Maybe a Source #