xlsx-0.6.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

Eq CellRef Source # 

Methods

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

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

Ord CellRef Source # 
Show CellRef Source # 
Generic CellRef Source # 

Associated Types

type Rep CellRef :: * -> * #

Methods

from :: CellRef -> Rep CellRef x #

to :: Rep CellRef x -> CellRef #

ToAttrVal CellRef Source # 
FromAttrVal CellRef Source # 
type Rep CellRef Source # 
type Rep CellRef = D1 (MetaData "CellRef" "Codec.Xlsx.Types.Common" "xlsx-0.6.0-IZdrXDBRg3BFENqFscUY0N" True) (C1 (MetaCons "CellRef" PrefixI True) (S1 (MetaSel (Just Symbol "unCellRef") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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 #

ToAttrVal SqRef Source # 

Methods

toAttrVal :: SqRef -> Text Source #

FromAttrVal SqRef Source # 
type Rep SqRef Source # 
type Rep SqRef = D1 (MetaData "SqRef" "Codec.Xlsx.Types.Common" "xlsx-0.6.0-IZdrXDBRg3BFENqFscUY0N" 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

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 #

ToElement Formula Source #

See ST_Formula, p. 3873

FromCursor Formula Source #

See ST_Formula, p. 3873

type Rep Formula Source # 
type Rep Formula = D1 (MetaData "Formula" "Codec.Xlsx.Types.Common" "xlsx-0.6.0-IZdrXDBRg3BFENqFscUY0N" 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

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