{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Types.PageSetup (
PageSetup(..)
, CellComments(..)
, PrintErrors(..)
, Orientation(..)
, PageOrder(..)
, PaperSize(..)
, pageSetupBlackAndWhite
, pageSetupCellComments
, pageSetupCopies
, pageSetupDraft
, pageSetupErrors
, pageSetupFirstPageNumber
, pageSetupFitToHeight
, pageSetupFitToWidth
, pageSetupHorizontalDpi
, pageSetupId
, pageSetupOrientation
, pageSetupPageOrder
, pageSetupPaperHeight
, pageSetupPaperSize
, pageSetupPaperWidth
, pageSetupScale
, pageSetupUseFirstPageNumber
, pageSetupUsePrinterDefaults
, pageSetupVerticalDpi
) where
#ifdef USE_MICROLENS
import Lens.Micro.TH (makeLenses)
#else
import Control.Lens (makeLenses)
#endif
import Control.DeepSeq (NFData)
import Data.Default
import qualified Data.Map as Map
import Data.Maybe (catMaybes)
import Data.Text (Text)
import GHC.Generics (Generic)
import Text.XML
import Codec.Xlsx.Writer.Internal
import Codec.Xlsx.Parser.Internal
data PageSetup = PageSetup {
PageSetup -> Maybe Bool
_pageSetupBlackAndWhite :: Maybe Bool
, :: Maybe CellComments
, PageSetup -> Maybe Int
_pageSetupCopies :: Maybe Int
, PageSetup -> Maybe Bool
_pageSetupDraft :: Maybe Bool
, PageSetup -> Maybe PrintErrors
_pageSetupErrors :: Maybe PrintErrors
, PageSetup -> Maybe Int
_pageSetupFirstPageNumber :: Maybe Int
, PageSetup -> Maybe Int
_pageSetupFitToHeight :: Maybe Int
, PageSetup -> Maybe Int
_pageSetupFitToWidth :: Maybe Int
, PageSetup -> Maybe Int
_pageSetupHorizontalDpi :: Maybe Int
, PageSetup -> Maybe Text
_pageSetupId :: Maybe Text
, PageSetup -> Maybe Orientation
_pageSetupOrientation :: Maybe Orientation
, PageSetup -> Maybe PageOrder
_pageSetupPageOrder :: Maybe PageOrder
, PageSetup -> Maybe Text
_pageSetupPaperHeight :: Maybe Text
, PageSetup -> Maybe PaperSize
_pageSetupPaperSize :: Maybe PaperSize
, PageSetup -> Maybe Text
_pageSetupPaperWidth :: Maybe Text
, PageSetup -> Maybe Int
_pageSetupScale :: Maybe Int
, PageSetup -> Maybe Bool
_pageSetupUseFirstPageNumber :: Maybe Bool
, PageSetup -> Maybe Bool
_pageSetupUsePrinterDefaults :: Maybe Bool
, PageSetup -> Maybe Int
_pageSetupVerticalDpi :: Maybe Int
}
deriving (PageSetup -> PageSetup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageSetup -> PageSetup -> Bool
$c/= :: PageSetup -> PageSetup -> Bool
== :: PageSetup -> PageSetup -> Bool
$c== :: PageSetup -> PageSetup -> Bool
Eq, Eq PageSetup
PageSetup -> PageSetup -> Bool
PageSetup -> PageSetup -> Ordering
PageSetup -> PageSetup -> PageSetup
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 :: PageSetup -> PageSetup -> PageSetup
$cmin :: PageSetup -> PageSetup -> PageSetup
max :: PageSetup -> PageSetup -> PageSetup
$cmax :: PageSetup -> PageSetup -> PageSetup
>= :: PageSetup -> PageSetup -> Bool
$c>= :: PageSetup -> PageSetup -> Bool
> :: PageSetup -> PageSetup -> Bool
$c> :: PageSetup -> PageSetup -> Bool
<= :: PageSetup -> PageSetup -> Bool
$c<= :: PageSetup -> PageSetup -> Bool
< :: PageSetup -> PageSetup -> Bool
$c< :: PageSetup -> PageSetup -> Bool
compare :: PageSetup -> PageSetup -> Ordering
$ccompare :: PageSetup -> PageSetup -> Ordering
Ord, Int -> PageSetup -> ShowS
[PageSetup] -> ShowS
PageSetup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageSetup] -> ShowS
$cshowList :: [PageSetup] -> ShowS
show :: PageSetup -> String
$cshow :: PageSetup -> String
showsPrec :: Int -> PageSetup -> ShowS
$cshowsPrec :: Int -> PageSetup -> ShowS
Show, forall x. Rep PageSetup x -> PageSetup
forall x. PageSetup -> Rep PageSetup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PageSetup x -> PageSetup
$cfrom :: forall x. PageSetup -> Rep PageSetup x
Generic)
instance NFData PageSetup
data =
|
|
deriving (CellComments -> CellComments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellComments -> CellComments -> Bool
$c/= :: CellComments -> CellComments -> Bool
== :: CellComments -> CellComments -> Bool
$c== :: CellComments -> CellComments -> Bool
Eq, Eq CellComments
CellComments -> CellComments -> Bool
CellComments -> CellComments -> Ordering
CellComments -> CellComments -> CellComments
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 :: CellComments -> CellComments -> CellComments
$cmin :: CellComments -> CellComments -> CellComments
max :: CellComments -> CellComments -> CellComments
$cmax :: CellComments -> CellComments -> CellComments
>= :: CellComments -> CellComments -> Bool
$c>= :: CellComments -> CellComments -> Bool
> :: CellComments -> CellComments -> Bool
$c> :: CellComments -> CellComments -> Bool
<= :: CellComments -> CellComments -> Bool
$c<= :: CellComments -> CellComments -> Bool
< :: CellComments -> CellComments -> Bool
$c< :: CellComments -> CellComments -> Bool
compare :: CellComments -> CellComments -> Ordering
$ccompare :: CellComments -> CellComments -> Ordering
Ord, Int -> CellComments -> ShowS
[CellComments] -> ShowS
CellComments -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CellComments] -> ShowS
$cshowList :: [CellComments] -> ShowS
show :: CellComments -> String
$cshow :: CellComments -> String
showsPrec :: Int -> CellComments -> ShowS
$cshowsPrec :: Int -> CellComments -> ShowS
Show, forall x. Rep CellComments x -> CellComments
forall x. CellComments -> Rep CellComments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CellComments x -> CellComments
$cfrom :: forall x. CellComments -> Rep CellComments x
Generic)
instance NFData CellComments
data PrintErrors =
PrintErrorsBlank
| PrintErrorsDash
| PrintErrorsDisplayed
| PrintErrorsNA
deriving (PrintErrors -> PrintErrors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrintErrors -> PrintErrors -> Bool
$c/= :: PrintErrors -> PrintErrors -> Bool
== :: PrintErrors -> PrintErrors -> Bool
$c== :: PrintErrors -> PrintErrors -> Bool
Eq, Eq PrintErrors
PrintErrors -> PrintErrors -> Bool
PrintErrors -> PrintErrors -> Ordering
PrintErrors -> PrintErrors -> PrintErrors
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 :: PrintErrors -> PrintErrors -> PrintErrors
$cmin :: PrintErrors -> PrintErrors -> PrintErrors
max :: PrintErrors -> PrintErrors -> PrintErrors
$cmax :: PrintErrors -> PrintErrors -> PrintErrors
>= :: PrintErrors -> PrintErrors -> Bool
$c>= :: PrintErrors -> PrintErrors -> Bool
> :: PrintErrors -> PrintErrors -> Bool
$c> :: PrintErrors -> PrintErrors -> Bool
<= :: PrintErrors -> PrintErrors -> Bool
$c<= :: PrintErrors -> PrintErrors -> Bool
< :: PrintErrors -> PrintErrors -> Bool
$c< :: PrintErrors -> PrintErrors -> Bool
compare :: PrintErrors -> PrintErrors -> Ordering
$ccompare :: PrintErrors -> PrintErrors -> Ordering
Ord, Int -> PrintErrors -> ShowS
[PrintErrors] -> ShowS
PrintErrors -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrintErrors] -> ShowS
$cshowList :: [PrintErrors] -> ShowS
show :: PrintErrors -> String
$cshow :: PrintErrors -> String
showsPrec :: Int -> PrintErrors -> ShowS
$cshowsPrec :: Int -> PrintErrors -> ShowS
Show, forall x. Rep PrintErrors x -> PrintErrors
forall x. PrintErrors -> Rep PrintErrors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PrintErrors x -> PrintErrors
$cfrom :: forall x. PrintErrors -> Rep PrintErrors x
Generic)
instance NFData PrintErrors
data Orientation =
OrientationDefault
| OrientationLandscape
| OrientationPortrait
deriving (Orientation -> Orientation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Orientation -> Orientation -> Bool
$c/= :: Orientation -> Orientation -> Bool
== :: Orientation -> Orientation -> Bool
$c== :: Orientation -> Orientation -> Bool
Eq, Eq Orientation
Orientation -> Orientation -> Bool
Orientation -> Orientation -> Ordering
Orientation -> Orientation -> Orientation
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 :: Orientation -> Orientation -> Orientation
$cmin :: Orientation -> Orientation -> Orientation
max :: Orientation -> Orientation -> Orientation
$cmax :: Orientation -> Orientation -> Orientation
>= :: Orientation -> Orientation -> Bool
$c>= :: Orientation -> Orientation -> Bool
> :: Orientation -> Orientation -> Bool
$c> :: Orientation -> Orientation -> Bool
<= :: Orientation -> Orientation -> Bool
$c<= :: Orientation -> Orientation -> Bool
< :: Orientation -> Orientation -> Bool
$c< :: Orientation -> Orientation -> Bool
compare :: Orientation -> Orientation -> Ordering
$ccompare :: Orientation -> Orientation -> Ordering
Ord, Int -> Orientation -> ShowS
[Orientation] -> ShowS
Orientation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Orientation] -> ShowS
$cshowList :: [Orientation] -> ShowS
show :: Orientation -> String
$cshow :: Orientation -> String
showsPrec :: Int -> Orientation -> ShowS
$cshowsPrec :: Int -> Orientation -> ShowS
Show, forall x. Rep Orientation x -> Orientation
forall x. Orientation -> Rep Orientation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Orientation x -> Orientation
$cfrom :: forall x. Orientation -> Rep Orientation x
Generic)
instance NFData Orientation
data PageOrder =
PageOrderDownThenOver
| PageOrderOverThenDown
deriving (PageOrder -> PageOrder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageOrder -> PageOrder -> Bool
$c/= :: PageOrder -> PageOrder -> Bool
== :: PageOrder -> PageOrder -> Bool
$c== :: PageOrder -> PageOrder -> Bool
Eq, Eq PageOrder
PageOrder -> PageOrder -> Bool
PageOrder -> PageOrder -> Ordering
PageOrder -> PageOrder -> PageOrder
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 :: PageOrder -> PageOrder -> PageOrder
$cmin :: PageOrder -> PageOrder -> PageOrder
max :: PageOrder -> PageOrder -> PageOrder
$cmax :: PageOrder -> PageOrder -> PageOrder
>= :: PageOrder -> PageOrder -> Bool
$c>= :: PageOrder -> PageOrder -> Bool
> :: PageOrder -> PageOrder -> Bool
$c> :: PageOrder -> PageOrder -> Bool
<= :: PageOrder -> PageOrder -> Bool
$c<= :: PageOrder -> PageOrder -> Bool
< :: PageOrder -> PageOrder -> Bool
$c< :: PageOrder -> PageOrder -> Bool
compare :: PageOrder -> PageOrder -> Ordering
$ccompare :: PageOrder -> PageOrder -> Ordering
Ord, Int -> PageOrder -> ShowS
[PageOrder] -> ShowS
PageOrder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageOrder] -> ShowS
$cshowList :: [PageOrder] -> ShowS
show :: PageOrder -> String
$cshow :: PageOrder -> String
showsPrec :: Int -> PageOrder -> ShowS
$cshowsPrec :: Int -> PageOrder -> ShowS
Show, forall x. Rep PageOrder x -> PageOrder
forall x. PageOrder -> Rep PageOrder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PageOrder x -> PageOrder
$cfrom :: forall x. PageOrder -> Rep PageOrder x
Generic)
instance NFData PageOrder
data PaperSize =
PaperA2
| PaperA3
|
|
| PaperA3Transverse
| PaperA4
|
| PaperA4Plus
| PaperA4Small
| PaperA4Transverse
| PaperA5
|
| PaperA5Transverse
| PaperB4
| PaperB5
| PaperC
| PaperD
| PaperE
| PaperExecutive
| PaperFanfoldGermanLegal
| PaperFanfoldGermanStandard
| PaperFanfoldUsStandard
| PaperFolio
| PaperIsoB4
|
| PaperJapaneseDoublePostcard
| PaperJisB5Transverse
| PaperLedger
| PaperLegal
|
| PaperLetter
|
|
| PaperLetterPlus
| PaperLetterSmall
| PaperLetterTransverse
| PaperNote
| PaperQuarto
| PaperStandard9_11
| PaperStandard10_11
| PaperStandard10_14
| PaperStandard11_17
| PaperStandard15_11
| PaperStatement
| PaperSuperA
| PaperSuperB
| PaperTabloid
|
| Envelope6_3_4
| Envelope9
| Envelope10
| Envelope11
| Envelope12
| Envelope14
| EnvelopeB4
| EnvelopeB5
| EnvelopeB6
| EnvelopeC3
| EnvelopeC4
| EnvelopeC5
| EnvelopeC6
| EnvelopeC65
| EnvelopeDL
| EnvelopeInvite
| EnvelopeItaly
| EnvelopeMonarch
deriving (PaperSize -> PaperSize -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaperSize -> PaperSize -> Bool
$c/= :: PaperSize -> PaperSize -> Bool
== :: PaperSize -> PaperSize -> Bool
$c== :: PaperSize -> PaperSize -> Bool
Eq, Eq PaperSize
PaperSize -> PaperSize -> Bool
PaperSize -> PaperSize -> Ordering
PaperSize -> PaperSize -> PaperSize
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 :: PaperSize -> PaperSize -> PaperSize
$cmin :: PaperSize -> PaperSize -> PaperSize
max :: PaperSize -> PaperSize -> PaperSize
$cmax :: PaperSize -> PaperSize -> PaperSize
>= :: PaperSize -> PaperSize -> Bool
$c>= :: PaperSize -> PaperSize -> Bool
> :: PaperSize -> PaperSize -> Bool
$c> :: PaperSize -> PaperSize -> Bool
<= :: PaperSize -> PaperSize -> Bool
$c<= :: PaperSize -> PaperSize -> Bool
< :: PaperSize -> PaperSize -> Bool
$c< :: PaperSize -> PaperSize -> Bool
compare :: PaperSize -> PaperSize -> Ordering
$ccompare :: PaperSize -> PaperSize -> Ordering
Ord, Int -> PaperSize -> ShowS
[PaperSize] -> ShowS
PaperSize -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaperSize] -> ShowS
$cshowList :: [PaperSize] -> ShowS
show :: PaperSize -> String
$cshow :: PaperSize -> String
showsPrec :: Int -> PaperSize -> ShowS
$cshowsPrec :: Int -> PaperSize -> ShowS
Show, forall x. Rep PaperSize x -> PaperSize
forall x. PaperSize -> Rep PaperSize x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PaperSize x -> PaperSize
$cfrom :: forall x. PaperSize -> Rep PaperSize x
Generic)
instance NFData PaperSize
instance Default PageSetup where
def :: PageSetup
def = PageSetup {
_pageSetupBlackAndWhite :: Maybe Bool
_pageSetupBlackAndWhite = forall a. Maybe a
Nothing
, _pageSetupCellComments :: Maybe CellComments
_pageSetupCellComments = forall a. Maybe a
Nothing
, _pageSetupCopies :: Maybe Int
_pageSetupCopies = forall a. Maybe a
Nothing
, _pageSetupDraft :: Maybe Bool
_pageSetupDraft = forall a. Maybe a
Nothing
, _pageSetupErrors :: Maybe PrintErrors
_pageSetupErrors = forall a. Maybe a
Nothing
, _pageSetupFirstPageNumber :: Maybe Int
_pageSetupFirstPageNumber = forall a. Maybe a
Nothing
, _pageSetupFitToHeight :: Maybe Int
_pageSetupFitToHeight = forall a. Maybe a
Nothing
, _pageSetupFitToWidth :: Maybe Int
_pageSetupFitToWidth = forall a. Maybe a
Nothing
, _pageSetupHorizontalDpi :: Maybe Int
_pageSetupHorizontalDpi = forall a. Maybe a
Nothing
, _pageSetupId :: Maybe Text
_pageSetupId = forall a. Maybe a
Nothing
, _pageSetupOrientation :: Maybe Orientation
_pageSetupOrientation = forall a. Maybe a
Nothing
, _pageSetupPageOrder :: Maybe PageOrder
_pageSetupPageOrder = forall a. Maybe a
Nothing
, _pageSetupPaperHeight :: Maybe Text
_pageSetupPaperHeight = forall a. Maybe a
Nothing
, _pageSetupPaperSize :: Maybe PaperSize
_pageSetupPaperSize = forall a. Maybe a
Nothing
, _pageSetupPaperWidth :: Maybe Text
_pageSetupPaperWidth = forall a. Maybe a
Nothing
, _pageSetupScale :: Maybe Int
_pageSetupScale = forall a. Maybe a
Nothing
, _pageSetupUseFirstPageNumber :: Maybe Bool
_pageSetupUseFirstPageNumber = forall a. Maybe a
Nothing
, _pageSetupUsePrinterDefaults :: Maybe Bool
_pageSetupUsePrinterDefaults = forall a. Maybe a
Nothing
, _pageSetupVerticalDpi :: Maybe Int
_pageSetupVerticalDpi = forall a. Maybe a
Nothing
}
instance ToElement PageSetup where
toElement :: Name -> PageSetup -> Element
toElement Name
nm PageSetup{Maybe Bool
Maybe Int
Maybe Text
Maybe PaperSize
Maybe PageOrder
Maybe Orientation
Maybe PrintErrors
Maybe CellComments
_pageSetupVerticalDpi :: Maybe Int
_pageSetupUsePrinterDefaults :: Maybe Bool
_pageSetupUseFirstPageNumber :: Maybe Bool
_pageSetupScale :: Maybe Int
_pageSetupPaperWidth :: Maybe Text
_pageSetupPaperSize :: Maybe PaperSize
_pageSetupPaperHeight :: Maybe Text
_pageSetupPageOrder :: Maybe PageOrder
_pageSetupOrientation :: Maybe Orientation
_pageSetupId :: Maybe Text
_pageSetupHorizontalDpi :: Maybe Int
_pageSetupFitToWidth :: Maybe Int
_pageSetupFitToHeight :: Maybe Int
_pageSetupFirstPageNumber :: Maybe Int
_pageSetupErrors :: Maybe PrintErrors
_pageSetupDraft :: Maybe Bool
_pageSetupCopies :: Maybe Int
_pageSetupCellComments :: Maybe CellComments
_pageSetupBlackAndWhite :: Maybe Bool
_pageSetupVerticalDpi :: PageSetup -> Maybe Int
_pageSetupUsePrinterDefaults :: PageSetup -> Maybe Bool
_pageSetupUseFirstPageNumber :: PageSetup -> Maybe Bool
_pageSetupScale :: PageSetup -> Maybe Int
_pageSetupPaperWidth :: PageSetup -> Maybe Text
_pageSetupPaperSize :: PageSetup -> Maybe PaperSize
_pageSetupPaperHeight :: PageSetup -> Maybe Text
_pageSetupPageOrder :: PageSetup -> Maybe PageOrder
_pageSetupOrientation :: PageSetup -> Maybe Orientation
_pageSetupId :: PageSetup -> Maybe Text
_pageSetupHorizontalDpi :: PageSetup -> Maybe Int
_pageSetupFitToWidth :: PageSetup -> Maybe Int
_pageSetupFitToHeight :: PageSetup -> Maybe Int
_pageSetupFirstPageNumber :: PageSetup -> Maybe Int
_pageSetupErrors :: PageSetup -> Maybe PrintErrors
_pageSetupDraft :: PageSetup -> Maybe Bool
_pageSetupCopies :: PageSetup -> Maybe Int
_pageSetupCellComments :: PageSetup -> Maybe CellComments
_pageSetupBlackAndWhite :: PageSetup -> Maybe Bool
..} = Element {
elementName :: Name
elementName = Name
nm
, elementNodes :: [Node]
elementNodes = []
, elementAttributes :: Map Name Text
elementAttributes = forall k a. Ord k => [(k, a)] -> Map k a
Map.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
"paperSize" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PaperSize
_pageSetupPaperSize
, Name
"paperHeight" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Text
_pageSetupPaperHeight
, Name
"paperWidth" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Text
_pageSetupPaperWidth
, Name
"scale" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_pageSetupScale
, Name
"firstPageNumber" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_pageSetupFirstPageNumber
, Name
"fitToWidth" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_pageSetupFitToWidth
, Name
"fitToHeight" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_pageSetupFitToHeight
, Name
"pageOrder" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PageOrder
_pageSetupPageOrder
, Name
"orientation" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Orientation
_pageSetupOrientation
, Name
"usePrinterDefaults" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_pageSetupUsePrinterDefaults
, Name
"blackAndWhite" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_pageSetupBlackAndWhite
, Name
"draft" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_pageSetupDraft
, Name
"cellComments" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe CellComments
_pageSetupCellComments
, Name
"useFirstPageNumber" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_pageSetupUseFirstPageNumber
, Name
"errors" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PrintErrors
_pageSetupErrors
, Name
"horizontalDpi" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_pageSetupHorizontalDpi
, Name
"verticalDpi" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_pageSetupVerticalDpi
, Name
"copies" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_pageSetupCopies
, Name
"id" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Text
_pageSetupId
]
}
instance ToAttrVal CellComments where
toAttrVal :: CellComments -> Text
toAttrVal CellComments
CellCommentsNone = Text
"none"
toAttrVal CellComments
CellCommentsAsDisplayed = Text
"asDisplayed"
toAttrVal CellComments
CellCommentsAtEnd = Text
"atEnd"
instance ToAttrVal PrintErrors where
toAttrVal :: PrintErrors -> Text
toAttrVal PrintErrors
PrintErrorsDisplayed = Text
"displayed"
toAttrVal PrintErrors
PrintErrorsBlank = Text
"blank"
toAttrVal PrintErrors
PrintErrorsDash = Text
"dash"
toAttrVal PrintErrors
PrintErrorsNA = Text
"NA"
instance ToAttrVal Orientation where
toAttrVal :: Orientation -> Text
toAttrVal Orientation
OrientationDefault = Text
"default"
toAttrVal Orientation
OrientationPortrait = Text
"portrait"
toAttrVal Orientation
OrientationLandscape = Text
"landscape"
instance ToAttrVal PageOrder where
toAttrVal :: PageOrder -> Text
toAttrVal PageOrder
PageOrderDownThenOver = Text
"downThenOver"
toAttrVal PageOrder
PageOrderOverThenDown = Text
"overThenDown"
instance ToAttrVal PaperSize where
toAttrVal :: PaperSize -> Text
toAttrVal PaperSize
PaperLetter = Text
"1"
toAttrVal PaperSize
PaperLetterSmall = Text
"2"
toAttrVal PaperSize
PaperTabloid = Text
"3"
toAttrVal PaperSize
PaperLedger = Text
"4"
toAttrVal PaperSize
PaperLegal = Text
"5"
toAttrVal PaperSize
PaperStatement = Text
"6"
toAttrVal PaperSize
PaperExecutive = Text
"7"
toAttrVal PaperSize
PaperA3 = Text
"8"
toAttrVal PaperSize
PaperA4 = Text
"9"
toAttrVal PaperSize
PaperA4Small = Text
"10"
toAttrVal PaperSize
PaperA5 = Text
"11"
toAttrVal PaperSize
PaperB4 = Text
"12"
toAttrVal PaperSize
PaperB5 = Text
"13"
toAttrVal PaperSize
PaperFolio = Text
"14"
toAttrVal PaperSize
PaperQuarto = Text
"15"
toAttrVal PaperSize
PaperStandard10_14 = Text
"16"
toAttrVal PaperSize
PaperStandard11_17 = Text
"17"
toAttrVal PaperSize
PaperNote = Text
"18"
toAttrVal PaperSize
Envelope9 = Text
"19"
toAttrVal PaperSize
Envelope10 = Text
"20"
toAttrVal PaperSize
Envelope11 = Text
"21"
toAttrVal PaperSize
Envelope12 = Text
"22"
toAttrVal PaperSize
Envelope14 = Text
"23"
toAttrVal PaperSize
PaperC = Text
"24"
toAttrVal PaperSize
PaperD = Text
"25"
toAttrVal PaperSize
PaperE = Text
"26"
toAttrVal PaperSize
EnvelopeDL = Text
"27"
toAttrVal PaperSize
EnvelopeC5 = Text
"28"
toAttrVal PaperSize
EnvelopeC3 = Text
"29"
toAttrVal PaperSize
EnvelopeC4 = Text
"30"
toAttrVal PaperSize
EnvelopeC6 = Text
"31"
toAttrVal PaperSize
EnvelopeC65 = Text
"32"
toAttrVal PaperSize
EnvelopeB4 = Text
"33"
toAttrVal PaperSize
EnvelopeB5 = Text
"34"
toAttrVal PaperSize
EnvelopeB6 = Text
"35"
toAttrVal PaperSize
EnvelopeItaly = Text
"36"
toAttrVal PaperSize
EnvelopeMonarch = Text
"37"
toAttrVal PaperSize
Envelope6_3_4 = Text
"38"
toAttrVal PaperSize
PaperFanfoldUsStandard = Text
"39"
toAttrVal PaperSize
PaperFanfoldGermanStandard = Text
"40"
toAttrVal PaperSize
PaperFanfoldGermanLegal = Text
"41"
toAttrVal PaperSize
PaperIsoB4 = Text
"42"
toAttrVal PaperSize
PaperJapaneseDoublePostcard = Text
"43"
toAttrVal PaperSize
PaperStandard9_11 = Text
"44"
toAttrVal PaperSize
PaperStandard10_11 = Text
"45"
toAttrVal PaperSize
PaperStandard15_11 = Text
"46"
toAttrVal PaperSize
EnvelopeInvite = Text
"47"
toAttrVal PaperSize
PaperLetterExtra = Text
"50"
toAttrVal PaperSize
PaperLegalExtra = Text
"51"
toAttrVal PaperSize
PaperTabloidExtra = Text
"52"
toAttrVal PaperSize
PaperA4Extra = Text
"53"
toAttrVal PaperSize
PaperLetterTransverse = Text
"54"
toAttrVal PaperSize
PaperA4Transverse = Text
"55"
toAttrVal PaperSize
PaperLetterExtraTransverse = Text
"56"
toAttrVal PaperSize
PaperSuperA = Text
"57"
toAttrVal PaperSize
PaperSuperB = Text
"58"
toAttrVal PaperSize
PaperLetterPlus = Text
"59"
toAttrVal PaperSize
PaperA4Plus = Text
"60"
toAttrVal PaperSize
PaperA5Transverse = Text
"61"
toAttrVal PaperSize
PaperJisB5Transverse = Text
"62"
toAttrVal PaperSize
PaperA3Extra = Text
"63"
toAttrVal PaperSize
PaperA5Extra = Text
"64"
toAttrVal PaperSize
PaperIsoB5Extra = Text
"65"
toAttrVal PaperSize
PaperA2 = Text
"66"
toAttrVal PaperSize
PaperA3Transverse = Text
"67"
toAttrVal PaperSize
PaperA3ExtraTransverse = Text
"68"
instance FromCursor PageSetup where
fromCursor :: Cursor -> [PageSetup]
fromCursor Cursor
cur = do
Maybe PaperSize
_pageSetupPaperSize <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"paperSize" Cursor
cur
Maybe Text
_pageSetupPaperHeight <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"paperHeight" Cursor
cur
Maybe Text
_pageSetupPaperWidth <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"paperWidth" Cursor
cur
Maybe Int
_pageSetupScale <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"scale" Cursor
cur
Maybe Int
_pageSetupFirstPageNumber <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"firstPageNumber" Cursor
cur
Maybe Int
_pageSetupFitToWidth <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"fitToWidth" Cursor
cur
Maybe Int
_pageSetupFitToHeight <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"fitToHeight" Cursor
cur
Maybe PageOrder
_pageSetupPageOrder <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"pageOrder" Cursor
cur
Maybe Orientation
_pageSetupOrientation <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"orientation" Cursor
cur
Maybe Bool
_pageSetupUsePrinterDefaults <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"usePrinterDefaults" Cursor
cur
Maybe Bool
_pageSetupBlackAndWhite <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"blackAndWhite" Cursor
cur
Maybe Bool
_pageSetupDraft <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"draft" Cursor
cur
Maybe CellComments
_pageSetupCellComments <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"cellComments" Cursor
cur
Maybe Bool
_pageSetupUseFirstPageNumber <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"useFirstPageNumber" Cursor
cur
Maybe PrintErrors
_pageSetupErrors <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"errors" Cursor
cur
Maybe Int
_pageSetupHorizontalDpi <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"horizontalDpi" Cursor
cur
Maybe Int
_pageSetupVerticalDpi <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"verticalDpi" Cursor
cur
Maybe Int
_pageSetupCopies <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"copies" Cursor
cur
Maybe Text
_pageSetupId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"id" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup{Maybe Bool
Maybe Int
Maybe Text
Maybe PaperSize
Maybe PageOrder
Maybe Orientation
Maybe PrintErrors
Maybe CellComments
_pageSetupId :: Maybe Text
_pageSetupCopies :: Maybe Int
_pageSetupVerticalDpi :: Maybe Int
_pageSetupHorizontalDpi :: Maybe Int
_pageSetupErrors :: Maybe PrintErrors
_pageSetupUseFirstPageNumber :: Maybe Bool
_pageSetupCellComments :: Maybe CellComments
_pageSetupDraft :: Maybe Bool
_pageSetupBlackAndWhite :: Maybe Bool
_pageSetupUsePrinterDefaults :: Maybe Bool
_pageSetupOrientation :: Maybe Orientation
_pageSetupPageOrder :: Maybe PageOrder
_pageSetupFitToHeight :: Maybe Int
_pageSetupFitToWidth :: Maybe Int
_pageSetupFirstPageNumber :: Maybe Int
_pageSetupScale :: Maybe Int
_pageSetupPaperWidth :: Maybe Text
_pageSetupPaperHeight :: Maybe Text
_pageSetupPaperSize :: Maybe PaperSize
_pageSetupVerticalDpi :: Maybe Int
_pageSetupUsePrinterDefaults :: Maybe Bool
_pageSetupUseFirstPageNumber :: Maybe Bool
_pageSetupScale :: Maybe Int
_pageSetupPaperWidth :: Maybe Text
_pageSetupPaperSize :: Maybe PaperSize
_pageSetupPaperHeight :: Maybe Text
_pageSetupPageOrder :: Maybe PageOrder
_pageSetupOrientation :: Maybe Orientation
_pageSetupId :: Maybe Text
_pageSetupHorizontalDpi :: Maybe Int
_pageSetupFitToWidth :: Maybe Int
_pageSetupFitToHeight :: Maybe Int
_pageSetupFirstPageNumber :: Maybe Int
_pageSetupErrors :: Maybe PrintErrors
_pageSetupDraft :: Maybe Bool
_pageSetupCopies :: Maybe Int
_pageSetupCellComments :: Maybe CellComments
_pageSetupBlackAndWhite :: Maybe Bool
..}
instance FromXenoNode PageSetup where
fromXenoNode :: Node -> Either Text PageSetup
fromXenoNode Node
root =
forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Maybe PaperSize
_pageSetupPaperSize <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"paperSize"
Maybe Text
_pageSetupPaperHeight <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"paperHeight"
Maybe Text
_pageSetupPaperWidth <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"paperWidth"
Maybe Int
_pageSetupScale <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"scale"
Maybe Int
_pageSetupFirstPageNumber <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"firstPageNumber"
Maybe Int
_pageSetupFitToWidth <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"fitToWidth"
Maybe Int
_pageSetupFitToHeight <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"fitToHeight"
Maybe PageOrder
_pageSetupPageOrder <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"pageOrder"
Maybe Orientation
_pageSetupOrientation <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"orientation"
Maybe Bool
_pageSetupUsePrinterDefaults <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"usePrinterDefaults"
Maybe Bool
_pageSetupBlackAndWhite <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"blackAndWhite"
Maybe Bool
_pageSetupDraft <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"draft"
Maybe CellComments
_pageSetupCellComments <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"cellComments"
Maybe Bool
_pageSetupUseFirstPageNumber <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"useFirstPageNumber"
Maybe PrintErrors
_pageSetupErrors <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"errors"
Maybe Int
_pageSetupHorizontalDpi <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"horizontalDpi"
Maybe Int
_pageSetupVerticalDpi <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"verticalDpi"
Maybe Int
_pageSetupCopies <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"copies"
Maybe Text
_pageSetupId <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"id"
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup {Maybe Bool
Maybe Int
Maybe Text
Maybe PaperSize
Maybe PageOrder
Maybe Orientation
Maybe PrintErrors
Maybe CellComments
_pageSetupId :: Maybe Text
_pageSetupCopies :: Maybe Int
_pageSetupVerticalDpi :: Maybe Int
_pageSetupHorizontalDpi :: Maybe Int
_pageSetupErrors :: Maybe PrintErrors
_pageSetupUseFirstPageNumber :: Maybe Bool
_pageSetupCellComments :: Maybe CellComments
_pageSetupDraft :: Maybe Bool
_pageSetupBlackAndWhite :: Maybe Bool
_pageSetupUsePrinterDefaults :: Maybe Bool
_pageSetupOrientation :: Maybe Orientation
_pageSetupPageOrder :: Maybe PageOrder
_pageSetupFitToHeight :: Maybe Int
_pageSetupFitToWidth :: Maybe Int
_pageSetupFirstPageNumber :: Maybe Int
_pageSetupScale :: Maybe Int
_pageSetupPaperWidth :: Maybe Text
_pageSetupPaperHeight :: Maybe Text
_pageSetupPaperSize :: Maybe PaperSize
_pageSetupVerticalDpi :: Maybe Int
_pageSetupUsePrinterDefaults :: Maybe Bool
_pageSetupUseFirstPageNumber :: Maybe Bool
_pageSetupScale :: Maybe Int
_pageSetupPaperWidth :: Maybe Text
_pageSetupPaperSize :: Maybe PaperSize
_pageSetupPaperHeight :: Maybe Text
_pageSetupPageOrder :: Maybe PageOrder
_pageSetupOrientation :: Maybe Orientation
_pageSetupId :: Maybe Text
_pageSetupHorizontalDpi :: Maybe Int
_pageSetupFitToWidth :: Maybe Int
_pageSetupFitToHeight :: Maybe Int
_pageSetupFirstPageNumber :: Maybe Int
_pageSetupErrors :: Maybe PrintErrors
_pageSetupDraft :: Maybe Bool
_pageSetupCopies :: Maybe Int
_pageSetupCellComments :: Maybe CellComments
_pageSetupBlackAndWhite :: Maybe Bool
..}
instance FromAttrVal PaperSize where
fromAttrVal :: Reader PaperSize
fromAttrVal Text
"1" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLetter
fromAttrVal Text
"2" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLetterSmall
fromAttrVal Text
"3" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperTabloid
fromAttrVal Text
"4" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLedger
fromAttrVal Text
"5" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLegal
fromAttrVal Text
"6" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperStatement
fromAttrVal Text
"7" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperExecutive
fromAttrVal Text
"8" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA3
fromAttrVal Text
"9" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA4
fromAttrVal Text
"10" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA4Small
fromAttrVal Text
"11" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA5
fromAttrVal Text
"12" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperB4
fromAttrVal Text
"13" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperB5
fromAttrVal Text
"14" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperFolio
fromAttrVal Text
"15" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperQuarto
fromAttrVal Text
"16" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperStandard10_14
fromAttrVal Text
"17" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperStandard11_17
fromAttrVal Text
"18" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperNote
fromAttrVal Text
"19" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
Envelope9
fromAttrVal Text
"20" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
Envelope10
fromAttrVal Text
"21" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
Envelope11
fromAttrVal Text
"22" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
Envelope12
fromAttrVal Text
"23" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
Envelope14
fromAttrVal Text
"24" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperC
fromAttrVal Text
"25" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperD
fromAttrVal Text
"26" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperE
fromAttrVal Text
"27" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeDL
fromAttrVal Text
"28" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeC5
fromAttrVal Text
"29" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeC3
fromAttrVal Text
"30" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeC4
fromAttrVal Text
"31" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeC6
fromAttrVal Text
"32" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeC65
fromAttrVal Text
"33" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeB4
fromAttrVal Text
"34" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeB5
fromAttrVal Text
"35" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeB6
fromAttrVal Text
"36" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeItaly
fromAttrVal Text
"37" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeMonarch
fromAttrVal Text
"38" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
Envelope6_3_4
fromAttrVal Text
"39" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperFanfoldUsStandard
fromAttrVal Text
"40" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperFanfoldGermanStandard
fromAttrVal Text
"41" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperFanfoldGermanLegal
fromAttrVal Text
"42" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperIsoB4
fromAttrVal Text
"43" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperJapaneseDoublePostcard
fromAttrVal Text
"44" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperStandard9_11
fromAttrVal Text
"45" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperStandard10_11
fromAttrVal Text
"46" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperStandard15_11
fromAttrVal Text
"47" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
EnvelopeInvite
fromAttrVal Text
"50" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLetterExtra
fromAttrVal Text
"51" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLegalExtra
fromAttrVal Text
"52" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperTabloidExtra
fromAttrVal Text
"53" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA4Extra
fromAttrVal Text
"54" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLetterTransverse
fromAttrVal Text
"55" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA4Transverse
fromAttrVal Text
"56" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLetterExtraTransverse
fromAttrVal Text
"57" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperSuperA
fromAttrVal Text
"58" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperSuperB
fromAttrVal Text
"59" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperLetterPlus
fromAttrVal Text
"60" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA4Plus
fromAttrVal Text
"61" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA5Transverse
fromAttrVal Text
"62" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperJisB5Transverse
fromAttrVal Text
"63" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA3Extra
fromAttrVal Text
"64" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA5Extra
fromAttrVal Text
"65" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperIsoB5Extra
fromAttrVal Text
"66" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA2
fromAttrVal Text
"67" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA3Transverse
fromAttrVal Text
"68" = forall a. a -> Either String (a, Text)
readSuccess PaperSize
PaperA3ExtraTransverse
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"PaperSize" Text
t
instance FromAttrBs PaperSize where
fromAttrBs :: ByteString -> Either Text PaperSize
fromAttrBs ByteString
"1" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLetter
fromAttrBs ByteString
"2" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLetterSmall
fromAttrBs ByteString
"3" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperTabloid
fromAttrBs ByteString
"4" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLedger
fromAttrBs ByteString
"5" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLegal
fromAttrBs ByteString
"6" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperStatement
fromAttrBs ByteString
"7" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperExecutive
fromAttrBs ByteString
"8" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA3
fromAttrBs ByteString
"9" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA4
fromAttrBs ByteString
"10" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA4Small
fromAttrBs ByteString
"11" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA5
fromAttrBs ByteString
"12" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperB4
fromAttrBs ByteString
"13" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperB5
fromAttrBs ByteString
"14" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperFolio
fromAttrBs ByteString
"15" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperQuarto
fromAttrBs ByteString
"16" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperStandard10_14
fromAttrBs ByteString
"17" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperStandard11_17
fromAttrBs ByteString
"18" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperNote
fromAttrBs ByteString
"19" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
Envelope9
fromAttrBs ByteString
"20" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
Envelope10
fromAttrBs ByteString
"21" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
Envelope11
fromAttrBs ByteString
"22" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
Envelope12
fromAttrBs ByteString
"23" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
Envelope14
fromAttrBs ByteString
"24" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperC
fromAttrBs ByteString
"25" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperD
fromAttrBs ByteString
"26" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperE
fromAttrBs ByteString
"27" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeDL
fromAttrBs ByteString
"28" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeC5
fromAttrBs ByteString
"29" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeC3
fromAttrBs ByteString
"30" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeC4
fromAttrBs ByteString
"31" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeC6
fromAttrBs ByteString
"32" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeC65
fromAttrBs ByteString
"33" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeB4
fromAttrBs ByteString
"34" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeB5
fromAttrBs ByteString
"35" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeB6
fromAttrBs ByteString
"36" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeItaly
fromAttrBs ByteString
"37" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeMonarch
fromAttrBs ByteString
"38" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
Envelope6_3_4
fromAttrBs ByteString
"39" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperFanfoldUsStandard
fromAttrBs ByteString
"40" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperFanfoldGermanStandard
fromAttrBs ByteString
"41" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperFanfoldGermanLegal
fromAttrBs ByteString
"42" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperIsoB4
fromAttrBs ByteString
"43" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperJapaneseDoublePostcard
fromAttrBs ByteString
"44" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperStandard9_11
fromAttrBs ByteString
"45" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperStandard10_11
fromAttrBs ByteString
"46" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperStandard15_11
fromAttrBs ByteString
"47" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
EnvelopeInvite
fromAttrBs ByteString
"50" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLetterExtra
fromAttrBs ByteString
"51" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLegalExtra
fromAttrBs ByteString
"52" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperTabloidExtra
fromAttrBs ByteString
"53" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA4Extra
fromAttrBs ByteString
"54" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLetterTransverse
fromAttrBs ByteString
"55" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA4Transverse
fromAttrBs ByteString
"56" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLetterExtraTransverse
fromAttrBs ByteString
"57" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperSuperA
fromAttrBs ByteString
"58" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperSuperB
fromAttrBs ByteString
"59" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperLetterPlus
fromAttrBs ByteString
"60" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA4Plus
fromAttrBs ByteString
"61" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA5Transverse
fromAttrBs ByteString
"62" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperJisB5Transverse
fromAttrBs ByteString
"63" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA3Extra
fromAttrBs ByteString
"64" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA5Extra
fromAttrBs ByteString
"65" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperIsoB5Extra
fromAttrBs ByteString
"66" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA2
fromAttrBs ByteString
"67" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA3Transverse
fromAttrBs ByteString
"68" = forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
PaperA3ExtraTransverse
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"PaperSize" ByteString
x
instance FromAttrVal PageOrder where
fromAttrVal :: Reader PageOrder
fromAttrVal Text
"downThenOver" = forall a. a -> Either String (a, Text)
readSuccess PageOrder
PageOrderDownThenOver
fromAttrVal Text
"overThenDown" = forall a. a -> Either String (a, Text)
readSuccess PageOrder
PageOrderOverThenDown
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"PageOrder" Text
t
instance FromAttrBs PageOrder where
fromAttrBs :: ByteString -> Either Text PageOrder
fromAttrBs ByteString
"downThenOver" = forall (m :: * -> *) a. Monad m => a -> m a
return PageOrder
PageOrderDownThenOver
fromAttrBs ByteString
"overThenDown" = forall (m :: * -> *) a. Monad m => a -> m a
return PageOrder
PageOrderOverThenDown
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"PageOrder" ByteString
x
instance FromAttrVal CellComments where
fromAttrVal :: Reader CellComments
fromAttrVal Text
"none" = forall a. a -> Either String (a, Text)
readSuccess CellComments
CellCommentsNone
fromAttrVal Text
"asDisplayed" = forall a. a -> Either String (a, Text)
readSuccess CellComments
CellCommentsAsDisplayed
fromAttrVal Text
"atEnd" = forall a. a -> Either String (a, Text)
readSuccess CellComments
CellCommentsAtEnd
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"CellComments" Text
t
instance FromAttrBs CellComments where
fromAttrBs :: ByteString -> Either Text CellComments
fromAttrBs ByteString
"none" = forall (m :: * -> *) a. Monad m => a -> m a
return CellComments
CellCommentsNone
fromAttrBs ByteString
"asDisplayed" = forall (m :: * -> *) a. Monad m => a -> m a
return CellComments
CellCommentsAsDisplayed
fromAttrBs ByteString
"atEnd" = forall (m :: * -> *) a. Monad m => a -> m a
return CellComments
CellCommentsAtEnd
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"CellComments" ByteString
x
instance FromAttrVal PrintErrors where
fromAttrVal :: Reader PrintErrors
fromAttrVal Text
"displayed" = forall a. a -> Either String (a, Text)
readSuccess PrintErrors
PrintErrorsDisplayed
fromAttrVal Text
"blank" = forall a. a -> Either String (a, Text)
readSuccess PrintErrors
PrintErrorsBlank
fromAttrVal Text
"dash" = forall a. a -> Either String (a, Text)
readSuccess PrintErrors
PrintErrorsDash
fromAttrVal Text
"NA" = forall a. a -> Either String (a, Text)
readSuccess PrintErrors
PrintErrorsNA
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"PrintErrors" Text
t
instance FromAttrBs PrintErrors where
fromAttrBs :: ByteString -> Either Text PrintErrors
fromAttrBs ByteString
"displayed" = forall (m :: * -> *) a. Monad m => a -> m a
return PrintErrors
PrintErrorsDisplayed
fromAttrBs ByteString
"blank" = forall (m :: * -> *) a. Monad m => a -> m a
return PrintErrors
PrintErrorsBlank
fromAttrBs ByteString
"dash" = forall (m :: * -> *) a. Monad m => a -> m a
return PrintErrors
PrintErrorsDash
fromAttrBs ByteString
"NA" = forall (m :: * -> *) a. Monad m => a -> m a
return PrintErrors
PrintErrorsNA
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"PrintErrors" ByteString
x
instance FromAttrVal Orientation where
fromAttrVal :: Reader Orientation
fromAttrVal Text
"default" = forall a. a -> Either String (a, Text)
readSuccess Orientation
OrientationDefault
fromAttrVal Text
"portrait" = forall a. a -> Either String (a, Text)
readSuccess Orientation
OrientationPortrait
fromAttrVal Text
"landscape" = forall a. a -> Either String (a, Text)
readSuccess Orientation
OrientationLandscape
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"Orientation" Text
t
instance FromAttrBs Orientation where
fromAttrBs :: ByteString -> Either Text Orientation
fromAttrBs ByteString
"default" = forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
OrientationDefault
fromAttrBs ByteString
"portrait" = forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
OrientationPortrait
fromAttrBs ByteString
"landscape" = forall (m :: * -> *) a. Monad m => a -> m a
return Orientation
OrientationLandscape
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"Orientation" ByteString
x