module Codec.Xlsx.Lens
( ixSheet
, atSheet
, ixCell
, ixCellRC
, ixCellXY
, atCell
, atCellRC
, atCellXY
, cellValueAt
, cellValueAtRC
, cellValueAtXY
) where
import Codec.Xlsx.Types
import Control.Lens
import Data.Function (on)
import Data.List (deleteBy)
import Data.Text
import Data.Tuple (swap)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
newtype SheetList = SheetList{ unSheetList :: [(Text, Worksheet)] }
deriving (Eq, Show)
type instance IxValue (SheetList) = Worksheet
type instance Index (SheetList) = Text
instance Ixed SheetList where
ix k f sl@(SheetList l) = case lookup k l of
Just v -> f v <&> \v' -> SheetList (upsert k v' l)
Nothing -> pure sl
instance At SheetList where
at k f (SheetList l) = f mv <&> \r -> case r of
Nothing -> SheetList $ maybe l (\v -> deleteBy ((==) `on` fst) (k,v) l) mv
Just v' -> SheetList $ upsert k v' l
where
mv = lookup k l
upsert :: (Eq k) => k -> v -> [(k,v)] -> [(k,v)]
upsert k v [] = [(k,v)]
upsert k v ((k1,v1):r) =
if k == k1
then (k,v):r
else (k1,v1):upsert k v r
sheetList :: Iso' [(Text, Worksheet)] SheetList
sheetList = iso SheetList unSheetList
ixSheet :: Text -> Traversal' Xlsx Worksheet
ixSheet s = xlSheets . sheetList . ix s
atSheet :: Text -> Lens' Xlsx (Maybe Worksheet)
atSheet s = xlSheets . sheetList . at s
ixCell :: (Int, Int) -> Traversal' Worksheet Cell
ixCell = ixCellRC
ixCellRC :: (Int, Int) -> Traversal' Worksheet Cell
ixCellRC i = wsCells . ix i
ixCellXY :: (Int, Int) -> Traversal' Worksheet Cell
ixCellXY = ixCellRC . swap
atCell :: (Int, Int) -> Lens' Worksheet (Maybe Cell)
atCell = atCellRC
atCellRC :: (Int, Int) -> Lens' Worksheet (Maybe Cell)
atCellRC i = wsCells . at i
atCellXY :: (Int, Int) -> Lens' Worksheet (Maybe Cell)
atCellXY = atCellRC . swap
cellValueAt :: (Int, Int) -> Lens' Worksheet (Maybe CellValue)
cellValueAt = cellValueAtRC
cellValueAtRC :: (Int, Int) -> Lens' Worksheet (Maybe CellValue)
cellValueAtRC i = atCell i . non def . cellValue
cellValueAtXY :: (Int, Int) -> Lens' Worksheet (Maybe CellValue)
cellValueAtXY = cellValueAtRC . swap