Skip to content

Instantly share code, notes, and snippets.

@cblp
Created February 14, 2018 09:42
Show Gist options
  • Save cblp/e7d930f30d10b144318305eb24d283eb to your computer and use it in GitHub Desktop.
Save cblp/e7d930f30d10b144318305eb24d283eb to your computer and use it in GitHub Desktop.
-- stack --resolver=lts-10.5 script
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Rank2Types #-}
module Write where
import Codec.Xlsx
import Control.Lens
import Control.Monad.State.Strict
import Data.ByteString.Lazy as L
import qualified Data.Map as Map
import Data.Text (Text)
import Data.Time.Clock.POSIX
main :: IO ()
main = do
ct <- getPOSIXTime
let sheet1 = def
& cellValueAt (1, 2) ?~ CellDouble 42.0
& cellValueAt (3, 2) ?~ CellText "foo"
xlsx1 = def & atSheet "List1" ?~ sheet1
example1 = fromXlsx ct xlsx1
let sheet2 = (cellValueAt (1, 2) ?~ CellDouble 42.0)
. (cellValueAt (3, 2) ?~ CellText "foo")
xlsx2 = atSheet' "List1" %~ sheet2
example2 = fromXlsxE ct xlsx2
let sheet3 = do
cellValueAt (1, 2) ?= CellDouble 42.0
cellValueAt (3, 2) ?= CellText "foo"
xlsx3 = zoom (atSheet' "List1") sheet3
example3 = fromXlsxM ct xlsx3
let example3' = fromXlsxM ct $
zoom (atSheet' "List1") $ do
cellValueAt (1, 2) ?= CellDouble 42.0
cellValueAt (3, 2) ?= CellText "foo"
print $ example1 == example2
print $ example1 == example3
print $ example1 == example3'
atSheet' :: Text -> Lens' Xlsx Worksheet
atSheet' sheetName = atSheet sheetName . non emptySheet
fromXlsxE :: POSIXTime -> (Xlsx -> Xlsx) -> ByteString
fromXlsxE ct xlsxM = fromXlsx ct $ xlsxM emptyXlsx
fromXlsxM :: POSIXTime -> State Xlsx () -> ByteString
fromXlsxM ct xlsxM = fromXlsx ct $ execState xlsxM emptyXlsx
emptyXlsx :: Xlsx
emptyXlsx = Xlsx [] emptyStyles def Map.empty
emptySheet :: Worksheet
emptySheet = Worksheet
{ _wsColumnsProperties = []
, _wsRowPropertiesMap = Map.empty
, _wsCells = Map.empty
, _wsDrawing = Nothing
, _wsMerges = []
, _wsSheetViews = Nothing
, _wsPageSetup = Nothing
, _wsConditionalFormattings = Map.empty
, _wsDataValidations = Map.empty
, _wsPivotTables = []
, _wsAutoFilter = Nothing
, _wsTables = []
, _wsProtection = Nothing
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment