xlsx-1.1.2.1: Simple and incomplete Excel file parser/writer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Codec.Xlsx.Types.Common

Contents

Synopsis

Documentation

newtype CellRef Source #

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).

Constructors

CellRef 

Fields

Instances

Instances details
Generic CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep CellRef :: Type -> Type #

Methods

from :: CellRef -> Rep CellRef x #

to :: Rep CellRef x -> CellRef #

Show CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: CellRef -> () #

Eq CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

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

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

Ord CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromAttrVal CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromAttrBs CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

ToAttrVal CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep CellRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep CellRef = D1 ('MetaData "CellRef" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "CellRef" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCellRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data RowCoord Source #

A helper type for coordinates to carry the intent of them being relative or absolute (preceded by $):

singleCellRefRaw' (RowRel 5, ColumnAbs 1) == "$A5"

Constructors

RowAbs !RowIndex 
RowRel !RowIndex 

Instances

Instances details
Generic RowCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep RowCoord :: Type -> Type #

Methods

from :: RowCoord -> Rep RowCoord x #

to :: Rep RowCoord x -> RowCoord #

Read RowCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Show RowCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData RowCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: RowCoord -> () #

Eq RowCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord RowCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep RowCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep RowCoord = D1 ('MetaData "RowCoord" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" '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

Instances details
Generic ColumnCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep ColumnCoord :: Type -> Type #

Read ColumnCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Show ColumnCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData ColumnCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: ColumnCoord -> () #

Eq ColumnCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord ColumnCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep ColumnCoord Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep ColumnCoord = D1 ('MetaData "ColumnCoord" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "ColumnAbs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ColumnIndex)) :+: C1 ('MetaCons "ColumnRel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ColumnIndex)))

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)

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.

type Range = CellRef Source #

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

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.

newtype SqRef Source #

A sequence of cell references

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

Constructors

SqRef [CellRef] 

Instances

Instances details
Generic SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep SqRef :: Type -> Type #

Methods

from :: SqRef -> Rep SqRef x #

to :: Rep SqRef x -> SqRef #

Show SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

showsPrec :: Int -> SqRef -> ShowS #

show :: SqRef -> String #

showList :: [SqRef] -> ShowS #

NFData SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: SqRef -> () #

Eq SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

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

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

Ord SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

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 #

FromAttrVal SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromAttrBs SqRef 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 #

type Rep SqRef Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep SqRef = D1 ('MetaData "SqRef" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "SqRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Generic XlsxText Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep XlsxText :: Type -> Type #

Methods

from :: XlsxText -> Rep XlsxText x #

to :: Rep XlsxText x -> XlsxText #

Show XlsxText Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData XlsxText Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: XlsxText -> () #

Eq XlsxText Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord XlsxText Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromCursor XlsxText Source #

See CT_Rst, p. 3903

Instance details

Defined in Codec.Xlsx.Types.Common

FromXenoNode XlsxText Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

ToElement XlsxText Source #

See CT_Rst, p. 3903

Instance details

Defined in Codec.Xlsx.Types.Common

type Rep XlsxText Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep XlsxText = D1 ('MetaData "XlsxText" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" '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])))

newtype Formula Source #

A formula

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

Constructors

Formula 

Fields

Instances

Instances details
Generic Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep Formula :: Type -> Type #

Methods

from :: Formula -> Rep Formula x #

to :: Rep Formula x -> Formula #

Show Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: Formula -> () #

Eq Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

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

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

Ord Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromAttrVal Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromCursor Formula Source #

See ST_Formula, p. 3873

Instance details

Defined in Codec.Xlsx.Types.Common

FromAttrBs Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromXenoNode Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

ToElement Formula Source #

See ST_Formula, p. 3873

Instance details

Defined in Codec.Xlsx.Types.Common

type Rep Formula Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep Formula = D1 ('MetaData "Formula" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "Formula" 'PrefixI 'True) (S1 ('MetaSel ('Just "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 Specification (ECMA-376): - 18.3.1.4 c (Cell) - 18.18.11 ST_CellType (Cell Type)

Instances

Instances details
Generic CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep CellValue :: Type -> Type #

Show CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: CellValue -> () #

Eq CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep CellValue Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

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

Instances details
Generic ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep ErrorType :: Type -> Type #

Show ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: ErrorType -> () #

Eq ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromAttrVal ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

FromAttrBs ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

ToAttrVal ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep ErrorType Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep ErrorType = D1 ('MetaData "ErrorType" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "ErrorDiv0" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorNA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorName" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorNull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorNum" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorRef" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorValue" 'PrefixI 'False) (U1 :: Type -> Type))))

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

Instances details
Generic DateBase Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep DateBase :: Type -> Type #

Methods

from :: DateBase -> Rep DateBase x #

to :: Rep DateBase x -> DateBase #

Show DateBase Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData DateBase Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: DateBase -> () #

Eq DateBase Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep DateBase Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep DateBase = D1 ('MetaData "DateBase" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "DateBase1900" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DateBase1904" 'PrefixI 'False) (U1 :: Type -> Type))

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")

prisms

newtype RowIndex Source #

Constructors

RowIndex 

Fields

Instances

Instances details
Enum RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Generic RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep RowIndex :: Type -> Type #

Methods

from :: RowIndex -> Rep RowIndex x #

to :: Rep RowIndex x -> RowIndex #

Num RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Read RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Integral RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Real RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Show RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: RowIndex -> () #

Eq RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

ToAttrVal RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep RowIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep RowIndex = D1 ('MetaData "RowIndex" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "RowIndex" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRowIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype ColumnIndex Source #

Constructors

ColumnIndex 

Fields

Instances

Instances details
Enum ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Generic ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Associated Types

type Rep ColumnIndex :: Type -> Type #

Num ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Read ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Integral ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Real ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Show ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

NFData ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Methods

rnf :: ColumnIndex -> () #

Eq ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

Ord ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep ColumnIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Common

type Rep ColumnIndex = D1 ('MetaData "ColumnIndex" "Codec.Xlsx.Types.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "ColumnIndex" 'PrefixI 'True) (S1 ('MetaSel ('Just "unColumnIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))