Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hledger.Write.Spreadsheet
Description
Rich data type to describe data in a table. This is the basis for ODS and HTML export.
Synopsis
- data Type
- data Style
- data Emphasis
- data Cell border text = Cell {
- cellType :: Type
- cellBorder :: Border border
- cellStyle :: Style
- cellSpan :: Span
- cellAnchor :: Text
- cellClass :: Class
- cellContent :: text
- newtype Class = Class Text
- textFromClass :: Class -> Text
- data Span
- data Border lines = Border {
- borderLeft, borderRight, borderTop, borderBottom :: lines
- class Lines border where
- noLine :: border
- data NumLines
- noBorder :: Lines border => Border border
- defaultCell :: Lines border => text -> Cell border text
- headerCell :: Lines borders => Text -> Cell borders Text
- emptyCell :: (Lines border, Monoid text) => Cell border text
- transposeCell :: Cell border text -> Cell border text
- transpose :: [[Cell border text]] -> [[Cell border text]]
- horizontalSpan :: (Lines border, Monoid text) => [a] -> Cell border text -> [Cell border text]
- addHeaderBorders :: [Cell () text] -> [Cell NumLines text]
- addRowSpanHeader :: Cell border text -> [[Cell border text]] -> [[Cell border text]]
- rawTableContent :: [[Cell border text]] -> [[text]]
- cellFromMixedAmount :: Lines border => AmountFormat -> (Class, MixedAmount) -> Cell border WideBuilder
- cellsFromMixedAmount :: Lines border => AmountFormat -> (Class, MixedAmount) -> [Cell border WideBuilder]
- cellFromAmount :: Lines border => AmountFormat -> (Class, (wb, Amount)) -> Cell border wb
- integerCell :: Lines border => Integer -> Cell border Text
Documentation
Constructors
TypeString | |
TypeInteger | |
TypeAmount !Amount | |
TypeMixedAmount | |
TypeDate |
data Cell border text Source #
Constructors
Cell | |
Fields
|
textFromClass :: Class -> Text Source #
NoSpan
means a single unmerged cell.Covered
is a cell if it is part of a horizontally or vertically merged cell. We maintain these cells although they are ignored in HTML output. In contrast to that, FODS can store covered cells and allows to access the hidden cell content via formulas. CSV does not support merged cells and thus simply writes the content of covered cells. MaintainingCovered
cells also simplifies transposing.
denotes the first cell in a row that is part of a merged cell. The merged cell containsSpanHorizontal
nn
atomic cells, including the first one. That isSpanHorizontal 1
is actually likeNoSpan
. The content of this cell is shown as content of the merged cell.
starts a vertically merged cell.SpanVertical
n
The writer functions expect consistent data,
that is, Covered
cells must actually be part of a merged cell
and merged cells must only cover Covered
cells.
Constructors
NoSpan | |
Covered | |
SpanHorizontal Int | |
SpanVertical Int |
Constructors
Border | |
Fields
|
Instances
Foldable Border Source # | |
Defined in Hledger.Write.Spreadsheet Methods fold :: Monoid m => Border m -> m # foldMap :: Monoid m => (a -> m) -> Border a -> m # foldMap' :: Monoid m => (a -> m) -> Border a -> m # foldr :: (a -> b -> b) -> b -> Border a -> b # foldr' :: (a -> b -> b) -> b -> Border a -> b # foldl :: (b -> a -> b) -> b -> Border a -> b # foldl' :: (b -> a -> b) -> b -> Border a -> b # foldr1 :: (a -> a -> a) -> Border a -> a # foldl1 :: (a -> a -> a) -> Border a -> a # elem :: Eq a => a -> Border a -> Bool # maximum :: Ord a => Border a -> a # minimum :: Ord a => Border a -> a # | |
Applicative Border Source # | |
Functor Border Source # | |
Show lines => Show (Border lines) Source # | |
Eq lines => Eq (Border lines) Source # | |
Ord lines => Ord (Border lines) Source # | |
Defined in Hledger.Write.Spreadsheet |
The same as Tab.Properties, but has Eq
and Ord
instances.
We need those for storing NumLines
in Set
s.
Constructors
NoLine | |
SingleLine | |
DoubleLine |
defaultCell :: Lines border => text -> Cell border text Source #
transposeCell :: Cell border text -> Cell border text Source #
horizontalSpan :: (Lines border, Monoid text) => [a] -> Cell border text -> [Cell border text] Source #
rawTableContent :: [[Cell border text]] -> [[text]] Source #
cellFromMixedAmount :: Lines border => AmountFormat -> (Class, MixedAmount) -> Cell border WideBuilder Source #
cellsFromMixedAmount :: Lines border => AmountFormat -> (Class, MixedAmount) -> [Cell border WideBuilder] Source #
cellFromAmount :: Lines border => AmountFormat -> (Class, (wb, Amount)) -> Cell border wb Source #