diagrams-lib-1.3.1.4: Embedded domain-specific language for declarative graphics

Copyright(c) 2011-2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Text

Contents

Description

Very basic text primitives along with associated attributes.

Synopsis

Creating text diagrams

data Text n Source #

A Text primitive consists of the string contents, text alignment and the transformation to be applied. The transformation is scale invarient, the average scale of the transform should always be 1. All text scaling is obtained from the FontSize attribute.

This constructor should not be used directly. Use text, alignedText or baselineText.

Constructors

Text (T2 n) (TextAlignment n) String 

Instances

Floating n => Transformable (Text n) Source # 

Methods

transform :: Transformation (V (Text n)) (N (Text n)) -> Text n -> Text n #

Floating n => HasOrigin (Text n) Source # 

Methods

moveOriginTo :: Point (V (Text n)) (N (Text n)) -> Text n -> Text n #

Floating n => Renderable (Text n) NullBackend Source # 

Methods

render :: NullBackend -> Text n -> Render NullBackend (V (Text n)) (N (Text n)) #

type V (Text n) Source # 
type V (Text n) = V2
type N (Text n) Source # 
type N (Text n) = n

data TextAlignment n Source #

TextAlignment specifies the alignment of the text's origin.

Constructors

BaselineText 
BoxAlignedText n n 

text :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, with center alignment, equivalent to alignedText 0.5 0.5.

Note that it takes up no space, as text size information is not available.

topLeftText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, origin at the top left corner of the text's bounding box, equivalent to alignedText 0 1.

Note that it takes up no space.

alignedText :: (TypeableFloat n, Renderable (Text n) b) => n -> n -> String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, with the origin set to a point interpolated within the bounding box. The first parameter varies from 0 (left) to 1 (right), and the second parameter from 0 (bottom) to 1 (top). Some backends do not implement this and instead snap to closest corner or the center.

The height of this box is determined by the font's potential ascent and descent, rather than the height of the particular string.

Note that it takes up no space.

baselineText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, with the origin set to be on the baseline, at the beginning (although not bounding). This is the reference point of showText in the Cairo graphics library.

Note that it takes up no space.

mkText :: (TypeableFloat n, Renderable (Text n) b) => TextAlignment n -> String -> QDiagram b V2 n Any Source #

Make a text from a TextAlignment.

Text attributes

Font family

newtype Font Source #

The Font attribute specifies the name of a font family. Inner Font attributes override outer ones.

Constructors

Font (Last String) 

Instances

getFont :: Font -> String Source #

Extract the font family name from a Font attribute.

font :: HasStyle a => String -> a -> a Source #

Specify a font family to be used for all text within a diagram.

_font :: Lens' (Style v n) (Maybe String) Source #

Lens onto the font name of a style.

Font size

newtype FontSize n Source #

The FontSize attribute specifies the size of a font's em-square. Inner FontSize attributes override outer ones.

Constructors

FontSize (Recommend (Last n)) 

Instances

Functor FontSize Source # 

Methods

fmap :: (a -> b) -> FontSize a -> FontSize b #

(<$) :: a -> FontSize b -> FontSize a #

Semigroup (FontSize n) Source # 

Methods

(<>) :: FontSize n -> FontSize n -> FontSize n #

sconcat :: NonEmpty (FontSize n) -> FontSize n #

stimes :: Integral b => b -> FontSize n -> FontSize n #

Typeable * n => AttributeClass (FontSize n) Source # 

getFontSize :: FontSize n -> n Source #

Extract the size from a FontSize attribute.

fontSizeM :: (N a ~ n, Typeable n, HasStyle a) => FontSizeM n -> a -> a Source #

Apply a FontSize attribute.

fontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a Source #

Set the font size, that is, the size of the font's em-square as measured within the current local vector space. The default size is 1.

fontSizeN :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source #

A convenient synonym for 'fontSize (Normalized w)'.

fontSizeO :: (N a ~ n, Typeable n, HasStyle a) => n -> a -> a Source #

A convenient synonym for 'fontSize (Output w)'.

fontSizeL :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source #

A convenient sysnonym for 'fontSize (Local w)'.

fontSizeG :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source #

A convenient synonym for 'fontSize (Global w)'.

_fontSize :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n) Source #

Lens to commit a font size. This is *not* a valid lens (see commited.

Font slant

data FontSlant Source #

The FontSlantA attribute specifies the slant (normal, italic, or oblique) that should be used for all text within a diagram. Inner FontSlantA attributes override outer ones.

getFontSlant :: FontSlant -> FontSlant Source #

Extract the font slant from a FontSlantA attribute.

fontSlant :: HasStyle a => FontSlant -> a -> a Source #

Specify the slant (normal, italic, or oblique) that should be used for all text within a diagram. See also italic and oblique for useful special cases.

italic :: HasStyle a => a -> a Source #

Set all text in italics.

oblique :: HasStyle a => a -> a Source #

Set all text using an oblique slant.

_fontSlant :: Lens' (Style v n) FontSlant Source #

Lens onto the font slant in a style.

Font weight

data FontWeight Source #

The FontWeightA attribute specifies the weight (normal or bold) that should be used for all text within a diagram. Inner FontWeightA attributes override outer ones.

getFontWeight :: FontWeight -> FontWeight Source #

Extract the font weight.

fontWeight :: HasStyle a => FontWeight -> a -> a Source #

Specify the weight (normal or bold) that should be used for all text within a diagram. See also bold for a useful special case.

bold :: HasStyle a => a -> a Source #

Set all text using a bold font weight.

_fontWeight :: Lens' (Style v n) FontWeight Source #

Lens onto the font weight in a style.