SVGFonts-1.8.0.1: Fonts from the SVG-Font format
Safe HaskellNone
LanguageHaskell2010

Graphics.SVGFonts

Description

Note: for help porting pre-1.8 code to SVGFonts-1.8, see the README.

Text drawing example

The following is a simple example that covers basic use cases of the predefined text drawing functions. The text rendering can be even more customized, see e.g. the implementation of svgText_fitRect_stretchySpace.

The example creates:

  • a width-adjusted text: textw
  • a height-adjusted text: texth
  • a text adjusted to both width and height with evenly stretched advances of characters: textr
  • a text adjusted to both width and height, where space characters are stretched more than others: textrs
  • a text, from which only the path is extracted, dropping the enclosing rectangle given by font: textp
  • a text wrapped and block-adjusted into a box: textbox


import Diagrams.Prelude hiding (text, width, height)
import Diagrams.Backend.SVG.CmdLine
import qualified Graphics.SVGFonts as F
import qualified Graphics.SVGFonts.Wrap as FW

main = mainWith diagram

diagram :: Diagram B
diagram = vsep 1 [textw, texth, textr, textrs, textp, textbox]

text = "Hello World, ahoy!"
long_text =
  "At vero eos et accusamus et iusto odio dignissimos ducimus qui blanditiis \
  \praesentium voluptatum deleniti atque corrupti quos dolores."

width = 200 :: Double
height = 22

stylize text = text # fc blue # lc blue # bg lightgrey # fillRule EvenOdd # showOrigin
text_diagram = stylize . F.set_envelope

textw = text_diagram$ F.fit_width width$ F.svgText def text
texth = text_diagram$ F.fit_height height$ F.svgText def text
textr = text_diagram$ F.svgText_fitRect def (width, height) text
textrs = text_diagram$ F.svgText_fitRect_stretchySpace def (width, height) 5 text
textp = stylize$ stroke$ F.drop_rect$ F.fit_height height$ F.svgText def text

textbox = stylize$ vcat$ map F.set_envelope$
  map (F.svgText_fitRect_stretchySpace def (width, height) 5) (init texts)
  ++ [F.fit_height height$ F.svgText def$ last texts]
  where
    texts = case FW.wrapText def height splits long_text of
      Just texts -> texts
      Nothing -> map return long_text

    splits =
      [ (FW.splitAtSpaces, (width - 30, width + 10))
      , (FW.splitEachTwoChars, (width - 30, width + 10))
      , (const Nothing, (-1, 1/0))
      ]

Font loading example

main = do
  font1 <- loadDataFont "fonts/LinLibertine.svg"
  font2 <- loadFont "/path/to/font.svg"
  let
    t1 = F.svgText_raw def{textFont = font1} "Hello"
    t2 = F.svgText_raw def{textFont = font2} "Hello"
  mainWith (stroke t1 === stroke t2 :: Diagram B)
Synopsis

Drawing text

svgText :: RealFloat n => TextOpts n -> String -> PathInRect n Source #

Render PathInRect from text. The enclosing rectangle, computed from the font, is kept, to be able to e.g. correctly position lines of text one above other.

svgText_raw :: RealFloat n => TextOpts n -> String -> Path V2 n Source #

Simply render path from text.

svgText_modifyPreglyphs :: (RealFloat n, Monad m) => TextOpts n -> (PreparedText n -> m [(String, n)]) -> String -> m (PathInRect n) Source #

Like svgText but preglyphs can be modified using the given monad before draw_glyphs is called. Simple examples of this function's specializations are e.g. svgText_fitRect and svgText_fitRect_stretchySpace.

svgText_fitRect :: forall n. RealFloat n => TextOpts n -> (n, n) -> String -> PathInRect n Source #

Like svgText but a rectangle is provided, into which the text will fit. The text is scaled according to the height of the rectengle. The glyphs are interleaved with even spaces to fit the width of the rectangle. The text must have at least two characters for correct functionality.

svgText_fitRect_stretchySpace :: forall n. RealFloat n => TextOpts n -> (n, n) -> n -> String -> PathInRect n Source #

Like svgText_fitRect but space characters are stretched k times more than others for svgText_fitRect_stretchySpace opts (w, h) k text.

set_envelope :: forall b n. (TypeableFloat n, Renderable (Path V2 n) b) => PathInRect n -> QDiagram b V2 n Any Source #

drop_rect :: forall n. RealFloat n => PathInRect n -> Path V2 n Source #

Options

data TextOpts n Source #

Constructors

TextOpts 

Instances

Instances details
(Read n, RealFloat n) => Default (TextOpts n) Source # 
Instance details

Defined in Graphics.SVGFonts.Text

Methods

def :: TextOpts n #

data Spacing Source #

Constructors

HADV

Every glyph has a unique horiz. advance

KERN

Recommended, same as HADV but sometimes overridden by kerning: As You can see there is less space between "A" and "V":

Instances

Instances details
Show Spacing Source # 
Instance details

Defined in Graphics.SVGFonts.Text

Provided fonts

bit :: (Read n, RealFloat n) => IO (PreparedFont n) Source #

Bitstream, a standard monospaced font (used in gedit)

lin :: (Read n, RealFloat n) => IO (PreparedFont n) Source #

Linux Libertine, for non-monospaced text. http://www.linuxlibertine.org/ Contains a lot of unicode characters.

lin2 :: (Read n, RealFloat n) => IO (PreparedFont n) Source #

Linux Libertine, cut to contain only the most common characters. This results in a smaller file and hence a quicker load time.

Loading fonts

loadFont :: (Read n, RealFloat n) => FilePath -> IO (PreparedFont n) Source #

Read font data from font file, and compute its outline map.

loadDataFont :: (Read n, RealFloat n) => FilePath -> IO (PreparedFont n) Source #

Load a font from a file in the data directory.

Backward compatibility

textSVG :: (Read n, RealFloat n) => String -> n -> Path V2 n Source #