Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Angle = Angle Int
- data TextBody = TextBody {}
- data TextVertOverflow
- data TextVertical
- data TextWrap
- data TextAnchoring
- data TextParagraph = TextParagraph {}
- data TextCharacterProperties = TextCharacterProperties {
- _txchBold :: Bool
- _txchItalic :: Bool
- _txchUnderline :: Bool
- data TextRun = RegularRun {}
- data Coordinate
- data UnitIdentifier
- data Point2D = Point2D {
- _pt2dX :: Coordinate
- _pt2dY :: Coordinate
- unqPoint2D :: Int -> Int -> Point2D
- newtype PositiveCoordinate = PositiveCoordinate Integer
- data PositiveSize2D = PositiveSize2D {}
- positiveSize2D :: Integer -> Integer -> PositiveSize2D
- cmSize2D :: Integer -> Integer -> PositiveSize2D
- cm2emu :: Integer -> Integer
- data Transform2D = Transform2D {}
- data Geometry = PresetGeometry
- data ShapeProperties = ShapeProperties {}
- data LineProperties = LineProperties {}
- data ColorChoice = RgbColor Text
- data FillProperties
- = NoFill
- | SolidFill (Maybe ColorChoice)
- solidRgb :: Text -> FillProperties
- spXfrm :: Lens' ShapeProperties (Maybe Transform2D)
- spOutline :: Lens' ShapeProperties (Maybe LineProperties)
- spGeometry :: Lens' ShapeProperties (Maybe Geometry)
- spFill :: Lens' ShapeProperties (Maybe FillProperties)
- geometryFromNode :: Node -> [Geometry]
- fillPropsFromNode :: Node -> [FillProperties]
- colorChoiceFromNode :: Node -> [ColorChoice]
- coordinate :: MonadFail m => Text -> m Coordinate
- geometryToElement :: Geometry -> Element
- fillPropsToElement :: FillProperties -> Element
- colorChoiceToElement :: ColorChoice -> Element
- a_ :: Text -> Name
- drawingNs :: Text
Documentation
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).
A string with rich text formatting
TODO: horzOverflow, lIns, tIns, rIns, bIns, numCol, spcCol, rtlCol, fromWordArt, forceAA, upright, compatLnSpc, prstTxWarp, a_EG_TextAutofit, scene3d, a_EG_Text3D, extLst
See CT_TextBody
(p. 4034)
TextBody | |
|
Instances
data TextVertOverflow Source #
Text vertical overflow See 20.1.10.83 "ST_TextVertOverflowType (Text Vertical Overflow)" (p. 3083)
TextVertOverflowClip | Pay attention to top and bottom barriers. Provide no indication that there is text which is not visible. |
TextVertOverflowEllipsis | Pay attention to top and bottom barriers. Use an ellipsis to denote that there is text which is not visible. |
TextVertOverflow | Overflow the text and pay no attention to top and bottom barriers. |
Instances
data TextVertical Source #
If there is vertical text, determines what kind of vertical text is going to be used.
See 20.1.10.82 "ST_TextVerticalType (Vertical Text Types)" (p. 3083)
TextVerticalEA | A special version of vertical text, where some fonts are displayed as if rotated by 90 degrees while some fonts (mostly East Asian) are displayed vertical. |
TextVerticalHorz | Horizontal text. This should be default. |
TextVerticalMongolian | A special version of vertical text, where some fonts are displayed as if rotated
by 90 degrees while some fonts (mostly East Asian) are displayed vertical. The
difference between this and the |
TextVertical | Determines if all of the text is vertical orientation (each line is 90 degrees rotated clockwise, so it goes from top to bottom; each next line is to the left from the previous one). |
TextVertical270 | Determines if all of the text is vertical orientation (each line is 270 degrees rotated clockwise, so it goes from bottom to top; each next line is to the right from the previous one). |
TextVerticalWordArt | Determines if all of the text is vertical ("one letter on top of another"). |
TextVerticalWordArtRtl | Specifies that vertical WordArt should be shown from right to left rather than left to right. |
Instances
Text wrapping types
See 20.1.10.84 "ST_TextWrappingType (Text Wrapping Types)" (p. 3084)
TextWrapNone | No wrapping occurs on this text body. Words spill out without paying attention to the bounding rectangle boundaries. |
TextWrapSquare | Determines whether we wrap words within the bounding rectangle. |
Instances
Generic TextWrap Source # | |
Show TextWrap Source # | |
NFData TextWrap Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common | |
Eq TextWrap Source # | |
FromAttrVal TextWrap Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common | |
ToAttrVal TextWrap Source # | |
type Rep TextWrap Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common |
data TextAnchoring Source #
This type specifies a list of available anchoring types for text.
See 20.1.10.59 "ST_TextAnchoringType (Text Anchoring Types)" (p. 3058)
TextAnchoringBottom | Anchor the text at the bottom of the bounding rectangle. |
TextAnchoringCenter | Anchor the text at the middle of the bounding rectangle. |
TextAnchoringDistributed | Anchor the text so that it is distributed vertically. When text is horizontal,
this spaces out the actual lines of text and is almost always identical in
behavior to |
TextAnchoringJustified | Anchor the text so that it is justified vertically. When text is horizontal,
this spaces out the actual lines of text and is almost always identical in
behavior to |
TextAnchoringTop | Anchor the text at the top of the bounding rectangle. |
Instances
data TextParagraph Source #
Instances
data TextCharacterProperties Source #
Text character properties
TODO: kumimoji, lang, altLang, sz, strike, kern, cap, spc, normalizeH, baseline, noProof, dirty, err, smtClean, smtId, bmk, ln, a_EG_FillProperties, a_EG_EffectProperties, highlight, a_EG_TextUnderlineLine, a_EG_TextUnderlineFill, latin, ea, cs, sym, hlinkClick, hlinkMouseOver, rtl, extLst
See CT_TextCharacterProperties
(p. 4039)
Instances
Text run
TODO: br, fld
Instances
Generic TextRun Source # | |
Show TextRun Source # | |
NFData TextRun Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common | |
Eq TextRun Source # | |
FromCursor TextRun Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common fromCursor :: Cursor -> [TextRun] Source # | |
ToElement TextRun Source # | |
type Rep TextRun Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common type Rep TextRun = D1 ('MetaData "TextRun" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "RegularRun" 'PrefixI 'True) (S1 ('MetaSel ('Just "_txrCharProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TextCharacterProperties)) :*: S1 ('MetaSel ('Just "_txrText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
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) |
Instances
data UnitIdentifier Source #
Units used in "Universal measure" coordinates see 22.9.2.15 "ST_UniversalMeasure (Universal Measurement)" (p. 3793)
Instances
Point2D | |
|
Instances
Generic Point2D Source # | |
Show Point2D Source # | |
NFData Point2D Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common | |
Eq Point2D Source # | |
FromCursor Point2D Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common fromCursor :: Cursor -> [Point2D] Source # | |
ToElement Point2D Source # | |
type Rep Point2D Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common type Rep Point2D = D1 ('MetaData "Point2D" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "Point2D" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pt2dX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coordinate) :*: S1 ('MetaSel ('Just "_pt2dY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coordinate))) |
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)
Instances
data PositiveSize2D Source #
Instances
positiveSize2D :: Integer -> Integer -> PositiveSize2D Source #
data Transform2D Source #
Transform2D | |
|
Instances
data ShapeProperties Source #
Instances
data LineProperties Source #
Specifies an outline style that can be applied to a number of different objects such as shapes and text.
TODO: cap, cmpd, algn, a_EG_LineDashProperties, a_EG_LineJoinProperties, headEnd, tailEnd, extLst
See 20.1.2.2.24 "ln (Outline)" (p. 2744)
LineProperties | |
|
Instances
data ColorChoice Source #
Color choice for some drawing element
TODO: scrgbClr, hslClr, sysClr, schemeClr, prstClr
See EG_ColorChoice
(p. 3996)
RgbColor Text | Specifies a color using the red, green, blue RGB color model. Red, green, and blue is expressed as sequence of hex digits, RRGGBB. A perceptual gamma of 2.2 is used. See 20.1.2.3.32 "srgbClr (RGB Color Model - Hex Variant)" (p. 2773) |
Instances
Generic ColorChoice Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common type Rep ColorChoice :: Type -> Type # from :: ColorChoice -> Rep ColorChoice x # to :: Rep ColorChoice x -> ColorChoice # | |
Show ColorChoice Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common showsPrec :: Int -> ColorChoice -> ShowS # show :: ColorChoice -> String # showList :: [ColorChoice] -> ShowS # | |
NFData ColorChoice Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common rnf :: ColorChoice -> () # | |
Eq ColorChoice Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common (==) :: ColorChoice -> ColorChoice -> Bool # (/=) :: ColorChoice -> ColorChoice -> Bool # | |
type Rep ColorChoice Source # | |
Defined in Codec.Xlsx.Types.Drawing.Common type Rep ColorChoice = D1 ('MetaData "ColorChoice" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.0.1-FKUF1Jx3xuq9irRu3xJWCs" 'False) (C1 ('MetaCons "RgbColor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
data FillProperties Source #
NoFill | See 20.1.8.44 "noFill (No Fill)" (p. 2872) |
SolidFill (Maybe ColorChoice) | Solid fill See 20.1.8.54 "solidFill (Solid Fill)" (p. 2879) |
Instances
solidRgb :: Text -> FillProperties Source #
solid fill with color specified by hexadecimal RGB color
geometryFromNode :: Node -> [Geometry] Source #
fillPropsFromNode :: Node -> [FillProperties] Source #
colorChoiceFromNode :: Node -> [ColorChoice] Source #
coordinate :: MonadFail m => Text -> m Coordinate Source #
geometryToElement :: Geometry -> Element Source #