xlsx-0.7.0: Simple and incomplete Excel file parser/writer

Safe HaskellNone
LanguageHaskell2010

Codec.Xlsx.Types.Drawing.Common

Synopsis

Documentation

newtype Angle Source #

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).

Constructors

Angle Int 

Instances

Eq Angle Source # 

Methods

(==) :: Angle -> Angle -> Bool #

(/=) :: Angle -> Angle -> Bool #

Show Angle Source # 

Methods

showsPrec :: Int -> Angle -> ShowS #

show :: Angle -> String #

showList :: [Angle] -> ShowS #

Generic Angle Source # 

Associated Types

type Rep Angle :: * -> * #

Methods

from :: Angle -> Rep Angle x #

to :: Rep Angle x -> Angle #

NFData Angle Source # 

Methods

rnf :: Angle -> () #

FromAttrVal Angle Source # 
ToAttrVal Angle Source # 

Methods

toAttrVal :: Angle -> Text Source #

type Rep Angle Source # 
type Rep Angle = D1 * (MetaData "Angle" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" True) (C1 * (MetaCons "Angle" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

data TextBody Source #

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)

Constructors

TextBody 

Fields

  • _txbdRotation :: Angle

    Specifies the rotation that is being applied to the text within the bounding box.

  • _txbdSpcFirstLastPara :: Bool

    Specifies whether the before and after paragraph spacing defined by the user is to be respected.

  • _txbdVertOverflow :: TextVertOverflow

    Determines whether the text can flow out of the bounding box vertically.

  • _txbdVertical :: TextVertical

    Determines if the text within the given text body should be displayed vertically.

  • _txbdWrap :: TextWrap

    Specifies the wrapping options to be used for this text body.

  • _txbdAnchor :: TextAnchoring

    Specifies the anchoring position of the txBody within the shape.

  • _txbdAnchorCenter :: Bool

    Specifies the centering of the text box. The way it works fundamentally is to determine the smallest possible "bounds box" for the text and then to center that "bounds box" accordingly. This is different than paragraph alignment, which aligns the text within the "bounds box" for the text.

  • _txbdParagraphs :: [TextParagraph]

    Paragraphs of text within the containing text body

Instances

Eq TextBody Source # 
Show TextBody Source # 
Generic TextBody Source # 

Associated Types

type Rep TextBody :: * -> * #

Methods

from :: TextBody -> Rep TextBody x #

to :: Rep TextBody x -> TextBody #

NFData TextBody Source # 

Methods

rnf :: TextBody -> () #

FromCursor TextBody Source # 
ToElement TextBody Source # 
type Rep TextBody Source # 

data TextVertOverflow Source #

Text vertical overflow See 20.1.10.83 "ST_TextVertOverflowType (Text Vertical Overflow)" (p. 3083)

Constructors

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.

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)

Constructors

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 TextVerticalEA is the text flows top down then LEFT RIGHT, instead of RIGHT LEFT

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

Eq TextVertical Source # 
Show TextVertical Source # 
Generic TextVertical Source # 

Associated Types

type Rep TextVertical :: * -> * #

NFData TextVertical Source # 

Methods

rnf :: TextVertical -> () #

FromAttrVal TextVertical Source # 
ToAttrVal TextVertical Source # 
type Rep TextVertical Source # 
type Rep TextVertical = D1 * (MetaData "TextVertical" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TextVerticalEA" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TextVerticalHorz" PrefixI False) (U1 *)) (C1 * (MetaCons "TextVerticalMongolian" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "TextVertical" PrefixI False) (U1 *)) (C1 * (MetaCons "TextVertical270" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TextVerticalWordArt" PrefixI False) (U1 *)) (C1 * (MetaCons "TextVerticalWordArtRtl" PrefixI False) (U1 *)))))

data TextWrap Source #

Text wrapping types

See 20.1.10.84 "ST_TextWrappingType (Text Wrapping Types)" (p. 3084)

Constructors

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

Eq TextWrap Source # 
Show TextWrap Source # 
Generic TextWrap Source # 

Associated Types

type Rep TextWrap :: * -> * #

Methods

from :: TextWrap -> Rep TextWrap x #

to :: Rep TextWrap x -> TextWrap #

NFData TextWrap Source # 

Methods

rnf :: TextWrap -> () #

FromAttrVal TextWrap Source # 
ToAttrVal TextWrap Source # 
type Rep TextWrap Source # 
type Rep TextWrap = D1 * (MetaData "TextWrap" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * (C1 * (MetaCons "TextWrapNone" PrefixI False) (U1 *)) (C1 * (MetaCons "TextWrapSquare" PrefixI False) (U1 *)))

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)

Constructors

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 (special case: if only 1 line, then anchored in middle). When text is vertical, then it distributes the letters vertically. This is different than TextAnchoringJustified, because it always forces distribution of the words, even if there are only one or two words in a line.

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 TextAnchoringDistributed (special case: if only 1 line, then anchored at top). When text is vertical, then it justifies the letters vertically. This is different than TextAnchoringDistributed because in some cases such as very little text in a line, it does not justify.

TextAnchoringTop

Anchor the text at the top of the bounding rectangle.

Instances

Eq TextAnchoring Source # 
Show TextAnchoring Source # 
Generic TextAnchoring Source # 

Associated Types

type Rep TextAnchoring :: * -> * #

NFData TextAnchoring Source # 

Methods

rnf :: TextAnchoring -> () #

FromAttrVal TextAnchoring Source # 
ToAttrVal TextAnchoring Source # 
type Rep TextAnchoring Source # 
type Rep TextAnchoring = D1 * (MetaData "TextAnchoring" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TextAnchoringBottom" PrefixI False) (U1 *)) (C1 * (MetaCons "TextAnchoringCenter" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TextAnchoringDistributed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TextAnchoringJustified" PrefixI False) (U1 *)) (C1 * (MetaCons "TextAnchoringTop" PrefixI False) (U1 *)))))

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

Eq TextCharacterProperties Source # 
Show TextCharacterProperties Source # 
Generic TextCharacterProperties Source # 
NFData TextCharacterProperties Source # 

Methods

rnf :: TextCharacterProperties -> () #

FromCursor TextCharacterProperties Source # 
ToElement TextCharacterProperties Source # 
type Rep TextCharacterProperties Source # 
type Rep TextCharacterProperties = D1 * (MetaData "TextCharacterProperties" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "TextCharacterProperties" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_txchBold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "_txchItalic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "_txchUnderline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))

data TextRun Source #

Text run

TODO: br, fld

Instances

Eq TextRun Source # 

Methods

(==) :: TextRun -> TextRun -> Bool #

(/=) :: TextRun -> TextRun -> Bool #

Show TextRun Source # 
Generic TextRun Source # 

Associated Types

type Rep TextRun :: * -> * #

Methods

from :: TextRun -> Rep TextRun x #

to :: Rep TextRun x -> TextRun #

NFData TextRun Source # 

Methods

rnf :: TextRun -> () #

FromCursor TextRun Source # 
ToElement TextRun Source # 
type Rep TextRun Source # 
type Rep TextRun = D1 * (MetaData "TextRun" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "RegularRun" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_txrCharProps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe TextCharacterProperties))) (S1 * (MetaSel (Just Symbol "_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)

Constructors

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)

Constructors

UnitCm 
UnitMm 
UnitIn 
UnitPt 
UnitPc 
UnitPi 

Instances

Eq UnitIdentifier Source # 
Show UnitIdentifier Source # 
Generic UnitIdentifier Source # 

Associated Types

type Rep UnitIdentifier :: * -> * #

NFData UnitIdentifier Source # 

Methods

rnf :: UnitIdentifier -> () #

type Rep UnitIdentifier Source # 
type Rep UnitIdentifier = D1 * (MetaData "UnitIdentifier" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * ((:+:) * (C1 * (MetaCons "UnitCm" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UnitMm" PrefixI False) (U1 *)) (C1 * (MetaCons "UnitIn" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "UnitPt" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UnitPc" PrefixI False) (U1 *)) (C1 * (MetaCons "UnitPi" PrefixI False) (U1 *)))))

data Point2D Source #

Constructors

Point2D 

Instances

Eq Point2D Source # 

Methods

(==) :: Point2D -> Point2D -> Bool #

(/=) :: Point2D -> Point2D -> Bool #

Show Point2D Source # 
Generic Point2D Source # 

Associated Types

type Rep Point2D :: * -> * #

Methods

from :: Point2D -> Rep Point2D x #

to :: Rep Point2D x -> Point2D #

NFData Point2D Source # 

Methods

rnf :: Point2D -> () #

FromCursor Point2D Source # 
ToElement Point2D Source # 
type Rep Point2D Source # 
type Rep Point2D = D1 * (MetaData "Point2D" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "Point2D" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pt2dX") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Coordinate)) (S1 * (MetaSel (Just Symbol "_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

Eq PositiveCoordinate Source # 
Ord PositiveCoordinate Source # 
Show PositiveCoordinate Source # 
Generic PositiveCoordinate Source # 
NFData PositiveCoordinate Source # 

Methods

rnf :: PositiveCoordinate -> () #

ToAttrVal PositiveCoordinate Source # 
type Rep PositiveCoordinate Source # 
type Rep PositiveCoordinate = D1 * (MetaData "PositiveCoordinate" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" True) (C1 * (MetaCons "PositiveCoordinate" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Integer)))

data Transform2D Source #

Constructors

Transform2D 

Fields

  • _trRot :: Angle

    Specifies the rotation of the Graphic Frame.

  • _trFlipH :: Bool

    Specifies a horizontal flip. When true, this attribute defines that the shape is flipped horizontally about the center of its bounding box.

  • _trFlipV :: Bool

    Specifies a vertical flip. When true, this attribute defines that the shape is flipped vetically about the center of its bounding box.

  • _trOffset :: Maybe Point2D

    See 20.1.7.4 "off (Offset)" (p. 2847)

  • _trExtents :: Maybe PositiveSize2D

    See 20.1.7.3 "ext (Extents)" (p. 2846) or 20.5.2.14 "ext (Shape Extent)" (p. 3165)

Instances

data Geometry Source #

Constructors

PresetGeometry 

Instances

Eq Geometry Source # 
Show Geometry Source # 
Generic Geometry Source # 

Associated Types

type Rep Geometry :: * -> * #

Methods

from :: Geometry -> Rep Geometry x #

to :: Rep Geometry x -> Geometry #

NFData Geometry Source # 

Methods

rnf :: Geometry -> () #

FromCursor Geometry Source # 
type Rep Geometry Source # 
type Rep Geometry = D1 * (MetaData "Geometry" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "PresetGeometry" PrefixI False) (U1 *))

data ShapeProperties Source #

Instances

Eq ShapeProperties Source # 
Show ShapeProperties Source # 
Generic ShapeProperties Source # 
Default ShapeProperties Source # 
NFData ShapeProperties Source # 

Methods

rnf :: ShapeProperties -> () #

FromCursor ShapeProperties Source # 
ToElement ShapeProperties Source # 
type Rep ShapeProperties Source # 

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)

Constructors

LineProperties 

Fields

data ColorChoice Source #

Color choice for some drawing element

TODO: scrgbClr, hslClr, sysClr, schemeClr, prstClr

See EG_ColorChoice (p. 3996)

Constructors

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

Eq ColorChoice Source # 
Show ColorChoice Source # 
Generic ColorChoice Source # 

Associated Types

type Rep ColorChoice :: * -> * #

NFData ColorChoice Source # 

Methods

rnf :: ColorChoice -> () #

type Rep ColorChoice Source # 
type Rep ColorChoice = D1 * (MetaData "ColorChoice" "Codec.Xlsx.Types.Drawing.Common" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "RgbColor" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

data FillProperties Source #

Constructors

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)

solidRgb :: Text -> FillProperties Source #

solid fill with color specified by hexadecimal RGB color

a_ :: Text -> Name Source #

Add DrawingML namespace to name