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 Control.Lens (makeLenses)
import Data.Default
import Data.Maybe (catMaybes, maybeToList, listToMaybe)
import Text.XML
import Text.XML.Cursor
import qualified Data.Map as Map
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ()
#endif
import Codec.Xlsx.Types.Common
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Writer.Internal
data SheetView = SheetView {
_sheetViewColorId :: Maybe Int
, _sheetViewDefaultGridColor :: Maybe Bool
, _sheetViewRightToLeft :: Maybe Bool
, _sheetViewShowFormulas :: Maybe Bool
, _sheetViewShowGridLines :: Maybe Bool
, _sheetViewShowOutlineSymbols :: Maybe Bool
, _sheetViewShowRowColHeaders :: Maybe Bool
, _sheetViewShowRuler :: Maybe Bool
, _sheetViewShowWhiteSpace :: Maybe Bool
, _sheetViewShowZeros :: Maybe Bool
, _sheetViewTabSelected :: Maybe Bool
, _sheetViewTopLeftCell :: Maybe CellRef
, _sheetViewType :: Maybe SheetViewType
, _sheetViewWindowProtection :: Maybe Bool
, _sheetViewWorkbookViewId :: Int
, _sheetViewZoomScale :: Maybe Int
, _sheetViewZoomScaleNormal :: Maybe Int
, _sheetViewZoomScalePageLayoutView :: Maybe Int
, _sheetViewZoomScaleSheetLayoutView :: Maybe Int
, _sheetViewPane :: Maybe Pane
, _sheetViewSelection :: [Selection]
}
deriving (Show, Eq, Ord)
data Selection = Selection {
_selectionActiveCell :: Maybe CellRef
, _selectionActiveCellId :: Maybe Int
, _selectionPane :: Maybe PaneType
, _selectionSqref :: Maybe SqRef
}
deriving (Show, Eq, Ord)
data Pane = Pane {
_paneActivePane :: Maybe PaneType
, _paneState :: Maybe PaneState
, _paneTopLeftCell :: Maybe CellRef
, _paneXSplit :: Maybe Double
, _paneYSplit :: Maybe Double
}
deriving (Show, Eq, Ord)
data SheetViewType =
SheetViewTypeNormal
| SheetViewTypePageBreakPreview
| SheetViewTypePageLayout
deriving (Show, Eq, Ord)
data PaneType =
PaneTypeBottomLeft
| PaneTypeBottomRight
| PaneTypeTopLeft
| PaneTypeTopRight
deriving (Eq, Show, Ord)
data PaneState =
PaneStateFrozen
| PaneStateFrozenSplit
| PaneStateSplit
deriving (Eq, Show, Ord)
makeLenses ''SheetView
makeLenses ''Selection
makeLenses ''Pane
instance Default SheetView where
def = SheetView {
_sheetViewColorId = Nothing
, _sheetViewDefaultGridColor = Nothing
, _sheetViewRightToLeft = Nothing
, _sheetViewShowFormulas = Nothing
, _sheetViewShowGridLines = Nothing
, _sheetViewShowOutlineSymbols = Nothing
, _sheetViewShowRowColHeaders = Nothing
, _sheetViewShowRuler = Nothing
, _sheetViewShowWhiteSpace = Nothing
, _sheetViewShowZeros = Nothing
, _sheetViewTabSelected = Nothing
, _sheetViewTopLeftCell = Nothing
, _sheetViewType = Nothing
, _sheetViewWindowProtection = Nothing
, _sheetViewWorkbookViewId = 0
, _sheetViewZoomScale = Nothing
, _sheetViewZoomScaleNormal = Nothing
, _sheetViewZoomScalePageLayoutView = Nothing
, _sheetViewZoomScaleSheetLayoutView = Nothing
, _sheetViewPane = Nothing
, _sheetViewSelection = []
}
instance Default Selection where
def = Selection {
_selectionActiveCell = Nothing
, _selectionActiveCellId = Nothing
, _selectionPane = Nothing
, _selectionSqref = Nothing
}
instance Default Pane where
def = Pane {
_paneActivePane = Nothing
, _paneState = Nothing
, _paneTopLeftCell = Nothing
, _paneXSplit = Nothing
, _paneYSplit = Nothing
}
instance ToElement SheetView where
toElement nm SheetView{..} = Element {
elementName = nm
, elementNodes = map NodeElement . concat $ [
map (toElement "pane") (maybeToList _sheetViewPane)
, map (toElement "selection") _sheetViewSelection
]
, elementAttributes = Map.fromList . catMaybes $ [
"windowProtection" .=? _sheetViewWindowProtection
, "showFormulas" .=? _sheetViewShowFormulas
, "showGridLines" .=? _sheetViewShowGridLines
, "showRowColHeaders" .=? _sheetViewShowRowColHeaders
, "showZeros" .=? _sheetViewShowZeros
, "rightToLeft" .=? _sheetViewRightToLeft
, "tabSelected" .=? _sheetViewTabSelected
, "showRuler" .=? _sheetViewShowRuler
, "showOutlineSymbols" .=? _sheetViewShowOutlineSymbols
, "defaultGridColor" .=? _sheetViewDefaultGridColor
, "showWhiteSpace" .=? _sheetViewShowWhiteSpace
, "view" .=? _sheetViewType
, "topLeftCell" .=? _sheetViewTopLeftCell
, "colorId" .=? _sheetViewColorId
, "zoomScale" .=? _sheetViewZoomScale
, "zoomScaleNormal" .=? _sheetViewZoomScaleNormal
, "zoomScaleSheetLayoutView" .=? _sheetViewZoomScaleSheetLayoutView
, "zoomScalePageLayoutView" .=? _sheetViewZoomScalePageLayoutView
, Just $ "workbookViewId" .= _sheetViewWorkbookViewId
]
}
instance ToElement Selection where
toElement nm Selection{..} = Element {
elementName = nm
, elementNodes = []
, elementAttributes = Map.fromList . catMaybes $ [
"pane" .=? _selectionPane
, "activeCell" .=? _selectionActiveCell
, "activeCellId" .=? _selectionActiveCellId
, "sqref" .=? _selectionSqref
]
}
instance ToElement Pane where
toElement nm Pane{..} = Element {
elementName = nm
, elementNodes = []
, elementAttributes = Map.fromList . catMaybes $ [
"xSplit" .=? _paneXSplit
, "ySplit" .=? _paneYSplit
, "topLeftCell" .=? _paneTopLeftCell
, "activePane" .=? _paneActivePane
, "state" .=? _paneState
]
}
instance ToAttrVal SheetViewType where
toAttrVal SheetViewTypeNormal = "normal"
toAttrVal SheetViewTypePageBreakPreview = "pageBreakPreview"
toAttrVal SheetViewTypePageLayout = "pageLayout"
instance ToAttrVal PaneType where
toAttrVal PaneTypeBottomRight = "bottomRight"
toAttrVal PaneTypeTopRight = "topRight"
toAttrVal PaneTypeBottomLeft = "bottomLeft"
toAttrVal PaneTypeTopLeft = "topLeft"
instance ToAttrVal PaneState where
toAttrVal PaneStateSplit = "split"
toAttrVal PaneStateFrozen = "frozen"
toAttrVal PaneStateFrozenSplit = "frozenSplit"
instance FromCursor SheetView where
fromCursor cur = do
_sheetViewWindowProtection <- maybeAttribute "windowProtection" cur
_sheetViewShowFormulas <- maybeAttribute "showFormulas" cur
_sheetViewShowGridLines <- maybeAttribute "showGridLines" cur
_sheetViewShowRowColHeaders <- maybeAttribute "showRowColHeaders"cur
_sheetViewShowZeros <- maybeAttribute "showZeros" cur
_sheetViewRightToLeft <- maybeAttribute "rightToLeft" cur
_sheetViewTabSelected <- maybeAttribute "tabSelected" cur
_sheetViewShowRuler <- maybeAttribute "showRuler" cur
_sheetViewShowOutlineSymbols <- maybeAttribute "showOutlineSymbols" cur
_sheetViewDefaultGridColor <- maybeAttribute "defaultGridColor" cur
_sheetViewShowWhiteSpace <- maybeAttribute "showWhiteSpace" cur
_sheetViewType <- maybeAttribute "view" cur
_sheetViewTopLeftCell <- maybeAttribute "topLeftCell" cur
_sheetViewColorId <- maybeAttribute "colorId" cur
_sheetViewZoomScale <- maybeAttribute "zoomScale" cur
_sheetViewZoomScaleNormal <- maybeAttribute "zoomScaleNormal" cur
_sheetViewZoomScaleSheetLayoutView <- maybeAttribute "zoomScaleSheetLayoutView" cur
_sheetViewZoomScalePageLayoutView <- maybeAttribute "zoomScalePageLayoutView" cur
_sheetViewWorkbookViewId <- fromAttribute "workbookViewId" cur
let _sheetViewPane = listToMaybe $ cur $/ element (n"pane") >=> fromCursor
_sheetViewSelection = cur $/ element (n"selection") >=> fromCursor
return SheetView{..}
instance FromCursor Pane where
fromCursor cur = do
_paneXSplit <- maybeAttribute "xSplit" cur
_paneYSplit <- maybeAttribute "ySplit" cur
_paneTopLeftCell <- maybeAttribute "topLeftCell" cur
_paneActivePane <- maybeAttribute "activePane" cur
_paneState <- maybeAttribute "state" cur
return Pane{..}
instance FromCursor Selection where
fromCursor cur = do
_selectionPane <- maybeAttribute "pane" cur
_selectionActiveCell <- maybeAttribute "activeCell" cur
_selectionActiveCellId <- maybeAttribute "activeCellId" cur
_selectionSqref <- maybeAttribute "sqref" cur
return Selection{..}
instance FromAttrVal SheetViewType where
fromAttrVal "normal" = readSuccess SheetViewTypeNormal
fromAttrVal "pageBreakPreview" = readSuccess SheetViewTypePageBreakPreview
fromAttrVal "pageLayout" = readSuccess SheetViewTypePageLayout
fromAttrVal t = invalidText "SheetViewType" t
instance FromAttrVal PaneType where
fromAttrVal "bottomRight" = readSuccess PaneTypeBottomRight
fromAttrVal "topRight" = readSuccess PaneTypeTopRight
fromAttrVal "bottomLeft" = readSuccess PaneTypeBottomLeft
fromAttrVal "topLeft" = readSuccess PaneTypeTopLeft
fromAttrVal t = invalidText "PaneType" t
instance FromAttrVal PaneState where
fromAttrVal "split" = readSuccess PaneStateSplit
fromAttrVal "frozen" = readSuccess PaneStateFrozen
fromAttrVal "frozenSplit" = readSuccess PaneStateFrozenSplit
fromAttrVal t = invalidText "PaneState" t