clerk-0.1.0.1: Declaratively describe spreadsheets and generate xlsx
Safe HaskellSafe-Inferred
LanguageHaskell2010

Clerk

Synopsis

Documentation

data Builder input output a Source #

A builder

Instances

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

Defined in Clerk

Methods

get :: Builder input output Coords #

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

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

Applicative (Builder input output) Source # 
Instance details

Defined in Clerk

Methods

pure :: a -> Builder input output a #

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

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

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

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

Functor (Builder input output) Source # 
Instance details

Defined in Clerk

Methods

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

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

Monad (Builder input output) Source # 
Instance details

Defined in Clerk

Methods

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

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

return :: a -> Builder input output a #

data Cell a Source #

Coordinates of a cell with a given phantom type

Instances

Instances details
Functor Cell Source # 
Instance details

Defined in Clerk

Methods

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

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

Num (Cell a) Source # 
Instance details

Defined in Clerk

Methods

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

(-) :: Cell a -> Cell a -> Cell a #

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

negate :: Cell a -> Cell a #

abs :: Cell a -> Cell a #

signum :: Cell a -> Cell a #

fromInteger :: Integer -> Cell a #

data CellData Source #

A union of some Cell components

Instances

Instances details
ToCellData CellData Source # 
Instance details

Defined in Clerk

data Coords Source #

Coords of a cell

Constructors

Coords Int Int 

Instances

Instances details
Num Coords Source # 
Instance details

Defined in Clerk

Show Coords Source # 
Instance details

Defined in Clerk

MonadState Coords (Builder input output) Source # 
Instance details

Defined in Clerk

Methods

get :: Builder input output Coords #

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

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

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

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

class ToCellData a Source #

Minimal complete definition

toCellData

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

Methods

toCellData :: Bool -> CellData

ToCellData Double Source # 
Instance details

Defined in Clerk

ToCellData Int Source # 
Instance details

Defined in Clerk

Methods

toCellData :: Int -> CellData

ToCellData (Expr a) Source # 
Instance details

Defined in Clerk

Methods

toCellData :: Expr a -> CellData

newtype SheetBuilder a Source #

Top monad to compose the results of Builders

Constructors

SheetBuilder 

Fields

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

column :: ToCellData output => FormatCell -> (input -> output) -> Builder input CellData (Cell a) Source #

Produce a column with a given style and get a cell

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

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

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

Produce a column with a given style

ex :: Cell a -> Expr a Source #

Convert a typed cell to an expression

ex' :: forall b a. Expr a -> Expr b Source #

Change phantom type of an Expr

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

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

(|+|) :: Num a => Expr a -> Expr a -> Expr a infixl 6 Source #

Assemble an addition expression

(|-|) :: Num a => Expr a -> Expr a -> Expr a infixl 6 Source #

Assemble a subtraction expression

(|*|) :: Num a => Expr a -> Expr a -> Expr a infixl 6 Source #

Assemble a multiplication expression

(|/|) :: Num a => Expr a -> Expr a -> Expr a infixl 7 Source #

Assemble a division expression

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

Assemble a range expression

(|^|) :: Num a => Expr a -> Expr a -> Expr a infixr 8 Source #

Assemble a multiplication expression

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

Assemble a function expression

data Expr t Source #

Formula expressions

Constructors

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

Instances

Instances details
Functor Expr Source # 
Instance details

Defined in Clerk

Methods

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

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

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

Methods

toCellData :: Expr a -> CellData