Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data FileInfo = FileInfo {}
- data Coordinate
- data UnitIdentifier
- data Point2D = Point2D {
- _pt2dX :: Coordinate
- _pt2dY :: Coordinate
- unqPoint2D :: Int -> Int -> Point2D
- newtype PositiveCoordinate = PositiveCoordinate Integer
- newtype Angle = Angle Int
- data PositiveSize2D = PositiveSize2D {}
- 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 a = Picture {}
- data ClientData = ClientData {}
- data PicNonVisual = PicNonVisual {}
- data PicDrawingNonVisual = PicDrawingNonVisual {
- _pdnvId :: Int
- _pdnvName :: Text
- _pdnvDescription :: Maybe Text
- _pdnvHidden :: Bool
- _pdnvTitle :: Maybe Text
- data BlipFillProperties a = BlipFillProperties {
- _bfpImageInfo :: Maybe a
- _bfpFillMode :: Maybe FillMode
- data FillMode
- data ShapeProperties = ShapeProperties {}
- data Transform2D = Transform2D {}
- data Geometry = PresetGeometry
- data LineProperties = LineProperties {}
- data LineFill = LineNoFill
- data Anchor a = Anchor {}
- data GenericDrawing a = Drawing {
- _xdrAnchors :: [Anchor a]
- type Drawing = GenericDrawing FileInfo
- type UnresolvedDrawing = GenericDrawing RefId
- anchObject :: forall a a. Lens (Anchor a) (Anchor a) (DrawingObject a) (DrawingObject a)
- anchClientData :: forall a. Lens' (Anchor a) ClientData
- anchAnchoring :: forall a. Lens' (Anchor a) Anchoring
- picShapeProperties :: forall a. Lens' (DrawingObject a) ShapeProperties
- picPublished :: forall a. Lens' (DrawingObject a) Bool
- picNonVisual :: forall a. Lens' (DrawingObject a) PicNonVisual
- picMacro :: forall a. Lens' (DrawingObject a) (Maybe Text)
- picBlipFill :: forall a a. Lens (DrawingObject a) (DrawingObject a) (BlipFillProperties a) (BlipFillProperties a)
- bfpImageInfo :: forall a a. Lens (BlipFillProperties a) (BlipFillProperties a) (Maybe a) (Maybe a)
- bfpFillMode :: forall a. Lens' (BlipFillProperties a) (Maybe FillMode)
- xdrAnchors :: forall a a. Iso (GenericDrawing a) (GenericDrawing a) [Anchor a] [Anchor a]
- anchoringFromNode :: Node -> [Anchoring]
- nodeElNameIs :: Node -> Name -> Bool
- drawingObjectFromNode :: Node -> [DrawingObject RefId]
- fillModeFromNode :: Node -> [FillMode]
- geometryFromNode :: Node -> [Geometry]
- lineFillFromNode :: Node -> [LineFill]
- coordinate :: Monad m => Text -> m Coordinate
- anchorToElement :: Anchor RefId -> Element
- anchoringToElement :: Anchoring -> Element
- drawingObjToElement :: DrawingObject RefId -> Element
- fillModeToElement :: FillMode -> Element
- geometryToElement :: Geometry -> Element
- lineFillToElement :: LineFill -> Element
- a :: Text -> Name
- drawingNs :: Text
- xdr :: Text -> Name
- xlDrawingNs :: Text
Documentation
information about image file as a par of a drawing
FileInfo | |
|
data Coordinate Source #
This simple type represents a one dimensional position or length
See 20.1.10.16 "ST_Coordinate (Coordinate)" (p. 2921)
UnqCoordinate Int | see 20.1.10.19 "ST_CoordinateUnqualified (Coordinate)" (p. 2922) |
UniversalMeasure UnitIdentifier Double | see 22.9.2.15 "ST_UniversalMeasure (Universal Measurement)" (p. 3793) |
data UnitIdentifier Source #
Units used in "Universal measure" coordinates see 22.9.2.15 "ST_UniversalMeasure (Universal Measurement)" (p. 3793)
Point2D | |
|
newtype PositiveCoordinate Source #
Positive position or length in EMUs, maximu allowed value is 27273042316900. see 20.1.10.41 "ST_PositiveCoordinate (Positive Coordinate)" (p. 2942)
This simple type represents an angle in 60,000ths of a degree. Positive angles are clockwise (i.e., towards the positive y axis); negative angles are counter-clockwise (i.e., towards the negative y axis).
data PositiveSize2D Source #
Marker | |
|
data DrawingObject a Source #
Eq a => Eq (DrawingObject a) Source # | |
Show a => Show (DrawingObject a) Source # | |
FromCursor (DrawingObject RefId) Source # | |
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 | |
|
data PicNonVisual Source #
data PicDrawingNonVisual Source #
PicDrawingNonVisual | |
|
data BlipFillProperties a Source #
Eq a => Eq (BlipFillProperties a) Source # | |
Show a => Show (BlipFillProperties a) Source # | |
ToElement (BlipFillProperties RefId) Source # | |
FromCursor (BlipFillProperties RefId) Source # | |
data Transform2D Source #
Transform2D | |
|
data LineProperties Source #
data GenericDrawing a Source #
Drawing | |
|
ToElement UnresolvedDrawing Source # | |
ToDocument UnresolvedDrawing Source # | |
FromCursor UnresolvedDrawing Source # | |
Eq a => Eq (GenericDrawing a) Source # | |
Show a => Show (GenericDrawing a) Source # | |
type Drawing = GenericDrawing FileInfo Source #
type UnresolvedDrawing = GenericDrawing RefId Source #
anchObject :: forall a a. Lens (Anchor a) (Anchor a) (DrawingObject a) (DrawingObject a) Source #
anchClientData :: forall a. Lens' (Anchor a) ClientData Source #
picShapeProperties :: forall a. Lens' (DrawingObject a) ShapeProperties Source #
picPublished :: forall a. Lens' (DrawingObject a) Bool Source #
picNonVisual :: forall a. Lens' (DrawingObject a) PicNonVisual Source #
picBlipFill :: forall a a. Lens (DrawingObject a) (DrawingObject a) (BlipFillProperties a) (BlipFillProperties a) 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 a a. Iso (GenericDrawing a) (GenericDrawing a) [Anchor a] [Anchor a] Source #
anchoringFromNode :: Node -> [Anchoring] Source #
drawingObjectFromNode :: Node -> [DrawingObject RefId] Source #
fillModeFromNode :: Node -> [FillMode] Source #
geometryFromNode :: Node -> [Geometry] Source #
lineFillFromNode :: Node -> [LineFill] Source #
coordinate :: Monad m => Text -> m Coordinate Source #
fillModeToElement :: FillMode -> Element Source #
geometryToElement :: Geometry -> Element Source #
lineFillToElement :: LineFill -> Element Source #
xlDrawingNs :: Text Source #