SVGFonts-1.0: Fonts from the SVG-Font format

Graphics.SVGFonts.ReadFont

Synopsis

Documentation

openFont :: FilePath -> FontDataSource

Open an SVG-Font File and extract the data

Some explanation how kerning is computed:

In Linlibertine.svg, there are two groups of chars: i.e. <hkern g1="f,longs,uni1E1F,f_f" g2="parenright,bracketright,braceright" k="-37" /> This line means: If there is an f followed by parentright, reduce the horizontal advance by -37 (add 37). Therefore to quickly check if two characters need kerning assign an index to the second group (g2 or u2) and assign to every unicode in the first group (g1 or u1) this index, then sort these tuples after their name (for binary search). Because the same unicode char can appear in several g1s, reduce this multiset, ie all the ("name1",0) ("name1",1) to ("name1",[0,1]). Now the g2s are converted in the same way as the g1s. Whenever two consecutive chars are being printed try to find an intersection of the list assigned to the first char and second char

makeOutlMaps :: String -> (Rx, Int) -> (FontData, OutlineMap, OutlineTexMap)Source

Generate a map of lists of outlines i.e. the letter i consists of two lists.

Two different kinds of outlines are produced because:

  • OutlineMap: There are non-equally-spaced points possible (for outlines)
  • OutlineTexMap: There are only equally spaced points (for spans in rasterization)

makeTexMap :: (Rx, Int) -> Props -> Transf -> TexMapSource

Texture images for all combinations of characters, fonts and transformations for combinations of fonts and transformations only those are used that exist in this combination in the property list while every character is used that exists in the svg-font file.

data Mode Source

Constructors

INSIDE_V1_V2

INSIDE_V1_V2: The string is inside v1 v2 boundaries (height/length-relation not kept)

INSIDE_V1

INSIDE_V1: Stay inside v1 boundary, size of v2 adjusted to height/length-relation

INSIDE_V2

INSIDE_V2: Stay inside v2 boundary, size of v1 adjusted to height/length-relation

data Spacing Source

Constructors

KERN

Recommended, same as HADV but sometimes overridden by kerning: i.e. the horizontal advance in VV is bigger than in VA

HADV

Every glyph has a unique constant horiz. advance

MONO

Mono spacing between glyphs. Experimental. Better use a monospaced font from the beginning. The longest glyph influences the bbox that is used.

data Rx Source

The y resolution is constant. The x resolution of a glyph changes in non-mono-spaced fonts.

Constructors

Exactly Int 
ConstDx

The x-resolution of a single glvph is chosen so that all pixels from several glyphs have the same size

XPowerOfTwo

With this option the resolution nearest of a power of two is chosen i.e. l would have (256,512), while w would have (512,512)

OneTexture

The whole string as one texture (not implemented yet)

displayString :: String -> String -> (Rx, Int) -> Mode -> Spacing -> (V3, V3, V3) -> P -> Props -> Transf -> TexMap -> SceneSource

Main library function, explained with an example (that is also in Fonts.hs):

 main = do
   args <- getArgs
   let str = if null args then "Haskell"
                          else head args
       resolution = (400, 400)

The resolution is used for textures but also for outlines. Every outline point is placed in one grid position

       mode = INSIDE_V2
       spacing = KERN
       tex = ConstDx
       bit = makeOutlMaps "......srcTest/Bitstream.svg" resolution
       lin = makeOutlMap "../../..src\Test/LinLibertine.svg" resolution

Several different fonts can be used. They are stored in Data.Map structures to avoid recalculation. Lazy Evaluation ensures that outlines are only calculated if needed.

      o  = V3 0 0 0 -- origin
      v1 = V3 (-5) 0 0 -- direction of char-advance
      v2 = V3 0 0 1  -- height direction
      v3 = V3 0 0.1 0 -- extrusion

The position and size of the string

       f :: String -> [String]
       f str = take (length str) (concat (repeat ["p","q"]))

Assigning a property to every character by a string. Here an alternation of 3d and textured characters

      props :: Props
      props = Map.fromList [(p, Outl bit to3d), (q, Outl bit to3d2),
                            (r, Tex bit red),   (s, Tex bit blue) ]

Finite data structures are assigned to every property string. This is needed to lazily make a Data.Map with every possible representation of a character. A textured character needs an unchanged (maybe colored) outline. Thats why "q" uses the id function. If several fonts are used, kerning is disabled between every two characters that are from different fonts.

       transf :: Transf
       transf = Map.fromList [(to3d,to3d), (to3d2,to3d2), (red, red.bgWhite), (blue,blue.bgWhite), (id,id)]

Although there might be finitely many functions that make sense it is still to much and we need a small finite list for Data.Map. The number of combinations is ((Number of chars in font0) + (Number of chars in font1) + ...) * (number of transformation functions) and every of these combinations is built (but only evaluated if needed because of lazy evaluation) Example: (font1: 40 chars + font2: 1000 chars) X (5 colors (transformation functions)) 5200 key-value-pairs (assuming all colors are used in both fonts).

      to3d geom = red $ ( ((extrude v3).deleteHoles) geom ) `atop` ( tri ((translate v3) geom) )
      to3d2 geom = blue $ ( ((extrude (0,0.2,0)).deleteHoles) geom ) atop ( tri ((translate (0,0.2,0)) geom) )
      tri = (triangulate ketTri).deleteHoles -- openglTriangulation
      red =  changeDiffuseColor red (1,0,0,1) -- if used with textures diffuse is interpreted as foreground color
      blue = changeDiffuseColor blue (0,0,1,1)
      bgWhite = changeAmbientColor white (1,1,1,1) -- if used with textures interpreted as background color

The functions can be anything like extrusion, triangulation, color

       texmap = makeTexMap resolution props transf

Again a Data.Map-structure to avoid recalculation of textures. This has been separated from the outlineMap because it may one day also store the transformations applied to the outlines and maybe not every char is a texture

      node = displayString str node resolution mode spacing (o,v1,v2) f props transf texmap
   genCollada (lightedScene node) emptyAnim
   putStrLn "Collada File generated"

node is a Node in a Scenegraph, that is inserted into a lighted scene and written into file that can be viewed in Blender

type KernSource

Arguments

 = (Map String [Int], Map String [Int], Map String [Int], Map String [Int], Vector X)

u1s, u2s, g1s, g2s, k

type SvgGlyphSource

Arguments

 = Map String (String, X, String)

[ (unicode, (glyph_name, horiz_advance, ds)) ]

type FontDataSource

Arguments

 = (SvgGlyph, Kern, [Float], String)

(SvgGlyph, Kern, bbox-string, filename)

type OutlineMap = Map String [[(X, Y)]]Source

type P = [Char] -> [String]Source

type X = FloatSource

type Y = FloatSource