hledger-lib-1.42.1: A library providing the core functionality of hledger
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hledger.Write.Spreadsheet

Description

Rich data type to describe data in a table. This is the basis for ODS and HTML export.

Synopsis

Documentation

data Type Source #

Instances

Instances details
Show Type Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

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

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

Ord Type Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

data Style Source #

Constructors

Body Emphasis 
Head 

Instances

Instances details
Show Style Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Eq Style Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

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

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

Ord Style Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

compare :: Style -> Style -> Ordering #

(<) :: Style -> Style -> Bool #

(<=) :: Style -> Style -> Bool #

(>) :: Style -> Style -> Bool #

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

max :: Style -> Style -> Style #

min :: Style -> Style -> Style #

data Emphasis Source #

Constructors

Item 
Total 

Instances

Instances details
Show Emphasis Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Eq Emphasis Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Ord Emphasis Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

data Cell border text Source #

Constructors

Cell 

Instances

Instances details
Functor (Cell border) Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

fmap :: (a -> b) -> Cell border a -> Cell border b #

(<$) :: a -> Cell border b -> Cell border a #

newtype Class Source #

Constructors

Class Text 

data Span 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. Maintaining Covered cells also simplifies transposing.
  • SpanHorizontal n denotes the first cell in a row that is part of a merged cell. The merged cell contains n atomic cells, including the first one. That is SpanHorizontal 1 is actually like NoSpan. The content of this cell is shown as content of the merged cell.
  • SpanVertical n starts a vertically merged cell.

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.

Instances

Instances details
Eq Span Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

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

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

data Border lines Source #

Constructors

Border 

Instances

Instances details
Foldable Border Source # 
Instance details

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 #

toList :: Border a -> [a] #

null :: Border a -> Bool #

length :: Border a -> Int #

elem :: Eq a => a -> Border a -> Bool #

maximum :: Ord a => Border a -> a #

minimum :: Ord a => Border a -> a #

sum :: Num a => Border a -> a #

product :: Num a => Border a -> a #

Applicative Border Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

pure :: a -> Border a #

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

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

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

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

Functor Border Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

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

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

Show lines => Show (Border lines) Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

showsPrec :: Int -> Border lines -> ShowS #

show :: Border lines -> String #

showList :: [Border lines] -> ShowS #

Eq lines => Eq (Border lines) Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

(==) :: Border lines -> Border lines -> Bool #

(/=) :: Border lines -> Border lines -> Bool #

Ord lines => Ord (Border lines) Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

compare :: Border lines -> Border lines -> Ordering #

(<) :: Border lines -> Border lines -> Bool #

(<=) :: Border lines -> Border lines -> Bool #

(>) :: Border lines -> Border lines -> Bool #

(>=) :: Border lines -> Border lines -> Bool #

max :: Border lines -> Border lines -> Border lines #

min :: Border lines -> Border lines -> Border lines #

class Lines border where Source #

Methods

noLine :: border Source #

Instances

Instances details
Lines NumLines Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Lines () Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Methods

noLine :: () Source #

data NumLines Source #

The same as Tab.Properties, but has Eq and Ord instances. We need those for storing NumLines in Sets.

Constructors

NoLine 
SingleLine 
DoubleLine 

Instances

Instances details
Show NumLines Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Eq NumLines Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Ord NumLines Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

Lines NumLines Source # 
Instance details

Defined in Hledger.Write.Html.HtmlCommon

Lines NumLines Source # 
Instance details

Defined in Hledger.Write.Spreadsheet

noBorder :: Lines border => Border border Source #

defaultCell :: Lines border => text -> Cell border text Source #

headerCell :: Lines borders => Text -> Cell borders Text Source #

emptyCell :: (Lines border, Monoid text) => Cell border text Source #

transposeCell :: Cell border text -> Cell border text Source #

transpose :: [[Cell border text]] -> [[Cell border text]] Source #

horizontalSpan :: (Lines border, Monoid text) => [a] -> Cell border text -> [Cell border text] Source #

addHeaderBorders :: [Cell () text] -> [Cell NumLines text] Source #

addRowSpanHeader :: Cell border text -> [[Cell border text]] -> [[Cell border text]] Source #

rawTableContent :: [[Cell border text]] -> [[text]] Source #

cellFromAmount :: Lines border => AmountFormat -> (Class, (wb, Amount)) -> Cell border wb Source #

integerCell :: Lines border => Integer -> Cell border Text Source #