Copyright | (c) Adam 2021 (c) Supercede 2021 |
---|---|
License | MIT |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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 SheetItem
s (a row) from a
particular sheet, using readSheetByIndex
, which is callback-based and tied to IO.
Synopsis
- data XlsxM a
- runXlsxM :: MonadIO m => FilePath -> XlsxM a -> m a
- data WorkbookInfo = WorkbookInfo {}
- data SheetInfo = SheetInfo {}
- wiSheets :: Iso' WorkbookInfo [SheetInfo]
- getWorkbookInfo :: XlsxM WorkbookInfo
- type CellRow = IntMap Cell
- readSheet :: SheetIndex -> (SheetItem -> IO ()) -> XlsxM Bool
- countRowsInSheet :: SheetIndex -> XlsxM (Maybe Int)
- collectItems :: SheetIndex -> XlsxM [SheetItem]
- data SheetIndex
- makeIndex :: Int -> SheetIndex
- makeIndexFromName :: Text -> XlsxM (Maybe SheetIndex)
- data SheetItem = MkSheetItem {
- _si_sheet_index :: Int
- _si_row :: ~Row
- si_sheet_index :: Lens' SheetItem Int
- si_row :: Lens' SheetItem Row
- data Row = MkRow {}
- ri_row_index :: Lens' Row RowIndex
- ri_cell_row :: Lens' Row CellRow
- data SheetErrors
- data AddCellErrors
- data CoordinateErrors
- = CoordinateNotFound SheetValues
- | NoListElement SheetValue SheetValues
- | NoTextContent Content SheetValues
- | DecodeFailure Text SheetValues
- data TypeError
- = TypeNotFound SheetValues
- | TypeNoListElement SheetValue SheetValues
- | UnkownType Text SheetValues
- | TypeNoTextContent Content SheetValues
- data WorkbookError
- = LookupError {
- lookup_attrs :: [(ByteString, Text)]
- lookup_field :: ByteString
- | ParseDecimalError Text String
- = LookupError {
Documentation
Instances
MonadIO XlsxM Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
Applicative XlsxM Source # | |
Functor XlsxM Source # | |
Monad XlsxM Source # | |
MonadCatch XlsxM Source # | |
MonadMask XlsxM Source # | |
MonadThrow XlsxM Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
MonadBaseControl IO XlsxM Source # | |
MonadBase IO XlsxM Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
type StM XlsxM a Source # | |
Defined in Codec.Xlsx.Parser.Stream |
data WorkbookInfo Source #
Information about the workbook contained in xl/workbook.xml (currently a subset)
Instances
Show WorkbookInfo Source # | |
Defined in Codec.Xlsx.Parser.Stream showsPrec :: Int -> WorkbookInfo -> ShowS # show :: WorkbookInfo -> String # showList :: [WorkbookInfo] -> ShowS # |
Represents sheets from the workbook.xml file. E.g. <sheet name=Data sheetId="1" state="hidden" r:id="rId2" /
SheetInfo | |
|
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.
:: 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 SheetItem
s, 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
NFData SheetIndex Source # | |
Defined in Codec.Xlsx.Parser.Stream 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
Sheet item
The current sheet at a time, every sheet is constructed of these items.
MkSheetItem | |
|
Instances
Generic SheetItem Source # | |
Show SheetItem Source # | |
NFData SheetItem Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
type Rep SheetItem Source # | |
Defined in Codec.Xlsx.Parser.Stream type Rep SheetItem = D1 ('MetaData "SheetItem" "Codec.Xlsx.Parser.Stream" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" '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
MkRow | |
|
Instances
Generic Row Source # | |
Show Row Source # | |
NFData Row Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
type Rep Row Source # | |
Defined in Codec.Xlsx.Parser.Stream type Rep Row = D1 ('MetaData "Row" "Codec.Xlsx.Parser.Stream" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" '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 SheetErrors Source #
ParseCoordinateError CoordinateErrors | Error while parsing coordinates |
ParseTypeError TypeError | Error while parsing types |
ParseCellError AddCellErrors | Error while parsing cells |
ParseStyleErrors StyleError | |
HexpatParseError XMLParseError |
Instances
Exception SheetErrors Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
Show SheetErrors Source # | |
Defined in Codec.Xlsx.Parser.Stream showsPrec :: Int -> SheetErrors -> ShowS # show :: SheetErrors -> String # showList :: [SheetErrors] -> ShowS # |
data AddCellErrors Source #
ReadError | Could not read current cell value |
SharedStringsNotFound | Could not find string by index in shared string table |
Instances
Show AddCellErrors Source # | |
Defined in Codec.Xlsx.Parser.Stream showsPrec :: Int -> AddCellErrors -> ShowS # show :: AddCellErrors -> String # showList :: [AddCellErrors] -> ShowS # |
data CoordinateErrors Source #
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 |
DecodeFailure Text SheetValues | If malformed coordinate text was passed |
Instances
Exception CoordinateErrors Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
Show CoordinateErrors Source # | |
Defined in Codec.Xlsx.Parser.Stream showsPrec :: Int -> CoordinateErrors -> ShowS # show :: CoordinateErrors -> String # showList :: [CoordinateErrors] -> ShowS # |
TypeNotFound SheetValues | |
TypeNoListElement SheetValue SheetValues | |
UnkownType Text SheetValues | |
TypeNoTextContent Content SheetValues |
Instances
Exception TypeError Source # | |
Defined in Codec.Xlsx.Parser.Stream toException :: TypeError -> SomeException # fromException :: SomeException -> Maybe TypeError # displayException :: TypeError -> String # | |
Show TypeError Source # | |
data WorkbookError Source #
LookupError | |
| |
ParseDecimalError Text String |
Instances
Exception WorkbookError Source # | |
Defined in Codec.Xlsx.Parser.Stream | |
Show WorkbookError Source # | |
Defined in Codec.Xlsx.Parser.Stream showsPrec :: Int -> WorkbookError -> ShowS # show :: WorkbookError -> String # showList :: [WorkbookError] -> ShowS # |