xlsx-0.1.0: Simple and incomplete Excel file parser/writer

Safe HaskellNone

Codec.Xlsx

Description

This module provides solution for parsing and writing MIcrosoft Open Office XML Workbook format i.e. *.xlsx files

As a simple example you could read cell B3 from the 1st sheet of workbook "report.xlsx" using the following code:

 {-# LANGUAGE OverloadedStrings #-}
 module Read where
 import Codec.Xlsx
 import qualified Data.ByteString.Lazy as L
 import Control.Lens

 main :: IO ()
 main = do
   bs <- L.readFile "report.xlsx"
   let value = toXlsx bs ^? ixSheet "List1" .
               ixCell (3,2) . cellValue . _Just
   putStrLn $ "Cell B3 contains " ++ show value

And the following example mudule shows a way to construct and write xlsx file

 {-# LANGUAGE OverloadedStrings #-}
 module Write where
 import Codec.Xlsx
 import Control.Lens
 import qualified Data.ByteString.Lazy as L
 import System.Time

 main :: IO ()
 main = do
   ct <- getClockTime
   let
       sheet = def & cellValueAt (1,2) ?~ CellDouble 42.0
                   & cellValueAt (3,2) ?~ CellText "foo"
       xlsx = def & atSheet "List1" ?~ sheet
   L.writeFile "example.xlsx" $ fromXlsx ct xlsx