| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Codec.Xlsx.Types.Common
Synopsis
- newtype CellRef = CellRef {}
- singleCellRef :: (Int, Int) -> CellRef
- fromSingleCellRef :: CellRef -> Maybe (Int, Int)
- fromSingleCellRefNoting :: CellRef -> (Int, Int)
- type Range = CellRef
- mkRange :: (Int, Int) -> (Int, Int) -> Range
- fromRange :: Range -> Maybe ((Int, Int), (Int, Int))
- newtype SqRef = SqRef [CellRef]
- data XlsxText
- xlsxTextToCellValue :: XlsxText -> CellValue
- newtype Formula = Formula {}
- data CellValue
- data ErrorType
- data DateBase
- dateFromNumber :: RealFrac t => DateBase -> t -> UTCTime
- dateToNumber :: Fractional a => DateBase -> UTCTime -> a
- int2col :: Int -> Text
- col2int :: Text -> Int
Documentation
Excel cell or cell range reference (e.g. E3)
 See 18.18.62 ST_Ref (p. 2482)
Instances
| Eq CellRef Source # | |
| Ord CellRef Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| Show CellRef Source # | |
| Generic CellRef Source # | |
| NFData CellRef Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| FromAttrBs CellRef Source # | |
| Defined in Codec.Xlsx.Types.Common Methods fromAttrBs :: ByteString -> Either Text CellRef Source # | |
| FromAttrVal CellRef Source # | |
| Defined in Codec.Xlsx.Types.Common Methods | |
| ToAttrVal CellRef Source # | |
| type Rep CellRef Source # | |
| Defined in Codec.Xlsx.Types.Common | |
singleCellRef :: (Int, Int) -> CellRef Source #
Render position in (row, col) format to an Excel reference.
mkCellRef (2, 4) == "D2"
fromSingleCellRefNoting :: CellRef -> (Int, Int) Source #
reverse to mkCellRef expecting valid reference and failig with
 a standard error message like "Bad cell reference XXX"
A sequence of cell references
See 18.18.76 "ST_Sqref (Reference Sequence)" (p.2488)
Instances
| Eq SqRef Source # | |
| Ord SqRef Source # | |
| Show SqRef Source # | |
| Generic SqRef Source # | |
| NFData SqRef Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| FromAttrBs SqRef Source # | |
| Defined in Codec.Xlsx.Types.Common Methods fromAttrBs :: ByteString -> Either Text SqRef Source # | |
| FromAttrVal SqRef Source # | |
| Defined in Codec.Xlsx.Types.Common Methods | |
| 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
Constructors
| XlsxText Text | |
| XlsxRichText [RichTextRun] | 
Instances
| Eq XlsxText Source # | |
| Ord XlsxText Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| Show XlsxText Source # | |
| Generic XlsxText Source # | |
| NFData XlsxText Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| FromXenoNode XlsxText Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| FromCursor XlsxText Source # | See  | 
| Defined in Codec.Xlsx.Types.Common Methods fromCursor :: Cursor -> [XlsxText] Source # | |
| 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-0.8.4-HaLEmVo1ZhGFVO4n3Yfot" '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
| Eq Formula Source # | |
| Ord Formula Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| Show Formula Source # | |
| Generic Formula Source # | |
| NFData Formula Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| FromAttrBs Formula Source # | |
| Defined in Codec.Xlsx.Types.Common Methods fromAttrBs :: ByteString -> Either Text Formula Source # | |
| FromXenoNode Formula Source # | |
| Defined in Codec.Xlsx.Types.Common | |
| FromAttrVal Formula Source # | |
| Defined in Codec.Xlsx.Types.Common Methods | |
| FromCursor Formula Source # | See  | 
| Defined in Codec.Xlsx.Types.Common Methods fromCursor :: Cursor -> [Formula] Source # | |
| 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
Constructors
| CellText Text | |
| CellDouble Double | |
| CellBool Bool | |
| CellRich [RichTextRun] | |
| CellError ErrorType | 
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)
Constructors
| 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)
Constructors
| 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 :: RealFrac t => DateBase -> t -> UTCTime Source #
Convertts serial value into datetime according to the specified date base
show (dateFromNumber DateBase1900 42929.75) == "2017-07-13 18:00:00 UTC"
dateToNumber :: Fractional a => DateBase -> UTCTime -> a Source #
Converts datetime into serial value