HExcel-0.1.0.0: Create Excel files with Haskell

MaintainerSasha Bogicevic <sasa.bogicevic@pm.me>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

HExcel

Description

Module exports

Example usage:

{-# LANGUAGE TypeApplications #-}
module Main where

import Control.Monad.Trans.State (execStateT)
import Control.Monad (forM_)
import Data.Time (getZonedTime)
import HExcel

main :: IO ()
main = do
  wb <- workbookNew "test.xlsx"
  let props = mkDocProperties
        { docPropertiesTitle   = "Test Workbook"
        , docPropertiesCompany = "HExcel"
        }
  workbookSetProperties wb props
  ws <- workbookAddWorksheet wb "First Sheet"
  df <- workbookAddFormat wb
  formatSetNumFormat df "mmm d yyyy hh:mm AM/PM"
  now <- getZonedTime
  -- You can create HExcelState which is convenient api for writing to cells
  let initState = HExcelState Nothing ws 4 1 0 1 0
  _ <- flip execStateT initState $ do
         writeCell "David"
         writeCell "Dimitrije"
         -- we can skip some rows
         skipRows 1
         writeCell "Jovana"
         -- skip some columns
         skipCols 1
         writeCell (zonedTimeToDateTime now)
         writeCell @Double 42.5

  -- or use functions that run in plain IO
  forM_ [5 .. 8] $ \n -> do
    writeString ws Nothing n 3 "xxx"
    writeNumber ws Nothing n 4 1234.56
    writeDateTime ws (Just df) n 5 (zonedTimeToDateTime now)
  workbookClose wb
Synopsis

Documentation

data Workbook Source #

Excel Workbook

workbookNew :: FilePath -> IO Workbook Source #

Create new workbook

workbookNewConstantMem :: FilePath -> IO Workbook Source #

Create new workbook but force constant memory. It reduces the amount of data stored in memory so that large files can be written efficiently.

workbookClose :: Workbook -> IO () Source #

Close the workbook

workbookAddFormat :: Workbook -> IO Format Source #

Add workbook format

workbookDefineName :: Workbook -> String -> String -> IO () Source #

Set workbook name

workbookSetProperties :: Workbook -> DocProperties -> IO () Source #

Set workbook properties

data Worksheet Source #

Excel WorkSheet

type Row = Word32 Source #

Excel Row

type Col = Word16 Source #

Excel Column

writeNumber :: Worksheet -> Maybe Format -> Row -> Col -> Double -> IO () Source #

Write a Double value to Excel cell

writeString :: Worksheet -> Maybe Format -> Row -> Col -> String -> IO () Source #

Write a String value to Excel cell

writeUTCTime :: Worksheet -> Maybe Format -> Row -> Col -> UTCTime -> IO () Source #

Write a UTCTime value to Excel cell

writeFormula :: Worksheet -> Maybe Format -> Row -> Col -> String -> IO () Source #

Write a formula to Excel cell

data DateTime Source #

Type to hold datetime values

Constructors

DateTime 
Instances
Show DateTime Source # 
Instance details

Defined in HExcel.Types

Storable DateTime Source # 
Instance details

Defined in HExcel.Types

HExcel DateTime Source # 
Instance details

Defined in HExcel.HExcelInternal

utcTimeToDateTime :: UTCTime -> DateTime Source #

Helper function to convert UTCTime to DateTime

zonedTimeToDateTime :: ZonedTime -> DateTime Source #

Helper function to convert ZonedTime to DateTime

writeDateTime :: Worksheet -> Maybe Format -> Row -> Col -> DateTime -> IO () Source #

Write a DateTime to Excel cell

writeUrl :: Worksheet -> Maybe Format -> Row -> Col -> String -> IO () Source #

Write a url to Excel cell

worksheetSetRow :: Worksheet -> Maybe Format -> Row -> Double -> IO () Source #

Set worksheet row

worksheetSetColumn :: Worksheet -> Maybe Format -> Col -> Col -> Double -> IO () Source #

Set worksheet column

worksheetInsertImage :: Worksheet -> Word32 -> Word16 -> String -> IO () Source #

Insert image to worksheet

worksheetMergeRange :: Worksheet -> Maybe Format -> Row -> Col -> Row -> Col -> String -> IO () Source #

Merge columns

worksheetSetLandscape :: Worksheet -> IO () Source #

Set worksheet to Landscape

worksheetSetPortrait :: Worksheet -> IO () Source #

Set worksheet to Portrait

data PaperSize Source #

Paper size

Instances
Eq PaperSize Source # 
Instance details

Defined in HExcel.Types

skipCols :: MonadIO m => Word16 -> StateT HExcelState m () Source #

Skip a number of columns

skipRows :: MonadIO m => Word32 -> StateT HExcelState m () Source #

Skip a number of rows

worksheetSetMargins :: Worksheet -> Double -> Double -> Double -> Double -> IO () Source #

Set worksheet margins

data Format Source #

Excel Format

formatSetFontName :: Format -> String -> IO () Source #

Set font name

formatSetFontSize :: Format -> Word16 -> IO () Source #

Set font size

formatSetFontColor :: Format -> Color -> IO () Source #

Set font color

formatSetNumFormat :: Format -> String -> IO () Source #

Set number format

formatSetBold :: Format -> IO () Source #

Set bold style

formatSetItalic :: Format -> IO () Source #

Set italic style

formatSetUnderline :: Format -> UnderlineStyle -> IO () Source #

Set underline style

data Align Source #

Alignment styles

Instances
Enum Align Source # 
Instance details

Defined in HExcel.Types

Eq Align Source # 
Instance details

Defined in HExcel.Types

Methods

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

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

Read Align Source # 
Instance details

Defined in HExcel.Types

Show Align Source # 
Instance details

Defined in HExcel.Types

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

data Border Source #

Border options

Instances
Eq Border Source # 
Instance details

Defined in HExcel.Types

Methods

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

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

Read Border Source # 
Instance details

Defined in HExcel.Types

Show Border Source # 
Instance details

Defined in HExcel.Types

data HExcelState Source #

HExcelState is the state we thread trough for the writeCell function of the HExcel typeclass. We are trying to create a convenient api for writing cell values without too much hassle.

Constructors

HExcelState 

Fields

class HExcel a where Source #

HExcel class that provides a single function writeCell as a convenient method of writing excel cell values

Methods

writeCell :: MonadIO m => a -> StateT HExcelState m () Source #

Instances
HExcel Double Source # 
Instance details

Defined in HExcel.HExcelInternal

HExcel Float Source # 
Instance details

Defined in HExcel.HExcelInternal

HExcel Int Source # 
Instance details

Defined in HExcel.HExcelInternal

Methods

writeCell :: MonadIO m => Int -> StateT HExcelState m () Source #

HExcel Integer Source # 
Instance details

Defined in HExcel.HExcelInternal

HExcel Word Source # 
Instance details

Defined in HExcel.HExcelInternal

HExcel String Source # 
Instance details

Defined in HExcel.HExcelInternal

HExcel UTCTime Source # 
Instance details

Defined in HExcel.HExcelInternal

HExcel DateTime Source # 
Instance details

Defined in HExcel.HExcelInternal