{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
module Codec.Xlsx.Types.ConditionalFormatting
( ConditionalFormatting
, CfRule(..)
, NStdDev(..)
, Inclusion(..)
, CfValue(..)
, MinCfValue(..)
, MaxCfValue(..)
, Condition(..)
, OperatorExpression(..)
, TimePeriod(..)
, IconSetOptions(..)
, IconSetType(..)
, DataBarOptions(..)
, dataBarWithColor
, cfrCondition
, cfrDxfId
, cfrPriority
, cfrStopIfTrue
, isoIconSet
, isoValues
, isoReverse
, isoShowValue
, dboMaxLength
, dboMinLength
, dboShowValue
, dboMinimum
, dboMaximum
, dboColor
, topCfPriority
) where
import Control.Arrow (first, right)
import Control.DeepSeq (NFData)
#ifdef USE_MICROLENS
import Lens.Micro.TH (makeLenses)
#else
import Control.Lens (makeLenses)
#endif
import Data.Bool (bool)
import Data.ByteString (ByteString)
import Data.Default
import Data.Map (Map)
import qualified Data.Map as M
import Data.Maybe
import Data.Monoid ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import GHC.Generics (Generic)
import Text.XML
import Text.XML.Cursor hiding (bool)
import qualified Xeno.DOM as Xeno
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Types.Common
import Codec.Xlsx.Types.StyleSheet (Color)
import Codec.Xlsx.Writer.Internal
data OperatorExpression
= OpBeginsWith Formula
| OpBetween Formula Formula
| OpContainsText Formula
| OpEndsWith Formula
| OpEqual Formula
| OpGreaterThan Formula
| OpGreaterThanOrEqual Formula
| OpLessThan Formula
| OpLessThanOrEqual Formula
| OpNotBetween Formula Formula
| OpNotContains Formula
| OpNotEqual Formula
deriving (OperatorExpression -> OperatorExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperatorExpression -> OperatorExpression -> Bool
$c/= :: OperatorExpression -> OperatorExpression -> Bool
== :: OperatorExpression -> OperatorExpression -> Bool
$c== :: OperatorExpression -> OperatorExpression -> Bool
Eq, Eq OperatorExpression
OperatorExpression -> OperatorExpression -> Bool
OperatorExpression -> OperatorExpression -> Ordering
OperatorExpression -> OperatorExpression -> OperatorExpression
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 :: OperatorExpression -> OperatorExpression -> OperatorExpression
$cmin :: OperatorExpression -> OperatorExpression -> OperatorExpression
max :: OperatorExpression -> OperatorExpression -> OperatorExpression
$cmax :: OperatorExpression -> OperatorExpression -> OperatorExpression
>= :: OperatorExpression -> OperatorExpression -> Bool
$c>= :: OperatorExpression -> OperatorExpression -> Bool
> :: OperatorExpression -> OperatorExpression -> Bool
$c> :: OperatorExpression -> OperatorExpression -> Bool
<= :: OperatorExpression -> OperatorExpression -> Bool
$c<= :: OperatorExpression -> OperatorExpression -> Bool
< :: OperatorExpression -> OperatorExpression -> Bool
$c< :: OperatorExpression -> OperatorExpression -> Bool
compare :: OperatorExpression -> OperatorExpression -> Ordering
$ccompare :: OperatorExpression -> OperatorExpression -> Ordering
Ord, Int -> OperatorExpression -> ShowS
[OperatorExpression] -> ShowS
OperatorExpression -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [OperatorExpression] -> ShowS
$cshowList :: [OperatorExpression] -> ShowS
show :: OperatorExpression -> [Char]
$cshow :: OperatorExpression -> [Char]
showsPrec :: Int -> OperatorExpression -> ShowS
$cshowsPrec :: Int -> OperatorExpression -> ShowS
Show, forall x. Rep OperatorExpression x -> OperatorExpression
forall x. OperatorExpression -> Rep OperatorExpression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OperatorExpression x -> OperatorExpression
$cfrom :: forall x. OperatorExpression -> Rep OperatorExpression x
Generic)
instance NFData OperatorExpression
data TimePeriod
= PerLast7Days
| PerLastMonth
| PerLastWeek
| PerNextMonth
| PerNextWeek
| PerThisMonth
| PerThisWeek
| PerToday
| PerTomorrow
| PerYesterday
deriving (TimePeriod -> TimePeriod -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimePeriod -> TimePeriod -> Bool
$c/= :: TimePeriod -> TimePeriod -> Bool
== :: TimePeriod -> TimePeriod -> Bool
$c== :: TimePeriod -> TimePeriod -> Bool
Eq, Eq TimePeriod
TimePeriod -> TimePeriod -> Bool
TimePeriod -> TimePeriod -> Ordering
TimePeriod -> TimePeriod -> TimePeriod
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 :: TimePeriod -> TimePeriod -> TimePeriod
$cmin :: TimePeriod -> TimePeriod -> TimePeriod
max :: TimePeriod -> TimePeriod -> TimePeriod
$cmax :: TimePeriod -> TimePeriod -> TimePeriod
>= :: TimePeriod -> TimePeriod -> Bool
$c>= :: TimePeriod -> TimePeriod -> Bool
> :: TimePeriod -> TimePeriod -> Bool
$c> :: TimePeriod -> TimePeriod -> Bool
<= :: TimePeriod -> TimePeriod -> Bool
$c<= :: TimePeriod -> TimePeriod -> Bool
< :: TimePeriod -> TimePeriod -> Bool
$c< :: TimePeriod -> TimePeriod -> Bool
compare :: TimePeriod -> TimePeriod -> Ordering
$ccompare :: TimePeriod -> TimePeriod -> Ordering
Ord, Int -> TimePeriod -> ShowS
[TimePeriod] -> ShowS
TimePeriod -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [TimePeriod] -> ShowS
$cshowList :: [TimePeriod] -> ShowS
show :: TimePeriod -> [Char]
$cshow :: TimePeriod -> [Char]
showsPrec :: Int -> TimePeriod -> ShowS
$cshowsPrec :: Int -> TimePeriod -> ShowS
Show, forall x. Rep TimePeriod x -> TimePeriod
forall x. TimePeriod -> Rep TimePeriod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TimePeriod x -> TimePeriod
$cfrom :: forall x. TimePeriod -> Rep TimePeriod x
Generic)
instance NFData TimePeriod
data Inclusion
= Inclusive
| Exclusive
deriving (Inclusion -> Inclusion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Inclusion -> Inclusion -> Bool
$c/= :: Inclusion -> Inclusion -> Bool
== :: Inclusion -> Inclusion -> Bool
$c== :: Inclusion -> Inclusion -> Bool
Eq, Eq Inclusion
Inclusion -> Inclusion -> Bool
Inclusion -> Inclusion -> Ordering
Inclusion -> Inclusion -> Inclusion
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 :: Inclusion -> Inclusion -> Inclusion
$cmin :: Inclusion -> Inclusion -> Inclusion
max :: Inclusion -> Inclusion -> Inclusion
$cmax :: Inclusion -> Inclusion -> Inclusion
>= :: Inclusion -> Inclusion -> Bool
$c>= :: Inclusion -> Inclusion -> Bool
> :: Inclusion -> Inclusion -> Bool
$c> :: Inclusion -> Inclusion -> Bool
<= :: Inclusion -> Inclusion -> Bool
$c<= :: Inclusion -> Inclusion -> Bool
< :: Inclusion -> Inclusion -> Bool
$c< :: Inclusion -> Inclusion -> Bool
compare :: Inclusion -> Inclusion -> Ordering
$ccompare :: Inclusion -> Inclusion -> Ordering
Ord, Int -> Inclusion -> ShowS
[Inclusion] -> ShowS
Inclusion -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Inclusion] -> ShowS
$cshowList :: [Inclusion] -> ShowS
show :: Inclusion -> [Char]
$cshow :: Inclusion -> [Char]
showsPrec :: Int -> Inclusion -> ShowS
$cshowsPrec :: Int -> Inclusion -> ShowS
Show, forall x. Rep Inclusion x -> Inclusion
forall x. Inclusion -> Rep Inclusion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Inclusion x -> Inclusion
$cfrom :: forall x. Inclusion -> Rep Inclusion x
Generic)
instance NFData Inclusion
newtype NStdDev =
NStdDev Int
deriving (NStdDev -> NStdDev -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NStdDev -> NStdDev -> Bool
$c/= :: NStdDev -> NStdDev -> Bool
== :: NStdDev -> NStdDev -> Bool
$c== :: NStdDev -> NStdDev -> Bool
Eq, Eq NStdDev
NStdDev -> NStdDev -> Bool
NStdDev -> NStdDev -> Ordering
NStdDev -> NStdDev -> NStdDev
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 :: NStdDev -> NStdDev -> NStdDev
$cmin :: NStdDev -> NStdDev -> NStdDev
max :: NStdDev -> NStdDev -> NStdDev
$cmax :: NStdDev -> NStdDev -> NStdDev
>= :: NStdDev -> NStdDev -> Bool
$c>= :: NStdDev -> NStdDev -> Bool
> :: NStdDev -> NStdDev -> Bool
$c> :: NStdDev -> NStdDev -> Bool
<= :: NStdDev -> NStdDev -> Bool
$c<= :: NStdDev -> NStdDev -> Bool
< :: NStdDev -> NStdDev -> Bool
$c< :: NStdDev -> NStdDev -> Bool
compare :: NStdDev -> NStdDev -> Ordering
$ccompare :: NStdDev -> NStdDev -> Ordering
Ord, Int -> NStdDev -> ShowS
[NStdDev] -> ShowS
NStdDev -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [NStdDev] -> ShowS
$cshowList :: [NStdDev] -> ShowS
show :: NStdDev -> [Char]
$cshow :: NStdDev -> [Char]
showsPrec :: Int -> NStdDev -> ShowS
$cshowsPrec :: Int -> NStdDev -> ShowS
Show, forall x. Rep NStdDev x -> NStdDev
forall x. NStdDev -> Rep NStdDev x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NStdDev x -> NStdDev
$cfrom :: forall x. NStdDev -> Rep NStdDev x
Generic)
instance NFData NStdDev
data Condition
= AboveAverage Inclusion (Maybe NStdDev)
| BeginsWith Text
| BelowAverage Inclusion (Maybe NStdDev)
| BottomNPercent Int
| BottomNValues Int
| CellIs OperatorExpression
| ColorScale2 MinCfValue Color MaxCfValue Color
| ColorScale3 MinCfValue Color CfValue Color MaxCfValue Color
| ContainsBlanks
| ContainsErrors
| ContainsText Text
| DataBar DataBarOptions
| DoesNotContainErrors
| DoesNotContainBlanks
| DoesNotContainText Text
| DuplicateValues
| EndsWith Text
| Expression Formula
| IconSet IconSetOptions
| InTimePeriod TimePeriod
| TopNPercent Int
| TopNValues Int
| UniqueValues
deriving (Condition -> Condition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Condition -> Condition -> Bool
$c/= :: Condition -> Condition -> Bool
== :: Condition -> Condition -> Bool
$c== :: Condition -> Condition -> Bool
Eq, Eq Condition
Condition -> Condition -> Bool
Condition -> Condition -> Ordering
Condition -> Condition -> Condition
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 :: Condition -> Condition -> Condition
$cmin :: Condition -> Condition -> Condition
max :: Condition -> Condition -> Condition
$cmax :: Condition -> Condition -> Condition
>= :: Condition -> Condition -> Bool
$c>= :: Condition -> Condition -> Bool
> :: Condition -> Condition -> Bool
$c> :: Condition -> Condition -> Bool
<= :: Condition -> Condition -> Bool
$c<= :: Condition -> Condition -> Bool
< :: Condition -> Condition -> Bool
$c< :: Condition -> Condition -> Bool
compare :: Condition -> Condition -> Ordering
$ccompare :: Condition -> Condition -> Ordering
Ord, Int -> Condition -> ShowS
[Condition] -> ShowS
Condition -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Condition] -> ShowS
$cshowList :: [Condition] -> ShowS
show :: Condition -> [Char]
$cshow :: Condition -> [Char]
showsPrec :: Int -> Condition -> ShowS
$cshowsPrec :: Int -> Condition -> ShowS
Show, forall x. Rep Condition x -> Condition
forall x. Condition -> Rep Condition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Condition x -> Condition
$cfrom :: forall x. Condition -> Rep Condition x
Generic)
instance NFData Condition
data CfValue
= CfValue Double
| CfPercent Double
| CfPercentile Double
| CfFormula Formula
deriving (CfValue -> CfValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CfValue -> CfValue -> Bool
$c/= :: CfValue -> CfValue -> Bool
== :: CfValue -> CfValue -> Bool
$c== :: CfValue -> CfValue -> Bool
Eq, Eq CfValue
CfValue -> CfValue -> Bool
CfValue -> CfValue -> Ordering
CfValue -> CfValue -> CfValue
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 :: CfValue -> CfValue -> CfValue
$cmin :: CfValue -> CfValue -> CfValue
max :: CfValue -> CfValue -> CfValue
$cmax :: CfValue -> CfValue -> CfValue
>= :: CfValue -> CfValue -> Bool
$c>= :: CfValue -> CfValue -> Bool
> :: CfValue -> CfValue -> Bool
$c> :: CfValue -> CfValue -> Bool
<= :: CfValue -> CfValue -> Bool
$c<= :: CfValue -> CfValue -> Bool
< :: CfValue -> CfValue -> Bool
$c< :: CfValue -> CfValue -> Bool
compare :: CfValue -> CfValue -> Ordering
$ccompare :: CfValue -> CfValue -> Ordering
Ord, Int -> CfValue -> ShowS
[CfValue] -> ShowS
CfValue -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CfValue] -> ShowS
$cshowList :: [CfValue] -> ShowS
show :: CfValue -> [Char]
$cshow :: CfValue -> [Char]
showsPrec :: Int -> CfValue -> ShowS
$cshowsPrec :: Int -> CfValue -> ShowS
Show, forall x. Rep CfValue x -> CfValue
forall x. CfValue -> Rep CfValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CfValue x -> CfValue
$cfrom :: forall x. CfValue -> Rep CfValue x
Generic)
instance NFData CfValue
data MinCfValue
= CfvMin
| MinCfValue CfValue
deriving (MinCfValue -> MinCfValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MinCfValue -> MinCfValue -> Bool
$c/= :: MinCfValue -> MinCfValue -> Bool
== :: MinCfValue -> MinCfValue -> Bool
$c== :: MinCfValue -> MinCfValue -> Bool
Eq, Eq MinCfValue
MinCfValue -> MinCfValue -> Bool
MinCfValue -> MinCfValue -> Ordering
MinCfValue -> MinCfValue -> MinCfValue
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 :: MinCfValue -> MinCfValue -> MinCfValue
$cmin :: MinCfValue -> MinCfValue -> MinCfValue
max :: MinCfValue -> MinCfValue -> MinCfValue
$cmax :: MinCfValue -> MinCfValue -> MinCfValue
>= :: MinCfValue -> MinCfValue -> Bool
$c>= :: MinCfValue -> MinCfValue -> Bool
> :: MinCfValue -> MinCfValue -> Bool
$c> :: MinCfValue -> MinCfValue -> Bool
<= :: MinCfValue -> MinCfValue -> Bool
$c<= :: MinCfValue -> MinCfValue -> Bool
< :: MinCfValue -> MinCfValue -> Bool
$c< :: MinCfValue -> MinCfValue -> Bool
compare :: MinCfValue -> MinCfValue -> Ordering
$ccompare :: MinCfValue -> MinCfValue -> Ordering
Ord, Int -> MinCfValue -> ShowS
[MinCfValue] -> ShowS
MinCfValue -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [MinCfValue] -> ShowS
$cshowList :: [MinCfValue] -> ShowS
show :: MinCfValue -> [Char]
$cshow :: MinCfValue -> [Char]
showsPrec :: Int -> MinCfValue -> ShowS
$cshowsPrec :: Int -> MinCfValue -> ShowS
Show, forall x. Rep MinCfValue x -> MinCfValue
forall x. MinCfValue -> Rep MinCfValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MinCfValue x -> MinCfValue
$cfrom :: forall x. MinCfValue -> Rep MinCfValue x
Generic)
instance NFData MinCfValue
data MaxCfValue
= CfvMax
| MaxCfValue CfValue
deriving (MaxCfValue -> MaxCfValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaxCfValue -> MaxCfValue -> Bool
$c/= :: MaxCfValue -> MaxCfValue -> Bool
== :: MaxCfValue -> MaxCfValue -> Bool
$c== :: MaxCfValue -> MaxCfValue -> Bool
Eq, Eq MaxCfValue
MaxCfValue -> MaxCfValue -> Bool
MaxCfValue -> MaxCfValue -> Ordering
MaxCfValue -> MaxCfValue -> MaxCfValue
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 :: MaxCfValue -> MaxCfValue -> MaxCfValue
$cmin :: MaxCfValue -> MaxCfValue -> MaxCfValue
max :: MaxCfValue -> MaxCfValue -> MaxCfValue
$cmax :: MaxCfValue -> MaxCfValue -> MaxCfValue
>= :: MaxCfValue -> MaxCfValue -> Bool
$c>= :: MaxCfValue -> MaxCfValue -> Bool
> :: MaxCfValue -> MaxCfValue -> Bool
$c> :: MaxCfValue -> MaxCfValue -> Bool
<= :: MaxCfValue -> MaxCfValue -> Bool
$c<= :: MaxCfValue -> MaxCfValue -> Bool
< :: MaxCfValue -> MaxCfValue -> Bool
$c< :: MaxCfValue -> MaxCfValue -> Bool
compare :: MaxCfValue -> MaxCfValue -> Ordering
$ccompare :: MaxCfValue -> MaxCfValue -> Ordering
Ord, Int -> MaxCfValue -> ShowS
[MaxCfValue] -> ShowS
MaxCfValue -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [MaxCfValue] -> ShowS
$cshowList :: [MaxCfValue] -> ShowS
show :: MaxCfValue -> [Char]
$cshow :: MaxCfValue -> [Char]
showsPrec :: Int -> MaxCfValue -> ShowS
$cshowsPrec :: Int -> MaxCfValue -> ShowS
Show, forall x. Rep MaxCfValue x -> MaxCfValue
forall x. MaxCfValue -> Rep MaxCfValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MaxCfValue x -> MaxCfValue
$cfrom :: forall x. MaxCfValue -> Rep MaxCfValue x
Generic)
instance NFData MaxCfValue
data CfvType =
CfvtFormula
| CfvtMax
| CfvtMin
| CfvtNum
| CfvtPercent
| CfvtPercentile
deriving (CfvType -> CfvType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CfvType -> CfvType -> Bool
$c/= :: CfvType -> CfvType -> Bool
== :: CfvType -> CfvType -> Bool
$c== :: CfvType -> CfvType -> Bool
Eq, Eq CfvType
CfvType -> CfvType -> Bool
CfvType -> CfvType -> Ordering
CfvType -> CfvType -> CfvType
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 :: CfvType -> CfvType -> CfvType
$cmin :: CfvType -> CfvType -> CfvType
max :: CfvType -> CfvType -> CfvType
$cmax :: CfvType -> CfvType -> CfvType
>= :: CfvType -> CfvType -> Bool
$c>= :: CfvType -> CfvType -> Bool
> :: CfvType -> CfvType -> Bool
$c> :: CfvType -> CfvType -> Bool
<= :: CfvType -> CfvType -> Bool
$c<= :: CfvType -> CfvType -> Bool
< :: CfvType -> CfvType -> Bool
$c< :: CfvType -> CfvType -> Bool
compare :: CfvType -> CfvType -> Ordering
$ccompare :: CfvType -> CfvType -> Ordering
Ord, Int -> CfvType -> ShowS
[CfvType] -> ShowS
CfvType -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CfvType] -> ShowS
$cshowList :: [CfvType] -> ShowS
show :: CfvType -> [Char]
$cshow :: CfvType -> [Char]
showsPrec :: Int -> CfvType -> ShowS
$cshowsPrec :: Int -> CfvType -> ShowS
Show, forall x. Rep CfvType x -> CfvType
forall x. CfvType -> Rep CfvType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CfvType x -> CfvType
$cfrom :: forall x. CfvType -> Rep CfvType x
Generic)
instance NFData CfvType
data IconSetOptions = IconSetOptions
{ IconSetOptions -> IconSetType
_isoIconSet :: IconSetType
, IconSetOptions -> [CfValue]
_isoValues :: [CfValue]
, IconSetOptions -> Bool
_isoReverse :: Bool
, IconSetOptions -> Bool
_isoShowValue :: Bool
} deriving (IconSetOptions -> IconSetOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IconSetOptions -> IconSetOptions -> Bool
$c/= :: IconSetOptions -> IconSetOptions -> Bool
== :: IconSetOptions -> IconSetOptions -> Bool
$c== :: IconSetOptions -> IconSetOptions -> Bool
Eq, Eq IconSetOptions
IconSetOptions -> IconSetOptions -> Bool
IconSetOptions -> IconSetOptions -> Ordering
IconSetOptions -> IconSetOptions -> IconSetOptions
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 :: IconSetOptions -> IconSetOptions -> IconSetOptions
$cmin :: IconSetOptions -> IconSetOptions -> IconSetOptions
max :: IconSetOptions -> IconSetOptions -> IconSetOptions
$cmax :: IconSetOptions -> IconSetOptions -> IconSetOptions
>= :: IconSetOptions -> IconSetOptions -> Bool
$c>= :: IconSetOptions -> IconSetOptions -> Bool
> :: IconSetOptions -> IconSetOptions -> Bool
$c> :: IconSetOptions -> IconSetOptions -> Bool
<= :: IconSetOptions -> IconSetOptions -> Bool
$c<= :: IconSetOptions -> IconSetOptions -> Bool
< :: IconSetOptions -> IconSetOptions -> Bool
$c< :: IconSetOptions -> IconSetOptions -> Bool
compare :: IconSetOptions -> IconSetOptions -> Ordering
$ccompare :: IconSetOptions -> IconSetOptions -> Ordering
Ord, Int -> IconSetOptions -> ShowS
[IconSetOptions] -> ShowS
IconSetOptions -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [IconSetOptions] -> ShowS
$cshowList :: [IconSetOptions] -> ShowS
show :: IconSetOptions -> [Char]
$cshow :: IconSetOptions -> [Char]
showsPrec :: Int -> IconSetOptions -> ShowS
$cshowsPrec :: Int -> IconSetOptions -> ShowS
Show, forall x. Rep IconSetOptions x -> IconSetOptions
forall x. IconSetOptions -> Rep IconSetOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IconSetOptions x -> IconSetOptions
$cfrom :: forall x. IconSetOptions -> Rep IconSetOptions x
Generic)
instance NFData IconSetOptions
data IconSetType =
IconSet3Arrows
| IconSet3ArrowsGray
| IconSet3Flags
| IconSet3Signs
| IconSet3Symbols
| IconSet3Symbols2
| IconSet3TrafficLights1
| IconSet3TrafficLights2
| IconSet4Arrows
| IconSet4ArrowsGray
| IconSet4Rating
| IconSet4RedToBlack
| IconSet4TrafficLights
| IconSet5Arrows
| IconSet5ArrowsGray
| IconSet5Quarters
| IconSet5Rating
deriving (IconSetType -> IconSetType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IconSetType -> IconSetType -> Bool
$c/= :: IconSetType -> IconSetType -> Bool
== :: IconSetType -> IconSetType -> Bool
$c== :: IconSetType -> IconSetType -> Bool
Eq, Eq IconSetType
IconSetType -> IconSetType -> Bool
IconSetType -> IconSetType -> Ordering
IconSetType -> IconSetType -> IconSetType
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 :: IconSetType -> IconSetType -> IconSetType
$cmin :: IconSetType -> IconSetType -> IconSetType
max :: IconSetType -> IconSetType -> IconSetType
$cmax :: IconSetType -> IconSetType -> IconSetType
>= :: IconSetType -> IconSetType -> Bool
$c>= :: IconSetType -> IconSetType -> Bool
> :: IconSetType -> IconSetType -> Bool
$c> :: IconSetType -> IconSetType -> Bool
<= :: IconSetType -> IconSetType -> Bool
$c<= :: IconSetType -> IconSetType -> Bool
< :: IconSetType -> IconSetType -> Bool
$c< :: IconSetType -> IconSetType -> Bool
compare :: IconSetType -> IconSetType -> Ordering
$ccompare :: IconSetType -> IconSetType -> Ordering
Ord, Int -> IconSetType -> ShowS
[IconSetType] -> ShowS
IconSetType -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [IconSetType] -> ShowS
$cshowList :: [IconSetType] -> ShowS
show :: IconSetType -> [Char]
$cshow :: IconSetType -> [Char]
showsPrec :: Int -> IconSetType -> ShowS
$cshowsPrec :: Int -> IconSetType -> ShowS
Show, forall x. Rep IconSetType x -> IconSetType
forall x. IconSetType -> Rep IconSetType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IconSetType x -> IconSetType
$cfrom :: forall x. IconSetType -> Rep IconSetType x
Generic)
instance NFData IconSetType
data DataBarOptions = DataBarOptions
{ DataBarOptions -> Int
_dboMaxLength :: Int
, DataBarOptions -> Int
_dboMinLength :: Int
, DataBarOptions -> Bool
_dboShowValue :: Bool
, DataBarOptions -> MinCfValue
_dboMinimum :: MinCfValue
, DataBarOptions -> MaxCfValue
_dboMaximum :: MaxCfValue
, DataBarOptions -> Color
_dboColor :: Color
} deriving (DataBarOptions -> DataBarOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataBarOptions -> DataBarOptions -> Bool
$c/= :: DataBarOptions -> DataBarOptions -> Bool
== :: DataBarOptions -> DataBarOptions -> Bool
$c== :: DataBarOptions -> DataBarOptions -> Bool
Eq, Eq DataBarOptions
DataBarOptions -> DataBarOptions -> Bool
DataBarOptions -> DataBarOptions -> Ordering
DataBarOptions -> DataBarOptions -> DataBarOptions
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 :: DataBarOptions -> DataBarOptions -> DataBarOptions
$cmin :: DataBarOptions -> DataBarOptions -> DataBarOptions
max :: DataBarOptions -> DataBarOptions -> DataBarOptions
$cmax :: DataBarOptions -> DataBarOptions -> DataBarOptions
>= :: DataBarOptions -> DataBarOptions -> Bool
$c>= :: DataBarOptions -> DataBarOptions -> Bool
> :: DataBarOptions -> DataBarOptions -> Bool
$c> :: DataBarOptions -> DataBarOptions -> Bool
<= :: DataBarOptions -> DataBarOptions -> Bool
$c<= :: DataBarOptions -> DataBarOptions -> Bool
< :: DataBarOptions -> DataBarOptions -> Bool
$c< :: DataBarOptions -> DataBarOptions -> Bool
compare :: DataBarOptions -> DataBarOptions -> Ordering
$ccompare :: DataBarOptions -> DataBarOptions -> Ordering
Ord, Int -> DataBarOptions -> ShowS
[DataBarOptions] -> ShowS
DataBarOptions -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DataBarOptions] -> ShowS
$cshowList :: [DataBarOptions] -> ShowS
show :: DataBarOptions -> [Char]
$cshow :: DataBarOptions -> [Char]
showsPrec :: Int -> DataBarOptions -> ShowS
$cshowsPrec :: Int -> DataBarOptions -> ShowS
Show, forall x. Rep DataBarOptions x -> DataBarOptions
forall x. DataBarOptions -> Rep DataBarOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataBarOptions x -> DataBarOptions
$cfrom :: forall x. DataBarOptions -> Rep DataBarOptions x
Generic)
instance NFData DataBarOptions
defaultDboMaxLength :: Int
defaultDboMaxLength :: Int
defaultDboMaxLength = Int
90
defaultDboMinLength :: Int
defaultDboMinLength :: Int
defaultDboMinLength = Int
10
dataBarWithColor :: Color -> Condition
dataBarWithColor :: Color -> Condition
dataBarWithColor Color
c =
DataBarOptions -> Condition
DataBar
DataBarOptions
{ _dboMaxLength :: Int
_dboMaxLength = Int
defaultDboMaxLength
, _dboMinLength :: Int
_dboMinLength = Int
defaultDboMinLength
, _dboShowValue :: Bool
_dboShowValue = Bool
True
, _dboMinimum :: MinCfValue
_dboMinimum = MinCfValue
CfvMin
, _dboMaximum :: MaxCfValue
_dboMaximum = MaxCfValue
CfvMax
, _dboColor :: Color
_dboColor = Color
c
}
data CfRule = CfRule
{ CfRule -> Condition
_cfrCondition :: Condition
, CfRule -> Maybe Int
_cfrDxfId :: Maybe Int
, CfRule -> Int
_cfrPriority :: Int
, CfRule -> Maybe Bool
_cfrStopIfTrue :: Maybe Bool
} deriving (CfRule -> CfRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CfRule -> CfRule -> Bool
$c/= :: CfRule -> CfRule -> Bool
== :: CfRule -> CfRule -> Bool
$c== :: CfRule -> CfRule -> Bool
Eq, Eq CfRule
CfRule -> CfRule -> Bool
CfRule -> CfRule -> Ordering
CfRule -> CfRule -> CfRule
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 :: CfRule -> CfRule -> CfRule
$cmin :: CfRule -> CfRule -> CfRule
max :: CfRule -> CfRule -> CfRule
$cmax :: CfRule -> CfRule -> CfRule
>= :: CfRule -> CfRule -> Bool
$c>= :: CfRule -> CfRule -> Bool
> :: CfRule -> CfRule -> Bool
$c> :: CfRule -> CfRule -> Bool
<= :: CfRule -> CfRule -> Bool
$c<= :: CfRule -> CfRule -> Bool
< :: CfRule -> CfRule -> Bool
$c< :: CfRule -> CfRule -> Bool
compare :: CfRule -> CfRule -> Ordering
$ccompare :: CfRule -> CfRule -> Ordering
Ord, Int -> CfRule -> ShowS
[CfRule] -> ShowS
CfRule -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CfRule] -> ShowS
$cshowList :: [CfRule] -> ShowS
show :: CfRule -> [Char]
$cshow :: CfRule -> [Char]
showsPrec :: Int -> CfRule -> ShowS
$cshowsPrec :: Int -> CfRule -> ShowS
Show, forall x. Rep CfRule x -> CfRule
forall x. CfRule -> Rep CfRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CfRule x -> CfRule
$cfrom :: forall x. CfRule -> Rep CfRule x
Generic)
instance NFData CfRule
instance Default IconSetOptions where
def :: IconSetOptions
def =
IconSetOptions
{ _isoIconSet :: IconSetType
_isoIconSet = IconSetType
IconSet3TrafficLights1
, _isoValues :: [CfValue]
_isoValues = [Double -> CfValue
CfPercent Double
0, Double -> CfValue
CfPercent Double
33.33, Double -> CfValue
CfPercent Double
66.67]
, _isoReverse :: Bool
_isoReverse = Bool
False
, _isoShowValue :: Bool
_isoShowValue = Bool
True
}
makeLenses ''CfRule
makeLenses ''IconSetOptions
makeLenses ''DataBarOptions
type ConditionalFormatting = [CfRule]
topCfPriority :: Int
topCfPriority :: Int
topCfPriority = Int
1
instance FromCursor CfRule where
fromCursor :: Cursor -> [CfRule]
fromCursor Cursor
cur = do
Maybe Int
_cfrDxfId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"dxfId" Cursor
cur
Int
_cfrPriority <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"priority" Cursor
cur
Maybe Bool
_cfrStopIfTrue <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"stopIfTrue" Cursor
cur
Text
cfType <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"type" Cursor
cur
Condition
_cfrCondition <- Text -> Cursor -> [Condition]
readCondition Text
cfType Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return CfRule{Int
Maybe Bool
Maybe Int
Condition
_cfrCondition :: Condition
_cfrStopIfTrue :: Maybe Bool
_cfrPriority :: Int
_cfrDxfId :: Maybe Int
_cfrStopIfTrue :: Maybe Bool
_cfrPriority :: Int
_cfrDxfId :: Maybe Int
_cfrCondition :: Condition
..}
readCondition :: Text -> Cursor -> [Condition]
readCondition :: Text -> Cursor -> [Condition]
readCondition Text
"aboveAverage" Cursor
cur = do
Bool
above <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"aboveAverage" Bool
True Cursor
cur
Inclusion
inclusion <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"equalAverage" Inclusion
Exclusive Cursor
cur
Maybe NStdDev
nStdDev <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"stdDev" Cursor
cur
if Bool
above
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Inclusion -> Maybe NStdDev -> Condition
AboveAverage Inclusion
inclusion Maybe NStdDev
nStdDev
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Inclusion -> Maybe NStdDev -> Condition
BelowAverage Inclusion
inclusion Maybe NStdDev
nStdDev
readCondition Text
"beginsWith" Cursor
cur = do
Text
txt <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"text" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Condition
BeginsWith Text
txt
readCondition Text
"colorScale" Cursor
cur = do
let cfvos :: [Node]
cfvos = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"colorScale") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (Text -> Name
n_ Text
"cfvo") forall node a b.
(Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b]
&| forall node. Cursor node -> node
node
colors :: [Node]
colors = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"colorScale") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (Text -> Name
n_ Text
"color") forall node a b.
(Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b]
&| forall node. Cursor node -> node
node
case ([Node]
cfvos, [Node]
colors) of
([Node
n1, Node
n2], [Node
cn1, Node
cn2]) -> do
MinCfValue
mincfv <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
n1
Color
minc <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
cn1
MaxCfValue
maxcfv <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
n2
Color
maxc <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
cn2
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ MinCfValue -> Color -> MaxCfValue -> Color -> Condition
ColorScale2 MinCfValue
mincfv Color
minc MaxCfValue
maxcfv Color
maxc
([Node
n1, Node
n2, Node
n3], [Node
cn1, Node
cn2, Node
cn3]) -> do
MinCfValue
mincfv <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
n1
Color
minc <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
cn1
CfValue
midcfv <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
n2
Color
midc <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
cn2
MaxCfValue
maxcfv <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
n3
Color
maxc <- forall a. FromCursor a => Cursor -> [a]
fromCursor forall a b. (a -> b) -> a -> b
$ Node -> Cursor
fromNode Node
cn3
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ MinCfValue
-> Color -> CfValue -> Color -> MaxCfValue -> Color -> Condition
ColorScale3 MinCfValue
mincfv Color
minc CfValue
midcfv Color
midc MaxCfValue
maxcfv Color
maxc
([Node], [Node])
_ ->
forall a. HasCallStack => [Char] -> a
error [Char]
"Malformed colorScale condition"
readCondition Text
"cellIs" Cursor
cur = do
Text
operator <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"operator" Cursor
cur
let formulas :: [Formula]
formulas = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"formula") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
OperatorExpression
expr <- Text -> [Formula] -> [OperatorExpression]
readOpExpression Text
operator [Formula]
formulas
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ OperatorExpression -> Condition
CellIs OperatorExpression
expr
readCondition Text
"containsBlanks" Cursor
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
ContainsBlanks
readCondition Text
"containsErrors" Cursor
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
ContainsErrors
readCondition Text
"containsText" Cursor
cur = do
Text
txt <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"text" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Condition
ContainsText Text
txt
readCondition Text
"dataBar" Cursor
cur = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DataBarOptions -> Condition
DataBar forall a b. (a -> b) -> a -> b
$ Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"dataBar") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
readCondition Text
"duplicateValues" Cursor
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
DuplicateValues
readCondition Text
"endsWith" Cursor
cur = do
Text
txt <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"text" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Condition
EndsWith Text
txt
readCondition Text
"expression" Cursor
cur = do
Formula
formula <- Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"formula") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Formula -> Condition
Expression Formula
formula
readCondition Text
"iconSet" Cursor
cur = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IconSetOptions -> Condition
IconSet forall a b. (a -> b) -> a -> b
$ Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"iconSet") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
readCondition Text
"notContainsBlanks" Cursor
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
DoesNotContainBlanks
readCondition Text
"notContainsErrors" Cursor
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
DoesNotContainErrors
readCondition Text
"notContainsText" Cursor
cur = do
Text
txt <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"text" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Condition
DoesNotContainText Text
txt
readCondition Text
"timePeriod" Cursor
cur = do
TimePeriod
period <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"timePeriod" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TimePeriod -> Condition
InTimePeriod TimePeriod
period
readCondition Text
"top10" Cursor
cur = do
Bool
bottom <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"bottom" Bool
False Cursor
cur
Bool
percent <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"percent" Bool
False Cursor
cur
Int
rank <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"rank" Cursor
cur
case (Bool
bottom, Bool
percent) of
(Bool
True, Bool
True) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
BottomNPercent Int
rank
(Bool
True, Bool
False) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
BottomNValues Int
rank
(Bool
False, Bool
True) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
TopNPercent Int
rank
(Bool
False, Bool
False) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
TopNValues Int
rank
readCondition Text
"uniqueValues" Cursor
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
UniqueValues
readCondition Text
t Cursor
_ = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Unexpected conditional formatting type " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Text
t
readOpExpression :: Text -> [Formula] -> [OperatorExpression]
readOpExpression :: Text -> [Formula] -> [OperatorExpression]
readOpExpression Text
"beginsWith" [Formula
f] = [Formula -> OperatorExpression
OpBeginsWith Formula
f ]
readOpExpression Text
"between" [Formula
f1, Formula
f2] = [Formula -> Formula -> OperatorExpression
OpBetween Formula
f1 Formula
f2]
readOpExpression Text
"containsText" [Formula
f] = [Formula -> OperatorExpression
OpContainsText Formula
f]
readOpExpression Text
"endsWith" [Formula
f] = [Formula -> OperatorExpression
OpEndsWith Formula
f]
readOpExpression Text
"equal" [Formula
f] = [Formula -> OperatorExpression
OpEqual Formula
f]
readOpExpression Text
"greaterThan" [Formula
f] = [Formula -> OperatorExpression
OpGreaterThan Formula
f]
readOpExpression Text
"greaterThanOrEqual" [Formula
f] = [Formula -> OperatorExpression
OpGreaterThanOrEqual Formula
f]
readOpExpression Text
"lessThan" [Formula
f] = [Formula -> OperatorExpression
OpLessThan Formula
f]
readOpExpression Text
"lessThanOrEqual" [Formula
f] = [Formula -> OperatorExpression
OpLessThanOrEqual Formula
f]
readOpExpression Text
"notBetween" [Formula
f1, Formula
f2] = [Formula -> Formula -> OperatorExpression
OpNotBetween Formula
f1 Formula
f2]
readOpExpression Text
"notContains" [Formula
f] = [Formula -> OperatorExpression
OpNotContains Formula
f]
readOpExpression Text
"notEqual" [Formula
f] = [Formula -> OperatorExpression
OpNotEqual Formula
f]
readOpExpression Text
_ [Formula]
_ = []
instance FromXenoNode CfRule where
fromXenoNode :: Node -> Either Text CfRule
fromXenoNode Node
root = forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Maybe Int
_cfrDxfId <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"dxfId"
Int
_cfrPriority <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"priority"
Maybe Bool
_cfrStopIfTrue <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"stopIfTrue"
ByteString
cfType <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"type"
Condition
_cfrCondition <- ByteString -> AttrParser Condition
readConditionX ByteString
cfType
forall (m :: * -> *) a. Monad m => a -> m a
return CfRule {Int
Maybe Bool
Maybe Int
Condition
_cfrCondition :: Condition
_cfrStopIfTrue :: Maybe Bool
_cfrPriority :: Int
_cfrDxfId :: Maybe Int
_cfrStopIfTrue :: Maybe Bool
_cfrPriority :: Int
_cfrDxfId :: Maybe Int
_cfrCondition :: Condition
..}
where
readConditionX :: ByteString -> AttrParser Condition
readConditionX (ByteString
"aboveAverage" :: ByteString) = do
Bool
above <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"aboveAverage" Bool
True
Inclusion
inclusion <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"equalAverage" Inclusion
Exclusive
Maybe NStdDev
nStdDev <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"stdDev"
if Bool
above
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Inclusion -> Maybe NStdDev -> Condition
AboveAverage Inclusion
inclusion Maybe NStdDev
nStdDev
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Inclusion -> Maybe NStdDev -> Condition
BelowAverage Inclusion
inclusion Maybe NStdDev
nStdDev
readConditionX ByteString
"beginsWith" = Text -> Condition
BeginsWith forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"text"
readConditionX ByteString
"colorScale" = forall a. Either Text a -> AttrParser a
toAttrParser forall a b. (a -> b) -> a -> b
$ do
Maybe ([Node], [Node])
xs <- forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
ByteString -> (Node -> Either Text a) -> ChildCollector (Maybe a)
maybeParse ByteString
"colorScale" forall a b. (a -> b) -> a -> b
$ \Node
node ->
forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
node forall a b. (a -> b) -> a -> b
$ (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> ChildCollector [Node]
childList ByteString
"cfvo"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ByteString -> ChildCollector [Node]
childList ByteString
"color"
case Maybe ([Node], [Node])
xs of
Just ([Node
n1, Node
n2], [Node
cn1, Node
cn2]) -> do
MinCfValue
mincfv <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
n1
Color
minc <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
cn1
MaxCfValue
maxcfv <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
n2
Color
maxc <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
cn2
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ MinCfValue -> Color -> MaxCfValue -> Color -> Condition
ColorScale2 MinCfValue
mincfv Color
minc MaxCfValue
maxcfv Color
maxc
Just ([Node
n1, Node
n2, Node
n3], [Node
cn1, Node
cn2, Node
cn3]) -> do
MinCfValue
mincfv <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
n1
Color
minc <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
cn1
CfValue
midcfv <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
n2
Color
midc <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
cn2
MaxCfValue
maxcfv <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
n3
Color
maxc <- forall a. FromXenoNode a => Node -> Either Text a
fromXenoNode Node
cn3
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ MinCfValue
-> Color -> CfValue -> Color -> MaxCfValue -> Color -> Condition
ColorScale3 MinCfValue
mincfv Color
minc CfValue
midcfv Color
midc MaxCfValue
maxcfv Color
maxc
Maybe ([Node], [Node])
_ ->
forall a b. a -> Either a b
Left Text
"Malformed colorScale condition"
readConditionX ByteString
"cellIs" = do
ByteString
operator <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"operator"
[Formula]
formulas <- forall a. Either Text a -> AttrParser a
toAttrParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$ forall a. FromXenoNode a => ByteString -> ChildCollector [a]
fromChildList ByteString
"formula"
case (ByteString
operator, [Formula]
formulas) of
(ByteString
"beginsWith" :: ByteString, [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpBeginsWith Formula
f
(ByteString
"between", [Formula
f1, Formula
f2]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> Formula -> OperatorExpression
OpBetween Formula
f1 Formula
f2
(ByteString
"containsText", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpContainsText Formula
f
(ByteString
"endsWith", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpEndsWith Formula
f
(ByteString
"equal", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpEqual Formula
f
(ByteString
"greaterThan", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpGreaterThan Formula
f
(ByteString
"greaterThanOrEqual", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpGreaterThanOrEqual Formula
f
(ByteString
"lessThan", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpLessThan Formula
f
(ByteString
"lessThanOrEqual", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpLessThanOrEqual Formula
f
(ByteString
"notBetween", [Formula
f1, Formula
f2]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> Formula -> OperatorExpression
OpNotBetween Formula
f1 Formula
f2
(ByteString
"notContains", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpNotContains Formula
f
(ByteString
"notEqual", [Formula
f]) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. OperatorExpression -> Condition
CellIs forall a b. (a -> b) -> a -> b
$ Formula -> OperatorExpression
OpNotEqual Formula
f
(ByteString, [Formula])
_ -> forall a. Either Text a -> AttrParser a
toAttrParser forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left Text
"Bad cellIs rule"
readConditionX ByteString
"containsBlanks" = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
ContainsBlanks
readConditionX ByteString
"containsErrors" = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
ContainsErrors
readConditionX ByteString
"containsText" = Text -> Condition
ContainsText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"text"
readConditionX ByteString
"dataBar" =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DataBarOptions -> Condition
DataBar forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Either Text a -> AttrParser a
toAttrParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$ forall a. FromXenoNode a => ByteString -> ChildCollector a
fromChild ByteString
"dataBar"
readConditionX ByteString
"duplicateValues" = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
DuplicateValues
readConditionX ByteString
"endsWith" = Text -> Condition
EndsWith forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"text"
readConditionX ByteString
"expression" =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Formula -> Condition
Expression forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Either Text a -> AttrParser a
toAttrParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$ forall a. FromXenoNode a => ByteString -> ChildCollector a
fromChild ByteString
"formula"
readConditionX ByteString
"iconSet" =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IconSetOptions -> Condition
IconSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Either Text a -> AttrParser a
toAttrParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$ forall a. FromXenoNode a => ByteString -> ChildCollector a
fromChild ByteString
"iconSet"
readConditionX ByteString
"notContainsBlanks" = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
DoesNotContainBlanks
readConditionX ByteString
"notContainsErrors" = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
DoesNotContainErrors
readConditionX ByteString
"notContainsText" =
Text -> Condition
DoesNotContainText forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"text"
readConditionX ByteString
"timePeriod" = TimePeriod -> Condition
InTimePeriod forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"timePeriod"
readConditionX ByteString
"top10" = do
Bool
bottom <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"bottom" Bool
False
Bool
percent <- forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"percent" Bool
False
Int
rank <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"rank"
case (Bool
bottom, Bool
percent) of
(Bool
True, Bool
True) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
BottomNPercent Int
rank
(Bool
True, Bool
False) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
BottomNValues Int
rank
(Bool
False, Bool
True) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
TopNPercent Int
rank
(Bool
False, Bool
False) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int -> Condition
TopNValues Int
rank
readConditionX ByteString
"uniqueValues" = forall (m :: * -> *) a. Monad m => a -> m a
return Condition
UniqueValues
readConditionX ByteString
x =
forall a. Either Text a -> AttrParser a
toAttrParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text
"Unexpected conditional formatting type " forall a. Semigroup a => a -> a -> a
<> [Char] -> Text
T.pack (forall a. Show a => a -> [Char]
show ByteString
x)
instance FromAttrVal TimePeriod where
fromAttrVal :: Reader TimePeriod
fromAttrVal Text
"last7Days" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerLast7Days
fromAttrVal Text
"lastMonth" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerLastMonth
fromAttrVal Text
"lastWeek" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerLastWeek
fromAttrVal Text
"nextMonth" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerNextMonth
fromAttrVal Text
"nextWeek" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerNextWeek
fromAttrVal Text
"thisMonth" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerThisMonth
fromAttrVal Text
"thisWeek" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerThisWeek
fromAttrVal Text
"today" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerToday
fromAttrVal Text
"tomorrow" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerTomorrow
fromAttrVal Text
"yesterday" = forall a. a -> Either [Char] (a, Text)
readSuccess TimePeriod
PerYesterday
fromAttrVal Text
t = forall a. Text -> Text -> Either [Char] (a, Text)
invalidText Text
"TimePeriod" Text
t
instance FromAttrBs TimePeriod where
fromAttrBs :: ByteString -> Either Text TimePeriod
fromAttrBs ByteString
"last7Days" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerLast7Days
fromAttrBs ByteString
"lastMonth" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerLastMonth
fromAttrBs ByteString
"lastWeek" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerLastWeek
fromAttrBs ByteString
"nextMonth" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerNextMonth
fromAttrBs ByteString
"nextWeek" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerNextWeek
fromAttrBs ByteString
"thisMonth" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerThisMonth
fromAttrBs ByteString
"thisWeek" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerThisWeek
fromAttrBs ByteString
"today" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerToday
fromAttrBs ByteString
"tomorrow" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerTomorrow
fromAttrBs ByteString
"yesterday" = forall (m :: * -> *) a. Monad m => a -> m a
return TimePeriod
PerYesterday
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"TimePeriod" ByteString
x
instance FromAttrVal CfvType where
fromAttrVal :: Reader CfvType
fromAttrVal Text
"num" = forall a. a -> Either [Char] (a, Text)
readSuccess CfvType
CfvtNum
fromAttrVal Text
"percent" = forall a. a -> Either [Char] (a, Text)
readSuccess CfvType
CfvtPercent
fromAttrVal Text
"max" = forall a. a -> Either [Char] (a, Text)
readSuccess CfvType
CfvtMax
fromAttrVal Text
"min" = forall a. a -> Either [Char] (a, Text)
readSuccess CfvType
CfvtMin
fromAttrVal Text
"formula" = forall a. a -> Either [Char] (a, Text)
readSuccess CfvType
CfvtFormula
fromAttrVal Text
"percentile" = forall a. a -> Either [Char] (a, Text)
readSuccess CfvType
CfvtPercentile
fromAttrVal Text
t = forall a. Text -> Text -> Either [Char] (a, Text)
invalidText Text
"CfvType" Text
t
instance FromAttrBs CfvType where
fromAttrBs :: ByteString -> Either Text CfvType
fromAttrBs ByteString
"num" = forall (m :: * -> *) a. Monad m => a -> m a
return CfvType
CfvtNum
fromAttrBs ByteString
"percent" = forall (m :: * -> *) a. Monad m => a -> m a
return CfvType
CfvtPercent
fromAttrBs ByteString
"max" = forall (m :: * -> *) a. Monad m => a -> m a
return CfvType
CfvtMax
fromAttrBs ByteString
"min" = forall (m :: * -> *) a. Monad m => a -> m a
return CfvType
CfvtMin
fromAttrBs ByteString
"formula" = forall (m :: * -> *) a. Monad m => a -> m a
return CfvType
CfvtFormula
fromAttrBs ByteString
"percentile" = forall (m :: * -> *) a. Monad m => a -> m a
return CfvType
CfvtPercentile
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"CfvType" ByteString
x
readCfValue :: (CfValue -> a) -> [a] -> [a] -> Cursor -> [a]
readCfValue :: forall a. (CfValue -> a) -> [a] -> [a] -> Cursor -> [a]
readCfValue CfValue -> a
f [a]
minVal [a]
maxVal Cursor
c = do
CfvType
vType <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"type" Cursor
c
case CfvType
vType of
CfvType
CfvtNum -> do
Double
v <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"val" Cursor
c
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Double -> CfValue
CfValue Double
v
CfvType
CfvtFormula -> do
Formula
v <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"val" Cursor
c
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Formula -> CfValue
CfFormula Formula
v
CfvType
CfvtPercent -> do
Double
v <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"val" Cursor
c
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Double -> CfValue
CfPercent Double
v
CfvType
CfvtPercentile -> do
Double
v <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"val" Cursor
c
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Double -> CfValue
CfPercentile Double
v
CfvType
CfvtMin -> [a]
minVal
CfvType
CfvtMax -> [a]
maxVal
readCfValueX ::
(CfValue -> a)
-> Either Text a
-> Either Text a
-> Xeno.Node
-> Either Text a
readCfValueX :: forall a.
(CfValue -> a)
-> Either Text a -> Either Text a -> Node -> Either Text a
readCfValueX CfValue -> a
f Either Text a
minVal Either Text a
maxVal Node
root =
forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
CfvType
vType <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"type"
case CfvType
vType of
CfvType
CfvtNum -> do
Double
v <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"val"
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Double -> CfValue
CfValue Double
v
CfvType
CfvtFormula -> do
Formula
v <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"val"
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Formula -> CfValue
CfFormula Formula
v
CfvType
CfvtPercent -> do
Double
v <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"val"
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Double -> CfValue
CfPercent Double
v
CfvType
CfvtPercentile -> do
Double
v <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"val"
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. CfValue -> a
f forall a b. (a -> b) -> a -> b
$ Double -> CfValue
CfPercentile Double
v
CfvType
CfvtMin -> forall a. Either Text a -> AttrParser a
toAttrParser Either Text a
minVal
CfvType
CfvtMax -> forall a. Either Text a -> AttrParser a
toAttrParser Either Text a
maxVal
failMinCfvType :: [a]
failMinCfvType :: forall a. [a]
failMinCfvType = forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"unexpected 'min' type"
failMinCfvTypeX :: Either Text a
failMinCfvTypeX :: forall a. Either Text a
failMinCfvTypeX = forall a b. a -> Either a b
Left Text
"unexpected 'min' type"
failMaxCfvType :: [a]
failMaxCfvType :: forall a. [a]
failMaxCfvType = forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"unexpected 'max' type"
failMaxCfvTypeX :: Either Text a
failMaxCfvTypeX :: forall a. Either Text a
failMaxCfvTypeX = forall a b. a -> Either a b
Left Text
"unexpected 'max' type"
instance FromCursor CfValue where
fromCursor :: Cursor -> [CfValue]
fromCursor = forall a. (CfValue -> a) -> [a] -> [a] -> Cursor -> [a]
readCfValue forall a. a -> a
id forall a. [a]
failMinCfvType forall a. [a]
failMaxCfvType
instance FromXenoNode CfValue where
fromXenoNode :: Node -> Either Text CfValue
fromXenoNode Node
root = forall a.
(CfValue -> a)
-> Either Text a -> Either Text a -> Node -> Either Text a
readCfValueX forall a. a -> a
id forall a. Either Text a
failMinCfvTypeX forall a. Either Text a
failMaxCfvTypeX Node
root
instance FromCursor MinCfValue where
fromCursor :: Cursor -> [MinCfValue]
fromCursor = forall a. (CfValue -> a) -> [a] -> [a] -> Cursor -> [a]
readCfValue CfValue -> MinCfValue
MinCfValue (forall (m :: * -> *) a. Monad m => a -> m a
return MinCfValue
CfvMin) forall a. [a]
failMaxCfvType
instance FromXenoNode MinCfValue where
fromXenoNode :: Node -> Either Text MinCfValue
fromXenoNode Node
root =
forall a.
(CfValue -> a)
-> Either Text a -> Either Text a -> Node -> Either Text a
readCfValueX CfValue -> MinCfValue
MinCfValue (forall (m :: * -> *) a. Monad m => a -> m a
return MinCfValue
CfvMin) forall a. Either Text a
failMaxCfvTypeX Node
root
instance FromCursor MaxCfValue where
fromCursor :: Cursor -> [MaxCfValue]
fromCursor = forall a. (CfValue -> a) -> [a] -> [a] -> Cursor -> [a]
readCfValue CfValue -> MaxCfValue
MaxCfValue forall a. [a]
failMinCfvType (forall (m :: * -> *) a. Monad m => a -> m a
return MaxCfValue
CfvMax)
instance FromXenoNode MaxCfValue where
fromXenoNode :: Node -> Either Text MaxCfValue
fromXenoNode Node
root =
forall a.
(CfValue -> a)
-> Either Text a -> Either Text a -> Node -> Either Text a
readCfValueX CfValue -> MaxCfValue
MaxCfValue forall a. Either Text a
failMinCfvTypeX (forall (m :: * -> *) a. Monad m => a -> m a
return MaxCfValue
CfvMax) Node
root
defaultIconSet :: IconSetType
defaultIconSet :: IconSetType
defaultIconSet = IconSetType
IconSet3TrafficLights1
instance FromCursor IconSetOptions where
fromCursor :: Cursor -> [IconSetOptions]
fromCursor Cursor
cur = do
IconSetType
_isoIconSet <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"iconSet" IconSetType
defaultIconSet Cursor
cur
let _isoValues :: [CfValue]
_isoValues = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"cfvo") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
Bool
_isoReverse <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"reverse" Bool
False Cursor
cur
Bool
_isoShowValue <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"showValue" Bool
True Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return IconSetOptions {Bool
[CfValue]
IconSetType
_isoShowValue :: Bool
_isoReverse :: Bool
_isoValues :: [CfValue]
_isoIconSet :: IconSetType
_isoShowValue :: Bool
_isoReverse :: Bool
_isoValues :: [CfValue]
_isoIconSet :: IconSetType
..}
instance FromXenoNode IconSetOptions where
fromXenoNode :: Node -> Either Text IconSetOptions
fromXenoNode Node
root = do
(IconSetType
_isoIconSet, Bool
_isoReverse, Bool
_isoShowValue) <-
forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ (,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"iconSet" IconSetType
defaultIconSet
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"reverse" Bool
False
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"showValue" Bool
True
[CfValue]
_isoValues <- forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$ forall a. FromXenoNode a => ByteString -> ChildCollector [a]
fromChildList ByteString
"cfvo"
forall (m :: * -> *) a. Monad m => a -> m a
return IconSetOptions {Bool
[CfValue]
IconSetType
_isoValues :: [CfValue]
_isoShowValue :: Bool
_isoReverse :: Bool
_isoIconSet :: IconSetType
_isoShowValue :: Bool
_isoReverse :: Bool
_isoValues :: [CfValue]
_isoIconSet :: IconSetType
..}
instance FromAttrVal IconSetType where
fromAttrVal :: Reader IconSetType
fromAttrVal Text
"3Arrows" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3Arrows
fromAttrVal Text
"3ArrowsGray" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3ArrowsGray
fromAttrVal Text
"3Flags" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3Flags
fromAttrVal Text
"3Signs" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3Signs
fromAttrVal Text
"3Symbols" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3Symbols
fromAttrVal Text
"3Symbols2" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3Symbols2
fromAttrVal Text
"3TrafficLights1" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3TrafficLights1
fromAttrVal Text
"3TrafficLights2" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet3TrafficLights2
fromAttrVal Text
"4Arrows" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet4Arrows
fromAttrVal Text
"4ArrowsGray" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet4ArrowsGray
fromAttrVal Text
"4Rating" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet4Rating
fromAttrVal Text
"4RedToBlack" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet4RedToBlack
fromAttrVal Text
"4TrafficLights" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet4TrafficLights
fromAttrVal Text
"5Arrows" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet5Arrows
fromAttrVal Text
"5ArrowsGray" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet5ArrowsGray
fromAttrVal Text
"5Quarters" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet5Quarters
fromAttrVal Text
"5Rating" = forall a. a -> Either [Char] (a, Text)
readSuccess IconSetType
IconSet5Rating
fromAttrVal Text
t = forall a. Text -> Text -> Either [Char] (a, Text)
invalidText Text
"IconSetType" Text
t
instance FromAttrBs IconSetType where
fromAttrBs :: ByteString -> Either Text IconSetType
fromAttrBs ByteString
"3Arrows" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3Arrows
fromAttrBs ByteString
"3ArrowsGray" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3ArrowsGray
fromAttrBs ByteString
"3Flags" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3Flags
fromAttrBs ByteString
"3Signs" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3Signs
fromAttrBs ByteString
"3Symbols" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3Symbols
fromAttrBs ByteString
"3Symbols2" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3Symbols2
fromAttrBs ByteString
"3TrafficLights1" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3TrafficLights1
fromAttrBs ByteString
"3TrafficLights2" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet3TrafficLights2
fromAttrBs ByteString
"4Arrows" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet4Arrows
fromAttrBs ByteString
"4ArrowsGray" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet4ArrowsGray
fromAttrBs ByteString
"4Rating" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet4Rating
fromAttrBs ByteString
"4RedToBlack" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet4RedToBlack
fromAttrBs ByteString
"4TrafficLights" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet4TrafficLights
fromAttrBs ByteString
"5Arrows" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet5Arrows
fromAttrBs ByteString
"5ArrowsGray" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet5ArrowsGray
fromAttrBs ByteString
"5Quarters" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet5Quarters
fromAttrBs ByteString
"5Rating" = forall (m :: * -> *) a. Monad m => a -> m a
return IconSetType
IconSet5Rating
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"IconSetType" ByteString
x
instance FromCursor DataBarOptions where
fromCursor :: Cursor -> [DataBarOptions]
fromCursor Cursor
cur = do
Int
_dboMaxLength <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"maxLength" Int
defaultDboMaxLength Cursor
cur
Int
_dboMinLength <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"minLength" Int
defaultDboMinLength Cursor
cur
Bool
_dboShowValue <- forall a. FromAttrVal a => Name -> a -> Cursor -> [a]
fromAttributeDef Name
"showValue" Bool
True Cursor
cur
let cfvos :: [Node]
cfvos = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"cfvo") forall node a b.
(Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b]
&| forall node. Cursor node -> node
node
case [Node]
cfvos of
[Node
nMin, Node
nMax] -> do
MinCfValue
_dboMinimum <- forall a. FromCursor a => Cursor -> [a]
fromCursor (Node -> Cursor
fromNode Node
nMin)
MaxCfValue
_dboMaximum <- forall a. FromCursor a => Cursor -> [a]
fromCursor (Node -> Cursor
fromNode Node
nMax)
Color
_dboColor <- Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"color") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
forall (m :: * -> *) a. Monad m => a -> m a
return DataBarOptions{Bool
Int
Color
MaxCfValue
MinCfValue
_dboColor :: Color
_dboMaximum :: MaxCfValue
_dboMinimum :: MinCfValue
_dboShowValue :: Bool
_dboMinLength :: Int
_dboMaxLength :: Int
_dboColor :: Color
_dboMaximum :: MaxCfValue
_dboMinimum :: MinCfValue
_dboShowValue :: Bool
_dboMinLength :: Int
_dboMaxLength :: Int
..}
[Node]
ns -> do
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
"expected minimum and maximum cfvo nodes but see instead " forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> [Char]
show (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Node]
ns) forall a. [a] -> [a] -> [a]
++ [Char]
" cfvo nodes"
instance FromXenoNode DataBarOptions where
fromXenoNode :: Node -> Either Text DataBarOptions
fromXenoNode Node
root = do
(Int
_dboMaxLength, Int
_dboMinLength, Bool
_dboShowValue) <-
forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ (,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"maxLength" Int
defaultDboMaxLength
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"minLength" Int
defaultDboMinLength
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromAttrBs a => ByteString -> a -> AttrParser a
fromAttrDef ByteString
"showValue" Bool
True
(MinCfValue
_dboMinimum, MaxCfValue
_dboMaximum, Color
_dboColor) <-
forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$ (,,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromXenoNode a => ByteString -> ChildCollector a
fromChild ByteString
"cfvo"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromXenoNode a => ByteString -> ChildCollector a
fromChild ByteString
"cfvo"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromXenoNode a => ByteString -> ChildCollector a
fromChild ByteString
"color"
forall (m :: * -> *) a. Monad m => a -> m a
return DataBarOptions{Bool
Int
Color
MaxCfValue
MinCfValue
_dboColor :: Color
_dboMaximum :: MaxCfValue
_dboMinimum :: MinCfValue
_dboShowValue :: Bool
_dboMinLength :: Int
_dboMaxLength :: Int
_dboColor :: Color
_dboMaximum :: MaxCfValue
_dboMinimum :: MinCfValue
_dboShowValue :: Bool
_dboMinLength :: Int
_dboMaxLength :: Int
..}
instance FromAttrVal Inclusion where
fromAttrVal :: Reader Inclusion
fromAttrVal = forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either d b) (Either d c)
right (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> Bool -> a
bool Inclusion
Exclusive Inclusion
Inclusive) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Reader a
fromAttrVal
instance FromAttrBs Inclusion where
fromAttrBs :: ByteString -> Either Text Inclusion
fromAttrBs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> a -> Bool -> a
bool Inclusion
Exclusive Inclusion
Inclusive) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrBs a => ByteString -> Either Text a
fromAttrBs
instance FromAttrVal NStdDev where
fromAttrVal :: Reader NStdDev
fromAttrVal = forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either d b) (Either d c)
right (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Int -> NStdDev
NStdDev) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Reader a
fromAttrVal
instance FromAttrBs NStdDev where
fromAttrBs :: ByteString -> Either Text NStdDev
fromAttrBs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> NStdDev
NStdDev forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrBs a => ByteString -> Either Text a
fromAttrBs
instance ToElement CfRule where
toElement :: Name -> CfRule -> Element
toElement Name
nm CfRule{Int
Maybe Bool
Maybe Int
Condition
_cfrStopIfTrue :: Maybe Bool
_cfrPriority :: Int
_cfrDxfId :: Maybe Int
_cfrCondition :: Condition
_cfrStopIfTrue :: CfRule -> Maybe Bool
_cfrPriority :: CfRule -> Int
_cfrDxfId :: CfRule -> Maybe Int
_cfrCondition :: CfRule -> Condition
..} =
let (Text
condType, Map Name Text
condAttrs, [Node]
condNodes) = Condition -> (Text, Map Name Text, [Node])
conditionData Condition
_cfrCondition
baseAttrs :: Map Name Text
baseAttrs = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Maybe a] -> [a]
catMaybes forall a b. (a -> b) -> a -> b
$
[ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
condType
, Name
"dxfId" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_cfrDxfId
, forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Name
"priority" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
_cfrPriority
, Name
"stopIfTrue" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_cfrStopIfTrue
]
in Element
{ elementName :: Name
elementName = Name
nm
, elementAttributes :: Map Name Text
elementAttributes = forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union Map Name Text
baseAttrs Map Name Text
condAttrs
, elementNodes :: [Node]
elementNodes = [Node]
condNodes
}
conditionData :: Condition -> (Text, Map Name Text, [Node])
conditionData :: Condition -> (Text, Map Name Text, [Node])
conditionData (AboveAverage Inclusion
i Maybe NStdDev
sDevs) =
(Text
"aboveAverage", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ [Name
"aboveAverage" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True] forall a. [a] -> [a] -> [a]
++
forall a. [Maybe a] -> [a]
catMaybes [ Name
"equalAverage" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef Inclusion
Exclusive Inclusion
i
, Name
"stdDev" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe NStdDev
sDevs], [])
conditionData (BeginsWith Text
t) = (Text
"beginsWith", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"text" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
t], [])
conditionData (BelowAverage Inclusion
i Maybe NStdDev
sDevs) =
(Text
"aboveAverage", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ [Name
"aboveAverage" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
False] forall a. [a] -> [a] -> [a]
++
forall a. [Maybe a] -> [a]
catMaybes [ Name
"equalAverage" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef Inclusion
Exclusive Inclusion
i
, Name
"stdDev" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe NStdDev
sDevs], [])
conditionData (BottomNPercent Int
n) = (Text
"top10", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"bottom" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True, Name
"rank" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
n, Name
"percent" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True ], [])
conditionData (BottomNValues Int
n) = (Text
"top10", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"bottom" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True, Name
"rank" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
n ], [])
conditionData (CellIs OperatorExpression
opExpr) = (Text
"cellIs", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"operator" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
op], [Node]
formulas)
where (Text
op, [Node]
formulas) = OperatorExpression -> (Text, [Node])
operatorExpressionData OperatorExpression
opExpr
conditionData (ColorScale2 MinCfValue
minv Color
minc MaxCfValue
maxv Color
maxc) =
( Text
"colorScale"
, forall k a. Map k a
M.empty
, [ Element -> Node
NodeElement forall a b. (a -> b) -> a -> b
$
Name -> [Element] -> Element
elementListSimple
Name
"colorScale"
[ forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo" MinCfValue
minv
, forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo" MaxCfValue
maxv
, forall a. ToElement a => Name -> a -> Element
toElement Name
"color" Color
minc
, forall a. ToElement a => Name -> a -> Element
toElement Name
"color" Color
maxc
]
])
conditionData (ColorScale3 MinCfValue
minv Color
minc CfValue
midv Color
midc MaxCfValue
maxv Color
maxc) =
( Text
"colorScale"
, forall k a. Map k a
M.empty
, [ Element -> Node
NodeElement forall a b. (a -> b) -> a -> b
$
Name -> [Element] -> Element
elementListSimple
Name
"colorScale"
[ forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo" MinCfValue
minv
, forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo" CfValue
midv
, forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo" MaxCfValue
maxv
, forall a. ToElement a => Name -> a -> Element
toElement Name
"color" Color
minc
, forall a. ToElement a => Name -> a -> Element
toElement Name
"color" Color
midc
, forall a. ToElement a => Name -> a -> Element
toElement Name
"color" Color
maxc
]
])
conditionData Condition
ContainsBlanks = (Text
"containsBlanks", forall k a. Map k a
M.empty, [])
conditionData Condition
ContainsErrors = (Text
"containsErrors", forall k a. Map k a
M.empty, [])
conditionData (ContainsText Text
t) = (Text
"containsText", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"text" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
t], [])
conditionData (DataBar DataBarOptions
dbOpts) = (Text
"dataBar", forall k a. Map k a
M.empty, [forall a. ToElement a => Name -> a -> Node
toNode Name
"dataBar" DataBarOptions
dbOpts])
conditionData Condition
DoesNotContainBlanks = (Text
"notContainsBlanks", forall k a. Map k a
M.empty, [])
conditionData Condition
DoesNotContainErrors = (Text
"notContainsErrors", forall k a. Map k a
M.empty, [])
conditionData (DoesNotContainText Text
t) = (Text
"notContainsText", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"text" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
t], [])
conditionData Condition
DuplicateValues = (Text
"duplicateValues", forall k a. Map k a
M.empty, [])
conditionData (EndsWith Text
t) = (Text
"endsWith", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"text" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
t], [])
conditionData (Expression Formula
formula) = (Text
"expression", forall k a. Map k a
M.empty, [Formula -> Node
formulaNode Formula
formula])
conditionData (InTimePeriod TimePeriod
period) = (Text
"timePeriod", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"timePeriod" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= TimePeriod
period ], [])
conditionData (IconSet IconSetOptions
isOptions) = (Text
"iconSet", forall k a. Map k a
M.empty, [forall a. ToElement a => Name -> a -> Node
toNode Name
"iconSet" IconSetOptions
isOptions])
conditionData (TopNPercent Int
n) = (Text
"top10", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"rank" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
n, Name
"percent" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True ], [])
conditionData (TopNValues Int
n) = (Text
"top10", forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [ Name
"rank" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
n ], [])
conditionData Condition
UniqueValues = (Text
"uniqueValues", forall k a. Map k a
M.empty, [])
operatorExpressionData :: OperatorExpression -> (Text, [Node])
operatorExpressionData :: OperatorExpression -> (Text, [Node])
operatorExpressionData (OpBeginsWith Formula
f) = (Text
"beginsWith", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpBetween Formula
f1 Formula
f2) = (Text
"between", [Formula -> Node
formulaNode Formula
f1, Formula -> Node
formulaNode Formula
f2])
operatorExpressionData (OpContainsText Formula
f) = (Text
"containsText", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpEndsWith Formula
f) = (Text
"endsWith", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpEqual Formula
f) = (Text
"equal", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpGreaterThan Formula
f) = (Text
"greaterThan", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpGreaterThanOrEqual Formula
f) = (Text
"greaterThanOrEqual", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpLessThan Formula
f) = (Text
"lessThan", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpLessThanOrEqual Formula
f) = (Text
"lessThanOrEqual", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpNotBetween Formula
f1 Formula
f2) = (Text
"notBetween", [Formula -> Node
formulaNode Formula
f1, Formula -> Node
formulaNode Formula
f2])
operatorExpressionData (OpNotContains Formula
f) = (Text
"notContains", [Formula -> Node
formulaNode Formula
f])
operatorExpressionData (OpNotEqual Formula
f) = (Text
"notEqual", [Formula -> Node
formulaNode Formula
f])
instance ToElement MinCfValue where
toElement :: Name -> MinCfValue -> Element
toElement Name
nm MinCfValue
CfvMin = Name -> [(Name, Text)] -> Element
leafElement Name
nm [Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CfvType
CfvtMin]
toElement Name
nm (MinCfValue CfValue
cfv) = forall a. ToElement a => Name -> a -> Element
toElement Name
nm CfValue
cfv
instance ToElement MaxCfValue where
toElement :: Name -> MaxCfValue -> Element
toElement Name
nm MaxCfValue
CfvMax = Name -> [(Name, Text)] -> Element
leafElement Name
nm [Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CfvType
CfvtMax]
toElement Name
nm (MaxCfValue CfValue
cfv) = forall a. ToElement a => Name -> a -> Element
toElement Name
nm CfValue
cfv
instance ToElement CfValue where
toElement :: Name -> CfValue -> Element
toElement Name
nm (CfValue Double
v) = Name -> [(Name, Text)] -> Element
leafElement Name
nm [Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CfvType
CfvtNum, Name
"val" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Double
v]
toElement Name
nm (CfPercent Double
v) =
Name -> [(Name, Text)] -> Element
leafElement Name
nm [Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CfvType
CfvtPercent, Name
"val" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Double
v]
toElement Name
nm (CfPercentile Double
v) =
Name -> [(Name, Text)] -> Element
leafElement Name
nm [Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CfvType
CfvtPercentile, Name
"val" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Double
v]
toElement Name
nm (CfFormula Formula
f) =
Name -> [(Name, Text)] -> Element
leafElement Name
nm [Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CfvType
CfvtFormula, Name
"val" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Formula -> Text
unFormula Formula
f]
instance ToAttrVal CfvType where
toAttrVal :: CfvType -> Text
toAttrVal CfvType
CfvtNum = Text
"num"
toAttrVal CfvType
CfvtPercent = Text
"percent"
toAttrVal CfvType
CfvtMax = Text
"max"
toAttrVal CfvType
CfvtMin = Text
"min"
toAttrVal CfvType
CfvtFormula = Text
"formula"
toAttrVal CfvType
CfvtPercentile = Text
"percentile"
instance ToElement IconSetOptions where
toElement :: Name -> IconSetOptions -> Element
toElement Name
nm IconSetOptions {Bool
[CfValue]
IconSetType
_isoShowValue :: Bool
_isoReverse :: Bool
_isoValues :: [CfValue]
_isoIconSet :: IconSetType
_isoShowValue :: IconSetOptions -> Bool
_isoReverse :: IconSetOptions -> Bool
_isoValues :: IconSetOptions -> [CfValue]
_isoIconSet :: IconSetOptions -> IconSetType
..} =
Name -> [(Name, Text)] -> [Element] -> Element
elementList Name
nm [(Name, Text)]
attrs forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo") [CfValue]
_isoValues
where
attrs :: [(Name, Text)]
attrs = forall a. [Maybe a] -> [a]
catMaybes
[ Name
"iconSet" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef IconSetType
defaultIconSet IconSetType
_isoIconSet
, Name
"reverse" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_isoReverse
, Name
"showValue" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_isoShowValue
]
instance ToAttrVal IconSetType where
toAttrVal :: IconSetType -> Text
toAttrVal IconSetType
IconSet3Arrows = Text
"3Arrows"
toAttrVal IconSetType
IconSet3ArrowsGray = Text
"3ArrowsGray"
toAttrVal IconSetType
IconSet3Flags = Text
"3Flags"
toAttrVal IconSetType
IconSet3Signs = Text
"3Signs"
toAttrVal IconSetType
IconSet3Symbols = Text
"3Symbols"
toAttrVal IconSetType
IconSet3Symbols2 = Text
"3Symbols2"
toAttrVal IconSetType
IconSet3TrafficLights1 = Text
"3TrafficLights1"
toAttrVal IconSetType
IconSet3TrafficLights2 = Text
"3TrafficLights2"
toAttrVal IconSetType
IconSet4Arrows = Text
"4Arrows"
toAttrVal IconSetType
IconSet4ArrowsGray = Text
"4ArrowsGray"
toAttrVal IconSetType
IconSet4Rating = Text
"4Rating"
toAttrVal IconSetType
IconSet4RedToBlack = Text
"4RedToBlack"
toAttrVal IconSetType
IconSet4TrafficLights = Text
"4TrafficLights"
toAttrVal IconSetType
IconSet5Arrows = Text
"5Arrows"
toAttrVal IconSetType
IconSet5ArrowsGray = Text
"5ArrowsGray"
toAttrVal IconSetType
IconSet5Quarters = Text
"5Quarters"
toAttrVal IconSetType
IconSet5Rating = Text
"5Rating"
instance ToElement DataBarOptions where
toElement :: Name -> DataBarOptions -> Element
toElement Name
nm DataBarOptions {Bool
Int
Color
MaxCfValue
MinCfValue
_dboColor :: Color
_dboMaximum :: MaxCfValue
_dboMinimum :: MinCfValue
_dboShowValue :: Bool
_dboMinLength :: Int
_dboMaxLength :: Int
_dboColor :: DataBarOptions -> Color
_dboMaximum :: DataBarOptions -> MaxCfValue
_dboMinimum :: DataBarOptions -> MinCfValue
_dboShowValue :: DataBarOptions -> Bool
_dboMinLength :: DataBarOptions -> Int
_dboMaxLength :: DataBarOptions -> Int
..} = Name -> [(Name, Text)] -> [Element] -> Element
elementList Name
nm [(Name, Text)]
attrs [Element]
elements
where
attrs :: [(Name, Text)]
attrs = forall a. [Maybe a] -> [a]
catMaybes
[ Name
"maxLength" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef Int
defaultDboMaxLength Int
_dboMaxLength
, Name
"minLength" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef Int
defaultDboMinLength Int
_dboMinLength
, Name
"showValue" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_dboShowValue
]
elements :: [Element]
elements =
[ forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo" MinCfValue
_dboMinimum
, forall a. ToElement a => Name -> a -> Element
toElement Name
"cfvo" MaxCfValue
_dboMaximum
, forall a. ToElement a => Name -> a -> Element
toElement Name
"color" Color
_dboColor
]
toNode :: ToElement a => Name -> a -> Node
toNode :: forall a. ToElement a => Name -> a -> Node
toNode Name
nm = Element -> Node
NodeElement forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToElement a => Name -> a -> Element
toElement Name
nm
formulaNode :: Formula -> Node
formulaNode :: Formula -> Node
formulaNode = forall a. ToElement a => Name -> a -> Node
toNode Name
"formula"
instance ToAttrVal TimePeriod where
toAttrVal :: TimePeriod -> Text
toAttrVal TimePeriod
PerLast7Days = Text
"last7Days"
toAttrVal TimePeriod
PerLastMonth = Text
"lastMonth"
toAttrVal TimePeriod
PerLastWeek = Text
"lastWeek"
toAttrVal TimePeriod
PerNextMonth = Text
"nextMonth"
toAttrVal TimePeriod
PerNextWeek = Text
"nextWeek"
toAttrVal TimePeriod
PerThisMonth = Text
"thisMonth"
toAttrVal TimePeriod
PerThisWeek = Text
"thisWeek"
toAttrVal TimePeriod
PerToday = Text
"today"
toAttrVal TimePeriod
PerTomorrow = Text
"tomorrow"
toAttrVal TimePeriod
PerYesterday = Text
"yesterday"
instance ToAttrVal Inclusion where
toAttrVal :: Inclusion -> Text
toAttrVal = forall a. ToAttrVal a => a -> Text
toAttrVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Eq a => a -> a -> Bool
== Inclusion
Inclusive)
instance ToAttrVal NStdDev where
toAttrVal :: NStdDev -> Text
toAttrVal (NStdDev Int
n) = forall a. ToAttrVal a => a -> Text
toAttrVal Int
n