{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Types.SheetViews (
SheetView(..)
, Selection(..)
, Pane(..)
, SheetViewType(..)
, PaneType(..)
, PaneState(..)
, sheetViewColorId
, sheetViewDefaultGridColor
, sheetViewRightToLeft
, sheetViewShowFormulas
, sheetViewShowGridLines
, sheetViewShowOutlineSymbols
, sheetViewShowRowColHeaders
, sheetViewShowRuler
, sheetViewShowWhiteSpace
, sheetViewShowZeros
, sheetViewTabSelected
, sheetViewTopLeftCell
, sheetViewType
, sheetViewWindowProtection
, sheetViewWorkbookViewId
, sheetViewZoomScale
, sheetViewZoomScaleNormal
, sheetViewZoomScalePageLayoutView
, sheetViewZoomScaleSheetLayoutView
, sheetViewPane
, sheetViewSelection
, selectionActiveCell
, selectionActiveCellId
, selectionPane
, selectionSqref
, paneActivePane
, paneState
, paneTopLeftCell
, paneXSplit
, paneYSplit
) where
import GHC.Generics (Generic)
#ifdef USE_MICROLENS
import Lens.Micro.TH (makeLenses)
#else
import Control.Lens (makeLenses)
#endif
import Control.DeepSeq (NFData)
import Data.Default
import Data.Maybe (catMaybes, maybeToList, listToMaybe)
import Text.XML
import Text.XML.Cursor
import qualified Data.Map as Map
import Codec.Xlsx.Types.Common
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Writer.Internal
data SheetView = SheetView {
SheetView -> Maybe Int
_sheetViewColorId :: Maybe Int
, SheetView -> Maybe Bool
_sheetViewDefaultGridColor :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewRightToLeft :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewShowFormulas :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewShowGridLines :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewShowOutlineSymbols :: Maybe Bool
, :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewShowRuler :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewShowWhiteSpace :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewShowZeros :: Maybe Bool
, SheetView -> Maybe Bool
_sheetViewTabSelected :: Maybe Bool
, SheetView -> Maybe CellRef
_sheetViewTopLeftCell :: Maybe CellRef
, SheetView -> Maybe SheetViewType
_sheetViewType :: Maybe SheetViewType
, SheetView -> Maybe Bool
_sheetViewWindowProtection :: Maybe Bool
, SheetView -> Int
_sheetViewWorkbookViewId :: Int
, SheetView -> Maybe Int
_sheetViewZoomScale :: Maybe Int
, SheetView -> Maybe Int
_sheetViewZoomScaleNormal :: Maybe Int
, SheetView -> Maybe Int
_sheetViewZoomScalePageLayoutView :: Maybe Int
, SheetView -> Maybe Int
_sheetViewZoomScaleSheetLayoutView :: Maybe Int
, SheetView -> Maybe Pane
_sheetViewPane :: Maybe Pane
, SheetView -> [Selection]
_sheetViewSelection :: [Selection]
}
deriving (SheetView -> SheetView -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SheetView -> SheetView -> Bool
$c/= :: SheetView -> SheetView -> Bool
== :: SheetView -> SheetView -> Bool
$c== :: SheetView -> SheetView -> Bool
Eq, Eq SheetView
SheetView -> SheetView -> Bool
SheetView -> SheetView -> Ordering
SheetView -> SheetView -> SheetView
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 :: SheetView -> SheetView -> SheetView
$cmin :: SheetView -> SheetView -> SheetView
max :: SheetView -> SheetView -> SheetView
$cmax :: SheetView -> SheetView -> SheetView
>= :: SheetView -> SheetView -> Bool
$c>= :: SheetView -> SheetView -> Bool
> :: SheetView -> SheetView -> Bool
$c> :: SheetView -> SheetView -> Bool
<= :: SheetView -> SheetView -> Bool
$c<= :: SheetView -> SheetView -> Bool
< :: SheetView -> SheetView -> Bool
$c< :: SheetView -> SheetView -> Bool
compare :: SheetView -> SheetView -> Ordering
$ccompare :: SheetView -> SheetView -> Ordering
Ord, Int -> SheetView -> ShowS
[SheetView] -> ShowS
SheetView -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SheetView] -> ShowS
$cshowList :: [SheetView] -> ShowS
show :: SheetView -> String
$cshow :: SheetView -> String
showsPrec :: Int -> SheetView -> ShowS
$cshowsPrec :: Int -> SheetView -> ShowS
Show, forall x. Rep SheetView x -> SheetView
forall x. SheetView -> Rep SheetView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SheetView x -> SheetView
$cfrom :: forall x. SheetView -> Rep SheetView x
Generic)
instance NFData SheetView
data Selection = Selection {
Selection -> Maybe CellRef
_selectionActiveCell :: Maybe CellRef
, Selection -> Maybe Int
_selectionActiveCellId :: Maybe Int
, Selection -> Maybe PaneType
_selectionPane :: Maybe PaneType
, Selection -> Maybe SqRef
_selectionSqref :: Maybe SqRef
}
deriving (Selection -> Selection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Selection -> Selection -> Bool
$c/= :: Selection -> Selection -> Bool
== :: Selection -> Selection -> Bool
$c== :: Selection -> Selection -> Bool
Eq, Eq Selection
Selection -> Selection -> Bool
Selection -> Selection -> Ordering
Selection -> Selection -> Selection
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 :: Selection -> Selection -> Selection
$cmin :: Selection -> Selection -> Selection
max :: Selection -> Selection -> Selection
$cmax :: Selection -> Selection -> Selection
>= :: Selection -> Selection -> Bool
$c>= :: Selection -> Selection -> Bool
> :: Selection -> Selection -> Bool
$c> :: Selection -> Selection -> Bool
<= :: Selection -> Selection -> Bool
$c<= :: Selection -> Selection -> Bool
< :: Selection -> Selection -> Bool
$c< :: Selection -> Selection -> Bool
compare :: Selection -> Selection -> Ordering
$ccompare :: Selection -> Selection -> Ordering
Ord, Int -> Selection -> ShowS
[Selection] -> ShowS
Selection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Selection] -> ShowS
$cshowList :: [Selection] -> ShowS
show :: Selection -> String
$cshow :: Selection -> String
showsPrec :: Int -> Selection -> ShowS
$cshowsPrec :: Int -> Selection -> ShowS
Show, forall x. Rep Selection x -> Selection
forall x. Selection -> Rep Selection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Selection x -> Selection
$cfrom :: forall x. Selection -> Rep Selection x
Generic)
instance NFData Selection
data Pane = Pane {
Pane -> Maybe PaneType
_paneActivePane :: Maybe PaneType
, Pane -> Maybe PaneState
_paneState :: Maybe PaneState
, Pane -> Maybe CellRef
_paneTopLeftCell :: Maybe CellRef
, Pane -> Maybe Double
_paneXSplit :: Maybe Double
, Pane -> Maybe Double
_paneYSplit :: Maybe Double
}
deriving (Pane -> Pane -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pane -> Pane -> Bool
$c/= :: Pane -> Pane -> Bool
== :: Pane -> Pane -> Bool
$c== :: Pane -> Pane -> Bool
Eq, Eq Pane
Pane -> Pane -> Bool
Pane -> Pane -> Ordering
Pane -> Pane -> Pane
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 :: Pane -> Pane -> Pane
$cmin :: Pane -> Pane -> Pane
max :: Pane -> Pane -> Pane
$cmax :: Pane -> Pane -> Pane
>= :: Pane -> Pane -> Bool
$c>= :: Pane -> Pane -> Bool
> :: Pane -> Pane -> Bool
$c> :: Pane -> Pane -> Bool
<= :: Pane -> Pane -> Bool
$c<= :: Pane -> Pane -> Bool
< :: Pane -> Pane -> Bool
$c< :: Pane -> Pane -> Bool
compare :: Pane -> Pane -> Ordering
$ccompare :: Pane -> Pane -> Ordering
Ord, Int -> Pane -> ShowS
[Pane] -> ShowS
Pane -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pane] -> ShowS
$cshowList :: [Pane] -> ShowS
show :: Pane -> String
$cshow :: Pane -> String
showsPrec :: Int -> Pane -> ShowS
$cshowsPrec :: Int -> Pane -> ShowS
Show, forall x. Rep Pane x -> Pane
forall x. Pane -> Rep Pane x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Pane x -> Pane
$cfrom :: forall x. Pane -> Rep Pane x
Generic)
instance NFData Pane
data SheetViewType =
SheetViewTypeNormal
| SheetViewTypePageBreakPreview
| SheetViewTypePageLayout
deriving (SheetViewType -> SheetViewType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SheetViewType -> SheetViewType -> Bool
$c/= :: SheetViewType -> SheetViewType -> Bool
== :: SheetViewType -> SheetViewType -> Bool
$c== :: SheetViewType -> SheetViewType -> Bool
Eq, Eq SheetViewType
SheetViewType -> SheetViewType -> Bool
SheetViewType -> SheetViewType -> Ordering
SheetViewType -> SheetViewType -> SheetViewType
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 :: SheetViewType -> SheetViewType -> SheetViewType
$cmin :: SheetViewType -> SheetViewType -> SheetViewType
max :: SheetViewType -> SheetViewType -> SheetViewType
$cmax :: SheetViewType -> SheetViewType -> SheetViewType
>= :: SheetViewType -> SheetViewType -> Bool
$c>= :: SheetViewType -> SheetViewType -> Bool
> :: SheetViewType -> SheetViewType -> Bool
$c> :: SheetViewType -> SheetViewType -> Bool
<= :: SheetViewType -> SheetViewType -> Bool
$c<= :: SheetViewType -> SheetViewType -> Bool
< :: SheetViewType -> SheetViewType -> Bool
$c< :: SheetViewType -> SheetViewType -> Bool
compare :: SheetViewType -> SheetViewType -> Ordering
$ccompare :: SheetViewType -> SheetViewType -> Ordering
Ord, Int -> SheetViewType -> ShowS
[SheetViewType] -> ShowS
SheetViewType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SheetViewType] -> ShowS
$cshowList :: [SheetViewType] -> ShowS
show :: SheetViewType -> String
$cshow :: SheetViewType -> String
showsPrec :: Int -> SheetViewType -> ShowS
$cshowsPrec :: Int -> SheetViewType -> ShowS
Show, forall x. Rep SheetViewType x -> SheetViewType
forall x. SheetViewType -> Rep SheetViewType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SheetViewType x -> SheetViewType
$cfrom :: forall x. SheetViewType -> Rep SheetViewType x
Generic)
instance NFData SheetViewType
data PaneType =
PaneTypeBottomLeft
| PaneTypeBottomRight
| PaneTypeTopLeft
| PaneTypeTopRight
deriving (PaneType -> PaneType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaneType -> PaneType -> Bool
$c/= :: PaneType -> PaneType -> Bool
== :: PaneType -> PaneType -> Bool
$c== :: PaneType -> PaneType -> Bool
Eq, Eq PaneType
PaneType -> PaneType -> Bool
PaneType -> PaneType -> Ordering
PaneType -> PaneType -> PaneType
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 :: PaneType -> PaneType -> PaneType
$cmin :: PaneType -> PaneType -> PaneType
max :: PaneType -> PaneType -> PaneType
$cmax :: PaneType -> PaneType -> PaneType
>= :: PaneType -> PaneType -> Bool
$c>= :: PaneType -> PaneType -> Bool
> :: PaneType -> PaneType -> Bool
$c> :: PaneType -> PaneType -> Bool
<= :: PaneType -> PaneType -> Bool
$c<= :: PaneType -> PaneType -> Bool
< :: PaneType -> PaneType -> Bool
$c< :: PaneType -> PaneType -> Bool
compare :: PaneType -> PaneType -> Ordering
$ccompare :: PaneType -> PaneType -> Ordering
Ord, Int -> PaneType -> ShowS
[PaneType] -> ShowS
PaneType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaneType] -> ShowS
$cshowList :: [PaneType] -> ShowS
show :: PaneType -> String
$cshow :: PaneType -> String
showsPrec :: Int -> PaneType -> ShowS
$cshowsPrec :: Int -> PaneType -> ShowS
Show, forall x. Rep PaneType x -> PaneType
forall x. PaneType -> Rep PaneType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PaneType x -> PaneType
$cfrom :: forall x. PaneType -> Rep PaneType x
Generic)
instance NFData PaneType
data PaneState =
PaneStateFrozen
| PaneStateFrozenSplit
| PaneStateSplit
deriving (PaneState -> PaneState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaneState -> PaneState -> Bool
$c/= :: PaneState -> PaneState -> Bool
== :: PaneState -> PaneState -> Bool
$c== :: PaneState -> PaneState -> Bool
Eq, Eq PaneState
PaneState -> PaneState -> Bool
PaneState -> PaneState -> Ordering
PaneState -> PaneState -> PaneState
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 :: PaneState -> PaneState -> PaneState
$cmin :: PaneState -> PaneState -> PaneState
max :: PaneState -> PaneState -> PaneState
$cmax :: PaneState -> PaneState -> PaneState
>= :: PaneState -> PaneState -> Bool
$c>= :: PaneState -> PaneState -> Bool
> :: PaneState -> PaneState -> Bool
$c> :: PaneState -> PaneState -> Bool
<= :: PaneState -> PaneState -> Bool
$c<= :: PaneState -> PaneState -> Bool
< :: PaneState -> PaneState -> Bool
$c< :: PaneState -> PaneState -> Bool
compare :: PaneState -> PaneState -> Ordering
$ccompare :: PaneState -> PaneState -> Ordering
Ord, Int -> PaneState -> ShowS
[PaneState] -> ShowS
PaneState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaneState] -> ShowS
$cshowList :: [PaneState] -> ShowS
show :: PaneState -> String
$cshow :: PaneState -> String
showsPrec :: Int -> PaneState -> ShowS
$cshowsPrec :: Int -> PaneState -> ShowS
Show, forall x. Rep PaneState x -> PaneState
forall x. PaneState -> Rep PaneState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PaneState x -> PaneState
$cfrom :: forall x. PaneState -> Rep PaneState x
Generic)
instance NFData PaneState
makeLenses ''Selection
makeLenses ''Pane
instance Default SheetView where
def :: SheetView
def = SheetView {
_sheetViewColorId :: Maybe Int
_sheetViewColorId = forall a. Maybe a
Nothing
, _sheetViewDefaultGridColor :: Maybe Bool
_sheetViewDefaultGridColor = forall a. Maybe a
Nothing
, _sheetViewRightToLeft :: Maybe Bool
_sheetViewRightToLeft = forall a. Maybe a
Nothing
, _sheetViewShowFormulas :: Maybe Bool
_sheetViewShowFormulas = forall a. Maybe a
Nothing
, _sheetViewShowGridLines :: Maybe Bool
_sheetViewShowGridLines = forall a. Maybe a
Nothing
, _sheetViewShowOutlineSymbols :: Maybe Bool
_sheetViewShowOutlineSymbols = forall a. Maybe a
Nothing
, _sheetViewShowRowColHeaders :: Maybe Bool
_sheetViewShowRowColHeaders = forall a. Maybe a
Nothing
, _sheetViewShowRuler :: Maybe Bool
_sheetViewShowRuler = forall a. Maybe a
Nothing
, _sheetViewShowWhiteSpace :: Maybe Bool
_sheetViewShowWhiteSpace = forall a. Maybe a
Nothing
, _sheetViewShowZeros :: Maybe Bool
_sheetViewShowZeros = forall a. Maybe a
Nothing
, _sheetViewTabSelected :: Maybe Bool
_sheetViewTabSelected = forall a. Maybe a
Nothing
, _sheetViewTopLeftCell :: Maybe CellRef
_sheetViewTopLeftCell = forall a. Maybe a
Nothing
, _sheetViewType :: Maybe SheetViewType
_sheetViewType = forall a. Maybe a
Nothing
, _sheetViewWindowProtection :: Maybe Bool
_sheetViewWindowProtection = forall a. Maybe a
Nothing
, _sheetViewWorkbookViewId :: Int
_sheetViewWorkbookViewId = Int
0
, _sheetViewZoomScale :: Maybe Int
_sheetViewZoomScale = forall a. Maybe a
Nothing
, _sheetViewZoomScaleNormal :: Maybe Int
_sheetViewZoomScaleNormal = forall a. Maybe a
Nothing
, _sheetViewZoomScalePageLayoutView :: Maybe Int
_sheetViewZoomScalePageLayoutView = forall a. Maybe a
Nothing
, _sheetViewZoomScaleSheetLayoutView :: Maybe Int
_sheetViewZoomScaleSheetLayoutView = forall a. Maybe a
Nothing
, _sheetViewPane :: Maybe Pane
_sheetViewPane = forall a. Maybe a
Nothing
, _sheetViewSelection :: [Selection]
_sheetViewSelection = []
}
instance Default Selection where
def :: Selection
def = Selection {
_selectionActiveCell :: Maybe CellRef
_selectionActiveCell = forall a. Maybe a
Nothing
, _selectionActiveCellId :: Maybe Int
_selectionActiveCellId = forall a. Maybe a
Nothing
, _selectionPane :: Maybe PaneType
_selectionPane = forall a. Maybe a
Nothing
, _selectionSqref :: Maybe SqRef
_selectionSqref = forall a. Maybe a
Nothing
}
instance Default Pane where
def :: Pane
def = Pane {
_paneActivePane :: Maybe PaneType
_paneActivePane = forall a. Maybe a
Nothing
, _paneState :: Maybe PaneState
_paneState = forall a. Maybe a
Nothing
, _paneTopLeftCell :: Maybe CellRef
_paneTopLeftCell = forall a. Maybe a
Nothing
, _paneXSplit :: Maybe Double
_paneXSplit = forall a. Maybe a
Nothing
, _paneYSplit :: Maybe Double
_paneYSplit = forall a. Maybe a
Nothing
}
instance ToElement SheetView where
toElement :: Name -> SheetView -> Element
toElement Name
nm SheetView{Int
[Selection]
Maybe Bool
Maybe Int
Maybe CellRef
Maybe SheetViewType
Maybe Pane
_sheetViewSelection :: [Selection]
_sheetViewPane :: Maybe Pane
_sheetViewZoomScaleSheetLayoutView :: Maybe Int
_sheetViewZoomScalePageLayoutView :: Maybe Int
_sheetViewZoomScaleNormal :: Maybe Int
_sheetViewZoomScale :: Maybe Int
_sheetViewWorkbookViewId :: Int
_sheetViewWindowProtection :: Maybe Bool
_sheetViewType :: Maybe SheetViewType
_sheetViewTopLeftCell :: Maybe CellRef
_sheetViewTabSelected :: Maybe Bool
_sheetViewShowZeros :: Maybe Bool
_sheetViewShowWhiteSpace :: Maybe Bool
_sheetViewShowRuler :: Maybe Bool
_sheetViewShowRowColHeaders :: Maybe Bool
_sheetViewShowOutlineSymbols :: Maybe Bool
_sheetViewShowGridLines :: Maybe Bool
_sheetViewShowFormulas :: Maybe Bool
_sheetViewRightToLeft :: Maybe Bool
_sheetViewDefaultGridColor :: Maybe Bool
_sheetViewColorId :: Maybe Int
_sheetViewSelection :: SheetView -> [Selection]
_sheetViewPane :: SheetView -> Maybe Pane
_sheetViewZoomScaleSheetLayoutView :: SheetView -> Maybe Int
_sheetViewZoomScalePageLayoutView :: SheetView -> Maybe Int
_sheetViewZoomScaleNormal :: SheetView -> Maybe Int
_sheetViewZoomScale :: SheetView -> Maybe Int
_sheetViewWorkbookViewId :: SheetView -> Int
_sheetViewWindowProtection :: SheetView -> Maybe Bool
_sheetViewType :: SheetView -> Maybe SheetViewType
_sheetViewTopLeftCell :: SheetView -> Maybe CellRef
_sheetViewTabSelected :: SheetView -> Maybe Bool
_sheetViewShowZeros :: SheetView -> Maybe Bool
_sheetViewShowWhiteSpace :: SheetView -> Maybe Bool
_sheetViewShowRuler :: SheetView -> Maybe Bool
_sheetViewShowRowColHeaders :: SheetView -> Maybe Bool
_sheetViewShowOutlineSymbols :: SheetView -> Maybe Bool
_sheetViewShowGridLines :: SheetView -> Maybe Bool
_sheetViewShowFormulas :: SheetView -> Maybe Bool
_sheetViewRightToLeft :: SheetView -> Maybe Bool
_sheetViewDefaultGridColor :: SheetView -> Maybe Bool
_sheetViewColorId :: SheetView -> Maybe Int
..} = 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 (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ [
forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"pane") (forall a. Maybe a -> [a]
maybeToList Maybe Pane
_sheetViewPane)
, forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"selection") [Selection]
_sheetViewSelection
]
, 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
"windowProtection" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewWindowProtection
, Name
"showFormulas" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewShowFormulas
, Name
"showGridLines" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewShowGridLines
, Name
"showRowColHeaders" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewShowRowColHeaders
, Name
"showZeros" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewShowZeros
, Name
"rightToLeft" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewRightToLeft
, Name
"tabSelected" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewTabSelected
, Name
"showRuler" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewShowRuler
, Name
"showOutlineSymbols" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewShowOutlineSymbols
, Name
"defaultGridColor" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewDefaultGridColor
, Name
"showWhiteSpace" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Bool
_sheetViewShowWhiteSpace
, Name
"view" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe SheetViewType
_sheetViewType
, Name
"topLeftCell" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe CellRef
_sheetViewTopLeftCell
, Name
"colorId" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_sheetViewColorId
, Name
"zoomScale" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_sheetViewZoomScale
, Name
"zoomScaleNormal" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_sheetViewZoomScaleNormal
, Name
"zoomScaleSheetLayoutView" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_sheetViewZoomScaleSheetLayoutView
, Name
"zoomScalePageLayoutView" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_sheetViewZoomScalePageLayoutView
, forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Name
"workbookViewId" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
_sheetViewWorkbookViewId
]
}
instance ToElement Selection where
toElement :: Name -> Selection -> Element
toElement Name
nm Selection{Maybe Int
Maybe SqRef
Maybe CellRef
Maybe PaneType
_selectionSqref :: Maybe SqRef
_selectionPane :: Maybe PaneType
_selectionActiveCellId :: Maybe Int
_selectionActiveCell :: Maybe CellRef
_selectionSqref :: Selection -> Maybe SqRef
_selectionPane :: Selection -> Maybe PaneType
_selectionActiveCellId :: Selection -> Maybe Int
_selectionActiveCell :: Selection -> Maybe CellRef
..} = 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
"pane" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PaneType
_selectionPane
, Name
"activeCell" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe CellRef
_selectionActiveCell
, Name
"activeCellId" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Int
_selectionActiveCellId
, Name
"sqref" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe SqRef
_selectionSqref
]
}
instance ToElement Pane where
toElement :: Name -> Pane -> Element
toElement Name
nm Pane{Maybe Double
Maybe CellRef
Maybe PaneState
Maybe PaneType
_paneYSplit :: Maybe Double
_paneXSplit :: Maybe Double
_paneTopLeftCell :: Maybe CellRef
_paneState :: Maybe PaneState
_paneActivePane :: Maybe PaneType
_paneYSplit :: Pane -> Maybe Double
_paneXSplit :: Pane -> Maybe Double
_paneTopLeftCell :: Pane -> Maybe CellRef
_paneState :: Pane -> Maybe PaneState
_paneActivePane :: Pane -> Maybe PaneType
..} = 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
"xSplit" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Double
_paneXSplit
, Name
"ySplit" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Double
_paneYSplit
, Name
"topLeftCell" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe CellRef
_paneTopLeftCell
, Name
"activePane" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PaneType
_paneActivePane
, Name
"state" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PaneState
_paneState
]
}
instance ToAttrVal SheetViewType where
toAttrVal :: SheetViewType -> Text
toAttrVal SheetViewType
SheetViewTypeNormal = Text
"normal"
toAttrVal SheetViewType
SheetViewTypePageBreakPreview = Text
"pageBreakPreview"
toAttrVal SheetViewType
SheetViewTypePageLayout = Text
"pageLayout"
instance ToAttrVal PaneType where
toAttrVal :: PaneType -> Text
toAttrVal PaneType
PaneTypeBottomRight = Text
"bottomRight"
toAttrVal PaneType
PaneTypeTopRight = Text
"topRight"
toAttrVal PaneType
PaneTypeBottomLeft = Text
"bottomLeft"
toAttrVal PaneType
PaneTypeTopLeft = Text
"topLeft"
instance ToAttrVal PaneState where
toAttrVal :: PaneState -> Text
toAttrVal PaneState
PaneStateSplit = Text
"split"
toAttrVal PaneState
PaneStateFrozen = Text
"frozen"
toAttrVal PaneState
PaneStateFrozenSplit = Text
"frozenSplit"
instance FromCursor SheetView where
fromCursor :: Cursor -> [SheetView]
fromCursor Cursor
cur = do
Maybe Bool
_sheetViewWindowProtection <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"windowProtection" Cursor
cur
Maybe Bool
_sheetViewShowFormulas <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"showFormulas" Cursor
cur
Maybe Bool
_sheetViewShowGridLines <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"showGridLines" Cursor
cur
Maybe Bool
_sheetViewShowRowColHeaders <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"showRowColHeaders"Cursor
cur
Maybe Bool
_sheetViewShowZeros <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"showZeros" Cursor
cur
Maybe Bool
_sheetViewRightToLeft <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"rightToLeft" Cursor
cur
Maybe Bool
_sheetViewTabSelected <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"tabSelected" Cursor
cur
Maybe Bool
_sheetViewShowRuler <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"showRuler" Cursor
cur
Maybe Bool
_sheetViewShowOutlineSymbols <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"showOutlineSymbols" Cursor
cur
Maybe Bool
_sheetViewDefaultGridColor <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"defaultGridColor" Cursor
cur
Maybe Bool
_sheetViewShowWhiteSpace <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"showWhiteSpace" Cursor
cur
Maybe SheetViewType
_sheetViewType <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"view" Cursor
cur
Maybe CellRef
_sheetViewTopLeftCell <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"topLeftCell" Cursor
cur
Maybe Int
_sheetViewColorId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"colorId" Cursor
cur
Maybe Int
_sheetViewZoomScale <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"zoomScale" Cursor
cur
Maybe Int
_sheetViewZoomScaleNormal <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"zoomScaleNormal" Cursor
cur
Maybe Int
_sheetViewZoomScaleSheetLayoutView <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"zoomScaleSheetLayoutView" Cursor
cur
Maybe Int
_sheetViewZoomScalePageLayoutView <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"zoomScalePageLayoutView" Cursor
cur
Int
_sheetViewWorkbookViewId <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"workbookViewId" Cursor
cur
let _sheetViewPane :: Maybe Pane
_sheetViewPane = forall a. [a] -> Maybe a
listToMaybe forall a b. (a -> b) -> a -> b
$ Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"pane") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
_sheetViewSelection :: [Selection]
_sheetViewSelection = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"selection") 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 SheetView{Int
[Selection]
Maybe Bool
Maybe Int
Maybe CellRef
Maybe SheetViewType
Maybe Pane
_sheetViewSelection :: [Selection]
_sheetViewPane :: Maybe Pane
_sheetViewWorkbookViewId :: Int
_sheetViewZoomScalePageLayoutView :: Maybe Int
_sheetViewZoomScaleSheetLayoutView :: Maybe Int
_sheetViewZoomScaleNormal :: Maybe Int
_sheetViewZoomScale :: Maybe Int
_sheetViewColorId :: Maybe Int
_sheetViewTopLeftCell :: Maybe CellRef
_sheetViewType :: Maybe SheetViewType
_sheetViewShowWhiteSpace :: Maybe Bool
_sheetViewDefaultGridColor :: Maybe Bool
_sheetViewShowOutlineSymbols :: Maybe Bool
_sheetViewShowRuler :: Maybe Bool
_sheetViewTabSelected :: Maybe Bool
_sheetViewRightToLeft :: Maybe Bool
_sheetViewShowZeros :: Maybe Bool
_sheetViewShowRowColHeaders :: Maybe Bool
_sheetViewShowGridLines :: Maybe Bool
_sheetViewShowFormulas :: Maybe Bool
_sheetViewWindowProtection :: Maybe Bool
_sheetViewSelection :: [Selection]
_sheetViewPane :: Maybe Pane
_sheetViewZoomScaleSheetLayoutView :: Maybe Int
_sheetViewZoomScalePageLayoutView :: Maybe Int
_sheetViewZoomScaleNormal :: Maybe Int
_sheetViewZoomScale :: Maybe Int
_sheetViewWorkbookViewId :: Int
_sheetViewWindowProtection :: Maybe Bool
_sheetViewType :: Maybe SheetViewType
_sheetViewTopLeftCell :: Maybe CellRef
_sheetViewTabSelected :: Maybe Bool
_sheetViewShowZeros :: Maybe Bool
_sheetViewShowWhiteSpace :: Maybe Bool
_sheetViewShowRuler :: Maybe Bool
_sheetViewShowRowColHeaders :: Maybe Bool
_sheetViewShowOutlineSymbols :: Maybe Bool
_sheetViewShowGridLines :: Maybe Bool
_sheetViewShowFormulas :: Maybe Bool
_sheetViewRightToLeft :: Maybe Bool
_sheetViewDefaultGridColor :: Maybe Bool
_sheetViewColorId :: Maybe Int
..}
instance FromXenoNode SheetView where
fromXenoNode :: Node -> Either Text SheetView
fromXenoNode Node
root = forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Maybe Bool
_sheetViewWindowProtection <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"windowProtection"
Maybe Bool
_sheetViewShowFormulas <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"showFormulas"
Maybe Bool
_sheetViewShowGridLines <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"showGridLines"
Maybe Bool
_sheetViewShowRowColHeaders <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"showRowColHeaders"
Maybe Bool
_sheetViewShowZeros <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"showZeros"
Maybe Bool
_sheetViewRightToLeft <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"rightToLeft"
Maybe Bool
_sheetViewTabSelected <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"tabSelected"
Maybe Bool
_sheetViewShowRuler <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"showRuler"
Maybe Bool
_sheetViewShowOutlineSymbols <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"showOutlineSymbols"
Maybe Bool
_sheetViewDefaultGridColor <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"defaultGridColor"
Maybe Bool
_sheetViewShowWhiteSpace <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"showWhiteSpace"
Maybe SheetViewType
_sheetViewType <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"view"
Maybe CellRef
_sheetViewTopLeftCell <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"topLeftCell"
Maybe Int
_sheetViewColorId <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"colorId"
Maybe Int
_sheetViewZoomScale <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"zoomScale"
Maybe Int
_sheetViewZoomScaleNormal <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"zoomScaleNormal"
Maybe Int
_sheetViewZoomScaleSheetLayoutView <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"zoomScaleSheetLayoutView"
Maybe Int
_sheetViewZoomScalePageLayoutView <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"zoomScalePageLayoutView"
Int
_sheetViewWorkbookViewId <- forall a. FromAttrBs a => ByteString -> AttrParser a
fromAttr ByteString
"workbookViewId"
(Maybe Pane
_sheetViewPane, [Selection]
_sheetViewSelection) <-
forall a. Either Text a -> AttrParser a
toAttrParser forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$
(,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromXenoNode a => ByteString -> ChildCollector (Maybe a)
maybeFromChild ByteString
"pane" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromXenoNode a => ByteString -> ChildCollector [a]
fromChildList ByteString
"selection"
forall (m :: * -> *) a. Monad m => a -> m a
return SheetView {Int
[Selection]
Maybe Bool
Maybe Int
Maybe CellRef
Maybe SheetViewType
Maybe Pane
_sheetViewSelection :: [Selection]
_sheetViewPane :: Maybe Pane
_sheetViewWorkbookViewId :: Int
_sheetViewZoomScalePageLayoutView :: Maybe Int
_sheetViewZoomScaleSheetLayoutView :: Maybe Int
_sheetViewZoomScaleNormal :: Maybe Int
_sheetViewZoomScale :: Maybe Int
_sheetViewColorId :: Maybe Int
_sheetViewTopLeftCell :: Maybe CellRef
_sheetViewType :: Maybe SheetViewType
_sheetViewShowWhiteSpace :: Maybe Bool
_sheetViewDefaultGridColor :: Maybe Bool
_sheetViewShowOutlineSymbols :: Maybe Bool
_sheetViewShowRuler :: Maybe Bool
_sheetViewTabSelected :: Maybe Bool
_sheetViewRightToLeft :: Maybe Bool
_sheetViewShowZeros :: Maybe Bool
_sheetViewShowRowColHeaders :: Maybe Bool
_sheetViewShowGridLines :: Maybe Bool
_sheetViewShowFormulas :: Maybe Bool
_sheetViewWindowProtection :: Maybe Bool
_sheetViewSelection :: [Selection]
_sheetViewPane :: Maybe Pane
_sheetViewZoomScaleSheetLayoutView :: Maybe Int
_sheetViewZoomScalePageLayoutView :: Maybe Int
_sheetViewZoomScaleNormal :: Maybe Int
_sheetViewZoomScale :: Maybe Int
_sheetViewWorkbookViewId :: Int
_sheetViewWindowProtection :: Maybe Bool
_sheetViewType :: Maybe SheetViewType
_sheetViewTopLeftCell :: Maybe CellRef
_sheetViewTabSelected :: Maybe Bool
_sheetViewShowZeros :: Maybe Bool
_sheetViewShowWhiteSpace :: Maybe Bool
_sheetViewShowRuler :: Maybe Bool
_sheetViewShowRowColHeaders :: Maybe Bool
_sheetViewShowOutlineSymbols :: Maybe Bool
_sheetViewShowGridLines :: Maybe Bool
_sheetViewShowFormulas :: Maybe Bool
_sheetViewRightToLeft :: Maybe Bool
_sheetViewDefaultGridColor :: Maybe Bool
_sheetViewColorId :: Maybe Int
..}
instance FromCursor Pane where
fromCursor :: Cursor -> [Pane]
fromCursor Cursor
cur = do
Maybe Double
_paneXSplit <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"xSplit" Cursor
cur
Maybe Double
_paneYSplit <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"ySplit" Cursor
cur
Maybe CellRef
_paneTopLeftCell <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"topLeftCell" Cursor
cur
Maybe PaneType
_paneActivePane <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"activePane" Cursor
cur
Maybe PaneState
_paneState <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"state" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Pane{Maybe Double
Maybe CellRef
Maybe PaneState
Maybe PaneType
_paneState :: Maybe PaneState
_paneActivePane :: Maybe PaneType
_paneTopLeftCell :: Maybe CellRef
_paneYSplit :: Maybe Double
_paneXSplit :: Maybe Double
_paneYSplit :: Maybe Double
_paneXSplit :: Maybe Double
_paneTopLeftCell :: Maybe CellRef
_paneState :: Maybe PaneState
_paneActivePane :: Maybe PaneType
..}
instance FromXenoNode Pane where
fromXenoNode :: Node -> Either Text Pane
fromXenoNode Node
root =
forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Maybe Double
_paneXSplit <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"xSplit"
Maybe Double
_paneYSplit <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"ySplit"
Maybe CellRef
_paneTopLeftCell <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"topLeftCell"
Maybe PaneType
_paneActivePane <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"activePane"
Maybe PaneState
_paneState <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"state"
forall (m :: * -> *) a. Monad m => a -> m a
return Pane {Maybe Double
Maybe CellRef
Maybe PaneState
Maybe PaneType
_paneState :: Maybe PaneState
_paneActivePane :: Maybe PaneType
_paneTopLeftCell :: Maybe CellRef
_paneYSplit :: Maybe Double
_paneXSplit :: Maybe Double
_paneYSplit :: Maybe Double
_paneXSplit :: Maybe Double
_paneTopLeftCell :: Maybe CellRef
_paneState :: Maybe PaneState
_paneActivePane :: Maybe PaneType
..}
instance FromCursor Selection where
fromCursor :: Cursor -> [Selection]
fromCursor Cursor
cur = do
Maybe PaneType
_selectionPane <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"pane" Cursor
cur
Maybe CellRef
_selectionActiveCell <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"activeCell" Cursor
cur
Maybe Int
_selectionActiveCellId <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"activeCellId" Cursor
cur
Maybe SqRef
_selectionSqref <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"sqref" Cursor
cur
forall (m :: * -> *) a. Monad m => a -> m a
return Selection{Maybe Int
Maybe SqRef
Maybe CellRef
Maybe PaneType
_selectionSqref :: Maybe SqRef
_selectionActiveCellId :: Maybe Int
_selectionActiveCell :: Maybe CellRef
_selectionPane :: Maybe PaneType
_selectionSqref :: Maybe SqRef
_selectionPane :: Maybe PaneType
_selectionActiveCellId :: Maybe Int
_selectionActiveCell :: Maybe CellRef
..}
instance FromXenoNode Selection where
fromXenoNode :: Node -> Either Text Selection
fromXenoNode Node
root =
forall a. Node -> AttrParser a -> Either Text a
parseAttributes Node
root forall a b. (a -> b) -> a -> b
$ do
Maybe PaneType
_selectionPane <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"pane"
Maybe CellRef
_selectionActiveCell <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"activeCell"
Maybe Int
_selectionActiveCellId <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"activeCellId"
Maybe SqRef
_selectionSqref <- forall a. FromAttrBs a => ByteString -> AttrParser (Maybe a)
maybeAttr ByteString
"sqref"
forall (m :: * -> *) a. Monad m => a -> m a
return Selection {Maybe Int
Maybe SqRef
Maybe CellRef
Maybe PaneType
_selectionSqref :: Maybe SqRef
_selectionActiveCellId :: Maybe Int
_selectionActiveCell :: Maybe CellRef
_selectionPane :: Maybe PaneType
_selectionSqref :: Maybe SqRef
_selectionPane :: Maybe PaneType
_selectionActiveCellId :: Maybe Int
_selectionActiveCell :: Maybe CellRef
..}
instance FromAttrVal SheetViewType where
fromAttrVal :: Reader SheetViewType
fromAttrVal Text
"normal" = forall a. a -> Either String (a, Text)
readSuccess SheetViewType
SheetViewTypeNormal
fromAttrVal Text
"pageBreakPreview" = forall a. a -> Either String (a, Text)
readSuccess SheetViewType
SheetViewTypePageBreakPreview
fromAttrVal Text
"pageLayout" = forall a. a -> Either String (a, Text)
readSuccess SheetViewType
SheetViewTypePageLayout
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"SheetViewType" Text
t
instance FromAttrBs SheetViewType where
fromAttrBs :: ByteString -> Either Text SheetViewType
fromAttrBs ByteString
"normal" = forall (m :: * -> *) a. Monad m => a -> m a
return SheetViewType
SheetViewTypeNormal
fromAttrBs ByteString
"pageBreakPreview" = forall (m :: * -> *) a. Monad m => a -> m a
return SheetViewType
SheetViewTypePageBreakPreview
fromAttrBs ByteString
"pageLayout" = forall (m :: * -> *) a. Monad m => a -> m a
return SheetViewType
SheetViewTypePageLayout
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"SheetViewType" ByteString
x
instance FromAttrVal PaneType where
fromAttrVal :: Reader PaneType
fromAttrVal Text
"bottomRight" = forall a. a -> Either String (a, Text)
readSuccess PaneType
PaneTypeBottomRight
fromAttrVal Text
"topRight" = forall a. a -> Either String (a, Text)
readSuccess PaneType
PaneTypeTopRight
fromAttrVal Text
"bottomLeft" = forall a. a -> Either String (a, Text)
readSuccess PaneType
PaneTypeBottomLeft
fromAttrVal Text
"topLeft" = forall a. a -> Either String (a, Text)
readSuccess PaneType
PaneTypeTopLeft
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"PaneType" Text
t
instance FromAttrBs PaneType where
fromAttrBs :: ByteString -> Either Text PaneType
fromAttrBs ByteString
"bottomRight" = forall (m :: * -> *) a. Monad m => a -> m a
return PaneType
PaneTypeBottomRight
fromAttrBs ByteString
"topRight" = forall (m :: * -> *) a. Monad m => a -> m a
return PaneType
PaneTypeTopRight
fromAttrBs ByteString
"bottomLeft" = forall (m :: * -> *) a. Monad m => a -> m a
return PaneType
PaneTypeBottomLeft
fromAttrBs ByteString
"topLeft" = forall (m :: * -> *) a. Monad m => a -> m a
return PaneType
PaneTypeTopLeft
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"PaneType" ByteString
x
instance FromAttrVal PaneState where
fromAttrVal :: Reader PaneState
fromAttrVal Text
"split" = forall a. a -> Either String (a, Text)
readSuccess PaneState
PaneStateSplit
fromAttrVal Text
"frozen" = forall a. a -> Either String (a, Text)
readSuccess PaneState
PaneStateFrozen
fromAttrVal Text
"frozenSplit" = forall a. a -> Either String (a, Text)
readSuccess PaneState
PaneStateFrozenSplit
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"PaneState" Text
t
instance FromAttrBs PaneState where
fromAttrBs :: ByteString -> Either Text PaneState
fromAttrBs ByteString
"split" = forall (m :: * -> *) a. Monad m => a -> m a
return PaneState
PaneStateSplit
fromAttrBs ByteString
"frozen" = forall (m :: * -> *) a. Monad m => a -> m a
return PaneState
PaneStateFrozen
fromAttrBs ByteString
"frozenSplit" = forall (m :: * -> *) a. Monad m => a -> m a
return PaneState
PaneStateFrozenSplit
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"PaneState" ByteString
x