Skip to content

Commit 5254a77

Browse files
committed
wip
1 parent 59cdba4 commit 5254a77

File tree

3 files changed

+80
-107
lines changed

3 files changed

+80
-107
lines changed

pub/xlsx/src/Codec/Xlsx/Formatted.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -477,8 +477,8 @@ mapDxf FormattedCondFmt {..} = do
477477
return newId
478478
return
479479
CfRule
480-
{ _cfrCondition = condfmtCondition,
481-
_cfrDxfId = Just dxfId,
482-
_cfrPriority = condfmtPriority,
483-
_cfrStopIfTrue = condfmtStopIfTrue
480+
{ cfrCondition = condfmtCondition,
481+
cfrDxfId = Just dxfId,
482+
cfrPriority = condfmtPriority,
483+
cfrStopIfTrue = condfmtStopIfTrue
484484
}

pub/xlsx/src/Codec/Xlsx/Types/ConditionalFormatting.hs

Lines changed: 60 additions & 87 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@
33
{-# LANGUAGE OverloadedStrings #-}
44
{-# LANGUAGE RecordWildCards #-}
55
{-# LANGUAGE ScopedTypeVariables #-}
6-
{-# LANGUAGE TemplateHaskell #-}
76

87
module Codec.Xlsx.Types.ConditionalFormatting
98
( ConditionalFormatting,
@@ -21,28 +20,6 @@ module Codec.Xlsx.Types.ConditionalFormatting
2120
DataBarOptions (..),
2221
dataBarWithColor,
2322

24-
-- * Lenses
25-
26-
-- ** CfRule
27-
cfrCondition,
28-
cfrDxfId,
29-
cfrPriority,
30-
cfrStopIfTrue,
31-
32-
-- ** IconSetOptions
33-
isoIconSet,
34-
isoValues,
35-
isoReverse,
36-
isoShowValue,
37-
38-
-- ** DataBarOptions
39-
dboMaxLength,
40-
dboMinLength,
41-
dboShowValue,
42-
dboMinimum,
43-
dboMaximum,
44-
dboColor,
45-
4623
-- * Misc
4724
topCfPriority,
4825
)
@@ -310,14 +287,14 @@ instance NFData CfvType
310287
-- See 18.3.1.49 "iconSet (Icon Set)" (p. 1645)
311288
data IconSetOptions = IconSetOptions
312289
{ -- | icon set used, default value is 'IconSet3Trafficlights1'
313-
_isoIconSet :: IconSetType,
290+
isoIconSet :: IconSetType,
314291
-- | values describing per icon ranges
315-
_isoValues :: [CfValue],
292+
isoValues :: [CfValue],
316293
-- | reverses the default order of the icons in the specified icon set
317-
_isoReverse :: Bool,
294+
isoReverse :: Bool,
318295
-- | indicates whether to show the values of the cells on which this
319296
-- icon set is applied.
320-
_isoShowValue :: Bool
297+
isoShowValue :: Bool
321298
}
322299
deriving (Eq, Ord, Show, Generic)
323300

@@ -359,16 +336,16 @@ instance NFData IconSetType
359336
data DataBarOptions = DataBarOptions
360337
{ -- | The maximum length of the data bar, as a percentage of the cell
361338
-- width.
362-
_dboMaxLength :: Int,
339+
dboMaxLength :: Int,
363340
-- | The minimum length of the data bar, as a percentage of the cell
364341
-- width.
365-
_dboMinLength :: Int,
342+
dboMinLength :: Int,
366343
-- | Indicates whether to show the values of the cells on which this
367344
-- data bar is applied.
368-
_dboShowValue :: Bool,
369-
_dboMinimum :: MinCfValue,
370-
_dboMaximum :: MaxCfValue,
371-
_dboColor :: Color
345+
dboShowValue :: Bool,
346+
dboMinimum :: MinCfValue,
347+
dboMaximum :: MaxCfValue,
348+
dboColor :: Color
372349
}
373350
deriving (Eq, Ord, Show, Generic)
374351

@@ -384,32 +361,32 @@ dataBarWithColor :: Color -> Condition
384361
dataBarWithColor c =
385362
DataBar
386363
DataBarOptions
387-
{ _dboMaxLength = defaultDboMaxLength,
388-
_dboMinLength = defaultDboMinLength,
389-
_dboShowValue = True,
390-
_dboMinimum = CfvMin,
391-
_dboMaximum = CfvMax,
392-
_dboColor = c
364+
{ dboMaxLength = defaultDboMaxLength,
365+
dboMinLength = defaultDboMinLength,
366+
dboShowValue = True,
367+
dboMinimum = CfvMin,
368+
dboMaximum = CfvMax,
369+
dboColor = c
393370
}
394371

395372
-- | This collection represents a description of a conditional formatting rule.
396373
--
397374
-- See 18.3.1.10 "cfRule (Conditional Formatting Rule)" (p. 1602)
398375
data CfRule = CfRule
399-
{ _cfrCondition :: Condition,
376+
{ cfrCondition :: Condition,
400377
-- | This is an index to a dxf element in the Styles Part
401378
-- indicating which cell formatting to
402379
-- apply when the conditional formatting rule criteria is met.
403-
_cfrDxfId :: Maybe Int,
380+
cfrDxfId :: Maybe Int,
404381
-- | The priority of this conditional formatting rule. This value
405382
-- is used to determine which format should be evaluated and
406383
-- rendered. Lower numeric values are higher priority than
407384
-- higher numeric values, where 1 is the highest priority.
408-
_cfrPriority :: Int,
385+
cfrPriority :: Int,
409386
-- | If this flag is set, no rules with lower priority shall
410387
-- be applied over this rule, when this rule
411388
-- evaluates to true.
412-
_cfrStopIfTrue :: Maybe Bool
389+
cfrStopIfTrue :: Maybe Bool
413390
}
414391
deriving (Eq, Ord, Show, Generic)
415392

@@ -418,17 +395,13 @@ instance NFData CfRule
418395
instance Default IconSetOptions where
419396
def =
420397
IconSetOptions
421-
{ _isoIconSet = IconSet3TrafficLights1,
422-
_isoValues = [CfPercent 0, CfPercent 33.33, CfPercent 66.67],
398+
{ isoIconSet = IconSet3TrafficLights1,
399+
isoValues = [CfPercent 0, CfPercent 33.33, CfPercent 66.67],
423400
-- IconSet3TrafficLights1 (CfPercent 0) (CfPercent 33.33) (CfPercent 66.67)
424-
_isoReverse = False,
425-
_isoShowValue = True
401+
isoReverse = False,
402+
isoShowValue = True
426403
}
427404

428-
makeLenses ''CfRule
429-
makeLenses ''IconSetOptions
430-
makeLenses ''DataBarOptions
431-
432405
type ConditionalFormatting = [CfRule]
433406

434407
topCfPriority :: Int
@@ -440,13 +413,13 @@ topCfPriority = 1
440413

441414
instance FromCursor CfRule where
442415
fromCursor cur = do
443-
_cfrDxfId <- maybeAttribute "dxfId" cur
444-
_cfrPriority <- fromAttribute "priority" cur
445-
_cfrStopIfTrue <- maybeAttribute "stopIfTrue" cur
416+
cfrDxfId <- maybeAttribute "dxfId" cur
417+
cfrPriority <- fromAttribute "priority" cur
418+
cfrStopIfTrue <- maybeAttribute "stopIfTrue" cur
446419
-- spec shows this attribute as optional but it's not clear why could
447420
-- conditional formatting record be needed with no condition type set
448421
cfType <- fromAttribute "type" cur
449-
_cfrCondition <- readCondition cfType cur
422+
cfrCondition <- readCondition cfType cur
450423
return CfRule {..}
451424

452425
readCondition :: Text -> Cursor -> [Condition]
@@ -537,13 +510,13 @@ readOpExpression _ _ = []
537510

538511
instance FromXenoNode CfRule where
539512
fromXenoNode root = parseAttributes root $ do
540-
_cfrDxfId <- maybeAttr "dxfId"
541-
_cfrPriority <- fromAttr "priority"
542-
_cfrStopIfTrue <- maybeAttr "stopIfTrue"
513+
cfrDxfId <- maybeAttr "dxfId"
514+
cfrPriority <- fromAttr "priority"
515+
cfrStopIfTrue <- maybeAttr "stopIfTrue"
543516
-- spec shows this attribute as optional but it's not clear why could
544517
-- conditional formatting record be needed with no condition type set
545518
cfType <- fromAttr "type"
546-
_cfrCondition <- readConditionX cfType
519+
cfrCondition <- readConditionX cfType
547520
return CfRule {..}
548521
where
549522
readConditionX ("aboveAverage" :: ByteString) = do
@@ -749,21 +722,21 @@ defaultIconSet = IconSet3TrafficLights1
749722

750723
instance FromCursor IconSetOptions where
751724
fromCursor cur = do
752-
_isoIconSet <- fromAttributeDef "iconSet" defaultIconSet cur
753-
let _isoValues = cur $/ element (n_ "cfvo") >=> fromCursor
754-
_isoReverse <- fromAttributeDef "reverse" False cur
755-
_isoShowValue <- fromAttributeDef "showValue" True cur
725+
isoIconSet <- fromAttributeDef "iconSet" defaultIconSet cur
726+
let isoValues = cur $/ element (n_ "cfvo") >=> fromCursor
727+
isoReverse <- fromAttributeDef "reverse" False cur
728+
isoShowValue <- fromAttributeDef "showValue" True cur
756729
return IconSetOptions {..}
757730

758731
instance FromXenoNode IconSetOptions where
759732
fromXenoNode root = do
760-
(_isoIconSet, _isoReverse, _isoShowValue) <-
733+
(isoIconSet, isoReverse, isoShowValue) <-
761734
parseAttributes root $
762735
(,,)
763736
<$> fromAttrDef "iconSet" defaultIconSet
764737
<*> fromAttrDef "reverse" False
765738
<*> fromAttrDef "showValue" True
766-
_isoValues <- collectChildren root $ fromChildList "cfvo"
739+
isoValues <- collectChildren root $ fromChildList "cfvo"
767740
return IconSetOptions {..}
768741

769742
instance FromAttrVal IconSetType where
@@ -808,15 +781,15 @@ instance FromAttrBs IconSetType where
808781

809782
instance FromCursor DataBarOptions where
810783
fromCursor cur = do
811-
_dboMaxLength <- fromAttributeDef "maxLength" defaultDboMaxLength cur
812-
_dboMinLength <- fromAttributeDef "minLength" defaultDboMinLength cur
813-
_dboShowValue <- fromAttributeDef "showValue" True cur
784+
dboMaxLength <- fromAttributeDef "maxLength" defaultDboMaxLength cur
785+
dboMinLength <- fromAttributeDef "minLength" defaultDboMinLength cur
786+
dboShowValue <- fromAttributeDef "showValue" True cur
814787
let cfvos = cur $/ element (n_ "cfvo") &| node
815788
case cfvos of
816789
[nMin, nMax] -> do
817-
_dboMinimum <- fromCursor (fromNode nMin)
818-
_dboMaximum <- fromCursor (fromNode nMax)
819-
_dboColor <- cur $/ element (n_ "color") >=> fromCursor
790+
dboMinimum <- fromCursor (fromNode nMin)
791+
dboMaximum <- fromCursor (fromNode nMax)
792+
dboColor <- cur $/ element (n_ "color") >=> fromCursor
820793
return DataBarOptions {..}
821794
ns -> do
822795
fail $
@@ -826,13 +799,13 @@ instance FromCursor DataBarOptions where
826799

827800
instance FromXenoNode DataBarOptions where
828801
fromXenoNode root = do
829-
(_dboMaxLength, _dboMinLength, _dboShowValue) <-
802+
(dboMaxLength, dboMinLength, dboShowValue) <-
830803
parseAttributes root $
831804
(,,)
832805
<$> fromAttrDef "maxLength" defaultDboMaxLength
833806
<*> fromAttrDef "minLength" defaultDboMinLength
834807
<*> fromAttrDef "showValue" True
835-
(_dboMinimum, _dboMaximum, _dboColor) <-
808+
(dboMinimum, dboMaximum, dboColor) <-
836809
collectChildren root $
837810
(,,)
838811
<$> fromChild "cfvo"
@@ -858,13 +831,13 @@ instance FromAttrBs NStdDev where
858831

859832
instance ToElement CfRule where
860833
toElement nm CfRule {..} =
861-
let (condType, condAttrs, condNodes) = conditionData _cfrCondition
834+
let (condType, condAttrs, condNodes) = conditionData cfrCondition
862835
baseAttrs =
863836
M.fromList . catMaybes $
864837
[ Just $ "type" .= condType,
865-
"dxfId" .=? _cfrDxfId,
866-
Just $ "priority" .= _cfrPriority,
867-
"stopIfTrue" .=? _cfrStopIfTrue
838+
"dxfId" .=? cfrDxfId,
839+
Just $ "priority" .= cfrPriority,
840+
"stopIfTrue" .=? cfrStopIfTrue
868841
]
869842
in Element
870843
{ elementName = nm,
@@ -985,13 +958,13 @@ instance ToAttrVal CfvType where
985958

986959
instance ToElement IconSetOptions where
987960
toElement nm IconSetOptions {..} =
988-
elementList nm attrs $ map (toElement "cfvo") _isoValues
961+
elementList nm attrs $ map (toElement "cfvo") isoValues
989962
where
990963
attrs =
991964
catMaybes
992-
[ "iconSet" .=? justNonDef defaultIconSet _isoIconSet,
993-
"reverse" .=? justTrue _isoReverse,
994-
"showValue" .=? justFalse _isoShowValue
965+
[ "iconSet" .=? justNonDef defaultIconSet isoIconSet,
966+
"reverse" .=? justTrue isoReverse,
967+
"showValue" .=? justFalse isoShowValue
995968
]
996969

997970
instance ToAttrVal IconSetType where
@@ -1018,14 +991,14 @@ instance ToElement DataBarOptions where
1018991
where
1019992
attrs =
1020993
catMaybes
1021-
[ "maxLength" .=? justNonDef defaultDboMaxLength _dboMaxLength,
1022-
"minLength" .=? justNonDef defaultDboMinLength _dboMinLength,
1023-
"showValue" .=? justFalse _dboShowValue
994+
[ "maxLength" .=? justNonDef defaultDboMaxLength dboMaxLength,
995+
"minLength" .=? justNonDef defaultDboMinLength dboMinLength,
996+
"showValue" .=? justFalse dboShowValue
1024997
]
1025998
elements =
1026-
[ toElement "cfvo" _dboMinimum,
1027-
toElement "cfvo" _dboMaximum,
1028-
toElement "color" _dboColor
999+
[ toElement "cfvo" dboMinimum,
1000+
toElement "cfvo" dboMaximum,
1001+
toElement "color" dboColor
10291002
]
10301003

10311004
toNode :: (ToElement a) => Name -> a -> Node

pub/xlsx/test/TestXlsx.hs

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -193,10 +193,10 @@ testXlsx = Xlsx sheets minimalStyles definedNames customProperties DateBase1904
193193
[(SqRef [CellRef "A1:B3"], rules1), (SqRef [CellRef "C1:C10"], rules2)]
194194
cfRule c d =
195195
CfRule
196-
{ _cfrCondition = c,
197-
_cfrDxfId = Just d,
198-
_cfrPriority = topCfPriority,
199-
_cfrStopIfTrue = Nothing
196+
{ cfrCondition = c,
197+
cfrDxfId = Just d,
198+
cfrPriority = topCfPriority,
199+
cfrStopIfTrue = Nothing
200200
}
201201
rules1 =
202202
[ cfRule ContainsBlanks 1,
@@ -760,24 +760,24 @@ testCondFormattedResult = CondFormatted styleSheet formattings
760760
]
761761
cfRule1 =
762762
CfRule
763-
{ _cfrCondition = ContainsBlanks,
764-
_cfrDxfId = Just 0,
765-
_cfrPriority = 1,
766-
_cfrStopIfTrue = Nothing
763+
{ cfrCondition = ContainsBlanks,
764+
cfrDxfId = Just 0,
765+
cfrPriority = 1,
766+
cfrStopIfTrue = Nothing
767767
}
768768
cfRule2 =
769769
CfRule
770-
{ _cfrCondition = BeginsWith "foo",
771-
_cfrDxfId = Just 1,
772-
_cfrPriority = 1,
773-
_cfrStopIfTrue = Nothing
770+
{ cfrCondition = BeginsWith "foo",
771+
cfrDxfId = Just 1,
772+
cfrPriority = 1,
773+
cfrStopIfTrue = Nothing
774774
}
775775
cfRule3 =
776776
CfRule
777-
{ _cfrCondition = CellIs (OpGreaterThan (Formula "A1")),
778-
_cfrDxfId = Just 2,
779-
_cfrPriority = 1,
780-
_cfrStopIfTrue = Nothing
777+
{ cfrCondition = CellIs (OpGreaterThan (Formula "A1")),
778+
cfrDxfId = Just 2,
779+
cfrPriority = 1,
780+
cfrStopIfTrue = Nothing
781781
}
782782

783783
testFormattedCells :: Map (RowIndex, ColumnIndex) FormattedCell

0 commit comments

Comments
 (0)