{-# LANGUAGE OverloadedStrings #-} import Codec.Xlsx import Control.Applicative ((<$>)) import Control.Lens import qualified Data.ByteString.Lazy as L import qualified Data.Map as M import Data.Text (Text,pack) import System.Time xEmpty :: Cell xEmpty = Cell{_cellValue=Nothing, _cellStyle=Just 0} xText :: Text -> Cell xText t = Cell{_cellValue=Just $ CellText t, _cellStyle=Just 0} xDouble :: Double -> Cell xDouble d = Cell{_cellValue=Just $ CellDouble d, _cellStyle=Just 0} styles :: Styles styles = Styles "\ \\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \" main :: IO () main = do ct <- getClockTime L.writeFile "test.xlsx" $ fromXlsx ct $ Xlsx sheets styles x <- toXlsx <$> L.readFile "test.xlsx" putStrLn $ "And cell (3,2) value in list 'List' is " ++ show (x ^? xlSheets . ix "List" . wsCells . ix (3,2) . cellValue . _Just) where cols = [ColumnsWidth 1 10 15 1] rowProps = M.fromList [(1, RowProps (Just 50) (Just 3))] cells = M.fromList [((r, c), v) | r <- [1..10000], (c, v) <- zip [1..] (row r) ] row r = [ xText $ pack $ "column1-r" ++ show r , xText $ pack $ "column2-r" ++ show r , xEmpty , xText $ pack $ "column4-r" ++ show r , xDouble 42.12345 , xText "False"] sheets = M.fromList [("List", Worksheet cols rowProps cells [])] -- wtf merges?