{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Types.StyleSheet (
StyleSheet(..)
, CellXf(..)
, minimalStyleSheet
, Alignment(..)
, Border(..)
, BorderStyle(..)
, Color(..)
, Dxf(..)
, Fill(..)
, FillPattern(..)
, Font(..)
, NumberFormat(..)
, NumFmt(..)
, ImpliedNumberFormat (..)
, FormatCode
, Protection(..)
, CellHorizontalAlignment(..)
, CellVerticalAlignment(..)
, FontFamily(..)
, FontScheme(..)
, FontUnderline(..)
, FontVerticalAlignment(..)
, LineStyle(..)
, PatternType(..)
, ReadingOrder(..)
, styleSheetBorders
, styleSheetFonts
, styleSheetFills
, styleSheetCellXfs
, styleSheetDxfs
, styleSheetNumFmts
, cellXfApplyAlignment
, cellXfApplyBorder
, cellXfApplyFill
, cellXfApplyFont
, cellXfApplyNumberFormat
, cellXfApplyProtection
, cellXfBorderId
, cellXfFillId
, cellXfFontId
, cellXfNumFmtId
, cellXfPivotButton
, cellXfQuotePrefix
, cellXfId
, cellXfAlignment
, cellXfProtection
, dxfAlignment
, dxfBorder
, dxfFill
, dxfFont
, dxfNumFmt
, dxfProtection
, alignmentHorizontal
, alignmentIndent
, alignmentJustifyLastLine
, alignmentReadingOrder
, alignmentRelativeIndent
, alignmentShrinkToFit
, alignmentTextRotation
, alignmentVertical
, alignmentWrapText
, borderDiagonalDown
, borderDiagonalUp
, borderOutline
, borderBottom
, borderDiagonal
, borderEnd
, borderHorizontal
, borderStart
, borderTop
, borderVertical
, borderLeft
, borderRight
, borderStyleColor
, borderStyleLine
, colorAutomatic
, colorARGB
, colorTheme
, colorTint
, fillPattern
, fillPatternBgColor
, fillPatternFgColor
, fillPatternType
, fontBold
, fontCharset
, fontColor
, fontCondense
, fontExtend
, fontFamily
, fontItalic
, fontName
, fontOutline
, fontScheme
, fontShadow
, fontStrikeThrough
, fontSize
, fontUnderline
, fontVertAlign
, protectionHidden
, protectionLocked
, fmtDecimals
, fmtDecimalsZeroes
, stdNumberFormatId
, idToStdNumberFormat
, firstUserNumFmtId
) where
#ifdef USE_MICROLENS
import Lens.Micro
import Lens.Micro.TH (makeLenses)
#else
import Control.Lens hiding (element, elements, (.=))
#endif
import Control.DeepSeq (NFData)
import Data.Default
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import Data.Maybe (catMaybes, maybeToList)
import Data.Monoid ((<>))
import Data.Text (Text)
import qualified Data.Text as T
import GHC.Generics (Generic)
import Text.XML
import Text.XML.Cursor
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Writer.Internal
data StyleSheet = StyleSheet
{ StyleSheet -> [Border]
_styleSheetBorders :: [Border]
, StyleSheet -> [CellXf]
_styleSheetCellXfs :: [CellXf]
, StyleSheet -> [Fill]
_styleSheetFills :: [Fill]
, StyleSheet -> [Font]
_styleSheetFonts :: [Font]
, StyleSheet -> [Dxf]
_styleSheetDxfs :: [Dxf]
, StyleSheet -> Map Int FormatCode
_styleSheetNumFmts :: Map Int FormatCode
} deriving (StyleSheet -> StyleSheet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StyleSheet -> StyleSheet -> Bool
$c/= :: StyleSheet -> StyleSheet -> Bool
== :: StyleSheet -> StyleSheet -> Bool
$c== :: StyleSheet -> StyleSheet -> Bool
Eq, Eq StyleSheet
StyleSheet -> StyleSheet -> Bool
StyleSheet -> StyleSheet -> Ordering
StyleSheet -> StyleSheet -> StyleSheet
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 :: StyleSheet -> StyleSheet -> StyleSheet
$cmin :: StyleSheet -> StyleSheet -> StyleSheet
max :: StyleSheet -> StyleSheet -> StyleSheet
$cmax :: StyleSheet -> StyleSheet -> StyleSheet
>= :: StyleSheet -> StyleSheet -> Bool
$c>= :: StyleSheet -> StyleSheet -> Bool
> :: StyleSheet -> StyleSheet -> Bool
$c> :: StyleSheet -> StyleSheet -> Bool
<= :: StyleSheet -> StyleSheet -> Bool
$c<= :: StyleSheet -> StyleSheet -> Bool
< :: StyleSheet -> StyleSheet -> Bool
$c< :: StyleSheet -> StyleSheet -> Bool
compare :: StyleSheet -> StyleSheet -> Ordering
$ccompare :: StyleSheet -> StyleSheet -> Ordering
Ord, Int -> StyleSheet -> ShowS
[StyleSheet] -> ShowS
StyleSheet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StyleSheet] -> ShowS
$cshowList :: [StyleSheet] -> ShowS
show :: StyleSheet -> String
$cshow :: StyleSheet -> String
showsPrec :: Int -> StyleSheet -> ShowS
$cshowsPrec :: Int -> StyleSheet -> ShowS
Show, forall x. Rep StyleSheet x -> StyleSheet
forall x. StyleSheet -> Rep StyleSheet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StyleSheet x -> StyleSheet
$cfrom :: forall x. StyleSheet -> Rep StyleSheet x
Generic)
instance NFData StyleSheet
data CellXf = CellXf {
CellXf -> Maybe Bool
_cellXfApplyAlignment :: Maybe Bool
, CellXf -> Maybe Bool
_cellXfApplyBorder :: Maybe Bool
, CellXf -> Maybe Bool
_cellXfApplyFill :: Maybe Bool
, CellXf -> Maybe Bool
_cellXfApplyFont :: Maybe Bool
, CellXf -> Maybe Bool
_cellXfApplyNumberFormat :: Maybe Bool
, CellXf -> Maybe Bool
_cellXfApplyProtection :: Maybe Bool
, CellXf -> Maybe Int
_cellXfBorderId :: Maybe Int
, CellXf -> Maybe Int
_cellXfFillId :: Maybe Int
, CellXf -> Maybe Int
_cellXfFontId :: Maybe Int
, CellXf -> Maybe Int
_cellXfNumFmtId :: Maybe Int
, CellXf -> Maybe Bool
_cellXfPivotButton :: Maybe Bool
, CellXf -> Maybe Bool
_cellXfQuotePrefix :: Maybe Bool
, CellXf -> Maybe Int
_cellXfId :: Maybe Int
, CellXf -> Maybe Alignment
_cellXfAlignment :: Maybe Alignment
, CellXf -> Maybe Protection
_cellXfProtection :: Maybe Protection
}
deriving (CellXf -> CellXf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellXf -> CellXf -> Bool
$c/= :: CellXf -> CellXf -> Bool
== :: CellXf -> CellXf -> Bool
$c== :: CellXf -> CellXf -> Bool
Eq, Eq CellXf
CellXf -> CellXf -> Bool
CellXf -> CellXf -> Ordering
CellXf -> CellXf -> CellXf
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 :: CellXf -> CellXf -> CellXf
$cmin :: CellXf -> CellXf -> CellXf
max :: CellXf -> CellXf -> CellXf
$cmax :: CellXf -> CellXf -> CellXf
>= :: CellXf -> CellXf -> Bool
$c>= :: CellXf -> CellXf -> Bool
> :: CellXf -> CellXf -> Bool
$c> :: CellXf -> CellXf -> Bool
<= :: CellXf -> CellXf -> Bool
$c<= :: CellXf -> CellXf -> Bool
< :: CellXf -> CellXf -> Bool
$c< :: CellXf -> CellXf -> Bool
compare :: CellXf -> CellXf -> Ordering
$ccompare :: CellXf -> CellXf -> Ordering
Ord, Int -> CellXf -> ShowS
[CellXf] -> ShowS
CellXf -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CellXf] -> ShowS
$cshowList :: [CellXf] -> ShowS
show :: CellXf -> String
$cshow :: CellXf -> String
showsPrec :: Int -> CellXf -> ShowS
$cshowsPrec :: Int -> CellXf -> ShowS
Show, forall x. Rep CellXf x -> CellXf
forall x. CellXf -> Rep CellXf x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CellXf x -> CellXf
$cfrom :: forall x. CellXf -> Rep CellXf x
Generic)
instance NFData CellXf
data Alignment = Alignment {
Alignment -> Maybe CellHorizontalAlignment
_alignmentHorizontal :: Maybe CellHorizontalAlignment
, Alignment -> Maybe Int
_alignmentIndent :: Maybe Int
, Alignment -> Maybe Bool
_alignmentJustifyLastLine :: Maybe Bool
, Alignment -> Maybe ReadingOrder
_alignmentReadingOrder :: Maybe ReadingOrder
, Alignment -> Maybe Int
_alignmentRelativeIndent :: Maybe Int
, Alignment -> Maybe Bool
_alignmentShrinkToFit :: Maybe Bool
, Alignment -> Maybe Int
_alignmentTextRotation :: Maybe Int
, Alignment -> Maybe CellVerticalAlignment
_alignmentVertical :: Maybe CellVerticalAlignment
, Alignment -> Maybe Bool
_alignmentWrapText :: Maybe Bool
}
deriving (Alignment -> Alignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Alignment -> Alignment -> Bool
$c/= :: Alignment -> Alignment -> Bool
== :: Alignment -> Alignment -> Bool
$c== :: Alignment -> Alignment -> Bool
Eq, Eq Alignment
Alignment -> Alignment -> Bool
Alignment -> Alignment -> Ordering
Alignment -> Alignment -> Alignment
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 :: Alignment -> Alignment -> Alignment
$cmin :: Alignment -> Alignment -> Alignment
max :: Alignment -> Alignment -> Alignment
$cmax :: Alignment -> Alignment -> Alignment
>= :: Alignment -> Alignment -> Bool
$c>= :: Alignment -> Alignment -> Bool
> :: Alignment -> Alignment -> Bool
$c> :: Alignment -> Alignment -> Bool
<= :: Alignment -> Alignment -> Bool
$c<= :: Alignment -> Alignment -> Bool
< :: Alignment -> Alignment -> Bool
$c< :: Alignment -> Alignment -> Bool
compare :: Alignment -> Alignment -> Ordering
$ccompare :: Alignment -> Alignment -> Ordering
Ord, Int -> Alignment -> ShowS
[Alignment] -> ShowS
Alignment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Alignment] -> ShowS
$cshowList :: [Alignment] -> ShowS
show :: Alignment -> String
$cshow :: Alignment -> String
showsPrec :: Int -> Alignment -> ShowS
$cshowsPrec :: Int -> Alignment -> ShowS
Show, forall x. Rep Alignment x -> Alignment
forall x. Alignment -> Rep Alignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Alignment x -> Alignment
$cfrom :: forall x. Alignment -> Rep Alignment x
Generic)
instance NFData Alignment
data Border = Border {
Border -> Maybe Bool
_borderDiagonalDown :: Maybe Bool
, Border -> Maybe Bool
_borderDiagonalUp :: Maybe Bool
, Border -> Maybe Bool
_borderOutline :: Maybe Bool
, Border -> Maybe BorderStyle
_borderBottom :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderDiagonal :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderEnd :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderHorizontal :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderLeft :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderRight :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderStart :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderTop :: Maybe BorderStyle
, Border -> Maybe BorderStyle
_borderVertical :: Maybe BorderStyle
}
deriving (Border -> Border -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Border -> Border -> Bool
$c/= :: Border -> Border -> Bool
== :: Border -> Border -> Bool
$c== :: Border -> Border -> Bool
Eq, Eq Border
Border -> Border -> Bool
Border -> Border -> Ordering
Border -> Border -> Border
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 :: Border -> Border -> Border
$cmin :: Border -> Border -> Border
max :: Border -> Border -> Border
$cmax :: Border -> Border -> Border
>= :: Border -> Border -> Bool
$c>= :: Border -> Border -> Bool
> :: Border -> Border -> Bool
$c> :: Border -> Border -> Bool
<= :: Border -> Border -> Bool
$c<= :: Border -> Border -> Bool
< :: Border -> Border -> Bool
$c< :: Border -> Border -> Bool
compare :: Border -> Border -> Ordering
$ccompare :: Border -> Border -> Ordering
Ord, Int -> Border -> ShowS
[Border] -> ShowS
Border -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Border] -> ShowS
$cshowList :: [Border] -> ShowS
show :: Border -> String
$cshow :: Border -> String
showsPrec :: Int -> Border -> ShowS
$cshowsPrec :: Int -> Border -> ShowS
Show, forall x. Rep Border x -> Border
forall x. Border -> Rep Border x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Border x -> Border
$cfrom :: forall x. Border -> Rep Border x
Generic)
instance NFData Border
data BorderStyle = BorderStyle {
BorderStyle -> Maybe Color
_borderStyleColor :: Maybe Color
, BorderStyle -> Maybe LineStyle
_borderStyleLine :: Maybe LineStyle
}
deriving (BorderStyle -> BorderStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BorderStyle -> BorderStyle -> Bool
$c/= :: BorderStyle -> BorderStyle -> Bool
== :: BorderStyle -> BorderStyle -> Bool
$c== :: BorderStyle -> BorderStyle -> Bool
Eq, Eq BorderStyle
BorderStyle -> BorderStyle -> Bool
BorderStyle -> BorderStyle -> Ordering
BorderStyle -> BorderStyle -> BorderStyle
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 :: BorderStyle -> BorderStyle -> BorderStyle
$cmin :: BorderStyle -> BorderStyle -> BorderStyle
max :: BorderStyle -> BorderStyle -> BorderStyle
$cmax :: BorderStyle -> BorderStyle -> BorderStyle
>= :: BorderStyle -> BorderStyle -> Bool
$c>= :: BorderStyle -> BorderStyle -> Bool
> :: BorderStyle -> BorderStyle -> Bool
$c> :: BorderStyle -> BorderStyle -> Bool
<= :: BorderStyle -> BorderStyle -> Bool
$c<= :: BorderStyle -> BorderStyle -> Bool
< :: BorderStyle -> BorderStyle -> Bool
$c< :: BorderStyle -> BorderStyle -> Bool
compare :: BorderStyle -> BorderStyle -> Ordering
$ccompare :: BorderStyle -> BorderStyle -> Ordering
Ord, Int -> BorderStyle -> ShowS
[BorderStyle] -> ShowS
BorderStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BorderStyle] -> ShowS
$cshowList :: [BorderStyle] -> ShowS
show :: BorderStyle -> String
$cshow :: BorderStyle -> String
showsPrec :: Int -> BorderStyle -> ShowS
$cshowsPrec :: Int -> BorderStyle -> ShowS
Show, forall x. Rep BorderStyle x -> BorderStyle
forall x. BorderStyle -> Rep BorderStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BorderStyle x -> BorderStyle
$cfrom :: forall x. BorderStyle -> Rep BorderStyle x
Generic)
instance NFData BorderStyle
data Color = Color {
Color -> Maybe Bool
_colorAutomatic :: Maybe Bool
, Color -> Maybe FormatCode
_colorARGB :: Maybe Text
, Color -> Maybe Int
_colorTheme :: Maybe Int
, Color -> Maybe Double
_colorTint :: Maybe Double
}
deriving (Color -> Color -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c== :: Color -> Color -> Bool
Eq, Eq Color
Color -> Color -> Bool
Color -> Color -> Ordering
Color -> Color -> Color
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 :: Color -> Color -> Color
$cmin :: Color -> Color -> Color
max :: Color -> Color -> Color
$cmax :: Color -> Color -> Color
>= :: Color -> Color -> Bool
$c>= :: Color -> Color -> Bool
> :: Color -> Color -> Bool
$c> :: Color -> Color -> Bool
<= :: Color -> Color -> Bool
$c<= :: Color -> Color -> Bool
< :: Color -> Color -> Bool
$c< :: Color -> Color -> Bool
compare :: Color -> Color -> Ordering
$ccompare :: Color -> Color -> Ordering
Ord, Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Color] -> ShowS
$cshowList :: [Color] -> ShowS
show :: Color -> String
$cshow :: Color -> String
showsPrec :: Int -> Color -> ShowS
$cshowsPrec :: Int -> Color -> ShowS
Show, forall x. Rep Color x -> Color
forall x. Color -> Rep Color x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Color x -> Color
$cfrom :: forall x. Color -> Rep Color x
Generic)
instance NFData Color
data Fill = Fill {
Fill -> Maybe FillPattern
_fillPattern :: Maybe FillPattern
}
deriving (Fill -> Fill -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Fill -> Fill -> Bool
$c/= :: Fill -> Fill -> Bool
== :: Fill -> Fill -> Bool
$c== :: Fill -> Fill -> Bool
Eq, Eq Fill
Fill -> Fill -> Bool
Fill -> Fill -> Ordering
Fill -> Fill -> Fill
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 :: Fill -> Fill -> Fill
$cmin :: Fill -> Fill -> Fill
max :: Fill -> Fill -> Fill
$cmax :: Fill -> Fill -> Fill
>= :: Fill -> Fill -> Bool
$c>= :: Fill -> Fill -> Bool
> :: Fill -> Fill -> Bool
$c> :: Fill -> Fill -> Bool
<= :: Fill -> Fill -> Bool
$c<= :: Fill -> Fill -> Bool
< :: Fill -> Fill -> Bool
$c< :: Fill -> Fill -> Bool
compare :: Fill -> Fill -> Ordering
$ccompare :: Fill -> Fill -> Ordering
Ord, Int -> Fill -> ShowS
[Fill] -> ShowS
Fill -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Fill] -> ShowS
$cshowList :: [Fill] -> ShowS
show :: Fill -> String
$cshow :: Fill -> String
showsPrec :: Int -> Fill -> ShowS
$cshowsPrec :: Int -> Fill -> ShowS
Show, forall x. Rep Fill x -> Fill
forall x. Fill -> Rep Fill x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Fill x -> Fill
$cfrom :: forall x. Fill -> Rep Fill x
Generic)
instance NFData Fill
data FillPattern = FillPattern {
FillPattern -> Maybe Color
_fillPatternBgColor :: Maybe Color
, FillPattern -> Maybe Color
_fillPatternFgColor :: Maybe Color
, FillPattern -> Maybe PatternType
_fillPatternType :: Maybe PatternType
}
deriving (FillPattern -> FillPattern -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FillPattern -> FillPattern -> Bool
$c/= :: FillPattern -> FillPattern -> Bool
== :: FillPattern -> FillPattern -> Bool
$c== :: FillPattern -> FillPattern -> Bool
Eq, Eq FillPattern
FillPattern -> FillPattern -> Bool
FillPattern -> FillPattern -> Ordering
FillPattern -> FillPattern -> FillPattern
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 :: FillPattern -> FillPattern -> FillPattern
$cmin :: FillPattern -> FillPattern -> FillPattern
max :: FillPattern -> FillPattern -> FillPattern
$cmax :: FillPattern -> FillPattern -> FillPattern
>= :: FillPattern -> FillPattern -> Bool
$c>= :: FillPattern -> FillPattern -> Bool
> :: FillPattern -> FillPattern -> Bool
$c> :: FillPattern -> FillPattern -> Bool
<= :: FillPattern -> FillPattern -> Bool
$c<= :: FillPattern -> FillPattern -> Bool
< :: FillPattern -> FillPattern -> Bool
$c< :: FillPattern -> FillPattern -> Bool
compare :: FillPattern -> FillPattern -> Ordering
$ccompare :: FillPattern -> FillPattern -> Ordering
Ord, Int -> FillPattern -> ShowS
[FillPattern] -> ShowS
FillPattern -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FillPattern] -> ShowS
$cshowList :: [FillPattern] -> ShowS
show :: FillPattern -> String
$cshow :: FillPattern -> String
showsPrec :: Int -> FillPattern -> ShowS
$cshowsPrec :: Int -> FillPattern -> ShowS
Show, forall x. Rep FillPattern x -> FillPattern
forall x. FillPattern -> Rep FillPattern x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FillPattern x -> FillPattern
$cfrom :: forall x. FillPattern -> Rep FillPattern x
Generic)
instance NFData FillPattern
data Font = Font {
Font -> Maybe Bool
_fontBold :: Maybe Bool
, Font -> Maybe Int
_fontCharset :: Maybe Int
, Font -> Maybe Color
_fontColor :: Maybe Color
, Font -> Maybe Bool
_fontCondense :: Maybe Bool
, Font -> Maybe Bool
_fontExtend :: Maybe Bool
, Font -> Maybe FontFamily
_fontFamily :: Maybe FontFamily
, Font -> Maybe Bool
_fontItalic :: Maybe Bool
, Font -> Maybe FormatCode
_fontName :: Maybe Text
, Font -> Maybe Bool
_fontOutline :: Maybe Bool
, Font -> Maybe FontScheme
_fontScheme :: Maybe FontScheme
, Font -> Maybe Bool
_fontShadow :: Maybe Bool
, Font -> Maybe Bool
_fontStrikeThrough :: Maybe Bool
, Font -> Maybe Double
_fontSize :: Maybe Double
, Font -> Maybe FontUnderline
_fontUnderline :: Maybe FontUnderline
, Font -> Maybe FontVerticalAlignment
_fontVertAlign :: Maybe FontVerticalAlignment
}
deriving (Font -> Font -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Font -> Font -> Bool
$c/= :: Font -> Font -> Bool
== :: Font -> Font -> Bool
$c== :: Font -> Font -> Bool
Eq, Eq Font
Font -> Font -> Bool
Font -> Font -> Ordering
Font -> Font -> Font
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 :: Font -> Font -> Font
$cmin :: Font -> Font -> Font
max :: Font -> Font -> Font
$cmax :: Font -> Font -> Font
>= :: Font -> Font -> Bool
$c>= :: Font -> Font -> Bool
> :: Font -> Font -> Bool
$c> :: Font -> Font -> Bool
<= :: Font -> Font -> Bool
$c<= :: Font -> Font -> Bool
< :: Font -> Font -> Bool
$c< :: Font -> Font -> Bool
compare :: Font -> Font -> Ordering
$ccompare :: Font -> Font -> Ordering
Ord, Int -> Font -> ShowS
[Font] -> ShowS
Font -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Font] -> ShowS
$cshowList :: [Font] -> ShowS
show :: Font -> String
$cshow :: Font -> String
showsPrec :: Int -> Font -> ShowS
$cshowsPrec :: Int -> Font -> ShowS
Show, forall x. Rep Font x -> Font
forall x. Font -> Rep Font x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Font x -> Font
$cfrom :: forall x. Font -> Rep Font x
Generic)
instance NFData Font
data Dxf = Dxf
{ Dxf -> Maybe Font
_dxfFont :: Maybe Font
, Dxf -> Maybe NumFmt
_dxfNumFmt :: Maybe NumFmt
, Dxf -> Maybe Fill
_dxfFill :: Maybe Fill
, Dxf -> Maybe Alignment
_dxfAlignment :: Maybe Alignment
, Dxf -> Maybe Border
_dxfBorder :: Maybe Border
, Dxf -> Maybe Protection
_dxfProtection :: Maybe Protection
} deriving (Dxf -> Dxf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dxf -> Dxf -> Bool
$c/= :: Dxf -> Dxf -> Bool
== :: Dxf -> Dxf -> Bool
$c== :: Dxf -> Dxf -> Bool
Eq, Eq Dxf
Dxf -> Dxf -> Bool
Dxf -> Dxf -> Ordering
Dxf -> Dxf -> Dxf
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 :: Dxf -> Dxf -> Dxf
$cmin :: Dxf -> Dxf -> Dxf
max :: Dxf -> Dxf -> Dxf
$cmax :: Dxf -> Dxf -> Dxf
>= :: Dxf -> Dxf -> Bool
$c>= :: Dxf -> Dxf -> Bool
> :: Dxf -> Dxf -> Bool
$c> :: Dxf -> Dxf -> Bool
<= :: Dxf -> Dxf -> Bool
$c<= :: Dxf -> Dxf -> Bool
< :: Dxf -> Dxf -> Bool
$c< :: Dxf -> Dxf -> Bool
compare :: Dxf -> Dxf -> Ordering
$ccompare :: Dxf -> Dxf -> Ordering
Ord, Int -> Dxf -> ShowS
[Dxf] -> ShowS
Dxf -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dxf] -> ShowS
$cshowList :: [Dxf] -> ShowS
show :: Dxf -> String
$cshow :: Dxf -> String
showsPrec :: Int -> Dxf -> ShowS
$cshowsPrec :: Int -> Dxf -> ShowS
Show, forall x. Rep Dxf x -> Dxf
forall x. Dxf -> Rep Dxf x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Dxf x -> Dxf
$cfrom :: forall x. Dxf -> Rep Dxf x
Generic)
instance NFData Dxf
type FormatCode = Text
data NumFmt = NumFmt
{ NumFmt -> Int
_numFmtId :: Int
, NumFmt -> FormatCode
_numFmtCode :: FormatCode
} deriving (NumFmt -> NumFmt -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumFmt -> NumFmt -> Bool
$c/= :: NumFmt -> NumFmt -> Bool
== :: NumFmt -> NumFmt -> Bool
$c== :: NumFmt -> NumFmt -> Bool
Eq, Eq NumFmt
NumFmt -> NumFmt -> Bool
NumFmt -> NumFmt -> Ordering
NumFmt -> NumFmt -> NumFmt
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 :: NumFmt -> NumFmt -> NumFmt
$cmin :: NumFmt -> NumFmt -> NumFmt
max :: NumFmt -> NumFmt -> NumFmt
$cmax :: NumFmt -> NumFmt -> NumFmt
>= :: NumFmt -> NumFmt -> Bool
$c>= :: NumFmt -> NumFmt -> Bool
> :: NumFmt -> NumFmt -> Bool
$c> :: NumFmt -> NumFmt -> Bool
<= :: NumFmt -> NumFmt -> Bool
$c<= :: NumFmt -> NumFmt -> Bool
< :: NumFmt -> NumFmt -> Bool
$c< :: NumFmt -> NumFmt -> Bool
compare :: NumFmt -> NumFmt -> Ordering
$ccompare :: NumFmt -> NumFmt -> Ordering
Ord, Int -> NumFmt -> ShowS
[NumFmt] -> ShowS
NumFmt -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NumFmt] -> ShowS
$cshowList :: [NumFmt] -> ShowS
show :: NumFmt -> String
$cshow :: NumFmt -> String
showsPrec :: Int -> NumFmt -> ShowS
$cshowsPrec :: Int -> NumFmt -> ShowS
Show, forall x. Rep NumFmt x -> NumFmt
forall x. NumFmt -> Rep NumFmt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NumFmt x -> NumFmt
$cfrom :: forall x. NumFmt -> Rep NumFmt x
Generic)
instance NFData NumFmt
mkNumFmtPair :: NumFmt -> (Int, FormatCode)
mkNumFmtPair :: NumFmt -> (Int, FormatCode)
mkNumFmtPair NumFmt{Int
FormatCode
_numFmtCode :: FormatCode
_numFmtId :: Int
_numFmtCode :: NumFmt -> FormatCode
_numFmtId :: NumFmt -> Int
..} = (Int
_numFmtId, FormatCode
_numFmtCode)
data NumberFormat
= StdNumberFormat ImpliedNumberFormat
| UserNumberFormat FormatCode
deriving (NumberFormat -> NumberFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumberFormat -> NumberFormat -> Bool
$c/= :: NumberFormat -> NumberFormat -> Bool
== :: NumberFormat -> NumberFormat -> Bool
$c== :: NumberFormat -> NumberFormat -> Bool
Eq, Eq NumberFormat
NumberFormat -> NumberFormat -> Bool
NumberFormat -> NumberFormat -> Ordering
NumberFormat -> NumberFormat -> NumberFormat
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 :: NumberFormat -> NumberFormat -> NumberFormat
$cmin :: NumberFormat -> NumberFormat -> NumberFormat
max :: NumberFormat -> NumberFormat -> NumberFormat
$cmax :: NumberFormat -> NumberFormat -> NumberFormat
>= :: NumberFormat -> NumberFormat -> Bool
$c>= :: NumberFormat -> NumberFormat -> Bool
> :: NumberFormat -> NumberFormat -> Bool
$c> :: NumberFormat -> NumberFormat -> Bool
<= :: NumberFormat -> NumberFormat -> Bool
$c<= :: NumberFormat -> NumberFormat -> Bool
< :: NumberFormat -> NumberFormat -> Bool
$c< :: NumberFormat -> NumberFormat -> Bool
compare :: NumberFormat -> NumberFormat -> Ordering
$ccompare :: NumberFormat -> NumberFormat -> Ordering
Ord, Int -> NumberFormat -> ShowS
[NumberFormat] -> ShowS
NumberFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NumberFormat] -> ShowS
$cshowList :: [NumberFormat] -> ShowS
show :: NumberFormat -> String
$cshow :: NumberFormat -> String
showsPrec :: Int -> NumberFormat -> ShowS
$cshowsPrec :: Int -> NumberFormat -> ShowS
Show, forall x. Rep NumberFormat x -> NumberFormat
forall x. NumberFormat -> Rep NumberFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NumberFormat x -> NumberFormat
$cfrom :: forall x. NumberFormat -> Rep NumberFormat x
Generic)
instance NFData NumberFormat
fmtDecimals :: Int -> NumberFormat
fmtDecimals :: Int -> NumberFormat
fmtDecimals Int
k = FormatCode -> NumberFormat
UserNumberFormat forall a b. (a -> b) -> a -> b
$ FormatCode
"0." forall a. Semigroup a => a -> a -> a
<> Int -> FormatCode -> FormatCode
T.replicate Int
k FormatCode
"#"
fmtDecimalsZeroes :: Int -> NumberFormat
fmtDecimalsZeroes :: Int -> NumberFormat
fmtDecimalsZeroes Int
k = FormatCode -> NumberFormat
UserNumberFormat forall a b. (a -> b) -> a -> b
$ FormatCode
"0." forall a. Semigroup a => a -> a -> a
<> Int -> FormatCode -> FormatCode
T.replicate Int
k FormatCode
"0"
data ImpliedNumberFormat =
NfGeneral
| NfZero
| Nf2Decimal
| NfMax3Decimal
| NfThousandSeparator2Decimal
| NfPercent
| NfPercent2Decimal
| NfExponent2Decimal
| NfSingleSpacedFraction
| NfDoubleSpacedFraction
| NfMmDdYy
| NfDMmmYy
| NfDMmm
| NfMmmYy
| NfHMm12Hr
| NfHMmSs12Hr
| NfHMm
| NfHMmSs
| NfMdyHMm
| NfThousandsNegativeParens
| NfThousandsNegativeRed
| NfThousands2DecimalNegativeParens
| NfThousands2DecimalNegativeRed
| NfMmSs
| NfOptHMmSs
| NfMmSs1Decimal
| NfExponent1Decimal
| NfTextPlaceHolder
| NfOtherImplied Int
deriving (ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
$c/= :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
== :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
$c== :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
Eq, Eq ImpliedNumberFormat
ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
ImpliedNumberFormat -> ImpliedNumberFormat -> Ordering
ImpliedNumberFormat -> ImpliedNumberFormat -> ImpliedNumberFormat
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 :: ImpliedNumberFormat -> ImpliedNumberFormat -> ImpliedNumberFormat
$cmin :: ImpliedNumberFormat -> ImpliedNumberFormat -> ImpliedNumberFormat
max :: ImpliedNumberFormat -> ImpliedNumberFormat -> ImpliedNumberFormat
$cmax :: ImpliedNumberFormat -> ImpliedNumberFormat -> ImpliedNumberFormat
>= :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
$c>= :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
> :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
$c> :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
<= :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
$c<= :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
< :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
$c< :: ImpliedNumberFormat -> ImpliedNumberFormat -> Bool
compare :: ImpliedNumberFormat -> ImpliedNumberFormat -> Ordering
$ccompare :: ImpliedNumberFormat -> ImpliedNumberFormat -> Ordering
Ord, Int -> ImpliedNumberFormat -> ShowS
[ImpliedNumberFormat] -> ShowS
ImpliedNumberFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImpliedNumberFormat] -> ShowS
$cshowList :: [ImpliedNumberFormat] -> ShowS
show :: ImpliedNumberFormat -> String
$cshow :: ImpliedNumberFormat -> String
showsPrec :: Int -> ImpliedNumberFormat -> ShowS
$cshowsPrec :: Int -> ImpliedNumberFormat -> ShowS
Show, forall x. Rep ImpliedNumberFormat x -> ImpliedNumberFormat
forall x. ImpliedNumberFormat -> Rep ImpliedNumberFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImpliedNumberFormat x -> ImpliedNumberFormat
$cfrom :: forall x. ImpliedNumberFormat -> Rep ImpliedNumberFormat x
Generic)
instance NFData ImpliedNumberFormat
stdNumberFormatId :: ImpliedNumberFormat -> Int
stdNumberFormatId :: ImpliedNumberFormat -> Int
stdNumberFormatId ImpliedNumberFormat
NfGeneral = Int
0
stdNumberFormatId ImpliedNumberFormat
NfZero = Int
1
stdNumberFormatId ImpliedNumberFormat
Nf2Decimal = Int
2
stdNumberFormatId ImpliedNumberFormat
NfMax3Decimal = Int
3
stdNumberFormatId ImpliedNumberFormat
NfThousandSeparator2Decimal = Int
4
stdNumberFormatId ImpliedNumberFormat
NfPercent = Int
9
stdNumberFormatId ImpliedNumberFormat
NfPercent2Decimal = Int
10
stdNumberFormatId ImpliedNumberFormat
NfExponent2Decimal = Int
11
stdNumberFormatId ImpliedNumberFormat
NfSingleSpacedFraction = Int
12
stdNumberFormatId ImpliedNumberFormat
NfDoubleSpacedFraction = Int
13
stdNumberFormatId ImpliedNumberFormat
NfMmDdYy = Int
14
stdNumberFormatId ImpliedNumberFormat
NfDMmmYy = Int
15
stdNumberFormatId ImpliedNumberFormat
NfDMmm = Int
16
stdNumberFormatId ImpliedNumberFormat
NfMmmYy = Int
17
stdNumberFormatId ImpliedNumberFormat
NfHMm12Hr = Int
18
stdNumberFormatId ImpliedNumberFormat
NfHMmSs12Hr = Int
19
stdNumberFormatId ImpliedNumberFormat
NfHMm = Int
20
stdNumberFormatId ImpliedNumberFormat
NfHMmSs = Int
21
stdNumberFormatId ImpliedNumberFormat
NfMdyHMm = Int
22
stdNumberFormatId ImpliedNumberFormat
NfThousandsNegativeParens = Int
37
stdNumberFormatId ImpliedNumberFormat
NfThousandsNegativeRed = Int
38
stdNumberFormatId ImpliedNumberFormat
NfThousands2DecimalNegativeParens = Int
39
stdNumberFormatId ImpliedNumberFormat
NfThousands2DecimalNegativeRed = Int
40
stdNumberFormatId ImpliedNumberFormat
NfMmSs = Int
45
stdNumberFormatId ImpliedNumberFormat
NfOptHMmSs = Int
46
stdNumberFormatId ImpliedNumberFormat
NfMmSs1Decimal = Int
47
stdNumberFormatId ImpliedNumberFormat
NfExponent1Decimal = Int
48
stdNumberFormatId ImpliedNumberFormat
NfTextPlaceHolder = Int
49
stdNumberFormatId (NfOtherImplied Int
i) = Int
i
idToStdNumberFormat :: Int -> Maybe ImpliedNumberFormat
idToStdNumberFormat :: Int -> Maybe ImpliedNumberFormat
idToStdNumberFormat Int
0 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfGeneral
idToStdNumberFormat Int
1 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfZero
idToStdNumberFormat Int
2 = forall a. a -> Maybe a
Just ImpliedNumberFormat
Nf2Decimal
idToStdNumberFormat Int
3 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfMax3Decimal
idToStdNumberFormat Int
4 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfThousandSeparator2Decimal
idToStdNumberFormat Int
9 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfPercent
idToStdNumberFormat Int
10 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfPercent2Decimal
idToStdNumberFormat Int
11 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfExponent2Decimal
idToStdNumberFormat Int
12 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfSingleSpacedFraction
idToStdNumberFormat Int
13 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfDoubleSpacedFraction
idToStdNumberFormat Int
14 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfMmDdYy
idToStdNumberFormat Int
15 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfDMmmYy
idToStdNumberFormat Int
16 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfDMmm
idToStdNumberFormat Int
17 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfMmmYy
idToStdNumberFormat Int
18 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfHMm12Hr
idToStdNumberFormat Int
19 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfHMmSs12Hr
idToStdNumberFormat Int
20 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfHMm
idToStdNumberFormat Int
21 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfHMmSs
idToStdNumberFormat Int
22 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfMdyHMm
idToStdNumberFormat Int
37 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfThousandsNegativeParens
idToStdNumberFormat Int
38 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfThousandsNegativeRed
idToStdNumberFormat Int
39 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfThousands2DecimalNegativeParens
idToStdNumberFormat Int
40 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfThousands2DecimalNegativeRed
idToStdNumberFormat Int
45 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfMmSs
idToStdNumberFormat Int
46 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfOptHMmSs
idToStdNumberFormat Int
47 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfMmSs1Decimal
idToStdNumberFormat Int
48 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfExponent1Decimal
idToStdNumberFormat Int
49 = forall a. a -> Maybe a
Just ImpliedNumberFormat
NfTextPlaceHolder
idToStdNumberFormat Int
i = if Int
i forall a. Ord a => a -> a -> Bool
< Int
firstUserNumFmtId then forall a. a -> Maybe a
Just (Int -> ImpliedNumberFormat
NfOtherImplied Int
i) else forall a. Maybe a
Nothing
firstUserNumFmtId :: Int
firstUserNumFmtId :: Int
firstUserNumFmtId = Int
164
data Protection = Protection {
Protection -> Maybe Bool
_protectionHidden :: Maybe Bool
, Protection -> Maybe Bool
_protectionLocked :: Maybe Bool
}
deriving (Protection -> Protection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Protection -> Protection -> Bool
$c/= :: Protection -> Protection -> Bool
== :: Protection -> Protection -> Bool
$c== :: Protection -> Protection -> Bool
Eq, Eq Protection
Protection -> Protection -> Bool
Protection -> Protection -> Ordering
Protection -> Protection -> Protection
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 :: Protection -> Protection -> Protection
$cmin :: Protection -> Protection -> Protection
max :: Protection -> Protection -> Protection
$cmax :: Protection -> Protection -> Protection
>= :: Protection -> Protection -> Bool
$c>= :: Protection -> Protection -> Bool
> :: Protection -> Protection -> Bool
$c> :: Protection -> Protection -> Bool
<= :: Protection -> Protection -> Bool
$c<= :: Protection -> Protection -> Bool
< :: Protection -> Protection -> Bool
$c< :: Protection -> Protection -> Bool
compare :: Protection -> Protection -> Ordering
$ccompare :: Protection -> Protection -> Ordering
Ord, Int -> Protection -> ShowS
[Protection] -> ShowS
Protection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Protection] -> ShowS
$cshowList :: [Protection] -> ShowS
show :: Protection -> String
$cshow :: Protection -> String
showsPrec :: Int -> Protection -> ShowS
$cshowsPrec :: Int -> Protection -> ShowS
Show, forall x. Rep Protection x -> Protection
forall x. Protection -> Rep Protection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Protection x -> Protection
$cfrom :: forall x. Protection -> Rep Protection x
Generic)
instance NFData Protection
data CellHorizontalAlignment =
CellHorizontalAlignmentCenter
| CellHorizontalAlignmentCenterContinuous
| CellHorizontalAlignmentDistributed
| CellHorizontalAlignmentFill
| CellHorizontalAlignmentGeneral
| CellHorizontalAlignmentJustify
| CellHorizontalAlignmentLeft
| CellHorizontalAlignmentRight
deriving (CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
$c/= :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
== :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
$c== :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
Eq, Eq CellHorizontalAlignment
CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
CellHorizontalAlignment -> CellHorizontalAlignment -> Ordering
CellHorizontalAlignment
-> CellHorizontalAlignment -> CellHorizontalAlignment
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 :: CellHorizontalAlignment
-> CellHorizontalAlignment -> CellHorizontalAlignment
$cmin :: CellHorizontalAlignment
-> CellHorizontalAlignment -> CellHorizontalAlignment
max :: CellHorizontalAlignment
-> CellHorizontalAlignment -> CellHorizontalAlignment
$cmax :: CellHorizontalAlignment
-> CellHorizontalAlignment -> CellHorizontalAlignment
>= :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
$c>= :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
> :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
$c> :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
<= :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
$c<= :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
< :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
$c< :: CellHorizontalAlignment -> CellHorizontalAlignment -> Bool
compare :: CellHorizontalAlignment -> CellHorizontalAlignment -> Ordering
$ccompare :: CellHorizontalAlignment -> CellHorizontalAlignment -> Ordering
Ord, Int -> CellHorizontalAlignment -> ShowS
[CellHorizontalAlignment] -> ShowS
CellHorizontalAlignment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CellHorizontalAlignment] -> ShowS
$cshowList :: [CellHorizontalAlignment] -> ShowS
show :: CellHorizontalAlignment -> String
$cshow :: CellHorizontalAlignment -> String
showsPrec :: Int -> CellHorizontalAlignment -> ShowS
$cshowsPrec :: Int -> CellHorizontalAlignment -> ShowS
Show, forall x. Rep CellHorizontalAlignment x -> CellHorizontalAlignment
forall x. CellHorizontalAlignment -> Rep CellHorizontalAlignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CellHorizontalAlignment x -> CellHorizontalAlignment
$cfrom :: forall x. CellHorizontalAlignment -> Rep CellHorizontalAlignment x
Generic)
instance NFData CellHorizontalAlignment
data CellVerticalAlignment =
CellVerticalAlignmentBottom
| CellVerticalAlignmentCenter
| CellVerticalAlignmentDistributed
| CellVerticalAlignmentJustify
| CellVerticalAlignmentTop
deriving (CellVerticalAlignment -> CellVerticalAlignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
$c/= :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
== :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
$c== :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
Eq, Eq CellVerticalAlignment
CellVerticalAlignment -> CellVerticalAlignment -> Bool
CellVerticalAlignment -> CellVerticalAlignment -> Ordering
CellVerticalAlignment
-> CellVerticalAlignment -> CellVerticalAlignment
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 :: CellVerticalAlignment
-> CellVerticalAlignment -> CellVerticalAlignment
$cmin :: CellVerticalAlignment
-> CellVerticalAlignment -> CellVerticalAlignment
max :: CellVerticalAlignment
-> CellVerticalAlignment -> CellVerticalAlignment
$cmax :: CellVerticalAlignment
-> CellVerticalAlignment -> CellVerticalAlignment
>= :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
$c>= :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
> :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
$c> :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
<= :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
$c<= :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
< :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
$c< :: CellVerticalAlignment -> CellVerticalAlignment -> Bool
compare :: CellVerticalAlignment -> CellVerticalAlignment -> Ordering
$ccompare :: CellVerticalAlignment -> CellVerticalAlignment -> Ordering
Ord, Int -> CellVerticalAlignment -> ShowS
[CellVerticalAlignment] -> ShowS
CellVerticalAlignment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CellVerticalAlignment] -> ShowS
$cshowList :: [CellVerticalAlignment] -> ShowS
show :: CellVerticalAlignment -> String
$cshow :: CellVerticalAlignment -> String
showsPrec :: Int -> CellVerticalAlignment -> ShowS
$cshowsPrec :: Int -> CellVerticalAlignment -> ShowS
Show, forall x. Rep CellVerticalAlignment x -> CellVerticalAlignment
forall x. CellVerticalAlignment -> Rep CellVerticalAlignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CellVerticalAlignment x -> CellVerticalAlignment
$cfrom :: forall x. CellVerticalAlignment -> Rep CellVerticalAlignment x
Generic)
instance NFData CellVerticalAlignment
data FontFamily =
FontFamilyNotApplicable
| FontFamilyRoman
| FontFamilySwiss
| FontFamilyModern
| FontFamilyScript
| FontFamilyDecorative
deriving (FontFamily -> FontFamily -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontFamily -> FontFamily -> Bool
$c/= :: FontFamily -> FontFamily -> Bool
== :: FontFamily -> FontFamily -> Bool
$c== :: FontFamily -> FontFamily -> Bool
Eq, Eq FontFamily
FontFamily -> FontFamily -> Bool
FontFamily -> FontFamily -> Ordering
FontFamily -> FontFamily -> FontFamily
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 :: FontFamily -> FontFamily -> FontFamily
$cmin :: FontFamily -> FontFamily -> FontFamily
max :: FontFamily -> FontFamily -> FontFamily
$cmax :: FontFamily -> FontFamily -> FontFamily
>= :: FontFamily -> FontFamily -> Bool
$c>= :: FontFamily -> FontFamily -> Bool
> :: FontFamily -> FontFamily -> Bool
$c> :: FontFamily -> FontFamily -> Bool
<= :: FontFamily -> FontFamily -> Bool
$c<= :: FontFamily -> FontFamily -> Bool
< :: FontFamily -> FontFamily -> Bool
$c< :: FontFamily -> FontFamily -> Bool
compare :: FontFamily -> FontFamily -> Ordering
$ccompare :: FontFamily -> FontFamily -> Ordering
Ord, Int -> FontFamily -> ShowS
[FontFamily] -> ShowS
FontFamily -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontFamily] -> ShowS
$cshowList :: [FontFamily] -> ShowS
show :: FontFamily -> String
$cshow :: FontFamily -> String
showsPrec :: Int -> FontFamily -> ShowS
$cshowsPrec :: Int -> FontFamily -> ShowS
Show, forall x. Rep FontFamily x -> FontFamily
forall x. FontFamily -> Rep FontFamily x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FontFamily x -> FontFamily
$cfrom :: forall x. FontFamily -> Rep FontFamily x
Generic)
instance NFData FontFamily
data FontScheme =
FontSchemeMajor
| FontSchemeMinor
| FontSchemeNone
deriving (FontScheme -> FontScheme -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontScheme -> FontScheme -> Bool
$c/= :: FontScheme -> FontScheme -> Bool
== :: FontScheme -> FontScheme -> Bool
$c== :: FontScheme -> FontScheme -> Bool
Eq, Eq FontScheme
FontScheme -> FontScheme -> Bool
FontScheme -> FontScheme -> Ordering
FontScheme -> FontScheme -> FontScheme
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 :: FontScheme -> FontScheme -> FontScheme
$cmin :: FontScheme -> FontScheme -> FontScheme
max :: FontScheme -> FontScheme -> FontScheme
$cmax :: FontScheme -> FontScheme -> FontScheme
>= :: FontScheme -> FontScheme -> Bool
$c>= :: FontScheme -> FontScheme -> Bool
> :: FontScheme -> FontScheme -> Bool
$c> :: FontScheme -> FontScheme -> Bool
<= :: FontScheme -> FontScheme -> Bool
$c<= :: FontScheme -> FontScheme -> Bool
< :: FontScheme -> FontScheme -> Bool
$c< :: FontScheme -> FontScheme -> Bool
compare :: FontScheme -> FontScheme -> Ordering
$ccompare :: FontScheme -> FontScheme -> Ordering
Ord, Int -> FontScheme -> ShowS
[FontScheme] -> ShowS
FontScheme -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontScheme] -> ShowS
$cshowList :: [FontScheme] -> ShowS
show :: FontScheme -> String
$cshow :: FontScheme -> String
showsPrec :: Int -> FontScheme -> ShowS
$cshowsPrec :: Int -> FontScheme -> ShowS
Show, forall x. Rep FontScheme x -> FontScheme
forall x. FontScheme -> Rep FontScheme x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FontScheme x -> FontScheme
$cfrom :: forall x. FontScheme -> Rep FontScheme x
Generic)
instance NFData FontScheme
data FontUnderline =
FontUnderlineSingle
| FontUnderlineDouble
| FontUnderlineSingleAccounting
| FontUnderlineDoubleAccounting
| FontUnderlineNone
deriving (FontUnderline -> FontUnderline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontUnderline -> FontUnderline -> Bool
$c/= :: FontUnderline -> FontUnderline -> Bool
== :: FontUnderline -> FontUnderline -> Bool
$c== :: FontUnderline -> FontUnderline -> Bool
Eq, Eq FontUnderline
FontUnderline -> FontUnderline -> Bool
FontUnderline -> FontUnderline -> Ordering
FontUnderline -> FontUnderline -> FontUnderline
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 :: FontUnderline -> FontUnderline -> FontUnderline
$cmin :: FontUnderline -> FontUnderline -> FontUnderline
max :: FontUnderline -> FontUnderline -> FontUnderline
$cmax :: FontUnderline -> FontUnderline -> FontUnderline
>= :: FontUnderline -> FontUnderline -> Bool
$c>= :: FontUnderline -> FontUnderline -> Bool
> :: FontUnderline -> FontUnderline -> Bool
$c> :: FontUnderline -> FontUnderline -> Bool
<= :: FontUnderline -> FontUnderline -> Bool
$c<= :: FontUnderline -> FontUnderline -> Bool
< :: FontUnderline -> FontUnderline -> Bool
$c< :: FontUnderline -> FontUnderline -> Bool
compare :: FontUnderline -> FontUnderline -> Ordering
$ccompare :: FontUnderline -> FontUnderline -> Ordering
Ord, Int -> FontUnderline -> ShowS
[FontUnderline] -> ShowS
FontUnderline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontUnderline] -> ShowS
$cshowList :: [FontUnderline] -> ShowS
show :: FontUnderline -> String
$cshow :: FontUnderline -> String
showsPrec :: Int -> FontUnderline -> ShowS
$cshowsPrec :: Int -> FontUnderline -> ShowS
Show, forall x. Rep FontUnderline x -> FontUnderline
forall x. FontUnderline -> Rep FontUnderline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FontUnderline x -> FontUnderline
$cfrom :: forall x. FontUnderline -> Rep FontUnderline x
Generic)
instance NFData FontUnderline
data FontVerticalAlignment =
FontVerticalAlignmentBaseline
| FontVerticalAlignmentSubscript
| FontVerticalAlignmentSuperscript
deriving (FontVerticalAlignment -> FontVerticalAlignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
$c/= :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
== :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
$c== :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
Eq, Eq FontVerticalAlignment
FontVerticalAlignment -> FontVerticalAlignment -> Bool
FontVerticalAlignment -> FontVerticalAlignment -> Ordering
FontVerticalAlignment
-> FontVerticalAlignment -> FontVerticalAlignment
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 :: FontVerticalAlignment
-> FontVerticalAlignment -> FontVerticalAlignment
$cmin :: FontVerticalAlignment
-> FontVerticalAlignment -> FontVerticalAlignment
max :: FontVerticalAlignment
-> FontVerticalAlignment -> FontVerticalAlignment
$cmax :: FontVerticalAlignment
-> FontVerticalAlignment -> FontVerticalAlignment
>= :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
$c>= :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
> :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
$c> :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
<= :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
$c<= :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
< :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
$c< :: FontVerticalAlignment -> FontVerticalAlignment -> Bool
compare :: FontVerticalAlignment -> FontVerticalAlignment -> Ordering
$ccompare :: FontVerticalAlignment -> FontVerticalAlignment -> Ordering
Ord, Int -> FontVerticalAlignment -> ShowS
[FontVerticalAlignment] -> ShowS
FontVerticalAlignment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontVerticalAlignment] -> ShowS
$cshowList :: [FontVerticalAlignment] -> ShowS
show :: FontVerticalAlignment -> String
$cshow :: FontVerticalAlignment -> String
showsPrec :: Int -> FontVerticalAlignment -> ShowS
$cshowsPrec :: Int -> FontVerticalAlignment -> ShowS
Show, forall x. Rep FontVerticalAlignment x -> FontVerticalAlignment
forall x. FontVerticalAlignment -> Rep FontVerticalAlignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FontVerticalAlignment x -> FontVerticalAlignment
$cfrom :: forall x. FontVerticalAlignment -> Rep FontVerticalAlignment x
Generic)
instance NFData FontVerticalAlignment
data LineStyle =
LineStyleDashDot
| LineStyleDashDotDot
| LineStyleDashed
| LineStyleDotted
| LineStyleDouble
| LineStyleHair
| LineStyleMedium
| LineStyleMediumDashDot
| LineStyleMediumDashDotDot
| LineStyleMediumDashed
| LineStyleNone
| LineStyleSlantDashDot
| LineStyleThick
| LineStyleThin
deriving (LineStyle -> LineStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LineStyle -> LineStyle -> Bool
$c/= :: LineStyle -> LineStyle -> Bool
== :: LineStyle -> LineStyle -> Bool
$c== :: LineStyle -> LineStyle -> Bool
Eq, Eq LineStyle
LineStyle -> LineStyle -> Bool
LineStyle -> LineStyle -> Ordering
LineStyle -> LineStyle -> LineStyle
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 :: LineStyle -> LineStyle -> LineStyle
$cmin :: LineStyle -> LineStyle -> LineStyle
max :: LineStyle -> LineStyle -> LineStyle
$cmax :: LineStyle -> LineStyle -> LineStyle
>= :: LineStyle -> LineStyle -> Bool
$c>= :: LineStyle -> LineStyle -> Bool
> :: LineStyle -> LineStyle -> Bool
$c> :: LineStyle -> LineStyle -> Bool
<= :: LineStyle -> LineStyle -> Bool
$c<= :: LineStyle -> LineStyle -> Bool
< :: LineStyle -> LineStyle -> Bool
$c< :: LineStyle -> LineStyle -> Bool
compare :: LineStyle -> LineStyle -> Ordering
$ccompare :: LineStyle -> LineStyle -> Ordering
Ord, Int -> LineStyle -> ShowS
[LineStyle] -> ShowS
LineStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LineStyle] -> ShowS
$cshowList :: [LineStyle] -> ShowS
show :: LineStyle -> String
$cshow :: LineStyle -> String
showsPrec :: Int -> LineStyle -> ShowS
$cshowsPrec :: Int -> LineStyle -> ShowS
Show, forall x. Rep LineStyle x -> LineStyle
forall x. LineStyle -> Rep LineStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LineStyle x -> LineStyle
$cfrom :: forall x. LineStyle -> Rep LineStyle x
Generic)
instance NFData LineStyle
data PatternType =
PatternTypeDarkDown
| PatternTypeDarkGray
| PatternTypeDarkGrid
| PatternTypeDarkHorizontal
| PatternTypeDarkTrellis
| PatternTypeDarkUp
| PatternTypeDarkVertical
| PatternTypeGray0625
| PatternTypeGray125
| PatternTypeLightDown
| PatternTypeLightGray
| PatternTypeLightGrid
| PatternTypeLightHorizontal
| PatternTypeLightTrellis
| PatternTypeLightUp
| PatternTypeLightVertical
| PatternTypeMediumGray
| PatternTypeNone
| PatternTypeSolid
deriving (PatternType -> PatternType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PatternType -> PatternType -> Bool
$c/= :: PatternType -> PatternType -> Bool
== :: PatternType -> PatternType -> Bool
$c== :: PatternType -> PatternType -> Bool
Eq, Eq PatternType
PatternType -> PatternType -> Bool
PatternType -> PatternType -> Ordering
PatternType -> PatternType -> PatternType
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 :: PatternType -> PatternType -> PatternType
$cmin :: PatternType -> PatternType -> PatternType
max :: PatternType -> PatternType -> PatternType
$cmax :: PatternType -> PatternType -> PatternType
>= :: PatternType -> PatternType -> Bool
$c>= :: PatternType -> PatternType -> Bool
> :: PatternType -> PatternType -> Bool
$c> :: PatternType -> PatternType -> Bool
<= :: PatternType -> PatternType -> Bool
$c<= :: PatternType -> PatternType -> Bool
< :: PatternType -> PatternType -> Bool
$c< :: PatternType -> PatternType -> Bool
compare :: PatternType -> PatternType -> Ordering
$ccompare :: PatternType -> PatternType -> Ordering
Ord, Int -> PatternType -> ShowS
[PatternType] -> ShowS
PatternType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PatternType] -> ShowS
$cshowList :: [PatternType] -> ShowS
show :: PatternType -> String
$cshow :: PatternType -> String
showsPrec :: Int -> PatternType -> ShowS
$cshowsPrec :: Int -> PatternType -> ShowS
Show, forall x. Rep PatternType x -> PatternType
forall x. PatternType -> Rep PatternType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PatternType x -> PatternType
$cfrom :: forall x. PatternType -> Rep PatternType x
Generic)
instance NFData PatternType
data ReadingOrder =
ReadingOrderContextDependent
| ReadingOrderLeftToRight
| ReadingOrderRightToLeft
deriving (ReadingOrder -> ReadingOrder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadingOrder -> ReadingOrder -> Bool
$c/= :: ReadingOrder -> ReadingOrder -> Bool
== :: ReadingOrder -> ReadingOrder -> Bool
$c== :: ReadingOrder -> ReadingOrder -> Bool
Eq, Eq ReadingOrder
ReadingOrder -> ReadingOrder -> Bool
ReadingOrder -> ReadingOrder -> Ordering
ReadingOrder -> ReadingOrder -> ReadingOrder
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 :: ReadingOrder -> ReadingOrder -> ReadingOrder
$cmin :: ReadingOrder -> ReadingOrder -> ReadingOrder
max :: ReadingOrder -> ReadingOrder -> ReadingOrder
$cmax :: ReadingOrder -> ReadingOrder -> ReadingOrder
>= :: ReadingOrder -> ReadingOrder -> Bool
$c>= :: ReadingOrder -> ReadingOrder -> Bool
> :: ReadingOrder -> ReadingOrder -> Bool
$c> :: ReadingOrder -> ReadingOrder -> Bool
<= :: ReadingOrder -> ReadingOrder -> Bool
$c<= :: ReadingOrder -> ReadingOrder -> Bool
< :: ReadingOrder -> ReadingOrder -> Bool
$c< :: ReadingOrder -> ReadingOrder -> Bool
compare :: ReadingOrder -> ReadingOrder -> Ordering
$ccompare :: ReadingOrder -> ReadingOrder -> Ordering
Ord, Int -> ReadingOrder -> ShowS
[ReadingOrder] -> ShowS
ReadingOrder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadingOrder] -> ShowS
$cshowList :: [ReadingOrder] -> ShowS
show :: ReadingOrder -> String
$cshow :: ReadingOrder -> String
showsPrec :: Int -> ReadingOrder -> ShowS
$cshowsPrec :: Int -> ReadingOrder -> ShowS
Show, forall x. Rep ReadingOrder x -> ReadingOrder
forall x. ReadingOrder -> Rep ReadingOrder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReadingOrder x -> ReadingOrder
$cfrom :: forall x. ReadingOrder -> Rep ReadingOrder x
Generic)
instance NFData ReadingOrder
makeLenses ''StyleSheet
makeLenses ''CellXf
makeLenses ''Dxf
makeLenses ''Alignment
makeLenses ''Border
makeLenses ''BorderStyle
makeLenses ''Color
makeLenses ''Fill
makeLenses ''FillPattern
makeLenses ''Font
makeLenses ''Protection
minimalStyleSheet :: StyleSheet
minimalStyleSheet :: StyleSheet
minimalStyleSheet = forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Lens' StyleSheet [Border]
styleSheetBorders forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Border
defaultBorder]
forall a b. a -> (a -> b) -> b
& Lens' StyleSheet [Font]
styleSheetFonts forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Font
defaultFont]
forall a b. a -> (a -> b) -> b
& Lens' StyleSheet [Fill]
styleSheetFills forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Fill
fillNone, Fill
fillGray125]
forall a b. a -> (a -> b) -> b
& Lens' StyleSheet [CellXf]
styleSheetCellXfs forall s t a b. ASetter s t a b -> b -> s -> t
.~ [CellXf
defaultCellXf]
where
defaultBorder :: Border
defaultBorder :: Border
defaultBorder = forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Lens' Border (Maybe BorderStyle)
borderBottom forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Lens' Border (Maybe BorderStyle)
borderTop forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Lens' Border (Maybe BorderStyle)
borderLeft forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Lens' Border (Maybe BorderStyle)
borderRight forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just forall a. Default a => a
def
defaultFont :: Font
defaultFont :: Font
defaultFont = forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Lens' Font (Maybe FontFamily)
fontFamily forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just FontFamily
FontFamilySwiss
forall a b. a -> (a -> b) -> b
& Lens' Font (Maybe Double)
fontSize forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just Double
11
fillNone, fillGray125 :: Fill
fillNone :: Fill
fillNone = forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Iso' Fill (Maybe FillPattern)
fillPattern forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just (forall a. Default a => a
def forall a b. a -> (a -> b) -> b
& Lens' FillPattern (Maybe PatternType)
fillPatternType forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just PatternType
PatternTypeNone)
fillGray125 :: Fill
fillGray125 = forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Iso' Fill (Maybe FillPattern)
fillPattern forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just (forall a. Default a => a
def forall a b. a -> (a -> b) -> b
& Lens' FillPattern (Maybe PatternType)
fillPatternType forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just PatternType
PatternTypeGray125)
defaultCellXf :: CellXf
defaultCellXf :: CellXf
defaultCellXf = forall a. Default a => a
def
forall a b. a -> (a -> b) -> b
& Lens' CellXf (Maybe Int)
cellXfBorderId forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just Int
0
forall a b. a -> (a -> b) -> b
& Lens' CellXf (Maybe Int)
cellXfFillId forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just Int
0
forall a b. a -> (a -> b) -> b
& Lens' CellXf (Maybe Int)
cellXfFontId forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall a. a -> Maybe a
Just Int
0
instance Default StyleSheet where
def :: StyleSheet
def = StyleSheet {
_styleSheetBorders :: [Border]
_styleSheetBorders = []
, _styleSheetFonts :: [Font]
_styleSheetFonts = []
, _styleSheetFills :: [Fill]
_styleSheetFills = []
, _styleSheetCellXfs :: [CellXf]
_styleSheetCellXfs = []
, _styleSheetDxfs :: [Dxf]
_styleSheetDxfs = []
, _styleSheetNumFmts :: Map Int FormatCode
_styleSheetNumFmts = forall k a. Map k a
M.empty
}
instance Default CellXf where
def :: CellXf
def = CellXf {
_cellXfApplyAlignment :: Maybe Bool
_cellXfApplyAlignment = forall a. Maybe a
Nothing
, _cellXfApplyBorder :: Maybe Bool
_cellXfApplyBorder = forall a. Maybe a
Nothing
, _cellXfApplyFill :: Maybe Bool
_cellXfApplyFill = forall a. Maybe a
Nothing
, _cellXfApplyFont :: Maybe Bool
_cellXfApplyFont = forall a. Maybe a
Nothing
, _cellXfApplyNumberFormat :: Maybe Bool
_cellXfApplyNumberFormat = forall a. Maybe a
Nothing
, _cellXfApplyProtection :: Maybe Bool
_cellXfApplyProtection = forall a. Maybe a
Nothing
, _cellXfBorderId :: Maybe Int
_cellXfBorderId = forall a. Maybe a
Nothing
, _cellXfFillId :: Maybe Int
_cellXfFillId = forall a. Maybe a
Nothing
, _cellXfFontId :: Maybe Int
_cellXfFontId = forall a. Maybe a
Nothing
, _cellXfNumFmtId :: Maybe Int
_cellXfNumFmtId = forall a. Maybe a
Nothing
, _cellXfPivotButton :: Maybe Bool
_cellXfPivotButton = forall a. Maybe a
Nothing
, _cellXfQuotePrefix :: Maybe Bool
_cellXfQuotePrefix = forall a. Maybe a
Nothing
, _cellXfId :: Maybe Int
_cellXfId = forall a. Maybe a
Nothing
, _cellXfAlignment :: Maybe Alignment
_cellXfAlignment = forall a. Maybe a
Nothing
, _cellXfProtection :: Maybe Protection
_cellXfProtection = forall a. Maybe a
Nothing
}
instance Default Dxf where
def :: Dxf
def = Dxf
{ _dxfFont :: Maybe Font
_dxfFont = forall a. Maybe a
Nothing
, _dxfNumFmt :: Maybe NumFmt
_dxfNumFmt = forall a. Maybe a
Nothing
, _dxfFill :: Maybe Fill
_dxfFill = forall a. Maybe a
Nothing
, _dxfAlignment :: Maybe Alignment
_dxfAlignment = forall a. Maybe a
Nothing
, _dxfBorder :: Maybe Border
_dxfBorder = forall a. Maybe a
Nothing
, _dxfProtection :: Maybe Protection
_dxfProtection = forall a. Maybe a
Nothing
}
instance Default Alignment where
def :: Alignment
def = Alignment {
_alignmentHorizontal :: Maybe CellHorizontalAlignment
_alignmentHorizontal = forall a. Maybe a
Nothing
, _alignmentIndent :: Maybe Int
_alignmentIndent = forall a. Maybe a
Nothing
, _alignmentJustifyLastLine :: Maybe Bool
_alignmentJustifyLastLine = forall a. Maybe a
Nothing
, _alignmentReadingOrder :: Maybe ReadingOrder
_alignmentReadingOrder = forall a. Maybe a
Nothing
, _alignmentRelativeIndent :: Maybe Int
_alignmentRelativeIndent = forall a. Maybe a
Nothing
, _alignmentShrinkToFit :: Maybe Bool
_alignmentShrinkToFit = forall a. Maybe a
Nothing
, _alignmentTextRotation :: Maybe Int
_alignmentTextRotation = forall a. Maybe a
Nothing
, _alignmentVertical :: Maybe CellVerticalAlignment
_alignmentVertical = forall a. Maybe a
Nothing
, _alignmentWrapText :: Maybe Bool
_alignmentWrapText = forall a. Maybe a
Nothing
}
instance Default Border where
def :: Border
def = Border {
_borderDiagonalDown :: Maybe Bool
_borderDiagonalDown = forall a. Maybe a
Nothing
, _borderDiagonalUp :: Maybe Bool
_borderDiagonalUp = forall a. Maybe a
Nothing
, _borderOutline :: Maybe Bool
_borderOutline = forall a. Maybe a
Nothing
, _borderBottom :: Maybe BorderStyle
_borderBottom = forall a. Maybe a
Nothing
, _borderDiagonal :: Maybe BorderStyle
_borderDiagonal = forall a. Maybe a
Nothing
, _borderEnd :: Maybe BorderStyle
_borderEnd = forall a. Maybe a
Nothing
, _borderHorizontal :: Maybe BorderStyle
_borderHorizontal = forall a. Maybe a
Nothing
, _borderStart :: Maybe BorderStyle
_borderStart = forall a. Maybe a
Nothing
, _borderTop :: Maybe BorderStyle
_borderTop = forall a. Maybe a
Nothing
, _borderVertical :: Maybe BorderStyle
_borderVertical = forall a. Maybe a
Nothing
, _borderLeft :: Maybe BorderStyle
_borderLeft = forall a. Maybe a
Nothing
, _borderRight :: Maybe BorderStyle
_borderRight = forall a. Maybe a
Nothing
}
instance Default BorderStyle where
def :: BorderStyle
def = BorderStyle {
_borderStyleColor :: Maybe Color
_borderStyleColor = forall a. Maybe a
Nothing
, _borderStyleLine :: Maybe LineStyle
_borderStyleLine = forall a. Maybe a
Nothing
}
instance Default Color where
def :: Color
def = Color {
_colorAutomatic :: Maybe Bool
_colorAutomatic = forall a. Maybe a
Nothing
, _colorARGB :: Maybe FormatCode
_colorARGB = forall a. Maybe a
Nothing
, _colorTheme :: Maybe Int
_colorTheme = forall a. Maybe a
Nothing
, _colorTint :: Maybe Double
_colorTint = forall a. Maybe a
Nothing
}
instance Default Fill where
def :: Fill
def = Fill {
_fillPattern :: Maybe FillPattern
_fillPattern = forall a. Maybe a
Nothing
}
instance Default FillPattern where
def :: FillPattern
def = FillPattern {
_fillPatternBgColor :: Maybe Color
_fillPatternBgColor = forall a. Maybe a
Nothing
, _fillPatternFgColor :: Maybe Color
_fillPatternFgColor = forall a. Maybe a
Nothing
, _fillPatternType :: Maybe PatternType
_fillPatternType = forall a. Maybe a
Nothing
}
instance Default Font where
def :: Font
def = Font {
_fontBold :: Maybe Bool
_fontBold = forall a. Maybe a
Nothing
, _fontCharset :: Maybe Int
_fontCharset = forall a. Maybe a
Nothing
, _fontColor :: Maybe Color
_fontColor = forall a. Maybe a
Nothing
, _fontCondense :: Maybe Bool
_fontCondense = forall a. Maybe a
Nothing
, _fontExtend :: Maybe Bool
_fontExtend = forall a. Maybe a
Nothing
, _fontFamily :: Maybe FontFamily
_fontFamily = forall a. Maybe a
Nothing
, _fontItalic :: Maybe Bool
_fontItalic = forall a. Maybe a
Nothing
, _fontName :: Maybe FormatCode
_fontName = forall a. Maybe a
Nothing
, _fontOutline :: Maybe Bool
_fontOutline = forall a. Maybe a
Nothing
, _fontScheme :: Maybe FontScheme
_fontScheme = forall a. Maybe a
Nothing
, _fontShadow :: Maybe Bool
_fontShadow = forall a. Maybe a
Nothing
, _fontStrikeThrough :: Maybe Bool
_fontStrikeThrough = forall a. Maybe a
Nothing
, _fontSize :: Maybe Double
_fontSize = forall a. Maybe a
Nothing
, _fontUnderline :: Maybe FontUnderline
_fontUnderline = forall a. Maybe a
Nothing
, _fontVertAlign :: Maybe FontVerticalAlignment
_fontVertAlign = forall a. Maybe a
Nothing
}
instance Default Protection where
def :: Protection
def = Protection {
_protectionHidden :: Maybe Bool
_protectionHidden = forall a. Maybe a
Nothing
, _protectionLocked :: Maybe Bool
_protectionLocked = forall a. Maybe a
Nothing
}
instance ToDocument StyleSheet where
toDocument :: StyleSheet -> Document
toDocument = FormatCode -> Element -> Document
documentFromElement FormatCode
"Stylesheet generated by xlsx"
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToElement a => Name -> a -> Element
toElement Name
"styleSheet"
instance ToElement StyleSheet where
toElement :: Name -> StyleSheet -> Element
toElement Name
nm StyleSheet{[Dxf]
[Font]
[Fill]
[Border]
[CellXf]
Map Int FormatCode
_styleSheetNumFmts :: Map Int FormatCode
_styleSheetDxfs :: [Dxf]
_styleSheetFonts :: [Font]
_styleSheetFills :: [Fill]
_styleSheetCellXfs :: [CellXf]
_styleSheetBorders :: [Border]
_styleSheetNumFmts :: StyleSheet -> Map Int FormatCode
_styleSheetDxfs :: StyleSheet -> [Dxf]
_styleSheetFonts :: StyleSheet -> [Font]
_styleSheetFills :: StyleSheet -> [Fill]
_styleSheetCellXfs :: StyleSheet -> [CellXf]
_styleSheetBorders :: StyleSheet -> [Border]
..} = Name -> [Element] -> Element
elementListSimple Name
nm [Element]
elements
where
countedElementList' :: Name -> [Element] -> [Element]
countedElementList' Name
nm' [Element]
xs = forall a. Maybe a -> [a]
maybeToList forall a b. (a -> b) -> a -> b
$ Name -> [Element] -> Maybe Element
nonEmptyCountedElementList Name
nm' [Element]
xs
elements :: [Element]
elements = Name -> [Element] -> [Element]
countedElementList' Name
"numFmts" (forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"numFmt") [NumFmt]
numFmts) forall a. [a] -> [a] -> [a]
++
Name -> [Element] -> [Element]
countedElementList' Name
"fonts" (forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"font") [Font]
_styleSheetFonts) forall a. [a] -> [a] -> [a]
++
Name -> [Element] -> [Element]
countedElementList' Name
"fills" (forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"fill") [Fill]
_styleSheetFills) forall a. [a] -> [a] -> [a]
++
Name -> [Element] -> [Element]
countedElementList' Name
"borders" (forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"border") [Border]
_styleSheetBorders) forall a. [a] -> [a] -> [a]
++
Name -> [Element] -> [Element]
countedElementList' Name
"cellXfs" (forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"xf") [CellXf]
_styleSheetCellXfs) forall a. [a] -> [a] -> [a]
++
Name -> [Element] -> [Element]
countedElementList' Name
"dxfs" (forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"dxf") [Dxf]
_styleSheetDxfs)
numFmts :: [NumFmt]
numFmts = forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> FormatCode -> NumFmt
NumFmt) forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
M.toList Map Int FormatCode
_styleSheetNumFmts
instance ToElement CellXf where
toElement :: Name -> CellXf -> Element
toElement Name
nm CellXf{Maybe Bool
Maybe Int
Maybe Protection
Maybe Alignment
_cellXfProtection :: Maybe Protection
_cellXfAlignment :: Maybe Alignment
_cellXfId :: Maybe Int
_cellXfQuotePrefix :: Maybe Bool
_cellXfPivotButton :: Maybe Bool
_cellXfNumFmtId :: Maybe Int
_cellXfFontId :: Maybe Int
_cellXfFillId :: Maybe Int
_cellXfBorderId :: Maybe Int
_cellXfApplyProtection :: Maybe Bool
_cellXfApplyNumberFormat :: Maybe Bool
_cellXfApplyFont :: Maybe Bool
_cellXfApplyFill :: Maybe Bool
_cellXfApplyBorder :: Maybe Bool
_cellXfApplyAlignment :: Maybe Bool
_cellXfProtection :: CellXf -> Maybe Protection
_cellXfAlignment :: CellXf -> Maybe Alignment
_cellXfId :: CellXf -> Maybe Int
_cellXfQuotePrefix :: CellXf -> Maybe Bool
_cellXfPivotButton :: CellXf -> Maybe Bool
_cellXfNumFmtId :: CellXf -> Maybe Int
_cellXfFontId :: CellXf -> Maybe Int
_cellXfFillId :: CellXf -> Maybe Int
_cellXfBorderId :: CellXf -> Maybe Int
_cellXfApplyProtection :: CellXf -> Maybe Bool
_cellXfApplyNumberFormat :: CellXf -> Maybe Bool
_cellXfApplyFont :: CellXf -> Maybe Bool
_cellXfApplyFill :: CellXf -> Maybe Bool
_cellXfApplyBorder :: CellXf -> Maybe Bool
_cellXfApplyAlignment :: CellXf -> Maybe Bool
..} = Element {
elementName :: Name
elementName = Name
nm
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement 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. ToElement a => Name -> a -> Element
toElement Name
"alignment" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Alignment
_cellXfAlignment
, forall a. ToElement a => Name -> a -> Element
toElement Name
"protection" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Protection
_cellXfProtection
]
, elementAttributes :: Map Name FormatCode
elementAttributes = 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
$ [
Name
"numFmtId" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_cellXfNumFmtId
, Name
"fontId" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_cellXfFontId
, Name
"fillId" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_cellXfFillId
, Name
"borderId" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_cellXfBorderId
, Name
"xfId" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_cellXfId
, Name
"quotePrefix" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfQuotePrefix
, Name
"pivotButton" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfPivotButton
, Name
"applyNumberFormat" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfApplyNumberFormat
, Name
"applyFont" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfApplyFont
, Name
"applyFill" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfApplyFill
, Name
"applyBorder" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfApplyBorder
, Name
"applyAlignment" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfApplyAlignment
, Name
"applyProtection" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_cellXfApplyProtection
]
}
instance ToElement Dxf where
toElement :: Name -> Dxf -> Element
toElement Name
nm Dxf{Maybe Protection
Maybe NumFmt
Maybe Font
Maybe Fill
Maybe Border
Maybe Alignment
_dxfProtection :: Maybe Protection
_dxfBorder :: Maybe Border
_dxfAlignment :: Maybe Alignment
_dxfFill :: Maybe Fill
_dxfNumFmt :: Maybe NumFmt
_dxfFont :: Maybe Font
_dxfProtection :: Dxf -> Maybe Protection
_dxfBorder :: Dxf -> Maybe Border
_dxfAlignment :: Dxf -> Maybe Alignment
_dxfFill :: Dxf -> Maybe Fill
_dxfNumFmt :: Dxf -> Maybe NumFmt
_dxfFont :: Dxf -> Maybe Font
..} = Element
{ elementName :: Name
elementName = Name
nm
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement forall a b. (a -> b) -> a -> b
$
forall a. [Maybe a] -> [a]
catMaybes [ forall a. ToElement a => Name -> a -> Element
toElement Name
"font" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Font
_dxfFont
, forall a. ToElement a => Name -> a -> Element
toElement Name
"numFmt" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe NumFmt
_dxfNumFmt
, forall a. ToElement a => Name -> a -> Element
toElement Name
"fill" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Fill
_dxfFill
, forall a. ToElement a => Name -> a -> Element
toElement Name
"alignment" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Alignment
_dxfAlignment
, forall a. ToElement a => Name -> a -> Element
toElement Name
"border" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Border
_dxfBorder
, forall a. ToElement a => Name -> a -> Element
toElement Name
"protection" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Protection
_dxfProtection
]
, elementAttributes :: Map Name FormatCode
elementAttributes = forall k a. Map k a
M.empty
}
instance ToElement Alignment where
toElement :: Name -> Alignment -> Element
toElement Name
nm Alignment{Maybe Bool
Maybe Int
Maybe ReadingOrder
Maybe CellVerticalAlignment
Maybe CellHorizontalAlignment
_alignmentWrapText :: Maybe Bool
_alignmentVertical :: Maybe CellVerticalAlignment
_alignmentTextRotation :: Maybe Int
_alignmentShrinkToFit :: Maybe Bool
_alignmentRelativeIndent :: Maybe Int
_alignmentReadingOrder :: Maybe ReadingOrder
_alignmentJustifyLastLine :: Maybe Bool
_alignmentIndent :: Maybe Int
_alignmentHorizontal :: Maybe CellHorizontalAlignment
_alignmentWrapText :: Alignment -> Maybe Bool
_alignmentVertical :: Alignment -> Maybe CellVerticalAlignment
_alignmentTextRotation :: Alignment -> Maybe Int
_alignmentShrinkToFit :: Alignment -> Maybe Bool
_alignmentRelativeIndent :: Alignment -> Maybe Int
_alignmentReadingOrder :: Alignment -> Maybe ReadingOrder
_alignmentJustifyLastLine :: Alignment -> Maybe Bool
_alignmentIndent :: Alignment -> Maybe Int
_alignmentHorizontal :: Alignment -> Maybe CellHorizontalAlignment
..} = Element {
elementName :: Name
elementName = Name
nm
, elementNodes :: [Node]
elementNodes = []
, elementAttributes :: Map Name FormatCode
elementAttributes = 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
$ [
Name
"horizontal" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe CellHorizontalAlignment
_alignmentHorizontal
, Name
"vertical" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe CellVerticalAlignment
_alignmentVertical
, Name
"textRotation" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_alignmentTextRotation
, Name
"wrapText" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_alignmentWrapText
, Name
"relativeIndent" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_alignmentRelativeIndent
, Name
"indent" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_alignmentIndent
, Name
"justifyLastLine" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_alignmentJustifyLastLine
, Name
"shrinkToFit" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_alignmentShrinkToFit
, Name
"readingOrder" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe ReadingOrder
_alignmentReadingOrder
]
}
instance ToElement Border where
toElement :: Name -> Border -> Element
toElement Name
nm Border{Maybe Bool
Maybe BorderStyle
_borderVertical :: Maybe BorderStyle
_borderTop :: Maybe BorderStyle
_borderStart :: Maybe BorderStyle
_borderRight :: Maybe BorderStyle
_borderLeft :: Maybe BorderStyle
_borderHorizontal :: Maybe BorderStyle
_borderEnd :: Maybe BorderStyle
_borderDiagonal :: Maybe BorderStyle
_borderBottom :: Maybe BorderStyle
_borderOutline :: Maybe Bool
_borderDiagonalUp :: Maybe Bool
_borderDiagonalDown :: Maybe Bool
_borderVertical :: Border -> Maybe BorderStyle
_borderTop :: Border -> Maybe BorderStyle
_borderStart :: Border -> Maybe BorderStyle
_borderRight :: Border -> Maybe BorderStyle
_borderLeft :: Border -> Maybe BorderStyle
_borderHorizontal :: Border -> Maybe BorderStyle
_borderEnd :: Border -> Maybe BorderStyle
_borderDiagonal :: Border -> Maybe BorderStyle
_borderBottom :: Border -> Maybe BorderStyle
_borderOutline :: Border -> Maybe Bool
_borderDiagonalUp :: Border -> Maybe Bool
_borderDiagonalDown :: Border -> Maybe Bool
..} = Element {
elementName :: Name
elementName = Name
nm
, elementAttributes :: Map Name FormatCode
elementAttributes = 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
$ [
Name
"diagonalUp" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_borderDiagonalUp
, Name
"diagonalDown" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_borderDiagonalDown
, Name
"outline" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_borderOutline
]
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement 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. ToElement a => Name -> a -> Element
toElement Name
"start" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderStart
, forall a. ToElement a => Name -> a -> Element
toElement Name
"end" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderEnd
, forall a. ToElement a => Name -> a -> Element
toElement Name
"left" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderLeft
, forall a. ToElement a => Name -> a -> Element
toElement Name
"right" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderRight
, forall a. ToElement a => Name -> a -> Element
toElement Name
"top" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderTop
, forall a. ToElement a => Name -> a -> Element
toElement Name
"bottom" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderBottom
, forall a. ToElement a => Name -> a -> Element
toElement Name
"diagonal" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderDiagonal
, forall a. ToElement a => Name -> a -> Element
toElement Name
"vertical" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderVertical
, forall a. ToElement a => Name -> a -> Element
toElement Name
"horizontal" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe BorderStyle
_borderHorizontal
]
}
instance ToElement BorderStyle where
toElement :: Name -> BorderStyle -> Element
toElement Name
nm BorderStyle{Maybe LineStyle
Maybe Color
_borderStyleLine :: Maybe LineStyle
_borderStyleColor :: Maybe Color
_borderStyleLine :: BorderStyle -> Maybe LineStyle
_borderStyleColor :: BorderStyle -> Maybe Color
..} = Element {
elementName :: Name
elementName = Name
nm
, elementAttributes :: Map Name FormatCode
elementAttributes = 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
$ [
Name
"style" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe LineStyle
_borderStyleLine
]
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement 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. ToElement a => Name -> a -> Element
toElement Name
"color" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Color
_borderStyleColor
]
}
instance ToElement Color where
toElement :: Name -> Color -> Element
toElement Name
nm Color{Maybe Bool
Maybe Double
Maybe Int
Maybe FormatCode
_colorTint :: Maybe Double
_colorTheme :: Maybe Int
_colorARGB :: Maybe FormatCode
_colorAutomatic :: Maybe Bool
_colorTint :: Color -> Maybe Double
_colorTheme :: Color -> Maybe Int
_colorARGB :: Color -> Maybe FormatCode
_colorAutomatic :: Color -> Maybe Bool
..} = Element {
elementName :: Name
elementName = Name
nm
, elementNodes :: [Node]
elementNodes = []
, elementAttributes :: Map Name FormatCode
elementAttributes = 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
$ [
Name
"auto" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_colorAutomatic
, Name
"rgb" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe FormatCode
_colorARGB
, Name
"theme" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Int
_colorTheme
, Name
"tint" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Double
_colorTint
]
}
instance ToElement Fill where
toElement :: Name -> Fill -> Element
toElement Name
nm Fill{Maybe FillPattern
_fillPattern :: Maybe FillPattern
_fillPattern :: Fill -> Maybe FillPattern
..} = Element {
elementName :: Name
elementName = Name
nm
, elementAttributes :: Map Name FormatCode
elementAttributes = forall k a. Map k a
M.empty
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement 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. ToElement a => Name -> a -> Element
toElement Name
"patternFill" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FillPattern
_fillPattern
]
}
instance ToElement FillPattern where
toElement :: Name -> FillPattern -> Element
toElement Name
nm FillPattern{Maybe PatternType
Maybe Color
_fillPatternType :: Maybe PatternType
_fillPatternFgColor :: Maybe Color
_fillPatternBgColor :: Maybe Color
_fillPatternType :: FillPattern -> Maybe PatternType
_fillPatternFgColor :: FillPattern -> Maybe Color
_fillPatternBgColor :: FillPattern -> Maybe Color
..} = Element {
elementName :: Name
elementName = Name
nm
, elementAttributes :: Map Name FormatCode
elementAttributes = 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
$ [
Name
"patternType" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe PatternType
_fillPatternType
]
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement 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. ToElement a => Name -> a -> Element
toElement Name
"fgColor" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Color
_fillPatternFgColor
, forall a. ToElement a => Name -> a -> Element
toElement Name
"bgColor" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Color
_fillPatternBgColor
]
}
instance ToElement Font where
toElement :: Name -> Font -> Element
toElement Name
nm Font{Maybe Bool
Maybe Double
Maybe Int
Maybe FormatCode
Maybe FontVerticalAlignment
Maybe FontUnderline
Maybe FontScheme
Maybe FontFamily
Maybe Color
_fontVertAlign :: Maybe FontVerticalAlignment
_fontUnderline :: Maybe FontUnderline
_fontSize :: Maybe Double
_fontStrikeThrough :: Maybe Bool
_fontShadow :: Maybe Bool
_fontScheme :: Maybe FontScheme
_fontOutline :: Maybe Bool
_fontName :: Maybe FormatCode
_fontItalic :: Maybe Bool
_fontFamily :: Maybe FontFamily
_fontExtend :: Maybe Bool
_fontCondense :: Maybe Bool
_fontColor :: Maybe Color
_fontCharset :: Maybe Int
_fontBold :: Maybe Bool
_fontVertAlign :: Font -> Maybe FontVerticalAlignment
_fontUnderline :: Font -> Maybe FontUnderline
_fontSize :: Font -> Maybe Double
_fontStrikeThrough :: Font -> Maybe Bool
_fontShadow :: Font -> Maybe Bool
_fontScheme :: Font -> Maybe FontScheme
_fontOutline :: Font -> Maybe Bool
_fontName :: Font -> Maybe FormatCode
_fontItalic :: Font -> Maybe Bool
_fontFamily :: Font -> Maybe FontFamily
_fontExtend :: Font -> Maybe Bool
_fontCondense :: Font -> Maybe Bool
_fontColor :: Font -> Maybe Color
_fontCharset :: Font -> Maybe Int
_fontBold :: Font -> Maybe Bool
..} = Element {
elementName :: Name
elementName = Name
nm
, elementAttributes :: Map Name FormatCode
elementAttributes = forall k a. Map k a
M.empty
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement 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. ToAttrVal a => Name -> a -> Element
elementValue Name
"name" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FormatCode
_fontName
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"charset" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
_fontCharset
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"family" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FontFamily
_fontFamily
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"b" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bool
_fontBold
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"i" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bool
_fontItalic
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"strike" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bool
_fontStrikeThrough
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"outline" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bool
_fontOutline
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"shadow" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bool
_fontShadow
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"condense" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bool
_fontCondense
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"extend" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Bool
_fontExtend
, forall a. ToElement a => Name -> a -> Element
toElement Name
"color" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Color
_fontColor
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"sz" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Double
_fontSize
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"u" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FontUnderline
_fontUnderline
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"vertAlign" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FontVerticalAlignment
_fontVertAlign
, forall a. ToAttrVal a => Name -> a -> Element
elementValue Name
"scheme" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FontScheme
_fontScheme
]
}
instance ToElement NumFmt where
toElement :: Name -> NumFmt -> Element
toElement Name
nm (NumFmt {Int
FormatCode
_numFmtCode :: FormatCode
_numFmtId :: Int
_numFmtCode :: NumFmt -> FormatCode
_numFmtId :: NumFmt -> Int
..}) =
Name -> [(Name, FormatCode)] -> Element
leafElement Name
nm
[ Name
"numFmtId" forall a. ToAttrVal a => Name -> a -> (Name, FormatCode)
.= forall a. ToAttrVal a => a -> FormatCode
toAttrVal Int
_numFmtId
, Name
"formatCode" forall a. ToAttrVal a => Name -> a -> (Name, FormatCode)
.= forall a. ToAttrVal a => a -> FormatCode
toAttrVal FormatCode
_numFmtCode
]
instance ToElement Protection where
toElement :: Name -> Protection -> Element
toElement Name
nm Protection{Maybe Bool
_protectionLocked :: Maybe Bool
_protectionHidden :: Maybe Bool
_protectionLocked :: Protection -> Maybe Bool
_protectionHidden :: Protection -> Maybe Bool
..} = Element {
elementName :: Name
elementName = Name
nm
, elementNodes :: [Node]
elementNodes = []
, elementAttributes :: Map Name FormatCode
elementAttributes = 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
$ [
Name
"locked" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_protectionLocked
, Name
"hidden" forall a.
ToAttrVal a =>
Name -> Maybe a -> Maybe (Name, FormatCode)
.=? Maybe Bool
_protectionHidden
]
}
instance ToAttrVal CellHorizontalAlignment where
toAttrVal :: CellHorizontalAlignment -> FormatCode
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentCenter = FormatCode
"center"
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentCenterContinuous = FormatCode
"centerContinuous"
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentDistributed = FormatCode
"distributed"
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentFill = FormatCode
"fill"
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentGeneral = FormatCode
"general"
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentJustify = FormatCode
"justify"
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentLeft = FormatCode
"left"
toAttrVal CellHorizontalAlignment
CellHorizontalAlignmentRight = FormatCode
"right"
instance ToAttrVal CellVerticalAlignment where
toAttrVal :: CellVerticalAlignment -> FormatCode
toAttrVal CellVerticalAlignment
CellVerticalAlignmentBottom = FormatCode
"bottom"
toAttrVal CellVerticalAlignment
CellVerticalAlignmentCenter = FormatCode
"center"
toAttrVal CellVerticalAlignment
CellVerticalAlignmentDistributed = FormatCode
"distributed"
toAttrVal CellVerticalAlignment
CellVerticalAlignmentJustify = FormatCode
"justify"
toAttrVal CellVerticalAlignment
CellVerticalAlignmentTop = FormatCode
"top"
instance ToAttrVal FontFamily where
toAttrVal :: FontFamily -> FormatCode
toAttrVal FontFamily
FontFamilyNotApplicable = FormatCode
"0"
toAttrVal FontFamily
FontFamilyRoman = FormatCode
"1"
toAttrVal FontFamily
FontFamilySwiss = FormatCode
"2"
toAttrVal FontFamily
FontFamilyModern = FormatCode
"3"
toAttrVal FontFamily
FontFamilyScript = FormatCode
"4"
toAttrVal FontFamily
FontFamilyDecorative = FormatCode
"5"
instance ToAttrVal FontScheme where
toAttrVal :: FontScheme -> FormatCode
toAttrVal FontScheme
FontSchemeMajor = FormatCode
"major"
toAttrVal FontScheme
FontSchemeMinor = FormatCode
"minor"
toAttrVal FontScheme
FontSchemeNone = FormatCode
"none"
instance ToAttrVal FontUnderline where
toAttrVal :: FontUnderline -> FormatCode
toAttrVal FontUnderline
FontUnderlineSingle = FormatCode
"single"
toAttrVal FontUnderline
FontUnderlineDouble = FormatCode
"double"
toAttrVal FontUnderline
FontUnderlineSingleAccounting = FormatCode
"singleAccounting"
toAttrVal FontUnderline
FontUnderlineDoubleAccounting = FormatCode
"doubleAccounting"
toAttrVal FontUnderline
FontUnderlineNone = FormatCode
"none"
instance ToAttrVal FontVerticalAlignment where
toAttrVal :: FontVerticalAlignment -> FormatCode
toAttrVal FontVerticalAlignment
FontVerticalAlignmentBaseline = FormatCode
"baseline"
toAttrVal FontVerticalAlignment
FontVerticalAlignmentSubscript = FormatCode
"subscript"
toAttrVal FontVerticalAlignment
FontVerticalAlignmentSuperscript = FormatCode
"superscript"
instance ToAttrVal LineStyle where
toAttrVal :: LineStyle -> FormatCode
toAttrVal LineStyle
LineStyleDashDot = FormatCode
"dashDot"
toAttrVal LineStyle
LineStyleDashDotDot = FormatCode
"dashDotDot"
toAttrVal LineStyle
LineStyleDashed = FormatCode
"dashed"
toAttrVal LineStyle
LineStyleDotted = FormatCode
"dotted"
toAttrVal LineStyle
LineStyleDouble = FormatCode
"double"
toAttrVal LineStyle
LineStyleHair = FormatCode
"hair"
toAttrVal LineStyle
LineStyleMedium = FormatCode
"medium"
toAttrVal LineStyle
LineStyleMediumDashDot = FormatCode
"mediumDashDot"
toAttrVal LineStyle
LineStyleMediumDashDotDot = FormatCode
"mediumDashDotDot"
toAttrVal LineStyle
LineStyleMediumDashed = FormatCode
"mediumDashed"
toAttrVal LineStyle
LineStyleNone = FormatCode
"none"
toAttrVal LineStyle
LineStyleSlantDashDot = FormatCode
"slantDashDot"
toAttrVal LineStyle
LineStyleThick = FormatCode
"thick"
toAttrVal LineStyle
LineStyleThin = FormatCode
"thin"
instance ToAttrVal PatternType where
toAttrVal :: PatternType -> FormatCode
toAttrVal PatternType
PatternTypeDarkDown = FormatCode
"darkDown"
toAttrVal PatternType
PatternTypeDarkGray = FormatCode
"darkGray"
toAttrVal PatternType
PatternTypeDarkGrid = FormatCode
"darkGrid"
toAttrVal PatternType
PatternTypeDarkHorizontal = FormatCode
"darkHorizontal"
toAttrVal PatternType
PatternTypeDarkTrellis = FormatCode
"darkTrellis"
toAttrVal PatternType
PatternTypeDarkUp = FormatCode
"darkUp"
toAttrVal PatternType
PatternTypeDarkVertical = FormatCode
"darkVertical"
toAttrVal PatternType
PatternTypeGray0625 = FormatCode
"gray0625"
toAttrVal PatternType
PatternTypeGray125 = FormatCode
"gray125"
toAttrVal PatternType
PatternTypeLightDown = FormatCode
"lightDown"
toAttrVal PatternType
PatternTypeLightGray = FormatCode
"lightGray"
toAttrVal PatternType
PatternTypeLightGrid = FormatCode
"lightGrid"
toAttrVal PatternType
PatternTypeLightHorizontal = FormatCode
"lightHorizontal"
toAttrVal PatternType
PatternTypeLightTrellis = FormatCode
"lightTrellis"
toAttrVal PatternType
PatternTypeLightUp = FormatCode
"lightUp"
toAttrVal PatternType
PatternTypeLightVertical = FormatCode
"lightVertical"
toAttrVal PatternType
PatternTypeMediumGray = FormatCode
"mediumGray"
toAttrVal PatternType
PatternTypeNone = FormatCode
"none"
toAttrVal PatternType
PatternTypeSolid = FormatCode
"solid"
instance ToAttrVal ReadingOrder where
toAttrVal :: ReadingOrder -> FormatCode
toAttrVal ReadingOrder
ReadingOrderContextDependent = FormatCode
"0"
toAttrVal ReadingOrder
ReadingOrderLeftToRight = FormatCode
"1"
toAttrVal ReadingOrder
ReadingOrderRightToLeft = FormatCode
"2"
instance FromCursor StyleSheet where
fromCursor :: Cursor -> [StyleSheet]
fromCursor Cursor
cur = do
let
_styleSheetFonts :: [Font]
_styleSheetFonts = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"fonts") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"font") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
_styleSheetFills :: [Fill]
_styleSheetFills = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"fills") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"fill") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
_styleSheetBorders :: [Border]
_styleSheetBorders = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"borders") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"border") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
_styleSheetCellXfs :: [CellXf]
_styleSheetCellXfs = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"cellXfs") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"xf") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
_styleSheetDxfs :: [Dxf]
_styleSheetDxfs = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"dxfs") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"dxf") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
_styleSheetNumFmts :: Map Int FormatCode
_styleSheetNumFmts = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map NumFmt -> (Int, FormatCode)
mkNumFmtPair forall a b. (a -> b) -> a -> b
$
Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"numFmts")forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (FormatCode -> Name
n_ FormatCode
"numFmt") 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 StyleSheet{[Dxf]
[Font]
[Fill]
[Border]
[CellXf]
Map Int FormatCode
_styleSheetNumFmts :: Map Int FormatCode
_styleSheetDxfs :: [Dxf]
_styleSheetCellXfs :: [CellXf]
_styleSheetBorders :: [Border]
_styleSheetFills :: [Fill]
_styleSheetFonts :: [Font]
_styleSheetNumFmts :: Map Int FormatCode
_styleSheetDxfs :: [Dxf]
_styleSheetFonts :: [Font]
_styleSheetFills :: [Fill]
_styleSheetCellXfs :: [CellXf]
_styleSheetBorders :: [Border]
..}
instance FromCursor Font where
fromCursor :: Cursor -> [Font]
fromCursor Cursor
cur = do
Maybe FormatCode
_fontName <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeElementValue (FormatCode -> Name
n_ FormatCode
"name") Cursor
cur
Maybe Int
_fontCharset <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeElementValue (FormatCode -> Name
n_ FormatCode
"charset") Cursor
cur
Maybe FontFamily
_fontFamily <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeElementValue (FormatCode -> Name
n_ FormatCode
"family") Cursor
cur
Maybe Bool
_fontBold <- Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue (FormatCode -> Name
n_ FormatCode
"b") Cursor
cur
Maybe Bool
_fontItalic <- Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue (FormatCode -> Name
n_ FormatCode
"i") Cursor
cur
Maybe Bool
_fontStrikeThrough<- Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue (FormatCode -> Name
n_ FormatCode
"strike") Cursor
cur
Maybe Bool
_fontOutline <- Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue (FormatCode -> Name
n_ FormatCode
"outline") Cursor
cur
Maybe Bool
_fontShadow <- Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue (FormatCode -> Name
n_ FormatCode
"shadow") Cursor
cur
Maybe Bool
_fontCondense <- Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue (FormatCode -> Name
n_ FormatCode
"condense") Cursor
cur
Maybe Bool
_fontExtend <- Name -> Cursor -> [Maybe Bool]
maybeBoolElementValue (FormatCode -> Name
n_ FormatCode
"extend") Cursor
cur
Maybe Color
_fontColor <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"color") Cursor
cur
Maybe Double
_fontSize <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeElementValue (FormatCode -> Name
n_ FormatCode
"sz") Cursor
cur
Maybe FontUnderline
_fontUnderline <- forall a. FromAttrVal a => Name -> a -> Cursor -> [Maybe a]
maybeElementValueDef (FormatCode -> Name
n_ FormatCode
"u") FontUnderline
FontUnderlineSingle Cursor
cur
Maybe FontVerticalAlignment
_fontVertAlign <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeElementValue (FormatCode -> Name
n_ FormatCode
"vertAlign") Cursor
cur
Maybe FontScheme
_fontScheme <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeElementValue (FormatCode -> Name
n_ FormatCode
"scheme") Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Font{Maybe Bool
Maybe Double
Maybe Int
Maybe FormatCode
Maybe FontVerticalAlignment
Maybe FontUnderline
Maybe FontScheme
Maybe FontFamily
Maybe Color
_fontScheme :: Maybe FontScheme
_fontVertAlign :: Maybe FontVerticalAlignment
_fontUnderline :: Maybe FontUnderline
_fontSize :: Maybe Double
_fontColor :: Maybe Color
_fontExtend :: Maybe Bool
_fontCondense :: Maybe Bool
_fontShadow :: Maybe Bool
_fontOutline :: Maybe Bool
_fontStrikeThrough :: Maybe Bool
_fontItalic :: Maybe Bool
_fontBold :: Maybe Bool
_fontFamily :: Maybe FontFamily
_fontCharset :: Maybe Int
_fontName :: Maybe FormatCode
_fontVertAlign :: Maybe FontVerticalAlignment
_fontUnderline :: Maybe FontUnderline
_fontSize :: Maybe Double
_fontStrikeThrough :: Maybe Bool
_fontShadow :: Maybe Bool
_fontScheme :: Maybe FontScheme
_fontOutline :: Maybe Bool
_fontName :: Maybe FormatCode
_fontItalic :: Maybe Bool
_fontFamily :: Maybe FontFamily
_fontExtend :: Maybe Bool
_fontCondense :: Maybe Bool
_fontColor :: Maybe Color
_fontCharset :: Maybe Int
_fontBold :: Maybe Bool
..}
instance FromAttrVal FontFamily where
fromAttrVal :: Reader FontFamily
fromAttrVal FormatCode
"0" = forall a. a -> Either String (a, FormatCode)
readSuccess FontFamily
FontFamilyNotApplicable
fromAttrVal FormatCode
"1" = forall a. a -> Either String (a, FormatCode)
readSuccess FontFamily
FontFamilyRoman
fromAttrVal FormatCode
"2" = forall a. a -> Either String (a, FormatCode)
readSuccess FontFamily
FontFamilySwiss
fromAttrVal FormatCode
"3" = forall a. a -> Either String (a, FormatCode)
readSuccess FontFamily
FontFamilyModern
fromAttrVal FormatCode
"4" = forall a. a -> Either String (a, FormatCode)
readSuccess FontFamily
FontFamilyScript
fromAttrVal FormatCode
"5" = forall a. a -> Either String (a, FormatCode)
readSuccess FontFamily
FontFamilyDecorative
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"FontFamily" FormatCode
t
instance FromAttrBs FontFamily where
fromAttrBs :: ByteString -> Either FormatCode FontFamily
fromAttrBs ByteString
"0" = forall (m :: * -> *) a. Monad m => a -> m a
return FontFamily
FontFamilyNotApplicable
fromAttrBs ByteString
"1" = forall (m :: * -> *) a. Monad m => a -> m a
return FontFamily
FontFamilyRoman
fromAttrBs ByteString
"2" = forall (m :: * -> *) a. Monad m => a -> m a
return FontFamily
FontFamilySwiss
fromAttrBs ByteString
"3" = forall (m :: * -> *) a. Monad m => a -> m a
return FontFamily
FontFamilyModern
fromAttrBs ByteString
"4" = forall (m :: * -> *) a. Monad m => a -> m a
return FontFamily
FontFamilyScript
fromAttrBs ByteString
"5" = forall (m :: * -> *) a. Monad m => a -> m a
return FontFamily
FontFamilyDecorative
fromAttrBs ByteString
x = forall a. FormatCode -> ByteString -> Either FormatCode a
unexpectedAttrBs FormatCode
"FontFamily" ByteString
x
instance FromCursor Color where
fromCursor :: Cursor -> [Color]
fromCursor Cursor
cur = do
Maybe Bool
_colorAutomatic <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"auto" Cursor
cur
Maybe FormatCode
_colorARGB <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"rgb" Cursor
cur
Maybe Int
_colorTheme <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"theme" Cursor
cur
Maybe Double
_colorTint <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"tint" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Color{Maybe Bool
Maybe Double
Maybe Int
Maybe FormatCode
_colorTint :: Maybe Double
_colorTheme :: Maybe Int
_colorARGB :: Maybe FormatCode
_colorAutomatic :: Maybe Bool
_colorTint :: Maybe Double
_colorTheme :: Maybe Int
_colorARGB :: Maybe FormatCode
_colorAutomatic :: Maybe Bool
..}
instance FromXenoNode Color where
fromXenoNode :: Node -> Either FormatCode Color
fromXenoNode Node
root =
forall a. Node -> AttrParser a -> Either FormatCode a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Maybe Bool
_colorAutomatic <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"auto"
Maybe FormatCode
_colorARGB <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"rgb"
Maybe Int
_colorTheme <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"theme"
Maybe Double
_colorTint <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"tint"
forall (m :: * -> *) a. Monad m => a -> m a
return Color {Maybe Bool
Maybe Double
Maybe Int
Maybe FormatCode
_colorTint :: Maybe Double
_colorTheme :: Maybe Int
_colorARGB :: Maybe FormatCode
_colorAutomatic :: Maybe Bool
_colorTint :: Maybe Double
_colorTheme :: Maybe Int
_colorARGB :: Maybe FormatCode
_colorAutomatic :: Maybe Bool
..}
instance FromAttrVal FontUnderline where
fromAttrVal :: Reader FontUnderline
fromAttrVal FormatCode
"single" = forall a. a -> Either String (a, FormatCode)
readSuccess FontUnderline
FontUnderlineSingle
fromAttrVal FormatCode
"double" = forall a. a -> Either String (a, FormatCode)
readSuccess FontUnderline
FontUnderlineDouble
fromAttrVal FormatCode
"singleAccounting" = forall a. a -> Either String (a, FormatCode)
readSuccess FontUnderline
FontUnderlineSingleAccounting
fromAttrVal FormatCode
"doubleAccounting" = forall a. a -> Either String (a, FormatCode)
readSuccess FontUnderline
FontUnderlineDoubleAccounting
fromAttrVal FormatCode
"none" = forall a. a -> Either String (a, FormatCode)
readSuccess FontUnderline
FontUnderlineNone
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"FontUnderline" FormatCode
t
instance FromAttrBs FontUnderline where
fromAttrBs :: ByteString -> Either FormatCode FontUnderline
fromAttrBs ByteString
"single" = forall (m :: * -> *) a. Monad m => a -> m a
return FontUnderline
FontUnderlineSingle
fromAttrBs ByteString
"double" = forall (m :: * -> *) a. Monad m => a -> m a
return FontUnderline
FontUnderlineDouble
fromAttrBs ByteString
"singleAccounting" = forall (m :: * -> *) a. Monad m => a -> m a
return FontUnderline
FontUnderlineSingleAccounting
fromAttrBs ByteString
"doubleAccounting" = forall (m :: * -> *) a. Monad m => a -> m a
return FontUnderline
FontUnderlineDoubleAccounting
fromAttrBs ByteString
"none" = forall (m :: * -> *) a. Monad m => a -> m a
return FontUnderline
FontUnderlineNone
fromAttrBs ByteString
x = forall a. FormatCode -> ByteString -> Either FormatCode a
unexpectedAttrBs FormatCode
"FontUnderline" ByteString
x
instance FromAttrVal FontVerticalAlignment where
fromAttrVal :: Reader FontVerticalAlignment
fromAttrVal FormatCode
"baseline" = forall a. a -> Either String (a, FormatCode)
readSuccess FontVerticalAlignment
FontVerticalAlignmentBaseline
fromAttrVal FormatCode
"subscript" = forall a. a -> Either String (a, FormatCode)
readSuccess FontVerticalAlignment
FontVerticalAlignmentSubscript
fromAttrVal FormatCode
"superscript" = forall a. a -> Either String (a, FormatCode)
readSuccess FontVerticalAlignment
FontVerticalAlignmentSuperscript
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"FontVerticalAlignment" FormatCode
t
instance FromAttrBs FontVerticalAlignment where
fromAttrBs :: ByteString -> Either FormatCode FontVerticalAlignment
fromAttrBs ByteString
"baseline" = forall (m :: * -> *) a. Monad m => a -> m a
return FontVerticalAlignment
FontVerticalAlignmentBaseline
fromAttrBs ByteString
"subscript" = forall (m :: * -> *) a. Monad m => a -> m a
return FontVerticalAlignment
FontVerticalAlignmentSubscript
fromAttrBs ByteString
"superscript" = forall (m :: * -> *) a. Monad m => a -> m a
return FontVerticalAlignment
FontVerticalAlignmentSuperscript
fromAttrBs ByteString
x = forall a. FormatCode -> ByteString -> Either FormatCode a
unexpectedAttrBs FormatCode
"FontVerticalAlignment" ByteString
x
instance FromAttrVal FontScheme where
fromAttrVal :: Reader FontScheme
fromAttrVal FormatCode
"major" = forall a. a -> Either String (a, FormatCode)
readSuccess FontScheme
FontSchemeMajor
fromAttrVal FormatCode
"minor" = forall a. a -> Either String (a, FormatCode)
readSuccess FontScheme
FontSchemeMinor
fromAttrVal FormatCode
"none" = forall a. a -> Either String (a, FormatCode)
readSuccess FontScheme
FontSchemeNone
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"FontScheme" FormatCode
t
instance FromAttrBs FontScheme where
fromAttrBs :: ByteString -> Either FormatCode FontScheme
fromAttrBs ByteString
"major" = forall (m :: * -> *) a. Monad m => a -> m a
return FontScheme
FontSchemeMajor
fromAttrBs ByteString
"minor" = forall (m :: * -> *) a. Monad m => a -> m a
return FontScheme
FontSchemeMinor
fromAttrBs ByteString
"none" = forall (m :: * -> *) a. Monad m => a -> m a
return FontScheme
FontSchemeNone
fromAttrBs ByteString
x = forall a. FormatCode -> ByteString -> Either FormatCode a
unexpectedAttrBs FormatCode
"FontScheme" ByteString
x
instance FromCursor Fill where
fromCursor :: Cursor -> [Fill]
fromCursor Cursor
cur = do
Maybe FillPattern
_fillPattern <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"patternFill") Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Fill{Maybe FillPattern
_fillPattern :: Maybe FillPattern
_fillPattern :: Maybe FillPattern
..}
instance FromCursor FillPattern where
fromCursor :: Cursor -> [FillPattern]
fromCursor Cursor
cur = do
Maybe PatternType
_fillPatternType <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"patternType" Cursor
cur
Maybe Color
_fillPatternFgColor <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"fgColor") Cursor
cur
Maybe Color
_fillPatternBgColor <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"bgColor") Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return FillPattern{Maybe PatternType
Maybe Color
_fillPatternBgColor :: Maybe Color
_fillPatternFgColor :: Maybe Color
_fillPatternType :: Maybe PatternType
_fillPatternType :: Maybe PatternType
_fillPatternFgColor :: Maybe Color
_fillPatternBgColor :: Maybe Color
..}
instance FromAttrVal PatternType where
fromAttrVal :: Reader PatternType
fromAttrVal FormatCode
"darkDown" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeDarkDown
fromAttrVal FormatCode
"darkGray" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeDarkGray
fromAttrVal FormatCode
"darkGrid" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeDarkGrid
fromAttrVal FormatCode
"darkHorizontal" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeDarkHorizontal
fromAttrVal FormatCode
"darkTrellis" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeDarkTrellis
fromAttrVal FormatCode
"darkUp" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeDarkUp
fromAttrVal FormatCode
"darkVertical" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeDarkVertical
fromAttrVal FormatCode
"gray0625" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeGray0625
fromAttrVal FormatCode
"gray125" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeGray125
fromAttrVal FormatCode
"lightDown" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeLightDown
fromAttrVal FormatCode
"lightGray" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeLightGray
fromAttrVal FormatCode
"lightGrid" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeLightGrid
fromAttrVal FormatCode
"lightHorizontal" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeLightHorizontal
fromAttrVal FormatCode
"lightTrellis" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeLightTrellis
fromAttrVal FormatCode
"lightUp" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeLightUp
fromAttrVal FormatCode
"lightVertical" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeLightVertical
fromAttrVal FormatCode
"mediumGray" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeMediumGray
fromAttrVal FormatCode
"none" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeNone
fromAttrVal FormatCode
"solid" = forall a. a -> Either String (a, FormatCode)
readSuccess PatternType
PatternTypeSolid
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"PatternType" FormatCode
t
instance FromCursor Border where
fromCursor :: Cursor -> [Border]
fromCursor Cursor
cur = do
Maybe Bool
_borderDiagonalUp <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"diagonalUp" Cursor
cur
Maybe Bool
_borderDiagonalDown <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"diagonalDown" Cursor
cur
Maybe Bool
_borderOutline <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"outline" Cursor
cur
Maybe BorderStyle
_borderStart <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"start") Cursor
cur
Maybe BorderStyle
_borderEnd <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"end") Cursor
cur
Maybe BorderStyle
_borderLeft <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"left") Cursor
cur
Maybe BorderStyle
_borderRight <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"right") Cursor
cur
Maybe BorderStyle
_borderTop <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"top") Cursor
cur
Maybe BorderStyle
_borderBottom <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"bottom") Cursor
cur
Maybe BorderStyle
_borderDiagonal <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"diagonal") Cursor
cur
Maybe BorderStyle
_borderVertical <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"vertical") Cursor
cur
Maybe BorderStyle
_borderHorizontal <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"horizontal") Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Border{Maybe Bool
Maybe BorderStyle
_borderHorizontal :: Maybe BorderStyle
_borderVertical :: Maybe BorderStyle
_borderDiagonal :: Maybe BorderStyle
_borderBottom :: Maybe BorderStyle
_borderTop :: Maybe BorderStyle
_borderRight :: Maybe BorderStyle
_borderLeft :: Maybe BorderStyle
_borderEnd :: Maybe BorderStyle
_borderStart :: Maybe BorderStyle
_borderOutline :: Maybe Bool
_borderDiagonalDown :: Maybe Bool
_borderDiagonalUp :: Maybe Bool
_borderVertical :: Maybe BorderStyle
_borderTop :: Maybe BorderStyle
_borderStart :: Maybe BorderStyle
_borderRight :: Maybe BorderStyle
_borderLeft :: Maybe BorderStyle
_borderHorizontal :: Maybe BorderStyle
_borderEnd :: Maybe BorderStyle
_borderDiagonal :: Maybe BorderStyle
_borderBottom :: Maybe BorderStyle
_borderOutline :: Maybe Bool
_borderDiagonalUp :: Maybe Bool
_borderDiagonalDown :: Maybe Bool
..}
instance FromCursor BorderStyle where
fromCursor :: Cursor -> [BorderStyle]
fromCursor Cursor
cur = do
Maybe LineStyle
_borderStyleLine <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"style" Cursor
cur
Maybe Color
_borderStyleColor <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"color") Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return BorderStyle{Maybe LineStyle
Maybe Color
_borderStyleColor :: Maybe Color
_borderStyleLine :: Maybe LineStyle
_borderStyleLine :: Maybe LineStyle
_borderStyleColor :: Maybe Color
..}
instance FromAttrVal LineStyle where
fromAttrVal :: Reader LineStyle
fromAttrVal FormatCode
"dashDot" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleDashDot
fromAttrVal FormatCode
"dashDotDot" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleDashDotDot
fromAttrVal FormatCode
"dashed" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleDashed
fromAttrVal FormatCode
"dotted" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleDotted
fromAttrVal FormatCode
"double" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleDouble
fromAttrVal FormatCode
"hair" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleHair
fromAttrVal FormatCode
"medium" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleMedium
fromAttrVal FormatCode
"mediumDashDot" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleMediumDashDot
fromAttrVal FormatCode
"mediumDashDotDot" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleMediumDashDotDot
fromAttrVal FormatCode
"mediumDashed" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleMediumDashed
fromAttrVal FormatCode
"none" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleNone
fromAttrVal FormatCode
"slantDashDot" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleSlantDashDot
fromAttrVal FormatCode
"thick" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleThick
fromAttrVal FormatCode
"thin" = forall a. a -> Either String (a, FormatCode)
readSuccess LineStyle
LineStyleThin
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"LineStyle" FormatCode
t
instance FromCursor CellXf where
fromCursor :: Cursor -> [CellXf]
fromCursor Cursor
cur = do
Maybe Alignment
_cellXfAlignment <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"alignment") Cursor
cur
Maybe Protection
_cellXfProtection <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"protection") Cursor
cur
Maybe Int
_cellXfNumFmtId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"numFmtId" Cursor
cur
Maybe Int
_cellXfFontId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"fontId" Cursor
cur
Maybe Int
_cellXfFillId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"fillId" Cursor
cur
Maybe Int
_cellXfBorderId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"borderId" Cursor
cur
Maybe Int
_cellXfId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"xfId" Cursor
cur
Maybe Bool
_cellXfQuotePrefix <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"quotePrefix" Cursor
cur
Maybe Bool
_cellXfPivotButton <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"pivotButton" Cursor
cur
Maybe Bool
_cellXfApplyNumberFormat <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"applyNumberFormat" Cursor
cur
Maybe Bool
_cellXfApplyFont <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"applyFont" Cursor
cur
Maybe Bool
_cellXfApplyFill <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"applyFill" Cursor
cur
Maybe Bool
_cellXfApplyBorder <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"applyBorder" Cursor
cur
Maybe Bool
_cellXfApplyAlignment <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"applyAlignment" Cursor
cur
Maybe Bool
_cellXfApplyProtection <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"applyProtection" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return CellXf{Maybe Bool
Maybe Int
Maybe Protection
Maybe Alignment
_cellXfApplyProtection :: Maybe Bool
_cellXfApplyAlignment :: Maybe Bool
_cellXfApplyBorder :: Maybe Bool
_cellXfApplyFill :: Maybe Bool
_cellXfApplyFont :: Maybe Bool
_cellXfApplyNumberFormat :: Maybe Bool
_cellXfPivotButton :: Maybe Bool
_cellXfQuotePrefix :: Maybe Bool
_cellXfId :: Maybe Int
_cellXfBorderId :: Maybe Int
_cellXfFillId :: Maybe Int
_cellXfFontId :: Maybe Int
_cellXfNumFmtId :: Maybe Int
_cellXfProtection :: Maybe Protection
_cellXfAlignment :: Maybe Alignment
_cellXfProtection :: Maybe Protection
_cellXfAlignment :: Maybe Alignment
_cellXfId :: Maybe Int
_cellXfQuotePrefix :: Maybe Bool
_cellXfPivotButton :: Maybe Bool
_cellXfNumFmtId :: Maybe Int
_cellXfFontId :: Maybe Int
_cellXfFillId :: Maybe Int
_cellXfBorderId :: Maybe Int
_cellXfApplyProtection :: Maybe Bool
_cellXfApplyNumberFormat :: Maybe Bool
_cellXfApplyFont :: Maybe Bool
_cellXfApplyFill :: Maybe Bool
_cellXfApplyBorder :: Maybe Bool
_cellXfApplyAlignment :: Maybe Bool
..}
instance FromCursor Dxf where
fromCursor :: Cursor -> [Dxf]
fromCursor Cursor
cur = do
Maybe Font
_dxfFont <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"font") Cursor
cur
Maybe NumFmt
_dxfNumFmt <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"numFmt") Cursor
cur
Maybe Fill
_dxfFill <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"fill") Cursor
cur
Maybe Alignment
_dxfAlignment <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"alignment") Cursor
cur
Maybe Border
_dxfBorder <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"border") Cursor
cur
Maybe Protection
_dxfProtection <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (FormatCode -> Name
n_ FormatCode
"protection") Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Dxf{Maybe Protection
Maybe NumFmt
Maybe Font
Maybe Fill
Maybe Border
Maybe Alignment
_dxfProtection :: Maybe Protection
_dxfBorder :: Maybe Border
_dxfAlignment :: Maybe Alignment
_dxfFill :: Maybe Fill
_dxfNumFmt :: Maybe NumFmt
_dxfFont :: Maybe Font
_dxfProtection :: Maybe Protection
_dxfBorder :: Maybe Border
_dxfAlignment :: Maybe Alignment
_dxfFill :: Maybe Fill
_dxfNumFmt :: Maybe NumFmt
_dxfFont :: Maybe Font
..}
instance FromCursor NumFmt where
fromCursor :: Cursor -> [NumFmt]
fromCursor Cursor
cur = do
FormatCode
_numFmtCode <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"formatCode" Cursor
cur
Int
_numFmtId <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"numFmtId" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return NumFmt{Int
FormatCode
_numFmtId :: Int
_numFmtCode :: FormatCode
_numFmtCode :: FormatCode
_numFmtId :: Int
..}
instance FromCursor Alignment where
fromCursor :: Cursor -> [Alignment]
fromCursor Cursor
cur = do
Maybe CellHorizontalAlignment
_alignmentHorizontal <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"horizontal" Cursor
cur
Maybe CellVerticalAlignment
_alignmentVertical <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"vertical" Cursor
cur
Maybe Int
_alignmentTextRotation <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"textRotation" Cursor
cur
Maybe Bool
_alignmentWrapText <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"wrapText" Cursor
cur
Maybe Int
_alignmentRelativeIndent <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"relativeIndent" Cursor
cur
Maybe Int
_alignmentIndent <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"indent" Cursor
cur
Maybe Bool
_alignmentJustifyLastLine <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"justifyLastLine" Cursor
cur
Maybe Bool
_alignmentShrinkToFit <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"shrinkToFit" Cursor
cur
Maybe ReadingOrder
_alignmentReadingOrder <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"readingOrder" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Alignment{Maybe Bool
Maybe Int
Maybe ReadingOrder
Maybe CellVerticalAlignment
Maybe CellHorizontalAlignment
_alignmentReadingOrder :: Maybe ReadingOrder
_alignmentShrinkToFit :: Maybe Bool
_alignmentJustifyLastLine :: Maybe Bool
_alignmentIndent :: Maybe Int
_alignmentRelativeIndent :: Maybe Int
_alignmentWrapText :: Maybe Bool
_alignmentTextRotation :: Maybe Int
_alignmentVertical :: Maybe CellVerticalAlignment
_alignmentHorizontal :: Maybe CellHorizontalAlignment
_alignmentWrapText :: Maybe Bool
_alignmentVertical :: Maybe CellVerticalAlignment
_alignmentTextRotation :: Maybe Int
_alignmentShrinkToFit :: Maybe Bool
_alignmentRelativeIndent :: Maybe Int
_alignmentReadingOrder :: Maybe ReadingOrder
_alignmentJustifyLastLine :: Maybe Bool
_alignmentIndent :: Maybe Int
_alignmentHorizontal :: Maybe CellHorizontalAlignment
..}
instance FromAttrVal CellHorizontalAlignment where
fromAttrVal :: Reader CellHorizontalAlignment
fromAttrVal FormatCode
"center" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentCenter
fromAttrVal FormatCode
"centerContinuous" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentCenterContinuous
fromAttrVal FormatCode
"distributed" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentDistributed
fromAttrVal FormatCode
"fill" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentFill
fromAttrVal FormatCode
"general" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentGeneral
fromAttrVal FormatCode
"justify" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentJustify
fromAttrVal FormatCode
"left" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentLeft
fromAttrVal FormatCode
"right" = forall a. a -> Either String (a, FormatCode)
readSuccess CellHorizontalAlignment
CellHorizontalAlignmentRight
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"CellHorizontalAlignment" FormatCode
t
instance FromAttrVal CellVerticalAlignment where
fromAttrVal :: Reader CellVerticalAlignment
fromAttrVal FormatCode
"bottom" = forall a. a -> Either String (a, FormatCode)
readSuccess CellVerticalAlignment
CellVerticalAlignmentBottom
fromAttrVal FormatCode
"center" = forall a. a -> Either String (a, FormatCode)
readSuccess CellVerticalAlignment
CellVerticalAlignmentCenter
fromAttrVal FormatCode
"distributed" = forall a. a -> Either String (a, FormatCode)
readSuccess CellVerticalAlignment
CellVerticalAlignmentDistributed
fromAttrVal FormatCode
"justify" = forall a. a -> Either String (a, FormatCode)
readSuccess CellVerticalAlignment
CellVerticalAlignmentJustify
fromAttrVal FormatCode
"top" = forall a. a -> Either String (a, FormatCode)
readSuccess CellVerticalAlignment
CellVerticalAlignmentTop
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"CellVerticalAlignment" FormatCode
t
instance FromAttrVal ReadingOrder where
fromAttrVal :: Reader ReadingOrder
fromAttrVal FormatCode
"0" = forall a. a -> Either String (a, FormatCode)
readSuccess ReadingOrder
ReadingOrderContextDependent
fromAttrVal FormatCode
"1" = forall a. a -> Either String (a, FormatCode)
readSuccess ReadingOrder
ReadingOrderLeftToRight
fromAttrVal FormatCode
"2" = forall a. a -> Either String (a, FormatCode)
readSuccess ReadingOrder
ReadingOrderRightToLeft
fromAttrVal FormatCode
t = forall a. FormatCode -> FormatCode -> Either String (a, FormatCode)
invalidText FormatCode
"ReadingOrder" FormatCode
t
instance FromCursor Protection where
fromCursor :: Cursor -> [Protection]
fromCursor Cursor
cur = do
Maybe Bool
_protectionLocked <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"locked" Cursor
cur
Maybe Bool
_protectionHidden <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"hidden" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Protection{Maybe Bool
_protectionHidden :: Maybe Bool
_protectionLocked :: Maybe Bool
_protectionLocked :: Maybe Bool
_protectionHidden :: Maybe Bool
..}