HExcel: Create Excel files with Haskell

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Easily create Excel files with Haskell. See README at https://github.com/green-lambda/HExcel


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.0.0, 0.1.0.1
Change log CHANGELOG.md
Dependencies base (>=4.5 && <4.13), microlens, microlens-th, time, transformers [details]
License BSD-3-Clause
Author Sasha Bogicevic
Maintainer sasa.bogicevic@pm.me
Category Data, Text, SpreadSheet
Uploaded by v0d1ch at 2019-06-24T19:55:18Z

Modules

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for HExcel-0.1.0.0

[back to package description]

HExcel

Create Excel files with Haskell

This is a fork of libxlsxwriter that tries the improve on the api and provide a library for creation of Excel files. Underneath the hood it uses C library called libxlsxwriter and provides bindings to C code to produce Excel 2007+ xlsx files.

Example

{-# 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"
		 -- or 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