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

Safe HaskellNone
LanguageHaskell2010

Codec.Xlsx.Types.Drawing

Synopsis

Documentation

data FileInfo Source #

information about image file as a par of a drawing

Constructors

FileInfo 

Fields

Instances

Eq FileInfo Source # 
Show FileInfo Source # 
Generic FileInfo Source # 

Associated Types

type Rep FileInfo :: * -> * #

Methods

from :: FileInfo -> Rep FileInfo x #

to :: Rep FileInfo x -> FileInfo #

NFData FileInfo Source # 

Methods

rnf :: FileInfo -> () #

type Rep FileInfo Source # 
type Rep FileInfo = D1 * (MetaData "FileInfo" "Codec.Xlsx.Types.Drawing" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "FileInfo" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_fiFilename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) ((:*:) * (S1 * (MetaSel (Just Symbol "_fiContentType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_fiContents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))))

data EditAs Source #

Instances

Eq EditAs Source # 

Methods

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

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

Show EditAs Source # 
Generic EditAs Source # 

Associated Types

type Rep EditAs :: * -> * #

Methods

from :: EditAs -> Rep EditAs x #

to :: Rep EditAs x -> EditAs #

NFData EditAs Source # 

Methods

rnf :: EditAs -> () #

FromAttrVal EditAs Source # 
ToAttrVal EditAs Source # 
type Rep EditAs Source # 
type Rep EditAs = D1 * (MetaData "EditAs" "Codec.Xlsx.Types.Drawing" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * (C1 * (MetaCons "EditAsTwoCell" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EditAsOneCell" PrefixI False) (U1 *)) (C1 * (MetaCons "EditAsAbsolute" PrefixI False) (U1 *))))

data Anchoring Source #

Instances

Eq Anchoring Source # 
Show Anchoring Source # 
Generic Anchoring Source # 

Associated Types

type Rep Anchoring :: * -> * #

NFData Anchoring Source # 

Methods

rnf :: Anchoring -> () #

FromCursor Anchoring Source # 
type Rep Anchoring Source # 

data DrawingObject p g Source #

Instances

(Eq g, Eq p) => Eq (DrawingObject p g) Source # 

Methods

(==) :: DrawingObject p g -> DrawingObject p g -> Bool #

(/=) :: DrawingObject p g -> DrawingObject p g -> Bool #

(Show g, Show p) => Show (DrawingObject p g) Source # 
Generic (DrawingObject p g) Source # 

Associated Types

type Rep (DrawingObject p g) :: * -> * #

Methods

from :: DrawingObject p g -> Rep (DrawingObject p g) x #

to :: Rep (DrawingObject p g) x -> DrawingObject p g #

(NFData p, NFData g) => NFData (DrawingObject p g) Source # 

Methods

rnf :: DrawingObject p g -> () #

FromCursor (DrawingObject RefId RefId) Source # 
type Rep (DrawingObject p g) Source # 

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)

Constructors

ClientData 

Fields

  • _cldLcksWithSheet :: Bool

    This attribute indicates whether to disable selection on drawing elements when the sheet is protected.

  • _cldPrintsWithSheet :: Bool

    This attribute indicates whether to print drawing elements when printing the sheet.

Instances

data NonVisualDrawingProperties Source #

Constructors

NonVisualDrawingProperties 

Fields

Instances

Eq NonVisualDrawingProperties Source # 
Show NonVisualDrawingProperties Source # 
Generic NonVisualDrawingProperties Source # 
NFData NonVisualDrawingProperties Source # 
FromCursor NonVisualDrawingProperties Source # 
ToElement NonVisualDrawingProperties Source # 
type Rep NonVisualDrawingProperties Source # 

data BlipFillProperties a Source #

data FillMode Source #

Constructors

FillTile 
FillStretch 

Instances

Eq FillMode Source # 
Show FillMode Source # 
Generic FillMode Source # 

Associated Types

type Rep FillMode :: * -> * #

Methods

from :: FillMode -> Rep FillMode x #

to :: Rep FillMode x -> FillMode #

NFData FillMode Source # 

Methods

rnf :: FillMode -> () #

FromCursor FillMode Source # 
type Rep FillMode Source # 
type Rep FillMode = D1 * (MetaData "FillMode" "Codec.Xlsx.Types.Drawing" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) ((:+:) * (C1 * (MetaCons "FillTile" PrefixI False) (U1 *)) (C1 * (MetaCons "FillStretch" PrefixI False) (U1 *)))

data Anchor p g Source #

Instances

(Eq p, Eq g) => Eq (Anchor p g) Source # 

Methods

(==) :: Anchor p g -> Anchor p g -> Bool #

(/=) :: Anchor p g -> Anchor p g -> Bool #

(Show p, Show g) => Show (Anchor p g) Source # 

Methods

showsPrec :: Int -> Anchor p g -> ShowS #

show :: Anchor p g -> String #

showList :: [Anchor p g] -> ShowS #

Generic (Anchor p g) Source # 

Associated Types

type Rep (Anchor p g) :: * -> * #

Methods

from :: Anchor p g -> Rep (Anchor p g) x #

to :: Rep (Anchor p g) x -> Anchor p g #

(NFData p, NFData g) => NFData (Anchor p g) Source # 

Methods

rnf :: Anchor p g -> () #

FromCursor (Anchor RefId RefId) Source # 
type Rep (Anchor p g) Source # 
type Rep (Anchor p g) = D1 * (MetaData "Anchor" "Codec.Xlsx.Types.Drawing" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "Anchor" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_anchAnchoring") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Anchoring)) ((:*:) * (S1 * (MetaSel (Just Symbol "_anchObject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (DrawingObject p g))) (S1 * (MetaSel (Just Symbol "_anchClientData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ClientData)))))

simpleAnchorXY Source #

Arguments

:: (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

data GenericDrawing p g Source #

Constructors

Drawing 

Fields

Instances

FromCursor UnresolvedDrawing Source # 
ToElement UnresolvedDrawing Source # 
ToDocument UnresolvedDrawing Source # 
(Eq g, Eq p) => Eq (GenericDrawing p g) Source # 
(Show g, Show p) => Show (GenericDrawing p g) Source # 
Generic (GenericDrawing p g) Source # 

Associated Types

type Rep (GenericDrawing p g) :: * -> * #

Methods

from :: GenericDrawing p g -> Rep (GenericDrawing p g) x #

to :: Rep (GenericDrawing p g) x -> GenericDrawing p g #

(NFData p, NFData g) => NFData (GenericDrawing p g) Source # 

Methods

rnf :: GenericDrawing p g -> () #

type Rep (GenericDrawing p g) Source # 
type Rep (GenericDrawing p g) = D1 * (MetaData "GenericDrawing" "Codec.Xlsx.Types.Drawing" "xlsx-0.7.0-67d30z0rd5vGH8ecLQYdXm" False) (C1 * (MetaCons "Drawing" PrefixI True) (S1 * (MetaSel (Just Symbol "_xdrAnchors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Anchor p g])))

anchObject :: forall p g p g. Lens (Anchor p g) (Anchor p g) (DrawingObject p g) (DrawingObject p g) Source #

grChartSpace :: forall p g g. Traversal (DrawingObject p g) (DrawingObject p g) g g Source #

xdrAnchors :: forall p g p g. Iso (GenericDrawing p g) (GenericDrawing p g) [Anchor p g] [Anchor p g] Source #

xdr :: Text -> Name Source #

Add Spreadsheet DrawingML namespace to name