xlsx-1.1.2.1: Simple and incomplete Excel file parser/writer
Copyright(c) Adam 2021
(c) Supercede 2021
LicenseMIT
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Codec.Xlsx.Parser.Stream

Description

Parse .xlsx sheets in constant memory.

All actions on an xlsx file run inside the XlsxM monad, and must be run with runXlsxM. XlsxM is not a monad transformer, a design inherited from the "zip" package's ZipArchive monad.

Inside the XlsxM monad, you can stream SheetItems (a row) from a particular sheet, using readSheetByIndex, which is callback-based and tied to IO.

Synopsis

Documentation

data XlsxM a Source #

Instances

Instances details
MonadIO XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

liftIO :: IO a -> XlsxM a #

Applicative XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

pure :: a -> XlsxM a #

(<*>) :: XlsxM (a -> b) -> XlsxM a -> XlsxM b #

liftA2 :: (a -> b -> c) -> XlsxM a -> XlsxM b -> XlsxM c #

(*>) :: XlsxM a -> XlsxM b -> XlsxM b #

(<*) :: XlsxM a -> XlsxM b -> XlsxM a #

Functor XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

fmap :: (a -> b) -> XlsxM a -> XlsxM b #

(<$) :: a -> XlsxM b -> XlsxM a #

Monad XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

(>>=) :: XlsxM a -> (a -> XlsxM b) -> XlsxM b #

(>>) :: XlsxM a -> XlsxM b -> XlsxM b #

return :: a -> XlsxM a #

MonadCatch XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

catch :: (HasCallStack, Exception e) => XlsxM a -> (e -> XlsxM a) -> XlsxM a #

MonadMask XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

mask :: HasCallStack => ((forall a. XlsxM a -> XlsxM a) -> XlsxM b) -> XlsxM b #

uninterruptibleMask :: HasCallStack => ((forall a. XlsxM a -> XlsxM a) -> XlsxM b) -> XlsxM b #

generalBracket :: HasCallStack => XlsxM a -> (a -> ExitCase b -> XlsxM c) -> (a -> XlsxM b) -> XlsxM (b, c) #

MonadThrow XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

throwM :: (HasCallStack, Exception e) => e -> XlsxM a #

MonadBaseControl IO XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Associated Types

type StM XlsxM a #

Methods

liftBaseWith :: (RunInBase XlsxM IO -> IO a) -> XlsxM a #

restoreM :: StM XlsxM a -> XlsxM a #

MonadBase IO XlsxM Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

liftBase :: IO α -> XlsxM α #

type StM XlsxM a Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

type StM XlsxM a

runXlsxM :: MonadIO m => FilePath -> XlsxM a -> m a Source #

Run a series of actions on an Xlsx file

data WorkbookInfo Source #

Information about the workbook contained in xl/workbook.xml (currently a subset)

Constructors

WorkbookInfo 

Fields

Instances

Instances details
Show WorkbookInfo Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

data SheetInfo Source #

Represents sheets from the workbook.xml file. E.g. <sheet name=Data sheetId="1" state="hidden" r:id="rId2" /

Constructors

SheetInfo 

Fields

Instances

Instances details
Show SheetInfo Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Eq SheetInfo Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

getWorkbookInfo :: XlsxM WorkbookInfo Source #

Returns information about the workbook, found in xl/workbook.xml. The result is cached so the XML will only be decompressed and parsed once inside a larger XlsxM action.

readSheet Source #

Arguments

:: SheetIndex 
-> (SheetItem -> IO ())

Function to consume the sheet's rows

-> XlsxM Bool

Returns False if sheet doesn't exist, or True otherwise

countRowsInSheet :: SheetIndex -> XlsxM (Maybe Int) Source #

Returns number of rows in the given sheet (identified by the sheet's ID, AKA the sheetId attribute, AKA sheetInfoSheetId), or Nothing if the sheet does not exist. Does not perform a full parse of the XML into SheetItems, so it should be more efficient than counting via readSheetByIndex.

collectItems :: SheetIndex -> XlsxM [SheetItem] Source #

this will collect the sheetitems in a list. useful for cases were memory is of no concern but a sheetitem type in a list is needed.

Index

data SheetIndex Source #

datatype representing a sheet index, looking it up by name can be done with makeIndexFromName, which is the preferred approach. although makeIndex is available in case it's already known.

Instances

Instances details
NFData SheetIndex Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

rnf :: SheetIndex -> () #

makeIndex :: Int -> SheetIndex Source #

This does *no* checking if the index exists or not. you could have index out of bounds issues because of this.

makeIndexFromName :: Text -> XlsxM (Maybe SheetIndex) Source #

Look up the index of a case insensitive sheet name

SheetItem

data SheetItem Source #

Sheet item

The current sheet at a time, every sheet is constructed of these items.

Constructors

MkSheetItem 

Fields

Instances

Instances details
Generic SheetItem Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Associated Types

type Rep SheetItem :: Type -> Type #

Show SheetItem Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

NFData SheetItem Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

rnf :: SheetItem -> () #

type Rep SheetItem Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

type Rep SheetItem = D1 ('MetaData "SheetItem" "Codec.Xlsx.Parser.Stream" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "MkSheetItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_si_sheet_index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "_si_row") 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 Row)))

Row

data Row Source #

Constructors

MkRow 

Fields

Instances

Instances details
Generic Row Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Associated Types

type Rep Row :: Type -> Type #

Methods

from :: Row -> Rep Row x #

to :: Rep Row x -> Row #

Show Row Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

showsPrec :: Int -> Row -> ShowS #

show :: Row -> String #

showList :: [Row] -> ShowS #

NFData Row Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

Methods

rnf :: Row -> () #

type Rep Row Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

type Rep Row = D1 ('MetaData "Row" "Codec.Xlsx.Parser.Stream" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "MkRow" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ri_row_index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RowIndex) :*: S1 ('MetaSel ('Just "_ri_cell_row") 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 CellRow)))

Errors

data AddCellErrors Source #

Constructors

ReadError

Could not read current cell value

Fields

SharedStringsNotFound

Could not find string by index in shared string table

Fields

Instances

Instances details
Show AddCellErrors Source # 
Instance details

Defined in Codec.Xlsx.Parser.Stream

data CoordinateErrors Source #

Constructors

CoordinateNotFound SheetValues

If the coordinate was not specified in "r" attribute

NoListElement SheetValue SheetValues

If the value is empty for some reason

NoTextContent Content SheetValues

If the value has something besides ContentText inside

DecodeFailure Text SheetValues

If malformed coordinate text was passed

data TypeError Source #

Constructors

TypeNotFound SheetValues 
TypeNoListElement SheetValue SheetValues 
UnkownType Text SheetValues 
TypeNoTextContent Content SheetValues