{-# LANGUAGE CPP #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RankNTypes #-}
module Codec.Xlsx.Types (
Xlsx(..)
, Styles(..)
, DefinedNames(..)
, ColumnsProperties(..)
, PageSetup(..)
, Worksheet(..)
, SheetState(..)
, CellMap
, CellValue(..)
, CellFormula(..)
, FormulaExpression(..)
, Cell.SharedFormulaIndex(..)
, Cell.SharedFormulaOptions(..)
, Cell(..)
, RowHeight(..)
, RowProperties (..)
, xlSheets
, xlStyles
, xlDefinedNames
, xlCustomProperties
, xlDateBase
, wsColumnsProperties
, wsRowPropertiesMap
, wsCells
, wsDrawing
, wsMerges
, wsSheetViews
, wsPageSetup
, wsConditionalFormattings
, wsDataValidations
, wsPivotTables
, wsAutoFilter
, wsTables
, wsProtection
, wsSharedFormulas
, wsState
, Cell.cellValue
, Cell.cellStyle
, Cell.cellComment
, Cell.cellFormula
, rowHeightLens
, _CustomHeight
, _AutomaticHeight
, emptyStyles
, renderStyleSheet
, parseStyleSheet
, simpleCellFormula
, sharedFormulaByIndex
, def
, toRows
, fromRows
, module X
) where
import Control.Exception (SomeException, toException)
#ifdef USE_MICROLENS
import Lens.Micro.TH
import Data.Profunctor(dimap)
import Data.Profunctor.Choice
#else
#endif
import Control.DeepSeq (NFData)
import qualified Data.ByteString.Lazy as L
import Data.Default
import Data.Function (on)
import Data.List (groupBy)
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (catMaybes, isJust)
import Data.Text (Text)
import GHC.Generics (Generic)
import Text.XML (parseLBS, renderLBS)
import Text.XML.Cursor
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Types.AutoFilter as X
import Codec.Xlsx.Types.Cell as Cell
import Codec.Xlsx.Types.Comment as X
import Codec.Xlsx.Types.Common as X
import Codec.Xlsx.Types.ConditionalFormatting as X
import Codec.Xlsx.Types.DataValidation as X
import Codec.Xlsx.Types.Drawing as X
import Codec.Xlsx.Types.Drawing.Chart as X
import Codec.Xlsx.Types.Drawing.Common as X
import Codec.Xlsx.Types.PageSetup as X
import Codec.Xlsx.Types.PivotTable as X
import Codec.Xlsx.Types.Protection as X
import Codec.Xlsx.Types.RichText as X
import Codec.Xlsx.Types.SheetViews as X
import Codec.Xlsx.Types.StyleSheet as X
import Codec.Xlsx.Types.Table as X
import Codec.Xlsx.Types.Variant as X
import Codec.Xlsx.Writer.Internal
#ifdef USE_MICROLENS
import Lens.Micro
#else
import Control.Lens (lens, Lens', makeLenses)
import Control.Lens.TH (makePrisms)
#endif
data RowHeight
= CustomHeight !Double
| AutomaticHeight !Double
deriving (RowHeight -> RowHeight -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowHeight -> RowHeight -> Bool
$c/= :: RowHeight -> RowHeight -> Bool
== :: RowHeight -> RowHeight -> Bool
$c== :: RowHeight -> RowHeight -> Bool
Eq, Eq RowHeight
RowHeight -> RowHeight -> Bool
RowHeight -> RowHeight -> Ordering
RowHeight -> RowHeight -> RowHeight
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RowHeight -> RowHeight -> RowHeight
$cmin :: RowHeight -> RowHeight -> RowHeight
max :: RowHeight -> RowHeight -> RowHeight
$cmax :: RowHeight -> RowHeight -> RowHeight
>= :: RowHeight -> RowHeight -> Bool
$c>= :: RowHeight -> RowHeight -> Bool
> :: RowHeight -> RowHeight -> Bool
$c> :: RowHeight -> RowHeight -> Bool
<= :: RowHeight -> RowHeight -> Bool
$c<= :: RowHeight -> RowHeight -> Bool
< :: RowHeight -> RowHeight -> Bool
$c< :: RowHeight -> RowHeight -> Bool
compare :: RowHeight -> RowHeight -> Ordering
$ccompare :: RowHeight -> RowHeight -> Ordering
Ord, Int -> RowHeight -> ShowS
[RowHeight] -> ShowS
RowHeight -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowHeight] -> ShowS
$cshowList :: [RowHeight] -> ShowS
show :: RowHeight -> String
$cshow :: RowHeight -> String
showsPrec :: Int -> RowHeight -> ShowS
$cshowsPrec :: Int -> RowHeight -> ShowS
Show, ReadPrec [RowHeight]
ReadPrec RowHeight
Int -> ReadS RowHeight
ReadS [RowHeight]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RowHeight]
$creadListPrec :: ReadPrec [RowHeight]
readPrec :: ReadPrec RowHeight
$creadPrec :: ReadPrec RowHeight
readList :: ReadS [RowHeight]
$creadList :: ReadS [RowHeight]
readsPrec :: Int -> ReadS RowHeight
$creadsPrec :: Int -> ReadS RowHeight
Read, forall x. Rep RowHeight x -> RowHeight
forall x. RowHeight -> Rep RowHeight x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RowHeight x -> RowHeight
$cfrom :: forall x. RowHeight -> Rep RowHeight x
Generic)
instance NFData RowHeight
#ifdef USE_MICROLENS
type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
type Prism' s a = Prism s s a a
prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
prism bt seta = dimap seta (either pure (fmap bt)) . right'
_CustomHeight :: Prism' RowHeight Double
_CustomHeight
= (prism (\ x1_a4xgd -> CustomHeight x1_a4xgd))
(\ x_a4xge
-> case x_a4xge of
CustomHeight y1_a4xgf -> Right y1_a4xgf
_ -> Left x_a4xge)
{-# INLINE _CustomHeight #-}
_AutomaticHeight :: Prism' RowHeight Double
_AutomaticHeight
= (prism (\ x1_a4xgg -> AutomaticHeight x1_a4xgg))
(\ x_a4xgh
-> case x_a4xgh of
AutomaticHeight y1_a4xgi -> Right y1_a4xgi
_ -> Left x_a4xgh)
{-# INLINE _AutomaticHeight #-}
#else
makePrisms ''RowHeight
#endif
data RowProperties = RowProps
{ RowProperties -> Maybe RowHeight
rowHeight :: Maybe RowHeight
, RowProperties -> Maybe Int
rowStyle :: Maybe Int
, RowProperties -> Bool
rowHidden :: Bool
} deriving (RowProperties -> RowProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowProperties -> RowProperties -> Bool
$c/= :: RowProperties -> RowProperties -> Bool
== :: RowProperties -> RowProperties -> Bool
$c== :: RowProperties -> RowProperties -> Bool
Eq, Eq RowProperties
RowProperties -> RowProperties -> Bool
RowProperties -> RowProperties -> Ordering
RowProperties -> RowProperties -> RowProperties
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RowProperties -> RowProperties -> RowProperties
$cmin :: RowProperties -> RowProperties -> RowProperties
max :: RowProperties -> RowProperties -> RowProperties
$cmax :: RowProperties -> RowProperties -> RowProperties
>= :: RowProperties -> RowProperties -> Bool
$c>= :: RowProperties -> RowProperties -> Bool
> :: RowProperties -> RowProperties -> Bool
$c> :: RowProperties -> RowProperties -> Bool
<= :: RowProperties -> RowProperties -> Bool
$c<= :: RowProperties -> RowProperties -> Bool
< :: RowProperties -> RowProperties -> Bool
$c< :: RowProperties -> RowProperties -> Bool
compare :: RowProperties -> RowProperties -> Ordering
$ccompare :: RowProperties -> RowProperties -> Ordering
Ord, Int -> RowProperties -> ShowS
[RowProperties] -> ShowS
RowProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowProperties] -> ShowS
$cshowList :: [RowProperties] -> ShowS
show :: RowProperties -> String
$cshow :: RowProperties -> String
showsPrec :: Int -> RowProperties -> ShowS
$cshowsPrec :: Int -> RowProperties -> ShowS
Show, ReadPrec [RowProperties]
ReadPrec RowProperties
Int -> ReadS RowProperties
ReadS [RowProperties]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RowProperties]
$creadListPrec :: ReadPrec [RowProperties]
readPrec :: ReadPrec RowProperties
$creadPrec :: ReadPrec RowProperties
readList :: ReadS [RowProperties]
$creadList :: ReadS [RowProperties]
readsPrec :: Int -> ReadS RowProperties
$creadsPrec :: Int -> ReadS RowProperties
Read, forall x. Rep RowProperties x -> RowProperties
forall x. RowProperties -> Rep RowProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RowProperties x -> RowProperties
$cfrom :: forall x. RowProperties -> Rep RowProperties x
Generic)
instance NFData RowProperties
rowHeightLens :: Lens' RowProperties (Maybe RowHeight)
rowHeightLens :: Lens' RowProperties (Maybe RowHeight)
rowHeightLens = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens RowProperties -> Maybe RowHeight
rowHeight forall a b. (a -> b) -> a -> b
$ \RowProperties
x Maybe RowHeight
y -> RowProperties
x{rowHeight :: Maybe RowHeight
rowHeight=Maybe RowHeight
y}
instance Default RowProperties where
def :: RowProperties
def = RowProps { rowHeight :: Maybe RowHeight
rowHeight = forall a. Maybe a
Nothing
, rowStyle :: Maybe Int
rowStyle = forall a. Maybe a
Nothing
, rowHidden :: Bool
rowHidden = Bool
False
}
data ColumnsProperties = ColumnsProperties
{ ColumnsProperties -> Int
cpMin :: Int
, ColumnsProperties -> Int
cpMax :: Int
, ColumnsProperties -> Maybe Double
cpWidth :: Maybe Double
, ColumnsProperties -> Maybe Int
cpStyle :: Maybe Int
, ColumnsProperties -> Bool
cpHidden :: Bool
, ColumnsProperties -> Bool
cpCollapsed :: Bool
, ColumnsProperties -> Bool
cpBestFit :: Bool
} deriving (ColumnsProperties -> ColumnsProperties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnsProperties -> ColumnsProperties -> Bool
$c/= :: ColumnsProperties -> ColumnsProperties -> Bool
== :: ColumnsProperties -> ColumnsProperties -> Bool
$c== :: ColumnsProperties -> ColumnsProperties -> Bool
Eq, Int -> ColumnsProperties -> ShowS
[ColumnsProperties] -> ShowS
ColumnsProperties -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnsProperties] -> ShowS
$cshowList :: [ColumnsProperties] -> ShowS
show :: ColumnsProperties -> String
$cshow :: ColumnsProperties -> String
showsPrec :: Int -> ColumnsProperties -> ShowS
$cshowsPrec :: Int -> ColumnsProperties -> ShowS
Show, forall x. Rep ColumnsProperties x -> ColumnsProperties
forall x. ColumnsProperties -> Rep ColumnsProperties x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColumnsProperties x -> ColumnsProperties
$cfrom :: forall x. ColumnsProperties -> Rep ColumnsProperties x
Generic)
instance NFData ColumnsProperties
instance FromCursor ColumnsProperties where
fromCursor :: Cursor -> [ColumnsProperties]
fromCursor Cursor
c = do
Int
cpMin <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"min" Cursor
c
Int
cpMax <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"max" Cursor
c
Maybe Double
cpWidth <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"width" Cursor
c
Maybe Int
cpStyle <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"style" Cursor
c
Bool
cpHidden <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"hidden" Bool
False Cursor
c
Bool
cpCollapsed <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"collapsed" Bool
False Cursor
c
Bool
cpBestFit <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"bestFit" Bool
False Cursor
c
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnsProperties {Bool
Int
Maybe Double
Maybe Int
cpBestFit :: Bool
cpCollapsed :: Bool
cpHidden :: Bool
cpStyle :: Maybe Int
cpWidth :: Maybe Double
cpMax :: Int
cpMin :: Int
cpBestFit :: Bool
cpCollapsed :: Bool
cpHidden :: Bool
cpStyle :: Maybe Int
cpWidth :: Maybe Double
cpMax :: Int
cpMin :: Int
..}
instance FromXenoNode ColumnsProperties where
fromXenoNode :: Node -> Either Text ColumnsProperties
fromXenoNode Node
root = forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Int
cpMin <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"min"
Int
cpMax <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"max"
Maybe Double
cpWidth <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"width"
Maybe Int
cpStyle <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"style"
Bool
cpHidden <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"hidden" Bool
False
Bool
cpCollapsed <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"collapsed" Bool
False
Bool
cpBestFit <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"bestFit" Bool
False
forall (m :: * -> *) a. Monad m => a -> m a
return ColumnsProperties {Bool
Int
Maybe Double
Maybe Int
cpBestFit :: Bool
cpCollapsed :: Bool
cpHidden :: Bool
cpStyle :: Maybe Int
cpWidth :: Maybe Double
cpMax :: Int
cpMin :: Int
cpBestFit :: Bool
cpCollapsed :: Bool
cpHidden :: Bool
cpStyle :: Maybe Int
cpWidth :: Maybe Double
cpMax :: Int
cpMin :: Int
..}
data SheetState =
Visible
| Hidden
| VeryHidden
deriving (SheetState -> SheetState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SheetState -> SheetState -> Bool
$c/= :: SheetState -> SheetState -> Bool
== :: SheetState -> SheetState -> Bool
$c== :: SheetState -> SheetState -> Bool
Eq, Int -> SheetState -> ShowS
[SheetState] -> ShowS
SheetState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SheetState] -> ShowS
$cshowList :: [SheetState] -> ShowS
show :: SheetState -> String
$cshow :: SheetState -> String
showsPrec :: Int -> SheetState -> ShowS
$cshowsPrec :: Int -> SheetState -> ShowS
Show, forall x. Rep SheetState x -> SheetState
forall x. SheetState -> Rep SheetState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SheetState x -> SheetState
$cfrom :: forall x. SheetState -> Rep SheetState x
Generic)
instance NFData SheetState
instance Default SheetState where
def :: SheetState
def = SheetState
Visible
instance FromAttrVal SheetState where
fromAttrVal :: Reader SheetState
fromAttrVal Text
"visible" = forall a. a -> Either String (a, Text)
readSuccess SheetState
Visible
fromAttrVal Text
"hidden" = forall a. a -> Either String (a, Text)
readSuccess SheetState
Hidden
fromAttrVal Text
"veryHidden" = forall a. a -> Either String (a, Text)
readSuccess SheetState
VeryHidden
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"SheetState" Text
t
instance FromAttrBs SheetState where
fromAttrBs :: ByteString -> Either Text SheetState
fromAttrBs ByteString
"visible" = forall (m :: * -> *) a. Monad m => a -> m a
return SheetState
Visible
fromAttrBs ByteString
"hidden" = forall (m :: * -> *) a. Monad m => a -> m a
return SheetState
Hidden
fromAttrBs ByteString
"veryHidden" = forall (m :: * -> *) a. Monad m => a -> m a
return SheetState
VeryHidden
fromAttrBs ByteString
t = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"SheetState" ByteString
t
instance ToAttrVal SheetState where
toAttrVal :: SheetState -> Text
toAttrVal SheetState
Visible = Text
"visible"
toAttrVal SheetState
Hidden = Text
"hidden"
toAttrVal SheetState
VeryHidden = Text
"veryHidden"
data Worksheet = Worksheet
{ Worksheet -> [ColumnsProperties]
_wsColumnsProperties :: [ColumnsProperties]
, Worksheet -> Map RowIndex RowProperties
_wsRowPropertiesMap :: Map RowIndex RowProperties
, Worksheet -> CellMap
_wsCells :: CellMap
, Worksheet -> Maybe Drawing
_wsDrawing :: Maybe Drawing
, Worksheet -> [Range]
_wsMerges :: [Range]
, Worksheet -> Maybe [SheetView]
_wsSheetViews :: Maybe [SheetView]
, Worksheet -> Maybe PageSetup
_wsPageSetup :: Maybe PageSetup
, Worksheet -> Map SqRef ConditionalFormatting
_wsConditionalFormattings :: Map SqRef ConditionalFormatting
, Worksheet -> Map SqRef DataValidation
_wsDataValidations :: Map SqRef DataValidation
, Worksheet -> [PivotTable]
_wsPivotTables :: [PivotTable]
, Worksheet -> Maybe AutoFilter
_wsAutoFilter :: Maybe AutoFilter
, Worksheet -> [Table]
_wsTables :: [Table]
, Worksheet -> Maybe SheetProtection
_wsProtection :: Maybe SheetProtection
, Worksheet -> Map SharedFormulaIndex SharedFormulaOptions
_wsSharedFormulas :: Map SharedFormulaIndex SharedFormulaOptions
, Worksheet -> SheetState
_wsState :: SheetState
} deriving (Worksheet -> Worksheet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Worksheet -> Worksheet -> Bool
$c/= :: Worksheet -> Worksheet -> Bool
== :: Worksheet -> Worksheet -> Bool
$c== :: Worksheet -> Worksheet -> Bool
Eq, Int -> Worksheet -> ShowS
[Worksheet] -> ShowS
Worksheet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Worksheet] -> ShowS
$cshowList :: [Worksheet] -> ShowS
show :: Worksheet -> String
$cshow :: Worksheet -> String
showsPrec :: Int -> Worksheet -> ShowS
$cshowsPrec :: Int -> Worksheet -> ShowS
Show, forall x. Rep Worksheet x -> Worksheet
forall x. Worksheet -> Rep Worksheet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Worksheet x -> Worksheet
$cfrom :: forall x. Worksheet -> Rep Worksheet x
Generic)
instance NFData Worksheet
makeLenses ''Worksheet
instance Default Worksheet where
def :: Worksheet
def =
Worksheet
{ _wsColumnsProperties :: [ColumnsProperties]
_wsColumnsProperties = []
, _wsRowPropertiesMap :: Map RowIndex RowProperties
_wsRowPropertiesMap = forall k a. Map k a
M.empty
, _wsCells :: CellMap
_wsCells = forall k a. Map k a
M.empty
, _wsDrawing :: Maybe Drawing
_wsDrawing = forall a. Maybe a
Nothing
, _wsMerges :: [Range]
_wsMerges = []
, _wsSheetViews :: Maybe [SheetView]
_wsSheetViews = forall a. Maybe a
Nothing
, _wsPageSetup :: Maybe PageSetup
_wsPageSetup = forall a. Maybe a
Nothing
, _wsConditionalFormattings :: Map SqRef ConditionalFormatting
_wsConditionalFormattings = forall k a. Map k a
M.empty
, _wsDataValidations :: Map SqRef DataValidation
_wsDataValidations = forall k a. Map k a
M.empty
, _wsPivotTables :: [PivotTable]
_wsPivotTables = []
, _wsAutoFilter :: Maybe AutoFilter
_wsAutoFilter = forall a. Maybe a
Nothing
, _wsTables :: [Table]
_wsTables = []
, _wsProtection :: Maybe SheetProtection
_wsProtection = forall a. Maybe a
Nothing
, _wsSharedFormulas :: Map SharedFormulaIndex SharedFormulaOptions
_wsSharedFormulas = forall k a. Map k a
M.empty
, _wsState :: SheetState
_wsState = forall a. Default a => a
def
}
newtype Styles = Styles {Styles -> ByteString
unStyles :: L.ByteString}
deriving (Styles -> Styles -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Styles -> Styles -> Bool
$c/= :: Styles -> Styles -> Bool
== :: Styles -> Styles -> Bool
$c== :: Styles -> Styles -> Bool
Eq, Int -> Styles -> ShowS
[Styles] -> ShowS
Styles -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Styles] -> ShowS
$cshowList :: [Styles] -> ShowS
show :: Styles -> String
$cshow :: Styles -> String
showsPrec :: Int -> Styles -> ShowS
$cshowsPrec :: Int -> Styles -> ShowS
Show, forall x. Rep Styles x -> Styles
forall x. Styles -> Rep Styles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Styles x -> Styles
$cfrom :: forall x. Styles -> Rep Styles x
Generic)
instance NFData Styles
data Xlsx = Xlsx
{ Xlsx -> [(Text, Worksheet)]
_xlSheets :: [(Text, Worksheet)]
, Xlsx -> Styles
_xlStyles :: Styles
, Xlsx -> DefinedNames
_xlDefinedNames :: DefinedNames
, Xlsx -> Map Text Variant
_xlCustomProperties :: Map Text Variant
, Xlsx -> DateBase
_xlDateBase :: DateBase
} deriving (Xlsx -> Xlsx -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Xlsx -> Xlsx -> Bool
$c/= :: Xlsx -> Xlsx -> Bool
== :: Xlsx -> Xlsx -> Bool
$c== :: Xlsx -> Xlsx -> Bool
Eq, Int -> Xlsx -> ShowS
[Xlsx] -> ShowS
Xlsx -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Xlsx] -> ShowS
$cshowList :: [Xlsx] -> ShowS
show :: Xlsx -> String
$cshow :: Xlsx -> String
showsPrec :: Int -> Xlsx -> ShowS
$cshowsPrec :: Int -> Xlsx -> ShowS
Show, forall x. Rep Xlsx x -> Xlsx
forall x. Xlsx -> Rep Xlsx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Xlsx x -> Xlsx
$cfrom :: forall x. Xlsx -> Rep Xlsx x
Generic)
instance NFData Xlsx
newtype DefinedNames = DefinedNames [(Text, Maybe Text, Text)]
deriving (DefinedNames -> DefinedNames -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefinedNames -> DefinedNames -> Bool
$c/= :: DefinedNames -> DefinedNames -> Bool
== :: DefinedNames -> DefinedNames -> Bool
$c== :: DefinedNames -> DefinedNames -> Bool
Eq, Int -> DefinedNames -> ShowS
[DefinedNames] -> ShowS
DefinedNames -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DefinedNames] -> ShowS
$cshowList :: [DefinedNames] -> ShowS
show :: DefinedNames -> String
$cshow :: DefinedNames -> String
showsPrec :: Int -> DefinedNames -> ShowS
$cshowsPrec :: Int -> DefinedNames -> ShowS
Show, forall x. Rep DefinedNames x -> DefinedNames
forall x. DefinedNames -> Rep DefinedNames x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DefinedNames x -> DefinedNames
$cfrom :: forall x. DefinedNames -> Rep DefinedNames x
Generic)
instance NFData DefinedNames
makeLenses ''Xlsx
instance Default Xlsx where
def :: Xlsx
def = [(Text, Worksheet)]
-> Styles -> DefinedNames -> Map Text Variant -> DateBase -> Xlsx
Xlsx [] Styles
emptyStyles forall a. Default a => a
def forall k a. Map k a
M.empty DateBase
DateBase1900
instance Default DefinedNames where
def :: DefinedNames
def = [(Text, Maybe Text, Text)] -> DefinedNames
DefinedNames []
emptyStyles :: Styles
emptyStyles :: Styles
emptyStyles = ByteString -> Styles
Styles ByteString
"<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?><styleSheet xmlns=\"http://schemas.openxmlformats.org/spreadsheetml/2006/main\"></styleSheet>"
renderStyleSheet :: StyleSheet -> Styles
renderStyleSheet :: StyleSheet -> Styles
renderStyleSheet = ByteString -> Styles
Styles forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderSettings -> Document -> ByteString
renderLBS forall a. Default a => a
def forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToDocument a => a -> Document
toDocument
parseStyleSheet :: Styles -> Either SomeException StyleSheet
parseStyleSheet :: Styles -> Either SomeException StyleSheet
parseStyleSheet (Styles ByteString
bs) = ParseSettings -> ByteString -> Either SomeException Document
parseLBS forall a. Default a => a
def ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall {b}. FromCursor b => Document -> Either SomeException b
parseDoc
where
parseDoc :: Document -> Either SomeException b
parseDoc Document
doc = case forall a. FromCursor a => Cursor -> [a]
fromCursor (Document -> Cursor
fromDocument Document
doc) of
[b
stylesheet] -> forall a b. b -> Either a b
Right b
stylesheet
[b]
_ -> forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. Exception e => e -> SomeException
toException forall a b. (a -> b) -> a -> b
$ String -> ParseException
ParseException String
"Could not parse style sheets"
toRows :: CellMap -> [(RowIndex, [(ColumnIndex, Cell)])]
toRows :: CellMap -> [(RowIndex, [(ColumnIndex, Cell)])]
toRows CellMap
cells =
forall a b. (a -> b) -> [a] -> [b]
map forall {a} {a} {b}. [((a, a), b)] -> (a, [(a, b)])
extractRow forall a b. (a -> b) -> a -> b
$ forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)) forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
M.toList CellMap
cells
where
extractRow :: [((a, a), b)] -> (a, [(a, b)])
extractRow row :: [((a, a), b)]
row@(((a
x,a
_),b
_):[((a, a), b)]
_) =
(a
x, forall a b. (a -> b) -> [a] -> [b]
map (\((a
_,a
y),b
v) -> (a
y,b
v)) [((a, a), b)]
row)
extractRow [((a, a), b)]
_ = forall a. HasCallStack => String -> a
error String
"invalid CellMap row"
fromRows :: [(RowIndex, [(ColumnIndex, Cell)])] -> CellMap
fromRows :: [(RowIndex, [(ColumnIndex, Cell)])] -> CellMap
fromRows [(RowIndex, [(ColumnIndex, Cell)])]
rows = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a} {b} {b}. (a, [(b, b)]) -> [((a, b), b)]
mapRow [(RowIndex, [(ColumnIndex, Cell)])]
rows
where
mapRow :: (a, [(b, b)]) -> [((a, b), b)]
mapRow (a
r, [(b, b)]
cells) = forall a b. (a -> b) -> [a] -> [b]
map (\(b
c, b
v) -> ((a
r, b
c), b
v)) [(b, b)]
cells
instance ToElement ColumnsProperties where
toElement :: Name -> ColumnsProperties -> Element
toElement Name
nm ColumnsProperties {Bool
Int
Maybe Double
Maybe Int
cpBestFit :: Bool
cpCollapsed :: Bool
cpHidden :: Bool
cpStyle :: Maybe Int
cpWidth :: Maybe Double
cpMax :: Int
cpMin :: Int
cpBestFit :: ColumnsProperties -> Bool
cpCollapsed :: ColumnsProperties -> Bool
cpHidden :: ColumnsProperties -> Bool
cpStyle :: ColumnsProperties -> Maybe Int
cpWidth :: ColumnsProperties -> Maybe Double
cpMax :: ColumnsProperties -> Int
cpMin :: ColumnsProperties -> Int
..} = Name -> [(Name, Text)] -> Element
leafElement Name
nm [(Name, Text)]
attrs
where
attrs :: [(Name, Text)]
attrs =
[Name
"min" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
cpMin, Name
"max" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
cpMax] forall a. [a] -> [a] -> [a]
++
forall a. [Maybe a] -> [a]
catMaybes
[ Name
"style" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? (forall a. Eq a => a -> a -> Maybe a
justNonDef Int
0 forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Int
cpStyle)
, Name
"width" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Double
cpWidth
, Name
"customWidth" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue (forall a. Maybe a -> Bool
isJust Maybe Double
cpWidth)
, Name
"hidden" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
cpHidden
, Name
"collapsed" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
cpCollapsed
, Name
"bestFit" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
cpBestFit
]