Safe Haskell | None |
---|---|
Language | Haskell2010 |
- textSVG :: String -> Double -> Path R2
- data TextOpts = TextOpts {}
- textSVG' :: TextOpts -> Path R2
- textSVG_ :: forall b. Renderable (Path R2) b => TextOpts -> QDiagram b R2 Any
- data FontData = FontData {
- fontDataGlyphs :: SvgGlyphs
- fontDataKerning :: Kern
- fontDataBoundingBox :: [Double]
- fontDataFileName :: String
- fontDataUnderlinePos :: Double
- fontDataUnderlineThickness :: Double
- fontDataOverlinePos :: Maybe Double
- fontDataOverlineThickness :: Maybe Double
- fontDataStrikethroughPos :: Maybe Double
- fontDataStrikethroughThickness :: Maybe Double
- fontDataHorizontalAdvance :: Double
- fontDataFamily :: String
- fontDataStyle :: String
- fontDataWeight :: String
- fontDataVariant :: String
- fontDataStretch :: String
- fontDataSize :: Maybe String
- fontDataUnitsPerEm :: Double
- fontDataPanose :: String
- fontDataSlope :: Maybe Double
- fontDataAscent :: Double
- fontDataDescent :: Double
- fontDataXHeight :: Double
- fontDataCapHeight :: Double
- fontDataAccentHeight :: Maybe Double
- fontDataWidths :: Maybe String
- fontDataHorizontalStem :: Maybe Double
- fontDataVerticalStem :: Maybe Double
- fontDataUnicodeRange :: String
- fontDataRawKernings :: [(String, [String], [String], [String], [String])]
- fontDataIdeographicBaseline :: Maybe Double
- fontDataAlphabeticBaseline :: Maybe Double
- fontDataMathematicalBaseline :: Maybe Double
- fontDataHangingBaseline :: Maybe Double
- fontDataVIdeographicBaseline :: Maybe Double
- fontDataVAlphabeticBaseline :: Maybe Double
- fontDataVMathematicalBaseline :: Maybe Double
- fontDataVHangingBaseline :: Maybe Double
- openFont :: FilePath -> FontData
- type SvgGlyphs = Map String (String, Double, String)
- horizontalAdvances :: [String] -> FontData -> Bool -> [Double]
- hadv :: String -> FontData -> Double
- data Kern = Kern {}
- kernAdvance :: String -> String -> Kern -> Bool -> Double
- type OutlineMap = Map String (Path R2)
- data Mode
- mWH :: Mode -> Bool
- mW :: Mode -> Bool
- mH :: Mode -> Bool
- data Spacing
- isKern :: Spacing -> Bool
- type FileName = String
- ro :: FilePath -> FilePath
- bbox_dy :: FontData -> Double
- bbox_lx :: FontData -> Double
- bbox_ly :: FontData -> Double
- underlinePosition :: FontData -> Double
- underlineThickness :: FontData -> Double
- outlMap :: String -> (FontData, OutlineMap)
- commandsToTrails :: [PathCommand] -> [Segment Closed R2] -> R2 -> R2 -> R2 -> [Path R2]
- commands :: String -> SvgGlyphs -> [PathCommand]
- bit :: (FontData, OutlineMap)
- lin :: (FontData, OutlineMap)
- lin2 :: (FontData, OutlineMap)
Documentation
textSVG :: String -> Double -> Path R2
A short version of textSVG' with standard values. The Double value is the height.
import Graphics.SVGFonts textSVGExample = stroke $ textSVG "Hello World" 1
textSVG' :: TextOpts -> Path R2
The origin is at the center of the text and the boundaries are given by the outlines of the chars.
import Graphics.SVGFonts text' t = stroke (textSVG' $ TextOpts t lin INSIDE_H KERN False 1 1 ) # fc blue # lc blue # bg lightgrey # fillRule EvenOdd # showOrigin textPic0 = (text' "Hello World") # showOrigin
textSVG_ :: forall b. Renderable (Path R2) b => TextOpts -> QDiagram b R2 Any
The origin is at the left end of the baseline of of the text and the boundaries are given by the bounding box of the Font. This is best for combining Text of different fonts and for several lines of text. As you can see you can also underline text by setting underline to True.
import Graphics.SVGFonts text'' t = (textSVG_ $ TextOpts t lin INSIDE_H KERN True 1 1 ) # fc blue # lc blue # bg lightgrey # fillRule EvenOdd # showOrigin textPic1 = text'' "Hello World"
data FontData
This type contains everything that a typical SVG font file produced by fontforge contains.
(SvgGlyph, Kern, bbox-string, filename, (underlinePos, underlineThickness), (fontHadv, fontFamily, fontWeight, fontStretch, unitsPerEm, panose, ascent, descent, xHeight, capHeight, stemh, stemv, unicodeRange) )
horizontalAdvances :: [String] -> FontData -> Bool -> [Double]
Horizontal advances of characters inside a string. A character is stored with a string (because of ligatures like "ffi").
hadv :: String -> FontData -> Double
Horizontal advance of a character consisting of its width and spacing, extracted out of the font data
data Kern
See http://www.w3.org/TR/SVG/fonts.html#KernElements
Some explanation how kerning is computed:
In Linlibertine.svg, there are two groups of chars: e.g.
<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
kernAdvance :: String -> String -> Kern -> Bool -> Double
Change the horizontal advance of two consective chars (kerning)
type OutlineMap = Map String (Path R2)
data Mode
INSIDE_H | The string fills the complete height, width adjusted. Used in text editors. The result can be smaller or bigger than the bounding box: |
INSIDE_W | The string fills the complete width, height adjusted. May be useful for single words in a diagram, or for headlines. The result can be smaller or bigger than the bounding box: |
INSIDE_WH | The string is stretched inside Width and Height boundaries. The horizontal advances are increased if the string is shorter than there is space. The horizontal advances are decreased if the string is longer than there is space. This feature is experimental and might change in the future. |
data Spacing
underlinePosition :: FontData -> Double
Position of the underline bar
underlineThickness :: FontData -> Double
Thickness of the underline bar
outlMap :: String -> (FontData, OutlineMap)
Generate Font Data and a Map from chars to outline paths
commandsToTrails :: [PathCommand] -> [Segment Closed R2] -> R2 -> R2 -> R2 -> [Path R2]
commands :: String -> SvgGlyphs -> [PathCommand]
bit :: (FontData, OutlineMap)
Bitstream, a standard monospaced font (used in gedit)
lin :: (FontData, OutlineMap)
Linux Libertine, for non-monospaced text: http://www.linuxlibertine.org/, contains a lot of unicode characters
lin2 :: (FontData, OutlineMap)
Linux Libertine, cut to contain only the most common characters, resulting in a smaller file and hence a quicker load time.