{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Types.PivotTable
( PivotTable(..)
, PivotFieldName(..)
, PivotFieldInfo(..)
, FieldSortType(..)
, PositionedField(..)
, DataField(..)
, ConsolidateFunction(..)
) where
import Control.Arrow (first)
import Control.DeepSeq (NFData)
import Data.Text (Text)
import GHC.Generics (Generic)
import Codec.Xlsx.Types.Common
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Writer.Internal
data PivotTable = PivotTable
{ PivotTable -> Text
_pvtName :: Text
, PivotTable -> Text
_pvtDataCaption :: Text
, PivotTable -> [PositionedField]
_pvtRowFields :: [PositionedField]
, PivotTable -> [PositionedField]
_pvtColumnFields :: [PositionedField]
, PivotTable -> [DataField]
_pvtDataFields :: [DataField]
, PivotTable -> [PivotFieldInfo]
_pvtFields :: [PivotFieldInfo]
, PivotTable -> Bool
_pvtRowGrandTotals :: Bool
, PivotTable -> Bool
_pvtColumnGrandTotals :: Bool
, PivotTable -> Bool
_pvtOutline :: Bool
, PivotTable -> Bool
_pvtOutlineData :: Bool
, PivotTable -> CellRef
_pvtLocation :: CellRef
, PivotTable -> Text
_pvtSrcSheet :: Text
, PivotTable -> CellRef
_pvtSrcRef :: Range
} deriving (PivotTable -> PivotTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PivotTable -> PivotTable -> Bool
$c/= :: PivotTable -> PivotTable -> Bool
== :: PivotTable -> PivotTable -> Bool
$c== :: PivotTable -> PivotTable -> Bool
Eq, Int -> PivotTable -> ShowS
[PivotTable] -> ShowS
PivotTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PivotTable] -> ShowS
$cshowList :: [PivotTable] -> ShowS
show :: PivotTable -> String
$cshow :: PivotTable -> String
showsPrec :: Int -> PivotTable -> ShowS
$cshowsPrec :: Int -> PivotTable -> ShowS
Show, forall x. Rep PivotTable x -> PivotTable
forall x. PivotTable -> Rep PivotTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PivotTable x -> PivotTable
$cfrom :: forall x. PivotTable -> Rep PivotTable x
Generic)
instance NFData PivotTable
data PivotFieldInfo = PivotFieldInfo
{ PivotFieldInfo -> Maybe PivotFieldName
_pfiName :: Maybe PivotFieldName
, PivotFieldInfo -> Bool
_pfiOutline :: Bool
, PivotFieldInfo -> FieldSortType
_pfiSortType :: FieldSortType
, PivotFieldInfo -> [CellValue]
_pfiHiddenItems :: [CellValue]
} deriving (PivotFieldInfo -> PivotFieldInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PivotFieldInfo -> PivotFieldInfo -> Bool
$c/= :: PivotFieldInfo -> PivotFieldInfo -> Bool
== :: PivotFieldInfo -> PivotFieldInfo -> Bool
$c== :: PivotFieldInfo -> PivotFieldInfo -> Bool
Eq, Int -> PivotFieldInfo -> ShowS
[PivotFieldInfo] -> ShowS
PivotFieldInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PivotFieldInfo] -> ShowS
$cshowList :: [PivotFieldInfo] -> ShowS
show :: PivotFieldInfo -> String
$cshow :: PivotFieldInfo -> String
showsPrec :: Int -> PivotFieldInfo -> ShowS
$cshowsPrec :: Int -> PivotFieldInfo -> ShowS
Show, forall x. Rep PivotFieldInfo x -> PivotFieldInfo
forall x. PivotFieldInfo -> Rep PivotFieldInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PivotFieldInfo x -> PivotFieldInfo
$cfrom :: forall x. PivotFieldInfo -> Rep PivotFieldInfo x
Generic)
instance NFData PivotFieldInfo
data FieldSortType
= FieldSortAscending
| FieldSortDescending
| FieldSortManual
deriving (FieldSortType -> FieldSortType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldSortType -> FieldSortType -> Bool
$c/= :: FieldSortType -> FieldSortType -> Bool
== :: FieldSortType -> FieldSortType -> Bool
$c== :: FieldSortType -> FieldSortType -> Bool
Eq, Eq FieldSortType
FieldSortType -> FieldSortType -> Bool
FieldSortType -> FieldSortType -> Ordering
FieldSortType -> FieldSortType -> FieldSortType
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 :: FieldSortType -> FieldSortType -> FieldSortType
$cmin :: FieldSortType -> FieldSortType -> FieldSortType
max :: FieldSortType -> FieldSortType -> FieldSortType
$cmax :: FieldSortType -> FieldSortType -> FieldSortType
>= :: FieldSortType -> FieldSortType -> Bool
$c>= :: FieldSortType -> FieldSortType -> Bool
> :: FieldSortType -> FieldSortType -> Bool
$c> :: FieldSortType -> FieldSortType -> Bool
<= :: FieldSortType -> FieldSortType -> Bool
$c<= :: FieldSortType -> FieldSortType -> Bool
< :: FieldSortType -> FieldSortType -> Bool
$c< :: FieldSortType -> FieldSortType -> Bool
compare :: FieldSortType -> FieldSortType -> Ordering
$ccompare :: FieldSortType -> FieldSortType -> Ordering
Ord, Int -> FieldSortType -> ShowS
[FieldSortType] -> ShowS
FieldSortType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FieldSortType] -> ShowS
$cshowList :: [FieldSortType] -> ShowS
show :: FieldSortType -> String
$cshow :: FieldSortType -> String
showsPrec :: Int -> FieldSortType -> ShowS
$cshowsPrec :: Int -> FieldSortType -> ShowS
Show, forall x. Rep FieldSortType x -> FieldSortType
forall x. FieldSortType -> Rep FieldSortType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FieldSortType x -> FieldSortType
$cfrom :: forall x. FieldSortType -> Rep FieldSortType x
Generic)
instance NFData FieldSortType
newtype PivotFieldName =
PivotFieldName Text
deriving (PivotFieldName -> PivotFieldName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PivotFieldName -> PivotFieldName -> Bool
$c/= :: PivotFieldName -> PivotFieldName -> Bool
== :: PivotFieldName -> PivotFieldName -> Bool
$c== :: PivotFieldName -> PivotFieldName -> Bool
Eq, Eq PivotFieldName
PivotFieldName -> PivotFieldName -> Bool
PivotFieldName -> PivotFieldName -> Ordering
PivotFieldName -> PivotFieldName -> PivotFieldName
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 :: PivotFieldName -> PivotFieldName -> PivotFieldName
$cmin :: PivotFieldName -> PivotFieldName -> PivotFieldName
max :: PivotFieldName -> PivotFieldName -> PivotFieldName
$cmax :: PivotFieldName -> PivotFieldName -> PivotFieldName
>= :: PivotFieldName -> PivotFieldName -> Bool
$c>= :: PivotFieldName -> PivotFieldName -> Bool
> :: PivotFieldName -> PivotFieldName -> Bool
$c> :: PivotFieldName -> PivotFieldName -> Bool
<= :: PivotFieldName -> PivotFieldName -> Bool
$c<= :: PivotFieldName -> PivotFieldName -> Bool
< :: PivotFieldName -> PivotFieldName -> Bool
$c< :: PivotFieldName -> PivotFieldName -> Bool
compare :: PivotFieldName -> PivotFieldName -> Ordering
$ccompare :: PivotFieldName -> PivotFieldName -> Ordering
Ord, Int -> PivotFieldName -> ShowS
[PivotFieldName] -> ShowS
PivotFieldName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PivotFieldName] -> ShowS
$cshowList :: [PivotFieldName] -> ShowS
show :: PivotFieldName -> String
$cshow :: PivotFieldName -> String
showsPrec :: Int -> PivotFieldName -> ShowS
$cshowsPrec :: Int -> PivotFieldName -> ShowS
Show, forall x. Rep PivotFieldName x -> PivotFieldName
forall x. PivotFieldName -> Rep PivotFieldName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PivotFieldName x -> PivotFieldName
$cfrom :: forall x. PivotFieldName -> Rep PivotFieldName x
Generic)
instance NFData PivotFieldName
data PositionedField
= DataPosition
| FieldPosition PivotFieldName
deriving (PositionedField -> PositionedField -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositionedField -> PositionedField -> Bool
$c/= :: PositionedField -> PositionedField -> Bool
== :: PositionedField -> PositionedField -> Bool
$c== :: PositionedField -> PositionedField -> Bool
Eq, Eq PositionedField
PositionedField -> PositionedField -> Bool
PositionedField -> PositionedField -> Ordering
PositionedField -> PositionedField -> PositionedField
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 :: PositionedField -> PositionedField -> PositionedField
$cmin :: PositionedField -> PositionedField -> PositionedField
max :: PositionedField -> PositionedField -> PositionedField
$cmax :: PositionedField -> PositionedField -> PositionedField
>= :: PositionedField -> PositionedField -> Bool
$c>= :: PositionedField -> PositionedField -> Bool
> :: PositionedField -> PositionedField -> Bool
$c> :: PositionedField -> PositionedField -> Bool
<= :: PositionedField -> PositionedField -> Bool
$c<= :: PositionedField -> PositionedField -> Bool
< :: PositionedField -> PositionedField -> Bool
$c< :: PositionedField -> PositionedField -> Bool
compare :: PositionedField -> PositionedField -> Ordering
$ccompare :: PositionedField -> PositionedField -> Ordering
Ord, Int -> PositionedField -> ShowS
[PositionedField] -> ShowS
PositionedField -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PositionedField] -> ShowS
$cshowList :: [PositionedField] -> ShowS
show :: PositionedField -> String
$cshow :: PositionedField -> String
showsPrec :: Int -> PositionedField -> ShowS
$cshowsPrec :: Int -> PositionedField -> ShowS
Show, forall x. Rep PositionedField x -> PositionedField
forall x. PositionedField -> Rep PositionedField x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PositionedField x -> PositionedField
$cfrom :: forall x. PositionedField -> Rep PositionedField x
Generic)
instance NFData PositionedField
data DataField = DataField
{ DataField -> PivotFieldName
_dfField :: PivotFieldName
, DataField -> Text
_dfName :: Text
, DataField -> ConsolidateFunction
_dfFunction :: ConsolidateFunction
} deriving (DataField -> DataField -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataField -> DataField -> Bool
$c/= :: DataField -> DataField -> Bool
== :: DataField -> DataField -> Bool
$c== :: DataField -> DataField -> Bool
Eq, Int -> DataField -> ShowS
[DataField] -> ShowS
DataField -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataField] -> ShowS
$cshowList :: [DataField] -> ShowS
show :: DataField -> String
$cshow :: DataField -> String
showsPrec :: Int -> DataField -> ShowS
$cshowsPrec :: Int -> DataField -> ShowS
Show, forall x. Rep DataField x -> DataField
forall x. DataField -> Rep DataField x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataField x -> DataField
$cfrom :: forall x. DataField -> Rep DataField x
Generic)
instance NFData DataField
data ConsolidateFunction
= ConsolidateAverage
| ConsolidateCount
| ConsolidateCountNums
| ConsolidateMaximum
| ConsolidateMinimum
| ConsolidateProduct
| ConsolidateStdDev
| ConsolidateStdDevP
| ConsolidateSum
| ConsolidateVariance
| ConsolidateVarP
deriving (ConsolidateFunction -> ConsolidateFunction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConsolidateFunction -> ConsolidateFunction -> Bool
$c/= :: ConsolidateFunction -> ConsolidateFunction -> Bool
== :: ConsolidateFunction -> ConsolidateFunction -> Bool
$c== :: ConsolidateFunction -> ConsolidateFunction -> Bool
Eq, Int -> ConsolidateFunction -> ShowS
[ConsolidateFunction] -> ShowS
ConsolidateFunction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConsolidateFunction] -> ShowS
$cshowList :: [ConsolidateFunction] -> ShowS
show :: ConsolidateFunction -> String
$cshow :: ConsolidateFunction -> String
showsPrec :: Int -> ConsolidateFunction -> ShowS
$cshowsPrec :: Int -> ConsolidateFunction -> ShowS
Show, forall x. Rep ConsolidateFunction x -> ConsolidateFunction
forall x. ConsolidateFunction -> Rep ConsolidateFunction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConsolidateFunction x -> ConsolidateFunction
$cfrom :: forall x. ConsolidateFunction -> Rep ConsolidateFunction x
Generic)
instance NFData ConsolidateFunction
instance ToAttrVal ConsolidateFunction where
toAttrVal :: ConsolidateFunction -> Text
toAttrVal ConsolidateFunction
ConsolidateAverage = Text
"average"
toAttrVal ConsolidateFunction
ConsolidateCount = Text
"count"
toAttrVal ConsolidateFunction
ConsolidateCountNums = Text
"countNums"
toAttrVal ConsolidateFunction
ConsolidateMaximum = Text
"max"
toAttrVal ConsolidateFunction
ConsolidateMinimum = Text
"min"
toAttrVal ConsolidateFunction
ConsolidateProduct = Text
"product"
toAttrVal ConsolidateFunction
ConsolidateStdDev = Text
"stdDev"
toAttrVal ConsolidateFunction
ConsolidateStdDevP = Text
"stdDevp"
toAttrVal ConsolidateFunction
ConsolidateSum = Text
"sum"
toAttrVal ConsolidateFunction
ConsolidateVariance = Text
"var"
toAttrVal ConsolidateFunction
ConsolidateVarP = Text
"varp"
instance ToAttrVal PivotFieldName where
toAttrVal :: PivotFieldName -> Text
toAttrVal (PivotFieldName Text
n) = forall a. ToAttrVal a => a -> Text
toAttrVal Text
n
instance ToAttrVal FieldSortType where
toAttrVal :: FieldSortType -> Text
toAttrVal FieldSortType
FieldSortManual = Text
"manual"
toAttrVal FieldSortType
FieldSortAscending = Text
"ascending"
toAttrVal FieldSortType
FieldSortDescending = Text
"descending"
instance FromAttrVal ConsolidateFunction where
fromAttrVal :: Reader ConsolidateFunction
fromAttrVal Text
"average" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateAverage
fromAttrVal Text
"count" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateCount
fromAttrVal Text
"countNums" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateCountNums
fromAttrVal Text
"max" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateMaximum
fromAttrVal Text
"min" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateMinimum
fromAttrVal Text
"product" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateProduct
fromAttrVal Text
"stdDev" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateStdDev
fromAttrVal Text
"stdDevp" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateStdDevP
fromAttrVal Text
"sum" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateSum
fromAttrVal Text
"var" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateVariance
fromAttrVal Text
"varp" = forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateVarP
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"ConsolidateFunction" Text
t
instance FromAttrVal PivotFieldName where
fromAttrVal :: Reader PivotFieldName
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 Text -> PivotFieldName
PivotFieldName) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Reader a
fromAttrVal
instance FromAttrVal FieldSortType where
fromAttrVal :: Reader FieldSortType
fromAttrVal Text
"manual" = forall a. a -> Either String (a, Text)
readSuccess FieldSortType
FieldSortManual
fromAttrVal Text
"ascending" = forall a. a -> Either String (a, Text)
readSuccess FieldSortType
FieldSortAscending
fromAttrVal Text
"descending" = forall a. a -> Either String (a, Text)
readSuccess FieldSortType
FieldSortDescending
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"FieldSortType" Text
t