Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype CellRef = CellRef {}
- data RowCoord
- data ColumnCoord
- type CellCoord = (RowCoord, ColumnCoord)
- type RangeCoord = (CellCoord, CellCoord)
- mapBoth :: (a -> b) -> (a, a) -> (b, b)
- col2coord :: Text -> ColumnCoord
- coord2col :: ColumnCoord -> Text
- row2coord :: Text -> RowCoord
- coord2row :: RowCoord -> Text
- singleCellRef :: (RowIndex, ColumnIndex) -> CellRef
- singleCellRef' :: CellCoord -> CellRef
- fromSingleCellRef :: CellRef -> Maybe (RowIndex, ColumnIndex)
- fromSingleCellRef' :: CellRef -> Maybe CellCoord
- fromSingleCellRefNoting :: CellRef -> (RowIndex, ColumnIndex)
- escapeRefSheetName :: Text -> Text
- unEscapeRefSheetName :: Text -> Text
- mkForeignSingleCellRef :: Text -> CellCoord -> CellRef
- fromForeignSingleCellRef :: CellRef -> Maybe (Text, CellCoord)
- type Range = CellRef
- mkRange :: (RowIndex, ColumnIndex) -> (RowIndex, ColumnIndex) -> Range
- mkRange' :: (RowCoord, ColumnCoord) -> (RowCoord, ColumnCoord) -> Range
- mkForeignRange :: Text -> CellCoord -> CellCoord -> Range
- fromRange :: Range -> Maybe ((RowIndex, ColumnIndex), (RowIndex, ColumnIndex))
- fromRange' :: Range -> Maybe RangeCoord
- fromForeignRange :: Range -> Maybe (Text, RangeCoord)
- newtype SqRef = SqRef [CellRef]
- data XlsxText
- xlsxTextToCellValue :: XlsxText -> CellValue
- newtype Formula = Formula {}
- data CellValue
- data ErrorType
- data DateBase
- dateFromNumber :: forall t. RealFrac t => DateBase -> t -> UTCTime
- dateToNumber :: Fractional a => DateBase -> UTCTime -> a
- int2col :: ColumnIndex -> Text
- col2int :: Text -> ColumnIndex
- columnIndexToText :: ColumnIndex -> Text
- textToColumnIndex :: Text -> ColumnIndex
- _XlsxText :: Prism' XlsxText Text
- _XlsxRichText :: Prism' XlsxText [RichTextRun]
- _CellText :: Prism' CellValue Text
- _CellDouble :: Prism' CellValue Double
- _CellBool :: Prism' CellValue Bool
- _CellRich :: Prism' CellValue [RichTextRun]
- _CellError :: Prism' CellValue ErrorType
- newtype RowIndex = RowIndex {
- unRowIndex :: Int
- newtype ColumnIndex = ColumnIndex {
- unColumnIndex :: Int
Documentation
Excel cell or cell range reference (e.g. E3
), possibly absolute.
See 18.18.62 ST_Ref
(p. 2482)
Note: The ST_Ref
type can point to another sheet (supported)
or a sheet in another workbook (separate .xlsx file, not implemented).
Instances
Generic CellRef Source # | |
Show CellRef Source # | |
NFData CellRef Source # | |
Defined in Codec.Xlsx.Types.Common | |
Eq CellRef Source # | |
Ord CellRef Source # | |
FromAttrVal CellRef Source # | |
Defined in Codec.Xlsx.Types.Common | |
FromAttrBs CellRef Source # | |
Defined in Codec.Xlsx.Types.Common fromAttrBs :: ByteString -> Either Text CellRef Source # | |
ToAttrVal CellRef Source # | |
type Rep CellRef Source # | |
Defined in Codec.Xlsx.Types.Common |
A helper type for coordinates to carry the intent of them being relative or absolute (preceded by $
):
singleCellRefRaw' (RowRel 5, ColumnAbs 1) == "$A5"
Instances
Generic RowCoord Source # | |
Read RowCoord Source # | |
Show RowCoord Source # | |
NFData RowCoord Source # | |
Defined in Codec.Xlsx.Types.Common | |
Eq RowCoord Source # | |
Ord RowCoord Source # | |
Defined in Codec.Xlsx.Types.Common | |
type Rep RowCoord Source # | |
Defined in Codec.Xlsx.Types.Common type Rep RowCoord = D1 ('MetaData "RowCoord" "Codec.Xlsx.Types.Common" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "RowAbs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RowIndex)) :+: C1 ('MetaCons "RowRel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RowIndex))) |
data ColumnCoord Source #
Instances
type CellCoord = (RowCoord, ColumnCoord) Source #
type RangeCoord = (CellCoord, CellCoord) Source #
mapBoth :: (a -> b) -> (a, a) -> (b, b) Source #
Helper function to apply the same transformation to both members of a tuple
mapBoth Abs (1, 2) == (Abs 1, Abs 2s)
col2coord :: Text -> ColumnCoord Source #
coord2col :: ColumnCoord -> Text Source #
singleCellRef :: (RowIndex, ColumnIndex) -> CellRef Source #
Render position in (row, col)
format to an Excel reference.
singleCellRef (RowIndex 2, ColumnIndex 4) == CellRef "D2"
singleCellRef' :: CellCoord -> CellRef Source #
Allow specifying whether a coordinate parameter is relative or absolute.
singleCellRef' (Rel 5, Abs 1) == CellRef "$A5"
fromSingleCellRef :: CellRef -> Maybe (RowIndex, ColumnIndex) Source #
Converse function to singleCellRef
Ignores a potential foreign sheet prefix.
fromSingleCellRef' :: CellRef -> Maybe CellCoord Source #
Converse function to 'singleCellRef'' Ignores a potential foreign sheet prefix.
fromSingleCellRefNoting :: CellRef -> (RowIndex, ColumnIndex) Source #
Converse function to singleCellRef
expecting valid reference and failig with
a standard error message like "Bad cell reference XXX
"
escapeRefSheetName :: Text -> Text Source #
Frame and escape the referenced sheet name in single quotes (apostrophe).
Sheet name in ST_Ref can be single-quoted when it contains non-alphanum class, non-ASCII range characters. Intermediate squote characters are escaped in a doubled fashion: "My ' Sheet" -> 'My '' Sheet'
unEscapeRefSheetName :: Text -> Text Source #
Unframe and unescape the referenced sheet name.
mkForeignSingleCellRef :: Text -> CellCoord -> CellRef Source #
Render a single cell existing in another worksheet.
This function always renders the sheet name single-quoted regardless the presence of spaces.
A sheet name shouldn't contain "[]*:?/"
chars and apostrophe "'"
should not happen at extremities.
mkForeignRange "MyOtherSheet" (Rel 2, Rel 4) (Abs 6, Abs 8) == "'MyOtherSheet'!D2:$H$6"
fromForeignSingleCellRef :: CellRef -> Maybe (Text, CellCoord) Source #
Converse function to mkForeignSingleCellRef
.
The provided CellRef must be a foreign range.
mkRange :: (RowIndex, ColumnIndex) -> (RowIndex, ColumnIndex) -> Range Source #
Render range
mkRange (RowIndex 2, ColumnIndex 4) (RowIndex 6, ColumnIndex 8) == CellRef "D2:H6"
mkRange' :: (RowCoord, ColumnCoord) -> (RowCoord, ColumnCoord) -> Range Source #
Render range with possibly absolute coordinates
mkRange' (Abs 2, Abs 4) (6, 8) == CellRef "$D$2:H6"
mkForeignRange :: Text -> CellCoord -> CellCoord -> Range Source #
Render a cell range existing in another worksheet.
This function always renders the sheet name single-quoted regardless the presence of spaces.
A sheet name shouldn't contain "[]*:?/"
chars and apostrophe "'"
should not happen at extremities.
mkForeignRange "MyOtherSheet" (Rel 2, Rel 4) (Abs 6, Abs 8) == "'MyOtherSheet'!D2:$H$6"
fromRange :: Range -> Maybe ((RowIndex, ColumnIndex), (RowIndex, ColumnIndex)) Source #
Converse function to mkRange
ignoring absolute coordinates.
Ignores a potential foreign sheet prefix.
fromRange' :: Range -> Maybe RangeCoord Source #
Converse function to 'mkRange'' to handle possibly absolute coordinates. Ignores a potential foreign sheet prefix.
fromForeignRange :: Range -> Maybe (Text, RangeCoord) Source #
Converse function to mkForeignRange
.
The provided Range must be a foreign range.
A sequence of cell references
See 18.18.76 "ST_Sqref (Reference Sequence)" (p.2488)
Instances
Generic SqRef Source # | |
Show SqRef Source # | |
NFData SqRef Source # | |
Defined in Codec.Xlsx.Types.Common | |
Eq SqRef Source # | |
Ord SqRef Source # | |
FromAttrVal SqRef Source # | |
Defined in Codec.Xlsx.Types.Common | |
FromAttrBs SqRef Source # | |
Defined in Codec.Xlsx.Types.Common fromAttrBs :: ByteString -> Either Text SqRef Source # | |
ToAttrVal SqRef Source # | |
type Rep SqRef Source # | |
Defined in Codec.Xlsx.Types.Common |
Common type containing either simple string or rich formatted text.
Used in si
, comment
and is
elements
E.g. si
spec says: "If the string is just a simple string with formatting applied
at the cell level, then the String Item (si) should contain a single text
element used to express the string. However, if the string in the cell is
more complex - i.e., has formatting applied at the character level - then the
string item shall consist of multiple rich text runs which collectively are
used to express the string.". So we have either a single Text field, or
else a list of RichTextRuns, each of which is some Text with layout
properties.
TODO: Currently we do not support phoneticPr
(Phonetic Properties, 18.4.3,
p. 1723) or rPh
(Phonetic Run, 18.4.6, p. 1725).
Section 18.4.8, "si (String Item)" (p. 1725)
See CT_Rst
, p. 3903
Instances
Generic XlsxText Source # | |
Show XlsxText Source # | |
NFData XlsxText Source # | |
Defined in Codec.Xlsx.Types.Common | |
Eq XlsxText Source # | |
Ord XlsxText Source # | |
Defined in Codec.Xlsx.Types.Common | |
FromCursor XlsxText Source # | See |
Defined in Codec.Xlsx.Types.Common fromCursor :: Cursor -> [XlsxText] Source # | |
FromXenoNode XlsxText Source # | |
Defined in Codec.Xlsx.Types.Common | |
ToElement XlsxText Source # | See |
type Rep XlsxText Source # | |
Defined in Codec.Xlsx.Types.Common type Rep XlsxText = D1 ('MetaData "XlsxText" "Codec.Xlsx.Types.Common" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "XlsxText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "XlsxRichText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RichTextRun]))) |
A formula
See 18.18.35 "ST_Formula (Formula)" (p. 2457)
Instances
Generic Formula Source # | |
Show Formula Source # | |
NFData Formula Source # | |
Defined in Codec.Xlsx.Types.Common | |
Eq Formula Source # | |
Ord Formula Source # | |
FromAttrVal Formula Source # | |
Defined in Codec.Xlsx.Types.Common | |
FromCursor Formula Source # | See |
Defined in Codec.Xlsx.Types.Common fromCursor :: Cursor -> [Formula] Source # | |
FromAttrBs Formula Source # | |
Defined in Codec.Xlsx.Types.Common fromAttrBs :: ByteString -> Either Text Formula Source # | |
FromXenoNode Formula Source # | |
Defined in Codec.Xlsx.Types.Common | |
ToElement Formula Source # | See |
type Rep Formula Source # | |
Defined in Codec.Xlsx.Types.Common |
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
The evaluation of an expression can result in an error having one of a number of error values.
See Annex L, L.2.16.8 "Error values" (p. 4764)
ErrorDiv0 |
|
ErrorNA |
|
ErrorName |
|
ErrorNull |
|
ErrorNum |
|
ErrorRef |
|
ErrorValue |
|
Instances
Specifies date base used for conversion of serial values to and from datetime values
See Annex L, L.2.16.9.1 "Date Conversion for Serial Values" (p. 4765)
DateBase1900 | 1900 date base system, the lower limit is January 1, -9999 00:00:00, which has serial value -4346018. The upper-limit is December 31, 9999, 23:59:59, which has serial value 2,958,465.9999884. The base date for this date base system is December 30, 1899, which has a serial value of 0. |
DateBase1904 | 1904 backward compatibility date-base system, the lower limit is January 1, 1904, 00:00:00, which has serial value 0. The upper limit is December 31, 9999, 23:59:59, which has serial value 2,957,003.9999884. The base date for this date base system is January 1, 1904, which has a serial value of 0. |
dateFromNumber :: forall t. RealFrac t => DateBase -> t -> UTCTime Source #
Converts serial value into datetime according to the specified
date base. Because Excel treats 1900 as a leap year even though it isn't,
this function converts any numbers that represent some time in 1900-02-29
in Excel to UTCTime
1900-03-01 00:00.
See https://docs.microsoft.com/en-gb/office/troubleshoot/excel/wrongly-assumes-1900-is-leap-year for details.
show (dateFromNumber DateBase1900 42929.75) == "2017-07-13 18:00:00 UTC" show (dateFromNumber DateBase1900 60) == "1900-03-01 00:00:00 UTC" show (dateFromNumber DateBase1900 61) == "1900-03-01 00:00:00 UTC"
dateToNumber :: Fractional a => DateBase -> UTCTime -> a Source #
Converts datetime into serial value.
Because Excel treats 1900 as a leap year even though it isn't,
the numbers that represent times in 1900-02-29 in Excel, in the range [60, 61[,
are never generated by this function for DateBase1900
. This means that
under those conditions this is not an inverse of dateFromNumber
.
See https://docs.microsoft.com/en-gb/office/troubleshoot/excel/wrongly-assumes-1900-is-leap-year for details.
int2col :: ColumnIndex -> Text Source #
Deprecated: this function will be removed in an upcoming release, use columnIndexToText instead.
col2int :: Text -> ColumnIndex Source #
Deprecated: this function will be removed in an upcoming release, use textToColumnIndex instead.
columnIndexToText :: ColumnIndex -> Text Source #
convert column number (starting from 1) to its textual form (e.g. 3 -> "C")
textToColumnIndex :: Text -> ColumnIndex Source #
reverse of columnIndexToText
prisms
Instances
Enum RowIndex Source # | |
Generic RowIndex Source # | |
Num RowIndex Source # | |
Read RowIndex Source # | |
Integral RowIndex Source # | |
Defined in Codec.Xlsx.Types.Common | |
Real RowIndex Source # | |
Defined in Codec.Xlsx.Types.Common toRational :: RowIndex -> Rational # | |
Show RowIndex Source # | |
NFData RowIndex Source # | |
Defined in Codec.Xlsx.Types.Common | |
Eq RowIndex Source # | |
Ord RowIndex Source # | |
Defined in Codec.Xlsx.Types.Common | |
ToAttrVal RowIndex Source # | |
type Rep RowIndex Source # | |
Defined in Codec.Xlsx.Types.Common |
newtype ColumnIndex Source #