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

Codec.Xlsx.Types.Cell

Synopsis

Documentation

data CellFormula Source #

Formula for the cell.

TODO: array, dataTable formula types support

See 18.3.1.40 "f (Formula)" (p. 1636)

Constructors

CellFormula 

Fields

Instances

Instances details
Generic CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep CellFormula :: Type -> Type #

Show CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

NFData CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: CellFormula -> () #

Eq CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

ToElement CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep CellFormula Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep CellFormula = D1 ('MetaData "CellFormula" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "CellFormula" 'PrefixI 'True) (S1 ('MetaSel ('Just "_cellfExpression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FormulaExpression) :*: (S1 ('MetaSel ('Just "_cellfAssignsToName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_cellfCalculate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data FormulaExpression Source #

formula type with type-specific options

Instances

Instances details
Generic FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep FormulaExpression :: Type -> Type #

Show FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

NFData FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: FormulaExpression -> () #

Eq FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep FormulaExpression Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep FormulaExpression = D1 ('MetaData "FormulaExpression" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "NormalFormula" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Formula)) :+: C1 ('MetaCons "SharedFormula" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SharedFormulaIndex)))

newtype SharedFormulaIndex Source #

index of shared formula in worksheet's wsSharedFormulas property

Constructors

SharedFormulaIndex Int 

Instances

Instances details
Generic SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep SharedFormulaIndex :: Type -> Type #

Show SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

NFData SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: SharedFormulaIndex -> () #

Eq SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Ord SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

FromAttrVal SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

FromAttrBs SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

ToAttrVal SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep SharedFormulaIndex Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep SharedFormulaIndex = D1 ('MetaData "SharedFormulaIndex" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'True) (C1 ('MetaCons "SharedFormulaIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Cell Source #

Currently cell details include cell values, style ids and cell formulas (inline strings from <is> subelements are ignored)

Instances

Instances details
Generic Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Associated Types

type Rep Cell :: Type -> Type #

Methods

from :: Cell -> Rep Cell x #

to :: Rep Cell x -> Cell #

Show Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Default Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

def :: Cell #

NFData Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

rnf :: Cell -> () #

Eq Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

Methods

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

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

type Rep Cell Source # 
Instance details

Defined in Codec.Xlsx.Types.Cell

type Rep Cell = D1 ('MetaData "Cell" "Codec.Xlsx.Types.Cell" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Cell" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_cellStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "_cellValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CellValue))) :*: (S1 ('MetaSel ('Just "_cellComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Comment)) :*: S1 ('MetaSel ('Just "_cellFormula") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CellFormula)))))

type CellMap = Map (RowIndex, ColumnIndex) Cell Source #

Map containing cell values which are indexed by row and column if you need to use more traditional (x,y) indexing please you could use corresponding accessors from 'Lens'