Copyright | (c) Olaf Klinke |
---|---|
License | GPL-3 |
Maintainer | olaf.klinke@phymetric.de |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Various formats for spreadsheet exist, e.g. the open office (xlsx) format, the Microsoft SpreadsheetML format, the binary Microsoft xls format and CSV.
This module defines the least common denominator of static cell data.
The intention is to use chunks of rows as alternative representation type
in your ProvenienceT transformer.
After performing the computation, extract all the spreasheet chunks
and combine into a worksheet using chunksToSheet
.
For example, in order to use the types of the xlsx package
which exports the Cell
and CellMap
types, you should provide the following instances.
instance ToCell Cell where instance ToSheetStaticRow
CellMap where rowMap = Data.Map.fromList . foldMap (\(rowidx,row) -> map (\(colidx,val) -> ((fromIntegral rowidx,fromIntegral colidx),staticCell
val)) row)
where the first instance aids in writing the second instance.
Then you can use SheetChunk
as alternative representation and
produce a CellMap
using chunksToSheet
.
Synopsis
- class ToCell cell where
- staticCell :: StaticCellValue -> cell
- class ToRow cell row where
- cellList :: Traversable f => f cell -> row
- cellMap :: Traversable f => f (Word64, cell) -> row
- class ToSheet row sheet where
- rowList :: Traversable f => f row -> sheet
- rowMap :: Traversable f => f (Word64, row) -> sheet
- data StaticCellValue
- cellBool :: ToCell cell => Bool -> cell
- cellNumber :: ToCell cell => Rational -> cell
- cellText :: ToCell cell => String -> cell
- cellTime :: ToCell cell => ZonedTime -> cell
- type StaticRow = [(Word64, StaticCellValue)]
- type StaticSheet = [(Word64, StaticRow)]
- type SheetChunk = Seq StaticRow
- chunksToSheet :: (Traversable f, Traversable chunk, Monoid (chunk (Word64, row)), ToSheet row sheet) => f (chunk row) -> sheet
Speadsheet type classes
class ToCell cell where Source #
Cell type supporting static values: Booleans, Numbers, Text and Time.
staticCell :: StaticCellValue -> cell Source #
Instances
ToCell Text Source # | for building CSV data |
Defined in Data.Spreadsheet staticCell :: StaticCellValue -> Text Source # | |
ToCell StaticCellValue Source # | |
Defined in Data.Spreadsheet |
class ToRow cell row where Source #
A row
holding several cell
s
cellList :: Traversable f => f cell -> row Source #
default is to number consecutively from 1
cellMap :: Traversable f => f (Word64, cell) -> row Source #
Instances
ToRow Text Text Source # | separates cells with semicolons |
Defined in Data.Spreadsheet | |
ToRow StaticCellValue Text Source # | |
Defined in Data.Spreadsheet cellList :: Traversable f => f StaticCellValue -> Text Source # cellMap :: Traversable f => f (Word64, StaticCellValue) -> Text Source # | |
ToRow cell [(Word64, cell)] Source # | |
Defined in Data.Spreadsheet |
class ToSheet row sheet where Source #
A worksheet sheet
holding several row
s.
Assemble a worksheet from cells using e.g. either of
import Control.Arrow (second)rowMap
.fmap
(secondcellMap
)rowList
.fmap
cellList
rowList :: Traversable f => f row -> sheet Source #
default is to number consecutively from 1
rowMap :: Traversable f => f (Word64, row) -> sheet Source #
Concrete spreadsheet types
data StaticCellValue Source #
A static cell value, the initial object of the ToCell
class.
Instances
Show StaticCellValue Source # | |
Defined in Data.Spreadsheet showsPrec :: Int -> StaticCellValue -> ShowS # show :: StaticCellValue -> String # showList :: [StaticCellValue] -> ShowS # | |
ToCell StaticCellValue Source # | |
Defined in Data.Spreadsheet | |
ToRow StaticCellValue Text Source # | |
Defined in Data.Spreadsheet cellList :: Traversable f => f StaticCellValue -> Text Source # cellMap :: Traversable f => f (Word64, StaticCellValue) -> Text Source # |
cellNumber :: ToCell cell => Rational -> cell Source #
type StaticRow = [(Word64, StaticCellValue)] Source #
generic row type: list of cells with column numbers
type StaticSheet = [(Word64, StaticRow)] Source #
generic sheet type: list of rows with row numbers
type SheetChunk = Seq StaticRow Source #
Part of a spreadsheet which does not yet know its absolute row numbers.
chunksToSheet :: (Traversable f, Traversable chunk, Monoid (chunk (Word64, row)), ToSheet row sheet) => f (chunk row) -> sheet Source #
Combine several chunks into a worksheet, e.g.
chunksToSheet
:: [SheetChunk
] ->StaticSheet