xlsx-1.1.2.1: Simple and incomplete Excel file parser/writer
Safe HaskellSafe-Inferred
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

Instances details
Generic Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep Angle :: Type -> Type #

Methods

from :: Angle -> Rep Angle x #

to :: Rep Angle x -> Angle #

Show Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

showsPrec :: Int -> Angle -> ShowS #

show :: Angle -> String #

showList :: [Angle] -> ShowS #

NFData Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: Angle -> () #

Eq Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

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

FromAttrVal Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

toAttrVal :: Angle -> Text Source #

type Rep Angle Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Angle = D1 ('MetaData "Angle" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "Angle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Generic TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextBody :: Type -> Type #

Methods

from :: TextBody -> Rep TextBody x #

to :: Rep TextBody x -> TextBody #

Show TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextBody -> () #

Eq TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextBody Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

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.

Instances

Instances details
Generic TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextVertOverflow :: Type -> Type #

Show TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextVertOverflow -> () #

Eq TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromAttrVal TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextVertOverflow Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextVertOverflow = D1 ('MetaData "TextVertOverflow" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "TextVertOverflowClip" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TextVertOverflowEllipsis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextVertOverflow" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances details
Generic TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextVertical :: Type -> Type #

Show TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextVertical -> () #

Eq TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromAttrVal TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextVertical Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextVertical = D1 ('MetaData "TextVertical" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "TextVerticalEA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TextVerticalHorz" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextVerticalMongolian" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TextVertical" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextVertical270" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TextVerticalWordArt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextVerticalWordArtRtl" 'PrefixI 'False) (U1 :: Type -> Type))))

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

Instances details
Generic TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextWrap :: Type -> Type #

Methods

from :: TextWrap -> Rep TextWrap x #

to :: Rep TextWrap x -> TextWrap #

Show TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextWrap -> () #

Eq TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromAttrVal TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextWrap Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextWrap = D1 ('MetaData "TextWrap" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "TextWrapNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextWrapSquare" 'PrefixI 'False) (U1 :: Type -> Type))

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

Instances details
Generic TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextAnchoring :: Type -> Type #

Show TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextAnchoring -> () #

Eq TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromAttrVal TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextAnchoring Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextAnchoring = D1 ('MetaData "TextAnchoring" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "TextAnchoringBottom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextAnchoringCenter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TextAnchoringDistributed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TextAnchoringJustified" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TextAnchoringTop" 'PrefixI 'False) (U1 :: Type -> Type))))

data TextParagraph Source #

Instances

Instances details
Generic TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextParagraph :: Type -> Type #

Show TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextParagraph -> () #

Eq TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextParagraph Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextParagraph = D1 ('MetaData "TextParagraph" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "TextParagraph" 'PrefixI 'True) (S1 ('MetaSel ('Just "_txpaDefCharProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TextCharacterProperties)) :*: S1 ('MetaSel ('Just "_txpaRuns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TextRun])))

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

Instances details
Generic TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextCharacterProperties :: Type -> Type #

Show TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextCharacterProperties -> () #

Eq TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextCharacterProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextCharacterProperties = D1 ('MetaData "TextCharacterProperties" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "TextCharacterProperties" 'PrefixI 'True) (S1 ('MetaSel ('Just "_txchBold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_txchItalic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_txchUnderline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data TextRun Source #

Text run

TODO: br, fld

Instances

Instances details
Generic TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep TextRun :: Type -> Type #

Methods

from :: TextRun -> Rep TextRun x #

to :: Rep TextRun x -> TextRun #

Show TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: TextRun -> () #

Eq TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

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

FromCursor TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextRun Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep TextRun = D1 ('MetaData "TextRun" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" '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)

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)

Instances

Instances details
Generic Coordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep Coordinate :: Type -> Type #

Show Coordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData Coordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: Coordinate -> () #

Eq Coordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal Coordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Coordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Coordinate = D1 ('MetaData "Coordinate" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "UnqCoordinate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "UniversalMeasure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitIdentifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

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

Instances details
Generic UnitIdentifier Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep UnitIdentifier :: Type -> Type #

Show UnitIdentifier Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData UnitIdentifier Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: UnitIdentifier -> () #

Eq UnitIdentifier Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep UnitIdentifier Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep UnitIdentifier = D1 ('MetaData "UnitIdentifier" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) ((C1 ('MetaCons "UnitCm" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnitMm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnitIn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "UnitPt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnitPc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnitPi" 'PrefixI 'False) (U1 :: Type -> Type))))

data Point2D Source #

Constructors

Point2D 

Instances

Instances details
Generic Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep Point2D :: Type -> Type #

Methods

from :: Point2D -> Rep Point2D x #

to :: Rep Point2D x -> Point2D #

Show Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: Point2D -> () #

Eq Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

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

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

FromCursor Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Point2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Point2D = D1 ('MetaData "Point2D" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" '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

Instances details
Generic PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep PositiveCoordinate :: Type -> Type #

Show PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: PositiveCoordinate -> () #

Eq PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Ord PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToAttrVal PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep PositiveCoordinate Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep PositiveCoordinate = D1 ('MetaData "PositiveCoordinate" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'True) (C1 ('MetaCons "PositiveCoordinate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))

data PositiveSize2D Source #

Instances

Instances details
Generic PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep PositiveSize2D :: Type -> Type #

Show PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: PositiveSize2D -> () #

Eq PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep PositiveSize2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep PositiveSize2D = D1 ('MetaData "PositiveSize2D" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "PositiveSize2D" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ps2dX") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PositiveCoordinate) :*: S1 ('MetaSel ('Just "_ps2dY") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PositiveCoordinate)))

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

Instances details
Generic Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep Transform2D :: Type -> Type #

Show Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: Transform2D -> () #

Eq Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Transform2D Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Transform2D = D1 ('MetaData "Transform2D" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "Transform2D" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_trRot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Angle) :*: S1 ('MetaSel ('Just "_trFlipH") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_trFlipV") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_trOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Point2D)) :*: S1 ('MetaSel ('Just "_trExtents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PositiveSize2D))))))

data Geometry Source #

Constructors

PresetGeometry 

Instances

Instances details
Generic Geometry Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep Geometry :: Type -> Type #

Methods

from :: Geometry -> Rep Geometry x #

to :: Rep Geometry x -> Geometry #

Show Geometry Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData Geometry Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: Geometry -> () #

Eq Geometry Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor Geometry Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Geometry Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep Geometry = D1 ('MetaData "Geometry" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "PresetGeometry" 'PrefixI 'False) (U1 :: Type -> Type))

data ShapeProperties Source #

Instances

Instances details
Generic ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep ShapeProperties :: Type -> Type #

Show ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Default ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: ShapeProperties -> () #

Eq ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep ShapeProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep ShapeProperties = D1 ('MetaData "ShapeProperties" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "ShapeProperties" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_spXfrm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Transform2D)) :*: S1 ('MetaSel ('Just "_spGeometry") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Geometry))) :*: (S1 ('MetaSel ('Just "_spFill") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FillProperties)) :*: S1 ('MetaSel ('Just "_spOutline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineProperties)))))

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

Instances

Instances details
Generic LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep LineProperties :: Type -> Type #

Show LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Default LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

def :: LineProperties #

NFData LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: LineProperties -> () #

Eq LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

ToElement LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep LineProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep LineProperties = D1 ('MetaData "LineProperties" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "LineProperties" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lnFill") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FillProperties)) :*: S1 ('MetaSel ('Just "_lnWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

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

Instances details
Generic ColorChoice Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep ColorChoice :: Type -> Type #

Show ColorChoice Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData ColorChoice Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: ColorChoice -> () #

Eq ColorChoice Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep ColorChoice Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep ColorChoice = D1 ('MetaData "ColorChoice" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "RgbColor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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)

Instances

Instances details
Generic FillProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Associated Types

type Rep FillProperties :: Type -> Type #

Show FillProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

NFData FillProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

Methods

rnf :: FillProperties -> () #

Eq FillProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

FromCursor FillProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep FillProperties Source # 
Instance details

Defined in Codec.Xlsx.Types.Drawing.Common

type Rep FillProperties = D1 ('MetaData "FillProperties" "Codec.Xlsx.Types.Drawing.Common" "xlsx-1.1.2.1-GdAjj0zF0PPpPuMGO3FJH" 'False) (C1 ('MetaCons "NoFill" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SolidFill" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ColorChoice))))

solidRgb :: Text -> FillProperties Source #

solid fill with color specified by hexadecimal RGB color

a_ :: Text -> Name Source #

Add DrawingML namespace to name