xlsx-0.7.0: Simple and incomplete Excel file parser/writer

Safe HaskellNone
LanguageHaskell2010

Codec.Xlsx.Types.Common

Synopsis

Documentation

newtype CellRef Source #

Excel cell or cell range reference (e.g. E3) See 18.18.62 ST_Ref (p. 2482)

Constructors

CellRef 

Fields

Instances

singleCellRef :: (Int, Int) -> CellRef Source #

Render position in (row, col) format to an Excel reference.

mkCellRef (2, 4) == "D2"

fromSingleCellRef :: CellRef -> Maybe (Int, Int) Source #

reverse to mkCellRef

fromSingleCellRefNoting :: CellRef -> (Int, Int) Source #

reverse to mkCellRef expecting valid reference and failig with a standard error message like "Bad cell reference XXX"

type Range = CellRef Source #

Excel range (e.g. D13:H14), actually store as as CellRef in xlsx

mkRange :: (Int, Int) -> (Int, Int) -> Range Source #

Render range

mkRange (2, 4) (6, 8) == "D2:H6"

fromRange :: Range -> Maybe ((Int, Int), (Int, Int)) Source #

reverse to mkRange

newtype SqRef Source #

A sequence of cell references

See 18.18.76 "ST_Sqref (Reference Sequence)" (p.2488)

Constructors

SqRef [CellRef] 

Instances

Eq SqRef Source # 

Methods

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

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

Ord SqRef Source # 

Methods

compare :: SqRef -> SqRef -> Ordering #

(<) :: SqRef -> SqRef -> Bool #

(<=) :: SqRef -> SqRef -> Bool #

(>) :: SqRef -> SqRef -> Bool #

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

max :: SqRef -> SqRef -> SqRef #

min :: SqRef -> SqRef -> SqRef #

Show SqRef Source # 

Methods

showsPrec :: Int -> SqRef -> ShowS #

show :: SqRef -> String #

showList :: [SqRef] -> ShowS #

Generic SqRef Source # 

Associated Types

type Rep SqRef :: * -> * #

Methods

from :: SqRef -> Rep SqRef x #

to :: Rep SqRef x -> SqRef #

NFData SqRef Source # 

Methods

rnf :: SqRef -> () #

FromAttrBs SqRef Source # 
FromAttrVal SqRef Source # 
ToAttrVal SqRef Source # 

Methods

toAttrVal :: SqRef -> Text Source #

type Rep SqRef Source # 
type Rep SqRef = D1 * (MetaData "SqRef" "Codec.Xlsx.Types.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" True) (C1 * (MetaCons "SqRef" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [CellRef])))

data XlsxText Source #

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

newtype Formula Source #

A formula

See 18.18.35 "ST_Formula (Formula)" (p. 2457)

Constructors

Formula 

Fields

Instances

Eq Formula Source # 

Methods

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

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

Ord Formula Source # 
Show Formula Source # 
Generic Formula Source # 

Associated Types

type Rep Formula :: * -> * #

Methods

from :: Formula -> Rep Formula x #

to :: Rep Formula x -> Formula #

NFData Formula Source # 

Methods

rnf :: Formula -> () #

FromAttrBs Formula Source # 
FromXenoNode Formula Source # 
FromAttrVal Formula Source # 
FromCursor Formula Source #

See ST_Formula, p. 3873

ToElement Formula Source #

See ST_Formula, p. 3873

type Rep Formula Source # 
type Rep Formula = D1 * (MetaData "Formula" "Codec.Xlsx.Types.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" True) (C1 * (MetaCons "Formula" PrefixI True) (S1 * (MetaSel (Just Symbol "unFormula") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

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

Instances

Eq CellValue Source # 
Ord CellValue Source # 
Show CellValue Source # 
Generic CellValue Source # 

Associated Types

type Rep CellValue :: * -> * #

NFData CellValue Source # 

Methods

rnf :: CellValue -> () #

type Rep CellValue Source # 

data ErrorType Source #

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

#DIV/0! - Intended to indicate when any number, including zero, is divided by zero.

ErrorNA

#N/A - Intended to indicate when a designated value is not available. For example, some functions, such as SUMX2MY2, perform a series of operations on corresponding elements in two arrays. If those arrays do not have the same number of elements, then for some elements in the longer array, there are no corresponding elements in the shorter one; that is, one or more values in the shorter array are not available. This error value can be produced by calling the function NA.

ErrorName

#NAME? - Intended to indicate when what looks like a name is used, but no such name has been defined. For example, XYZ/3, where XYZ is not a defined name. Total is & A10, where neither Total nor is is a defined name. Presumably, "Total is " & A10 was intended. SUM(A1C10), where the range A1:C10 was intended.

ErrorNull

#NULL! - Intended to indicate when two areas are required to intersect, but do not. For example, In the case of SUM(B1 C1), the space between B1 and C1 is treated as the binary intersection operator, when a comma was intended.

ErrorNum

#NUM! - Intended to indicate when an argument to a function has a compatible type, but has a value that is outside the domain over which that function is defined. (This is known as a domain error.) For example, Certain calls to ASIN, ATANH, FACT, and SQRT might result in domain errors. Intended to indicate that the result of a function cannot be represented in a value of the specified type, typically due to extreme magnitude. (This is known as a range error.) For example, FACT(1000) might result in a range error.

ErrorRef

#REF! - Intended to indicate when a cell reference is invalid. For example, If a formula contains a reference to a cell, and then the row or column containing that cell is deleted, a #REF! error results. If a worksheet does not support 20,001 columns, OFFSET(A1,0,20000) results in a #REF! error.

ErrorValue

#VALUE! - Intended to indicate when an incompatible type argument is passed to a function, or an incompatible type operand is used with an operator. For example, In the case of a function argument, a number was expected, but text was provided. In the case of 1+ABC, the binary addition operator is not defined for text.

Instances

Eq ErrorType Source # 
Ord ErrorType Source # 
Show ErrorType Source # 
Generic ErrorType Source # 

Associated Types

type Rep ErrorType :: * -> * #

NFData ErrorType Source # 

Methods

rnf :: ErrorType -> () #

FromAttrBs ErrorType Source # 
FromAttrVal ErrorType Source # 
ToAttrVal ErrorType Source # 
type Rep ErrorType Source # 
type Rep ErrorType = D1 * (MetaData "ErrorType" "Codec.Xlsx.Types.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ErrorDiv0" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ErrorNA" PrefixI False) (U1 *)) (C1 * (MetaCons "ErrorName" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "ErrorNull" PrefixI False) (U1 *)) (C1 * (MetaCons "ErrorNum" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ErrorRef" PrefixI False) (U1 *)) (C1 * (MetaCons "ErrorValue" PrefixI False) (U1 *)))))

data DateBase Source #

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.

Instances

Eq DateBase Source # 
Show DateBase Source # 
Generic DateBase Source # 

Associated Types

type Rep DateBase :: * -> * #

Methods

from :: DateBase -> Rep DateBase x #

to :: Rep DateBase x -> DateBase #

NFData DateBase Source # 

Methods

rnf :: DateBase -> () #

type Rep DateBase Source # 
type Rep DateBase = D1 * (MetaData "DateBase" "Codec.Xlsx.Types.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * (C1 * (MetaCons "DateBase1900" PrefixI False) (U1 *)) (C1 * (MetaCons "DateBase1904" PrefixI False) (U1 *)))

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

int2col :: Int -> Text Source #

convert column number (starting from 1) to its textual form (e.g. 3 -> "C")

col2int :: Text -> Int Source #

reverse to int2col