Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data FileInfo = FileInfo {}
- data Marker = Marker {
- _mrkCol :: Int
- _mrkColOff :: Coordinate
- _mrkRow :: Int
- _mrkRowOff :: Coordinate
- unqMarker :: (Int, Int) -> (Int, Int) -> Marker
- data EditAs
- data Anchoring
- = AbsoluteAnchor { }
- | OneCellAnchor { }
- | TwoCellAnchor { }
- data DrawingObject p g
- picture :: DrawingElementId -> FileInfo -> DrawingObject FileInfo c
- extractPictures :: Drawing -> [(Anchoring, FileInfo)]
- data ClientData = ClientData {}
- data PicNonVisual = PicNonVisual {}
- data GraphNonVisual = GraphNonVisual {}
- newtype DrawingElementId = DrawingElementId {}
- data NonVisualDrawingProperties = NonVisualDrawingProperties {}
- data BlipFillProperties a = BlipFillProperties {
- _bfpImageInfo :: Maybe a
- _bfpFillMode :: Maybe FillMode
- data FillMode
- data Anchor p g = Anchor {}
- data GenericDrawing p g = Drawing {
- _xdrAnchors :: [Anchor p g]
- type Drawing = GenericDrawing FileInfo ChartSpace
- type UnresolvedDrawing = GenericDrawing RefId RefId
- anchObject :: forall p g p g. Lens (Anchor p g) (Anchor p g) (DrawingObject p g) (DrawingObject p g)
- anchClientData :: forall p g. Lens' (Anchor p g) ClientData
- anchAnchoring :: forall p g. Lens' (Anchor p g) Anchoring
- picShapeProperties :: forall p g. Traversal' (DrawingObject p g) ShapeProperties
- picPublished :: forall p g. Traversal' (DrawingObject p g) Bool
- picNonVisual :: forall p g. Traversal' (DrawingObject p g) PicNonVisual
- picMacro :: forall p g. Traversal' (DrawingObject p g) (Maybe Text)
- picBlipFill :: forall p g p. Traversal (DrawingObject p g) (DrawingObject p g) (BlipFillProperties p) (BlipFillProperties p)
- grTransform :: forall p g. Traversal' (DrawingObject p g) Transform2D
- grNonVisual :: forall p g. Traversal' (DrawingObject p g) GraphNonVisual
- grChartSpace :: forall p g g. Traversal (DrawingObject p g) (DrawingObject p g) g g
- bfpImageInfo :: forall a a. Lens (BlipFillProperties a) (BlipFillProperties a) (Maybe a) (Maybe a)
- bfpFillMode :: forall a. Lens' (BlipFillProperties a) (Maybe FillMode)
- xdrAnchors :: forall p g p g. Iso (GenericDrawing p g) (GenericDrawing p g) [Anchor p g] [Anchor p g]
- simpleAnchorXY :: (Int, Int) -> PositiveSize2D -> DrawingObject p g -> Anchor p g
- anchoringFromNode :: Node -> [Anchoring]
- drawingObjectFromNode :: Node -> [DrawingObject RefId RefId]
- fillModeFromNode :: Node -> [FillMode]
- anchorToElement :: Anchor RefId RefId -> Element
- anchoringToElement :: Anchoring -> Element
- drawingObjToElement :: DrawingObject RefId RefId -> Element
- fillModeToElement :: FillMode -> Element
- xdr :: Text -> Name
- xlDrawingNs :: Text
Documentation
information about image file as a par of a drawing
FileInfo | |
|
Instances
Generic FileInfo Source # | |
Show FileInfo Source # | |
NFData FileInfo Source # | |
Defined in Codec.Xlsx.Types.Drawing | |
Eq FileInfo Source # | |
type Rep FileInfo Source # | |
Defined in Codec.Xlsx.Types.Drawing type Rep FileInfo = D1 ('MetaData "FileInfo" "Codec.Xlsx.Types.Drawing" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "FileInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fiFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "_fiContentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_fiContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))) |
Marker | |
|
Instances
Generic Marker Source # | |
Show Marker Source # | |
NFData Marker Source # | |
Defined in Codec.Xlsx.Types.Drawing | |
Eq Marker Source # | |
FromCursor Marker Source # | |
Defined in Codec.Xlsx.Types.Drawing fromCursor :: Cursor -> [Marker] Source # | |
ToElement Marker Source # | |
type Rep Marker Source # | |
Defined in Codec.Xlsx.Types.Drawing type Rep Marker = D1 ('MetaData "Marker" "Codec.Xlsx.Types.Drawing" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Marker" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mrkCol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_mrkColOff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coordinate)) :*: (S1 ('MetaSel ('Just "_mrkRow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_mrkRowOff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coordinate)))) |
Instances
Generic EditAs Source # | |
Show EditAs Source # | |
NFData EditAs Source # | |
Defined in Codec.Xlsx.Types.Drawing | |
Eq EditAs Source # | |
FromAttrVal EditAs Source # | |
Defined in Codec.Xlsx.Types.Drawing | |
ToAttrVal EditAs Source # | |
type Rep EditAs Source # | |
Defined in Codec.Xlsx.Types.Drawing type Rep EditAs = D1 ('MetaData "EditAs" "Codec.Xlsx.Types.Drawing" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "EditAsTwoCell" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EditAsOneCell" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EditAsAbsolute" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
data DrawingObject p g Source #
Instances
picture :: DrawingElementId -> FileInfo -> DrawingObject FileInfo c Source #
basic function to create picture drawing object
Note: specification says that drawing element ids need to be unique within 1 document, otherwise /...document shall be considered non-conformant/.
extractPictures :: Drawing -> [(Anchoring, FileInfo)] Source #
helper to retrive information about all picture files in particular drawing alongside with their anchorings (i.e. sizes and positions)
data ClientData Source #
This element is used to set certain properties related to a drawing element on the client spreadsheet application.
see 20.5.2.3 "clientData (Client Data)" (p. 3156)
ClientData | |
|
Instances
data PicNonVisual Source #
Instances
data GraphNonVisual Source #
Instances
newtype DrawingElementId Source #
Instances
data NonVisualDrawingProperties Source #
NonVisualDrawingProperties | |
|
Instances
data BlipFillProperties a Source #
Instances
Instances
Generic (Anchor p g) Source # | |
(Show p, Show g) => Show (Anchor p g) Source # | |
(NFData p, NFData g) => NFData (Anchor p g) Source # | |
Defined in Codec.Xlsx.Types.Drawing | |
(Eq p, Eq g) => Eq (Anchor p g) Source # | |
FromCursor (Anchor RefId RefId) Source # | |
Defined in Codec.Xlsx.Types.Drawing | |
type Rep (Anchor p g) Source # | |
Defined in Codec.Xlsx.Types.Drawing type Rep (Anchor p g) = D1 ('MetaData "Anchor" "Codec.Xlsx.Types.Drawing" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Anchor" 'PrefixI 'True) (S1 ('MetaSel ('Just "_anchAnchoring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Anchoring) :*: (S1 ('MetaSel ('Just "_anchObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DrawingObject p g)) :*: S1 ('MetaSel ('Just "_anchClientData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClientData)))) |
data GenericDrawing p g Source #
Drawing | |
|
Instances
type Drawing = GenericDrawing FileInfo ChartSpace Source #
type UnresolvedDrawing = GenericDrawing RefId RefId Source #
anchObject :: forall p g p g. Lens (Anchor p g) (Anchor p g) (DrawingObject p g) (DrawingObject p g) Source #
anchClientData :: forall p g. Lens' (Anchor p g) ClientData Source #
picShapeProperties :: forall p g. Traversal' (DrawingObject p g) ShapeProperties Source #
picPublished :: forall p g. Traversal' (DrawingObject p g) Bool Source #
picNonVisual :: forall p g. Traversal' (DrawingObject p g) PicNonVisual Source #
picMacro :: forall p g. Traversal' (DrawingObject p g) (Maybe Text) Source #
picBlipFill :: forall p g p. Traversal (DrawingObject p g) (DrawingObject p g) (BlipFillProperties p) (BlipFillProperties p) Source #
grTransform :: forall p g. Traversal' (DrawingObject p g) Transform2D Source #
grNonVisual :: forall p g. Traversal' (DrawingObject p g) GraphNonVisual Source #
grChartSpace :: forall p g g. Traversal (DrawingObject p g) (DrawingObject p g) g g Source #
bfpImageInfo :: forall a a. Lens (BlipFillProperties a) (BlipFillProperties a) (Maybe a) (Maybe a) Source #
bfpFillMode :: forall a. Lens' (BlipFillProperties a) (Maybe FillMode) Source #
xdrAnchors :: forall p g p g. Iso (GenericDrawing p g) (GenericDrawing p g) [Anchor p g] [Anchor p g] Source #
:: (Int, Int) | x+y coordinates of a cell used as top left anchoring corner |
-> PositiveSize2D | size of drawing object to be anchored |
-> DrawingObject p g | |
-> Anchor p g |
simple drawing object anchoring using one cell as a top lelft corner and dimensions of that object
anchoringFromNode :: Node -> [Anchoring] Source #
drawingObjectFromNode :: Node -> [DrawingObject RefId RefId] Source #
fillModeFromNode :: Node -> [FillMode] Source #
fillModeToElement :: FillMode -> Element Source #
xlDrawingNs :: Text Source #