{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Types.Cell
( CellFormula(..)
, FormulaExpression(..)
, simpleCellFormula
, sharedFormulaByIndex
, SharedFormulaIndex(..)
, SharedFormulaOptions(..)
, formulaDataFromCursor
, applySharedFormulaOpts
, Cell(..)
, cellStyle
, cellValue
, cellComment
, cellFormula
, CellMap
) where
import Control.Arrow (first)
#ifdef USE_MICROLENS
import Lens.Micro.TH (makeLenses)
#else
import Control.Lens.TH (makeLenses)
#endif
import Control.DeepSeq (NFData)
import Data.Default
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe (catMaybes, listToMaybe)
import Data.Monoid ((<>))
import Data.Text (Text)
import GHC.Generics (Generic)
import Text.XML
import Text.XML.Cursor
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Types.Comment
import Codec.Xlsx.Types.Common
import Codec.Xlsx.Writer.Internal
data CellFormula = CellFormula
{ CellFormula -> FormulaExpression
_cellfExpression :: FormulaExpression
, CellFormula -> Bool
_cellfAssignsToName :: Bool
, CellFormula -> Bool
_cellfCalculate :: Bool
} deriving (CellFormula -> CellFormula -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellFormula -> CellFormula -> Bool
$c/= :: CellFormula -> CellFormula -> Bool
== :: CellFormula -> CellFormula -> Bool
$c== :: CellFormula -> CellFormula -> Bool
Eq, Int -> CellFormula -> ShowS
[CellFormula] -> ShowS
CellFormula -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CellFormula] -> ShowS
$cshowList :: [CellFormula] -> ShowS
show :: CellFormula -> [Char]
$cshow :: CellFormula -> [Char]
showsPrec :: Int -> CellFormula -> ShowS
$cshowsPrec :: Int -> CellFormula -> ShowS
Show, forall x. Rep CellFormula x -> CellFormula
forall x. CellFormula -> Rep CellFormula x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CellFormula x -> CellFormula
$cfrom :: forall x. CellFormula -> Rep CellFormula x
Generic)
instance NFData CellFormula
data FormulaExpression
= NormalFormula Formula
| SharedFormula SharedFormulaIndex
deriving (FormulaExpression -> FormulaExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormulaExpression -> FormulaExpression -> Bool
$c/= :: FormulaExpression -> FormulaExpression -> Bool
== :: FormulaExpression -> FormulaExpression -> Bool
$c== :: FormulaExpression -> FormulaExpression -> Bool
Eq, Int -> FormulaExpression -> ShowS
[FormulaExpression] -> ShowS
FormulaExpression -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [FormulaExpression] -> ShowS
$cshowList :: [FormulaExpression] -> ShowS
show :: FormulaExpression -> [Char]
$cshow :: FormulaExpression -> [Char]
showsPrec :: Int -> FormulaExpression -> ShowS
$cshowsPrec :: Int -> FormulaExpression -> ShowS
Show, forall x. Rep FormulaExpression x -> FormulaExpression
forall x. FormulaExpression -> Rep FormulaExpression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormulaExpression x -> FormulaExpression
$cfrom :: forall x. FormulaExpression -> Rep FormulaExpression x
Generic)
instance NFData FormulaExpression
defaultFormulaType :: Text
defaultFormulaType :: Text
defaultFormulaType = Text
"normal"
newtype SharedFormulaIndex = SharedFormulaIndex Int
deriving (SharedFormulaIndex -> SharedFormulaIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
$c/= :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
== :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
$c== :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
Eq, Eq SharedFormulaIndex
SharedFormulaIndex -> SharedFormulaIndex -> Bool
SharedFormulaIndex -> SharedFormulaIndex -> Ordering
SharedFormulaIndex -> SharedFormulaIndex -> SharedFormulaIndex
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 :: SharedFormulaIndex -> SharedFormulaIndex -> SharedFormulaIndex
$cmin :: SharedFormulaIndex -> SharedFormulaIndex -> SharedFormulaIndex
max :: SharedFormulaIndex -> SharedFormulaIndex -> SharedFormulaIndex
$cmax :: SharedFormulaIndex -> SharedFormulaIndex -> SharedFormulaIndex
>= :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
$c>= :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
> :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
$c> :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
<= :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
$c<= :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
< :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
$c< :: SharedFormulaIndex -> SharedFormulaIndex -> Bool
compare :: SharedFormulaIndex -> SharedFormulaIndex -> Ordering
$ccompare :: SharedFormulaIndex -> SharedFormulaIndex -> Ordering
Ord, Int -> SharedFormulaIndex -> ShowS
[SharedFormulaIndex] -> ShowS
SharedFormulaIndex -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SharedFormulaIndex] -> ShowS
$cshowList :: [SharedFormulaIndex] -> ShowS
show :: SharedFormulaIndex -> [Char]
$cshow :: SharedFormulaIndex -> [Char]
showsPrec :: Int -> SharedFormulaIndex -> ShowS
$cshowsPrec :: Int -> SharedFormulaIndex -> ShowS
Show, forall x. Rep SharedFormulaIndex x -> SharedFormulaIndex
forall x. SharedFormulaIndex -> Rep SharedFormulaIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SharedFormulaIndex x -> SharedFormulaIndex
$cfrom :: forall x. SharedFormulaIndex -> Rep SharedFormulaIndex x
Generic)
instance NFData SharedFormulaIndex
data SharedFormulaOptions = SharedFormulaOptions
{ SharedFormulaOptions -> CellRef
_sfoRef :: CellRef
, SharedFormulaOptions -> Formula
_sfoExpression :: Formula
}
deriving (SharedFormulaOptions -> SharedFormulaOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SharedFormulaOptions -> SharedFormulaOptions -> Bool
$c/= :: SharedFormulaOptions -> SharedFormulaOptions -> Bool
== :: SharedFormulaOptions -> SharedFormulaOptions -> Bool
$c== :: SharedFormulaOptions -> SharedFormulaOptions -> Bool
Eq, Int -> SharedFormulaOptions -> ShowS
[SharedFormulaOptions] -> ShowS
SharedFormulaOptions -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SharedFormulaOptions] -> ShowS
$cshowList :: [SharedFormulaOptions] -> ShowS
show :: SharedFormulaOptions -> [Char]
$cshow :: SharedFormulaOptions -> [Char]
showsPrec :: Int -> SharedFormulaOptions -> ShowS
$cshowsPrec :: Int -> SharedFormulaOptions -> ShowS
Show, forall x. Rep SharedFormulaOptions x -> SharedFormulaOptions
forall x. SharedFormulaOptions -> Rep SharedFormulaOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SharedFormulaOptions x -> SharedFormulaOptions
$cfrom :: forall x. SharedFormulaOptions -> Rep SharedFormulaOptions x
Generic)
instance NFData SharedFormulaOptions
simpleCellFormula :: Text -> CellFormula
simpleCellFormula :: Text -> CellFormula
simpleCellFormula Text
expr = CellFormula
{ _cellfExpression :: FormulaExpression
_cellfExpression = Formula -> FormulaExpression
NormalFormula forall a b. (a -> b) -> a -> b
$ Text -> Formula
Formula Text
expr
, _cellfAssignsToName :: Bool
_cellfAssignsToName = Bool
False
, _cellfCalculate :: Bool
_cellfCalculate = Bool
False
}
sharedFormulaByIndex :: SharedFormulaIndex -> CellFormula
sharedFormulaByIndex :: SharedFormulaIndex -> CellFormula
sharedFormulaByIndex SharedFormulaIndex
si =
CellFormula
{ _cellfExpression :: FormulaExpression
_cellfExpression = SharedFormulaIndex -> FormulaExpression
SharedFormula SharedFormulaIndex
si
, _cellfAssignsToName :: Bool
_cellfAssignsToName = Bool
False
, _cellfCalculate :: Bool
_cellfCalculate = Bool
False
}
data Cell = Cell
{ Cell -> Maybe Int
_cellStyle :: Maybe Int
, Cell -> Maybe CellValue
_cellValue :: Maybe CellValue
, :: Maybe Comment
, Cell -> Maybe CellFormula
_cellFormula :: Maybe CellFormula
} deriving (Cell -> Cell -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cell -> Cell -> Bool
$c/= :: Cell -> Cell -> Bool
== :: Cell -> Cell -> Bool
$c== :: Cell -> Cell -> Bool
Eq, Int -> Cell -> ShowS
[Cell] -> ShowS
Cell -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Cell] -> ShowS
$cshowList :: [Cell] -> ShowS
show :: Cell -> [Char]
$cshow :: Cell -> [Char]
showsPrec :: Int -> Cell -> ShowS
$cshowsPrec :: Int -> Cell -> ShowS
Show, forall x. Rep Cell x -> Cell
forall x. Cell -> Rep Cell x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Cell x -> Cell
$cfrom :: forall x. Cell -> Rep Cell x
Generic)
instance NFData Cell
instance Default Cell where
def :: Cell
def = Maybe Int
-> Maybe CellValue -> Maybe Comment -> Maybe CellFormula -> Cell
Cell forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
type CellMap = Map (RowIndex, ColumnIndex) Cell
formulaDataFromCursor ::
Cursor -> [(CellFormula, Maybe (SharedFormulaIndex, SharedFormulaOptions))]
formulaDataFromCursor :: Cursor
-> [(CellFormula,
Maybe (SharedFormulaIndex, SharedFormulaOptions))]
formulaDataFromCursor Cursor
cur = do
Bool
_cellfAssignsToName <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"bx" Bool
False Cursor
cur
Bool
_cellfCalculate <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"ca" Bool
False Cursor
cur
Text
t <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"t" Text
defaultFormulaType Cursor
cur
(FormulaExpression
_cellfExpression, Maybe (SharedFormulaIndex, SharedFormulaOptions)
shared) <-
case Text
t of
Text
d| Text
d forall a. Eq a => a -> a -> Bool
== Text
defaultFormulaType -> do
Formula
formula <- forall a. FromCursor a => Cursor -> [a]
fromCursor Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return (Formula -> FormulaExpression
NormalFormula Formula
formula, forall a. Maybe a
Nothing)
Text
"shared" -> do
let expr :: Maybe Formula
expr = forall a. [a] -> Maybe a
listToMaybe forall a b. (a -> b) -> a -> b
$ forall a. FromCursor a => Cursor -> [a]
fromCursor Cursor
cur
Maybe CellRef
ref <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"ref" Cursor
cur
SharedFormulaIndex
si <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"si" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return (SharedFormulaIndex -> FormulaExpression
SharedFormula SharedFormulaIndex
si, (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Applicative f => a -> f a
pure SharedFormulaIndex
si forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
(CellRef -> Formula -> SharedFormulaOptions
SharedFormulaOptions forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe CellRef
ref forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Formula
expr))
Text
_ ->
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"Unexpected formula type" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Text
t
forall (m :: * -> *) a. Monad m => a -> m a
return (CellFormula {Bool
FormulaExpression
_cellfExpression :: FormulaExpression
_cellfCalculate :: Bool
_cellfAssignsToName :: Bool
_cellfCalculate :: Bool
_cellfAssignsToName :: Bool
_cellfExpression :: FormulaExpression
..}, Maybe (SharedFormulaIndex, SharedFormulaOptions)
shared)
instance FromAttrVal SharedFormulaIndex where
fromAttrVal :: Reader SharedFormulaIndex
fromAttrVal = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Int -> SharedFormulaIndex
SharedFormulaIndex) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Reader a
fromAttrVal
instance FromAttrBs SharedFormulaIndex where
fromAttrBs :: ByteString -> Either Text SharedFormulaIndex
fromAttrBs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> SharedFormulaIndex
SharedFormulaIndex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrBs a => ByteString -> Either Text a
fromAttrBs
instance ToElement CellFormula where
toElement :: Name -> CellFormula -> Element
toElement Name
nm CellFormula {Bool
FormulaExpression
_cellfCalculate :: Bool
_cellfAssignsToName :: Bool
_cellfExpression :: FormulaExpression
_cellfCalculate :: CellFormula -> Bool
_cellfAssignsToName :: CellFormula -> Bool
_cellfExpression :: CellFormula -> FormulaExpression
..} =
Element
formulaEl {elementAttributes :: Map Name Text
elementAttributes = Element -> Map Name Text
elementAttributes Element
formulaEl forall a. Semigroup a => a -> a -> a
<> Map Name Text
commonAttrs}
where
commonAttrs :: Map Name Text
commonAttrs =
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$
forall a. [Maybe a] -> [a]
catMaybes
[ Name
"bx" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_cellfAssignsToName
, Name
"ca" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_cellfCalculate
, Name
"t" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef Text
defaultFormulaType Text
fType
]
(Element
formulaEl, Text
fType) =
case FormulaExpression
_cellfExpression of
NormalFormula Formula
f -> (forall a. ToElement a => Name -> a -> Element
toElement Name
nm Formula
f, Text
defaultFormulaType)
SharedFormula SharedFormulaIndex
si -> (Name -> [(Name, Text)] -> Element
leafElement Name
nm [Name
"si" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= SharedFormulaIndex
si], Text
"shared")
instance ToAttrVal SharedFormulaIndex where
toAttrVal :: SharedFormulaIndex -> Text
toAttrVal (SharedFormulaIndex Int
si) = forall a. ToAttrVal a => a -> Text
toAttrVal Int
si
applySharedFormulaOpts :: SharedFormulaOptions -> Element -> Element
applySharedFormulaOpts :: SharedFormulaOptions -> Element -> Element
applySharedFormulaOpts SharedFormulaOptions {Formula
CellRef
_sfoExpression :: Formula
_sfoRef :: CellRef
_sfoExpression :: SharedFormulaOptions -> Formula
_sfoRef :: SharedFormulaOptions -> CellRef
..} Element
el =
Element
el
{ elementAttributes :: Map Name Text
elementAttributes = Element -> Map Name Text
elementAttributes Element
el forall a. Semigroup a => a -> a -> a
<> forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [Name
"ref" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CellRef
_sfoRef]
, elementNodes :: [Node]
elementNodes = Text -> Node
NodeContent (Formula -> Text
unFormula Formula
_sfoExpression) forall a. a -> [a] -> [a]
: Element -> [Node]
elementNodes Element
el
}