Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Builder input output a
- data Cell a
- data CellData
- data Coords = Coords Int Int
- type FCTransform = FormattedCell -> FormattedCell
- type FormatCell = Coords -> Index -> CellData -> FormattedCell
- class ToCellData a
- newtype SheetBuilder a = SheetBuilder {
- unSheetBuilder :: Writer Transform a
- column :: ToCellData output => FormatCell -> (input -> output) -> Builder input CellData (Cell a)
- columnWidth :: ToCellData output => Double -> FormatCell -> (input -> output) -> Builder input CellData (Cell a)
- columnWidth_ :: ToCellData output => Double -> FormatCell -> (input -> output) -> Builder input CellData ()
- column_ :: ToCellData output => FormatCell -> (input -> output) -> Builder input CellData ()
- composeXlsx :: [(Text, SheetBuilder ())] -> Xlsx
- ex :: Cell a -> Expr a
- ex' :: forall b a. Expr a -> Expr b
- horizontalAlignment :: CellHorizontalAlignment -> FCTransform
- mkColorStyle :: Text -> FormatCell
- overCol :: (Int -> Int) -> Coords -> Coords
- overRow :: (Int -> Int) -> Coords -> Coords
- placeInput :: ToCellData output => Coords -> input -> Builder input output a -> SheetBuilder a
- placeInputs_ :: ToCellData output => Coords -> [input] -> Builder input output a -> SheetBuilder ()
- (|+|) :: Num a => Expr a -> Expr a -> Expr a
- (|-|) :: Num a => Expr a -> Expr a -> Expr a
- (|*|) :: Num a => Expr a -> Expr a -> Expr a
- (|/|) :: Num a => Expr a -> Expr a -> Expr a
- (|:|) :: Cell a -> Cell b -> Expr c
- (|^|) :: Num a => Expr a -> Expr a -> Expr a
- (|$|) :: ToExpr a => String -> [a] -> Expr t
- (<|) :: FCTransform -> FormatCell -> FormatCell
- data Expr t
Documentation
data Builder input output a Source #
A builder
Instances
MonadState Coords (Builder input output) Source # | |
Applicative (Builder input output) Source # | |
Defined in Clerk 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 # | |
Monad (Builder input output) Source # | |
Coordinates of a cell with a given phantom type
A union of some Cell components
Instances
ToCellData CellData Source # | |
Defined in Clerk toCellData :: CellData -> CellData |
Coords of a cell
type FCTransform = FormattedCell -> FormattedCell Source #
type FormatCell = Coords -> Index -> CellData -> FormattedCell Source #
Format a single cell depending on its coordinates, index, and data
class ToCellData a Source #
toCellData
Instances
ToCellData CellData Source # | |
Defined in Clerk toCellData :: CellData -> CellData | |
ToCellData String Source # | |
Defined in Clerk toCellData :: String -> CellData | |
ToCellData Bool Source # | |
Defined in Clerk toCellData :: Bool -> CellData | |
ToCellData Double Source # | |
Defined in Clerk toCellData :: Double -> CellData | |
ToCellData Int Source # | |
Defined in Clerk toCellData :: Int -> CellData | |
ToCellData (Expr a) Source # | |
Defined in Clerk toCellData :: Expr a -> CellData |
newtype SheetBuilder a Source #
Top monad to compose the results of Builders
SheetBuilder | |
|
Instances
Applicative SheetBuilder Source # | |
Defined in Clerk pure :: a -> SheetBuilder a # (<*>) :: SheetBuilder (a -> b) -> SheetBuilder a -> SheetBuilder b # liftA2 :: (a -> b -> c) -> SheetBuilder a -> SheetBuilder b -> SheetBuilder c # (*>) :: SheetBuilder a -> SheetBuilder b -> SheetBuilder b # (<*) :: SheetBuilder a -> SheetBuilder b -> SheetBuilder a # | |
Functor SheetBuilder Source # | |
Defined in Clerk fmap :: (a -> b) -> SheetBuilder a -> SheetBuilder b # (<$) :: a -> SheetBuilder b -> SheetBuilder a # | |
Monad SheetBuilder Source # | |
Defined in Clerk (>>=) :: SheetBuilder a -> (a -> SheetBuilder b) -> SheetBuilder b # (>>) :: SheetBuilder a -> SheetBuilder b -> SheetBuilder b # return :: a -> SheetBuilder a # |
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
composeXlsx :: [(Text, SheetBuilder ())] -> Xlsx Source #
mkColorStyle :: Text -> FormatCell Source #
placeInput :: ToCellData output => Coords -> input -> Builder input output a -> SheetBuilder a Source #
placeInputs_ :: ToCellData output => Coords -> [input] -> Builder input output a -> SheetBuilder () Source #
(<|) :: FCTransform -> FormatCell -> FormatCell infixl 5 Source #
Formula expressions
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) |