{-# 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
(PivotTable -> PivotTable -> Bool)
-> (PivotTable -> PivotTable -> Bool) -> Eq PivotTable
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
(Int -> PivotTable -> ShowS)
-> (PivotTable -> String)
-> ([PivotTable] -> ShowS)
-> Show PivotTable
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. PivotTable -> Rep PivotTable x)
-> (forall x. Rep PivotTable x -> PivotTable) -> Generic PivotTable
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
(PivotFieldInfo -> PivotFieldInfo -> Bool)
-> (PivotFieldInfo -> PivotFieldInfo -> Bool) -> Eq PivotFieldInfo
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
(Int -> PivotFieldInfo -> ShowS)
-> (PivotFieldInfo -> String)
-> ([PivotFieldInfo] -> ShowS)
-> Show PivotFieldInfo
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. PivotFieldInfo -> Rep PivotFieldInfo x)
-> (forall x. Rep PivotFieldInfo x -> PivotFieldInfo)
-> Generic PivotFieldInfo
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

-- | Sort orders that can be applied to fields in a PivotTable
--
-- See 18.18.28 "ST_FieldSortType (Field Sort Type)" (p. 2454)
data FieldSortType
  = FieldSortAscending
  | FieldSortDescending
  | FieldSortManual
  deriving (FieldSortType -> FieldSortType -> Bool
(FieldSortType -> FieldSortType -> Bool)
-> (FieldSortType -> FieldSortType -> Bool) -> Eq FieldSortType
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
Eq FieldSortType
-> (FieldSortType -> FieldSortType -> Ordering)
-> (FieldSortType -> FieldSortType -> Bool)
-> (FieldSortType -> FieldSortType -> Bool)
-> (FieldSortType -> FieldSortType -> Bool)
-> (FieldSortType -> FieldSortType -> Bool)
-> (FieldSortType -> FieldSortType -> FieldSortType)
-> (FieldSortType -> FieldSortType -> FieldSortType)
-> Ord 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
$cp1Ord :: Eq FieldSortType
Ord, Int -> FieldSortType -> ShowS
[FieldSortType] -> ShowS
FieldSortType -> String
(Int -> FieldSortType -> ShowS)
-> (FieldSortType -> String)
-> ([FieldSortType] -> ShowS)
-> Show FieldSortType
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. FieldSortType -> Rep FieldSortType x)
-> (forall x. Rep FieldSortType x -> FieldSortType)
-> Generic FieldSortType
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
(PivotFieldName -> PivotFieldName -> Bool)
-> (PivotFieldName -> PivotFieldName -> Bool) -> Eq PivotFieldName
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
Eq PivotFieldName
-> (PivotFieldName -> PivotFieldName -> Ordering)
-> (PivotFieldName -> PivotFieldName -> Bool)
-> (PivotFieldName -> PivotFieldName -> Bool)
-> (PivotFieldName -> PivotFieldName -> Bool)
-> (PivotFieldName -> PivotFieldName -> Bool)
-> (PivotFieldName -> PivotFieldName -> PivotFieldName)
-> (PivotFieldName -> PivotFieldName -> PivotFieldName)
-> Ord 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
$cp1Ord :: Eq PivotFieldName
Ord, Int -> PivotFieldName -> ShowS
[PivotFieldName] -> ShowS
PivotFieldName -> String
(Int -> PivotFieldName -> ShowS)
-> (PivotFieldName -> String)
-> ([PivotFieldName] -> ShowS)
-> Show PivotFieldName
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. PivotFieldName -> Rep PivotFieldName x)
-> (forall x. Rep PivotFieldName x -> PivotFieldName)
-> Generic PivotFieldName
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
(PositionedField -> PositionedField -> Bool)
-> (PositionedField -> PositionedField -> Bool)
-> Eq PositionedField
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
Eq PositionedField
-> (PositionedField -> PositionedField -> Ordering)
-> (PositionedField -> PositionedField -> Bool)
-> (PositionedField -> PositionedField -> Bool)
-> (PositionedField -> PositionedField -> Bool)
-> (PositionedField -> PositionedField -> Bool)
-> (PositionedField -> PositionedField -> PositionedField)
-> (PositionedField -> PositionedField -> PositionedField)
-> Ord 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
$cp1Ord :: Eq PositionedField
Ord, Int -> PositionedField -> ShowS
[PositionedField] -> ShowS
PositionedField -> String
(Int -> PositionedField -> ShowS)
-> (PositionedField -> String)
-> ([PositionedField] -> ShowS)
-> Show PositionedField
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. PositionedField -> Rep PositionedField x)
-> (forall x. Rep PositionedField x -> PositionedField)
-> Generic PositionedField
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
(DataField -> DataField -> Bool)
-> (DataField -> DataField -> Bool) -> Eq DataField
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
(Int -> DataField -> ShowS)
-> (DataField -> String)
-> ([DataField] -> ShowS)
-> Show DataField
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. DataField -> Rep DataField x)
-> (forall x. Rep DataField x -> DataField) -> Generic DataField
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 consolidation functions specified by the user and used to
-- consolidate ranges of data
--
-- See 18.18.17 "ST_DataConsolidateFunction (Data Consolidation
-- Functions)" (p.  2447)
data ConsolidateFunction
  = ConsolidateAverage
    -- ^ The average of the values.
  | ConsolidateCount
    -- ^ The number of data values. The Count consolidation function
    -- works the same as the COUNTA worksheet function.
  | ConsolidateCountNums
    -- ^ The number of data values that are numbers. The Count Nums
    -- consolidation function works the same as the COUNT worksheet
    -- function.
  | ConsolidateMaximum
    -- ^ The largest value.
  | ConsolidateMinimum
    -- ^ The smallest value.
  | ConsolidateProduct
    -- ^ The product of the values.
  | ConsolidateStdDev
    -- ^ An estimate of the standard deviation of a population, where
    -- the sample is a subset of the entire population.
  | ConsolidateStdDevP
    -- ^ The standard deviation of a population, where the population
    -- is all of the data to be summarized.
  | ConsolidateSum
    -- ^ The sum of the values.
  | ConsolidateVariance
    -- ^ An estimate of the variance of a population, where the sample
    -- is a subset of the entire population.
  | ConsolidateVarP
    -- ^ The variance of a population, where the population is all of
    -- the data to be summarized.
  deriving (ConsolidateFunction -> ConsolidateFunction -> Bool
(ConsolidateFunction -> ConsolidateFunction -> Bool)
-> (ConsolidateFunction -> ConsolidateFunction -> Bool)
-> Eq ConsolidateFunction
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
(Int -> ConsolidateFunction -> ShowS)
-> (ConsolidateFunction -> String)
-> ([ConsolidateFunction] -> ShowS)
-> Show ConsolidateFunction
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. ConsolidateFunction -> Rep ConsolidateFunction x)
-> (forall x. Rep ConsolidateFunction x -> ConsolidateFunction)
-> Generic ConsolidateFunction
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

{-------------------------------------------------------------------------------
  Rendering
-------------------------------------------------------------------------------}

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) = Text -> Text
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"

{-------------------------------------------------------------------------------
  Parsing
-------------------------------------------------------------------------------}

instance FromAttrVal ConsolidateFunction where
  fromAttrVal :: Reader ConsolidateFunction
fromAttrVal Text
"average" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateAverage
  fromAttrVal Text
"count" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateCount
  fromAttrVal Text
"countNums" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateCountNums
  fromAttrVal Text
"max" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateMaximum
  fromAttrVal Text
"min" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateMinimum
  fromAttrVal Text
"product" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateProduct
  fromAttrVal Text
"stdDev" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateStdDev
  fromAttrVal Text
"stdDevp" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateStdDevP
  fromAttrVal Text
"sum" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateSum
  fromAttrVal Text
"var" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateVariance
  fromAttrVal Text
"varp" = ConsolidateFunction -> Either String (ConsolidateFunction, Text)
forall a. a -> Either String (a, Text)
readSuccess ConsolidateFunction
ConsolidateVarP
  fromAttrVal Text
t = Text -> Reader ConsolidateFunction
forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"ConsolidateFunction" Text
t

instance FromAttrVal PivotFieldName where
  fromAttrVal :: Reader PivotFieldName
fromAttrVal = ((Text, Text) -> (PivotFieldName, Text))
-> Either String (Text, Text)
-> Either String (PivotFieldName, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Text -> PivotFieldName) -> (Text, Text) -> (PivotFieldName, Text)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Text -> PivotFieldName
PivotFieldName) (Either String (Text, Text)
 -> Either String (PivotFieldName, Text))
-> (Text -> Either String (Text, Text)) -> Reader PivotFieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either String (Text, Text)
forall a. FromAttrVal a => Reader a
fromAttrVal

instance FromAttrVal FieldSortType where
  fromAttrVal :: Reader FieldSortType
fromAttrVal Text
"manual" = FieldSortType -> Either String (FieldSortType, Text)
forall a. a -> Either String (a, Text)
readSuccess FieldSortType
FieldSortManual
  fromAttrVal Text
"ascending" = FieldSortType -> Either String (FieldSortType, Text)
forall a. a -> Either String (a, Text)
readSuccess FieldSortType
FieldSortAscending
  fromAttrVal Text
"descending" = FieldSortType -> Either String (FieldSortType, Text)
forall a. a -> Either String (a, Text)
readSuccess FieldSortType
FieldSortDescending
  fromAttrVal Text
t = Text -> Reader FieldSortType
forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"FieldSortType" Text
t