clerk-0.1.0.3: Declaratively describe spreadsheets
Safe HaskellSafe-Inferred
LanguageHaskell2010

Clerk

Description

Clerk library

Synopsis

Coords

 

data Coords Source #

Coords of a cell

Constructors

Coords 

Fields

Instances

Instances details
Num Coords Source # 
Instance details

Defined in Clerk

Show Coords Source # 
Instance details

Defined in Clerk

ToExpr Coords Source # 
Instance details

Defined in Clerk

Methods

toExpr :: Coords -> Expr t Source #

MonadState Coords (RowBuilder input output) Source # 
Instance details

Defined in Clerk

Methods

get :: RowBuilder input output Coords #

put :: Coords -> RowBuilder input output () #

state :: (Coords -> (a, Coords)) -> RowBuilder input output a #

Cell references

{- FOURMOLU_ENABLE -}

newtype CellRef a Source #

A typed reference to a cell.

The user is responsible for setting the necessary cell type.

The type prevents operations between cell references with incompatible types.

>>> str = CellRef (Coords 1 1) :: CellRef String
>>> str |+| str
No instance for (Num String) arising from a use of ‘|+|’

When necessary, the user may change the cell reference type via unsafeChangeCellRefType

>>> int = CellRef (Coords 1 1) :: CellRef Int
>>> double = CellRef (Coords 2 5) :: CellRef Double
>>> unsafeChangeCellRefType int |+| double
A1+E2

Constructors

CellRef 

Fields

Instances

Instances details
Num (CellRef a) Source # 
Instance details

Defined in Clerk

Methods

(+) :: CellRef a -> CellRef a -> CellRef a #

(-) :: CellRef a -> CellRef a -> CellRef a #

(*) :: CellRef a -> CellRef a -> CellRef a #

negate :: CellRef a -> CellRef a #

abs :: CellRef a -> CellRef a #

signum :: CellRef a -> CellRef a #

fromInteger :: Integer -> CellRef a #

ToExpr (CellRef a) Source # 
Instance details

Defined in Clerk

Methods

toExpr :: CellRef a -> Expr t Source #

getCol :: CellRef a -> Int Source #

Get a column number from a CellRef

getRow :: CellRef a -> Int Source #

Get a row number from a CellRef

overCol :: (Int -> Int) -> Coords -> Coords Source #

Apply a function over a column of a coordinate

overRow :: (Int -> Int) -> Coords -> Coords Source #

Apply a function over a row of a coordinate

unsafeChangeCellRefType :: forall b a. CellRef a -> CellRef b Source #

Change the type of a cell reference. Use with caution!

The type variables in the forall clause are swapped for the conveniece of type applications

Cell formatting

 

type InputIndex = Int Source #

Index of an input

type FormatCell = Coords -> InputIndex -> CellData -> FormattedCell Source #

Format a single cell depending on its coordinates, index, and data

data CellTemplate input output Source #

Template of a cell with contents, style, column properties

type FormattedMap = Map (RowIndex, ColumnIndex) FormattedCell Source #

Map of coordinates to cell formatting

type FMTransform = FormattedMap -> FormattedMap Source #

Transform of a map that maps coordinates to cell formatting

type WSTransform = Worksheet -> Worksheet Source #

Transform of a worksheet

data Transform Source #

Combined: a transform of a map of formats and a transform of a worksheet

Instances

Instances details
Monoid Transform Source # 
Instance details

Defined in Clerk

Semigroup Transform Source # 
Instance details

Defined in Clerk

Default Transform Source # 
Instance details

Defined in Clerk

Methods

def :: Transform #

MonadWriter Transform SheetBuilder Source # 
Instance details

Defined in Clerk

type FCTransform = FormattedCell -> FormattedCell Source #

Transform of a formatted cell

horizontalAlignment :: CellHorizontalAlignment -> FCTransform Source #

Get a FCTransform with a given horizontal alignment in a cell

mkColorStyle :: Show a => a -> FormatCell Source #

Make a FormatCell for a single color

show on the input should translate into an ARGB color. See Color

Templates

 

newtype RowBuilder input output a Source #

Allows to describe how to build a template for a row

Constructors

RowBuilder 

Fields

Instances

Instances details
MonadState Coords (RowBuilder input output) Source # 
Instance details

Defined in Clerk

Methods

get :: RowBuilder input output Coords #

put :: Coords -> RowBuilder input output () #

state :: (Coords -> (a, Coords)) -> RowBuilder input output a #

Applicative (RowBuilder input output) Source # 
Instance details

Defined in Clerk

Methods

pure :: a -> RowBuilder input output a #

(<*>) :: RowBuilder input output (a -> b) -> RowBuilder input output a -> RowBuilder input output b #

liftA2 :: (a -> b -> c) -> RowBuilder input output a -> RowBuilder input output b -> RowBuilder input output c #

(*>) :: RowBuilder input output a -> RowBuilder input output b -> RowBuilder input output b #

(<*) :: RowBuilder input output a -> RowBuilder input output b -> RowBuilder input output a #

Functor (RowBuilder input output) Source # 
Instance details

Defined in Clerk

Methods

fmap :: (a -> b) -> RowBuilder input output a -> RowBuilder input output b #

(<$) :: a -> RowBuilder input output b -> RowBuilder input output a #

Monad (RowBuilder input output) Source # 
Instance details

Defined in Clerk

Methods

(>>=) :: RowBuilder input output a -> (a -> RowBuilder input output b) -> RowBuilder input output b #

(>>) :: RowBuilder input output a -> RowBuilder input output b -> RowBuilder input output b #

return :: a -> RowBuilder input output a #

MonadWriter (Template input output) (RowBuilder input output) Source # 
Instance details

Defined in Clerk

Methods

writer :: (a, Template input output) -> RowBuilder input output a #

tell :: Template input output -> RowBuilder input output () #

listen :: RowBuilder input output a -> RowBuilder input output (a, Template input output) #

pass :: RowBuilder input output (a, Template input output -> Template input output) -> RowBuilder input output a #

newtype Template input output Source #

Template for multiple cells

Constructors

Template [CellTemplate input output] 

Instances

Instances details
Monoid (Template input output) Source # 
Instance details

Defined in Clerk

Methods

mempty :: Template input output #

mappend :: Template input output -> Template input output -> Template input output #

mconcat :: [Template input output] -> Template input output #

Semigroup (Template input output) Source # 
Instance details

Defined in Clerk

Methods

(<>) :: Template input output -> Template input output -> Template input output #

sconcat :: NonEmpty (Template input output) -> Template input output #

stimes :: Integral b => b -> Template input output -> Template input output #

MonadWriter (Template input output) (RowBuilder input output) Source # 
Instance details

Defined in Clerk

Methods

writer :: (a, Template input output) -> RowBuilder input output a #

tell :: Template input output -> RowBuilder input output () #

listen :: RowBuilder input output a -> RowBuilder input output (a, Template input output) #

pass :: RowBuilder input output (a, Template input output -> Template input output) -> RowBuilder input output a #

Columns

 

newtype ColumnsProperties Source #

Properties of a column

Instances

Instances details
Default ColumnsProperties Source # 
Instance details

Defined in Clerk

columnWidthCell :: forall a input output. Maybe Double -> FormatCell -> (input -> output) -> RowBuilder input output (CellRef a) Source #

A column with a possibly given width and cell format. Returns a cell reference

columnWidth :: ToCellData output => Double -> FormatCell -> (input -> output) -> RowBuilder input CellData (CellRef a) Source #

A column with a given width and cell format. Returns a cell reference

columnWidth_ :: ToCellData output => Double -> FormatCell -> (input -> output) -> RowBuilder input CellData () Source #

A column with a given width and cell format

column :: ToCellData output => FormatCell -> (input -> output) -> RowBuilder input CellData (CellRef a) Source #

A column with a given cell format. Returns a cell reference

column_ :: ToCellData output => FormatCell -> (input -> output) -> RowBuilder input CellData () Source #

A column with a given cell format

Sheet builder

 

newtype SheetBuilder a Source #

A builder to compose the results of RowBuilders

Constructors

SheetBuilder 

Instances

Instances details
Applicative SheetBuilder Source # 
Instance details

Defined in Clerk

Functor SheetBuilder Source # 
Instance details

Defined in Clerk

Methods

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

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

Monad SheetBuilder Source # 
Instance details

Defined in Clerk

MonadWriter Transform SheetBuilder Source # 
Instance details

Defined in Clerk

placeInputs :: ToCellData output => Coords -> [input] -> RowBuilder input output a -> SheetBuilder a Source #

Starting at given coordinates, place rows of data made from a list of inputs according to a row builder. Return the result of the row builder.

placeInputs_ :: ToCellData output => Coords -> [input] -> RowBuilder input output a -> SheetBuilder () Source #

Starting at given coordinates, place rows of data made from a list of inputs according to a row builder.

placeInput :: ToCellData output => Coords -> input -> RowBuilder input output a -> SheetBuilder a Source #

Starting at given coordinates, place a row of data made from a single input according to a row builder. Return the result of the row builder.

placeInput_ :: ToCellData output => Coords -> input -> RowBuilder input output a -> SheetBuilder () Source #

Starting at given coordinates, place a row of data made from a single input according to a row builder.

Expressions

 

data Expr t Source #

Expression syntax

Constructors

Add (Expr t) (Expr t) 
Sub (Expr t) (Expr t) 
Mul (Expr t) (Expr t) 
Div (Expr t) (Expr t) 
Power (Expr t) (Expr t) 
Function String [Expr t] 
Range (Expr t) (Expr t) 
ExprCell (CellRef t) 

Instances

Instances details
Show (Expr t) Source # 
Instance details

Defined in Clerk

Methods

showsPrec :: Int -> Expr t -> ShowS #

show :: Expr t -> String #

showList :: [Expr t] -> ShowS #

ToCellData (Expr a) Source # 
Instance details

Defined in Clerk

ToExpr (Expr a) Source # 
Instance details

Defined in Clerk

Methods

toExpr :: Expr a -> Expr t Source #

class ToExpr v where Source #

Something that can be turned into an expression

Methods

toExpr :: v -> Expr t Source #

Instances

Instances details
ToExpr Coords Source # 
Instance details

Defined in Clerk

Methods

toExpr :: Coords -> Expr t Source #

ToExpr (CellRef a) Source # 
Instance details

Defined in Clerk

Methods

toExpr :: CellRef a -> Expr t Source #

ToExpr (Expr a) Source # 
Instance details

Defined in Clerk

Methods

toExpr :: Expr a -> Expr t Source #

type ArithmeticOperator a b c = (Num a, ToExpr (b a), ToExpr (c a)) => b a -> c a -> Expr a Source #

A type for arithmetic operators

(|+|) :: ArithmeticOperator a b c infixl 6 Source #

Assemble an addition expression

(|-|) :: ArithmeticOperator a b c infixl 6 Source #

Assemble a subtraction expression

(|*|) :: ArithmeticOperator a b c infixl 6 Source #

Assemble a multiplication expression

(|/|) :: ArithmeticOperator a b c infixl 7 Source #

Assemble a division expression

(|:|) :: CellRef a -> CellRef b -> Expr c infixr 5 Source #

Assemble a range expression

(|^|) :: ArithmeticOperator a b c infixr 8 Source #

Assemble a multiplication expression

(|$|) :: ToExpr a => String -> [a] -> Expr t infixr 0 Source #

Assemble a function expression

(+>) :: FormatCell -> FCTransform -> FormatCell infixl 5 Source #

Apply FCTransform to a FormatCell to get a new FormatCell

Cells

 

data CellData Source #

A union of what can be inside a cell

Instances

Instances details
ToCellData CellData Source # 
Instance details

Defined in Clerk

class ToCellData a where Source #

Something that can be turned into CellData

Methods

toCellData :: a -> CellData Source #

Instances

Instances details
ToCellData CellData Source # 
Instance details

Defined in Clerk

ToCellData String Source # 
Instance details

Defined in Clerk

ToCellData Bool Source # 
Instance details

Defined in Clerk

ToCellData Double Source # 
Instance details

Defined in Clerk

ToCellData Int Source # 
Instance details

Defined in Clerk

ToCellData (Expr a) Source # 
Instance details

Defined in Clerk

Produce xlsx

 

composeXlsx :: [(Text, SheetBuilder ())] -> Xlsx Source #

Compose an xlsx from a list of sheet names and builders