module Graphics.PlotFont (
PlotFont,
PFWidth, PFPoint, PFStroke, PFGlyph,
render, render', optimizeStrokes,
canvastextFont
) where
import Control.Monad
import qualified Data.Map as M
import qualified Data.List as L
import qualified Data.Traversable as T
import qualified Data.Either as E
import Data.Ord
type PFWidth = Double
type PFPoint = (Double, Double)
type PFStroke = [PFPoint]
type PFGlyph = (PFWidth, [PFStroke])
dist:: PFPoint -> PFPoint -> Double
dist (xa,ya) (xb,yb) = sqrt $ (xa xb)^2 + (ya yb)^2
data PlotFont = PlotFont (M.Map Char PFGlyph)
render :: PlotFont -> String -> Either String [PFStroke]
render f = getGlyphs f >=> (Right . renderLine 0)
getGlyphs :: PlotFont -> String -> Either String [PFGlyph]
getGlyphs f = addErrorMsg . leftsOrRights . map (getGlyph f)
addErrorMsg :: (Either String a) -> (Either String a)
addErrorMsg (Left a) = Left $ "Missing chars: " ++ a
addErrorMsg a = a
leftsOrRights :: [Either a b] -> Either [a] [b]
leftsOrRights = pick . E.partitionEithers
where pick ([],bs) = Right bs
pick (as,_) = Left as
getGlyph :: PlotFont -> Char -> Either Char PFGlyph
getGlyph (PlotFont m) c = maybe (Left c) Right $ c `M.lookup` m
render' :: PlotFont -> String -> [PFStroke]
render' f = renderLine 0 . map (getGlyph' f)
getGlyph' :: PlotFont -> Char -> PFGlyph
getGlyph' (PlotFont m) c = M.findWithDefault fallbackGlyph c m
fallbackGlyph :: PFGlyph
fallbackGlyph = (18.0, optimizeStrokes
[ [ (3.0,16.0), (3.0,17.0), (4.0,19.0), (5.0,20.0),
(7.0,21.0), (11.0,21.0), (13.0,20.0), (14.0,19.0),
(15.0,17.0), (15.0,15.0), (14.0,13.0), (13.0,12.0),
(9.0,10.0), (9.0,7.0) ],
[ (9.0,2.0), (8.0,1.0), (9.0,0.0), (10.0,1.0), (9.0,2.0) ]
])
renderLine :: PFWidth -> [PFGlyph] -> [PFStroke]
renderLine _ [] = []
renderLine dx ((w,ss):sss) = offset ss ++ renderLine (dx + w) sss
where offset = (liftM . liftM) (\(x,y) -> (x + dx,y))
optimizeStrokes :: [PFStroke] -> [PFStroke]
optimizeStrokes = pickBest . map joinStrokes . allArrangements . filter (not . null)
where pickBest = L.minimumBy (comparing score)
allArrangements :: [[a]] -> [[[a]]]
allArrangements = concatMap allDirs . L.permutations
allDirs :: [[a]] -> [[[a]]]
allDirs strokes = [ zipWith ($) ops strokes | ops <- opss ]
where opss = replicateM (length strokes) [id, reverse]
score :: [PFStroke] -> (Int, Double, PFPoint)
score ss | length ss < 2 = (length ss, 0.0, (0.0,0.0))
score ss = (length ss, sum skips, firstPoint)
where skips = zipWith (\as bs -> dist (last as) (head bs)) ss (tail ss)
firstPoint = head $ head ss
joinStrokes (s0:s1:ss) | last s0 == head s1 = joinStrokes $ (s0 ++ tail s1) : ss
| otherwise = s0 : joinStrokes (s1:ss)
joinStrokes ss = ss
canvastextFont :: PlotFont
canvastextFont = PlotFont $ M.fromList
[ (' ',(16.0,[]))
,('!',(10.0,[[(5.0,2.0),(4.0,1.0),(5.0,0.0),(6.0,1.0),(5.0,2.0)]
,[(5.0,7.0),(5.0,21.0)]]))
,('"',(10.0,[[(4.0,15.0),(5.0,16.0),(6.0,18.0),(6.0,20.0),(5.0,21.0)
,(4.0,20.0),(5.0,19.0)]]))
,('#',(21.0,[[(10.0,7.0),(17.0,25.0)],[(11.0,25.0),(4.0,7.0)],[(3.0,6.0),(17.0,6.0)],
[(18.0,12.0),(4.0,12.0)]]))
,('$',(20.0,[[(3.0,3.0),(5.0,1.0),(8.0,0.0),(12.0,0.0),(15.0,1.0),(17.0,3.0),(17.0,6.0)
,(16.0,8.0),(15.0,9.0),(13.0,10.0),(7.0,12.0),(5.0,13.0),(4.0,14.0),(3.0,16.0)
,(3.0,18.0),(5.0,20.0),(8.0,21.0),(12.0,21.0),(15.0,20.0),(17.0,18.0)]
,[(12.0,25.0),(12.0,4.0)],[(8.0,4.0),(8.0,25.0)]]))
,('%',(24.0,[[(8.0,21.0),(10.0,19.0),(10.0,17.0),(9.0,15.0),(7.0,14.0),(5.0,14.0)
,(3.0,16.0),(3.0,18.0),(4.0,20.0),(6.0,21.0),(8.0,21.0),(10.0,20.0)
,(13.0,19.0),(16.0,19.0),(19.0,20.0),(21.0,21.0),(3.0,0.0)]
,[(17.0,7.0),(15.0,6.0),(14.0,4.0),(14.0,2.0),(16.0,0.0),(18.0,0.0)
,(20.0,1.0),(21.0,3.0),(21.0,5.0),(19.0,7.0),(17.0,7.0)]]))
,('&',(26.0,[[(23.0,2.0),(23.0,1.0),(22.0,0.0),(20.0,0.0),(18.0,1.0),(16.0,3.0)
,(11.0,10.0),(9.0,13.0),(8.0,16.0),(8.0,18.0),(9.0,20.0),(11.0,21.0)
,(13.0,20.0),(14.0,18.0),(14.0,16.0),(13.0,14.0),(12.0,13.0),(5.0,9.0)
,(4.0,8.0),(3.0,6.0),(3.0,4.0),(4.0,2.0),(5.0,1.0),(7.0,0.0),(11.0,0.0)
,(13.0,1.0),(15.0,3.0),(17.0,6.0),(19.0,11.0),(20.0,13.0),(21.0,14.0)
,(22.0,14.0),(23.0,13.0),(23.0,12.0)]]))
,('(',(14.0,[[(11.0,7.0),(9.0,5.0),(7.0,2.0),(5.0,2.0),(4.0,7.0),(4.0,11.0)
,(5.0,16.0),(7.0,20.0),(9.0,23.0),(11.0,25.0)]]))
,(')',(14.0,[[(3.0,7.0),(5.0,5.0),(7.0,2.0),(9.0,2.0),(10.0,7.0),(10.0,11.0)
,(9.0,16.0),(7.0,20.0),(5.0,23.0),(3.0,25.0)]]))
,('*',(16.0,[[(3.0,12.0),(13.0,18.0)],[(8.0,21.0),(8.0,9.0)],[(13.0,12.0),(3.0,18.0)]]))
,('+',(26.0,[[(4.0,9.0),(22.0,9.0)],[(13.0,0.0),(13.0,18.0)]]))
,(',',(10.0,[[(4.0,4.0),(5.0,3.0),(6.0,1.0),(6.0,1.0),(5.0,2.0),(4.0,1.0),(5.0,0.0)
,(6.0,1.0)]]))
,('-',(26.0,[[(4.0,9.0),(22.0,9.0)]]))
,('.',(10.0,[[(5.0,2.0),(4.0,1.0),(5.0,0.0),(6.0,1.0),(5.0,2.0)]]))
,('/',(22.0,[[(2.0,7.0),(20.0,25.0)]]))
,('0',(20.0,[[(9.0,21.0),(6.0,20.0),(4.0,17.0),(3.0,12.0),(3.0,9.0),(4.0,4.0),(6.0,1.0)
,(9.0,0.0),(11.0,0.0),(14.0,1.0),(16.0,4.0),(17.0,9.0),(17.0,12.0)
,(16.0,17.0),(14.0,20.0),(11.0,21.0),(9.0,21.0)]]))
,('1',(20.0,[[(6.0,17.0),(8.0,18.0),(11.0,21.0),(11.0,0.0)]]))
,('2',(20.0,[[(4.0,16.0),(4.0,17.0),(5.0,19.0),(6.0,20.0),(8.0,21.0),(12.0,21.0)
,(14.0,20.0),(15.0,19.0),(16.0,17.0),(16.0,15.0),(15.0,13.0)
,(13.0,10.0),(3.0,0.0),(17.0,0.0)]]))
,('3',(20.0,[[(3.0,4.0),(4.0,2.0),(5.0,1.0),(8.0,0.0),(11.0,0.0),(14.0,1.0)
,(16.0,3.0),(17.0,6.0),(17.0,8.0),(16.0,11.0),(15.0,12.0),(13.0,13.0)
,(10.0,13.0),(16.0,21.0),(5.0,21.0)]]))
,('4',(20.0,[[(13.0,0.0),(13.0,21.0),(3.0,7.0),(18.0,7.0)]]))
,('5',(20.0,[[(3.0,4.0),(4.0,2.0),(5.0,1.0),(8.0,0.0),(11.0,0.0),(14.0,1.0)
,(16.0,3.0),(17.0,6.0),(17.0,8.0),(16.0,11.0),(14.0,13.0),(11.0,14.0)
,(8.0,14.0),(5.0,13.0),(4.0,12.0),(5.0,21.0),(15.0,21.0)]]))
,('6',(20.0,[[(4.0,7.0),(5.0,10.0),(7.0,12.0),(10.0,13.0),(11.0,13.0),(14.0,12.0)
,(16.0,10.0),(17.0,7.0),(17.0,6.0),(16.0,3.0),(14.0,1.0),(11.0,0.0)
,(10.0,0.0),(7.0,1.0),(5.0,3.0),(4.0,7.0),(4.0,12.0),(5.0,17.0)
,(7.0,20.0),(10.0,21.0),(12.0,21.0),(15.0,20.0),(16.0,18.0)]]))
,('7',(20.0,[[(3.0,21.0),(17.0,21.0),(7.0,0.0)]]))
,('8',(20.0,[[(8.0,21.0),(5.0,20.0),(4.0,18.0),(4.0,16.0),(5.0,14.0),(7.0,13.0)
,(11.0,12.0),(14.0,11.0),(16.0,9.0),(17.0,7.0),(17.0,4.0),(16.0,2.0)
,(15.0,1.0),(12.0,0.0),(8.0,0.0),(5.0,1.0),(4.0,2.0),(3.0,4.0)
,(3.0,7.0),(4.0,9.0),(6.0,11.0),(9.0,12.0),(13.0,13.0),(15.0,14.0)
,(16.0,16.0),(16.0,18.0),(15.0,20.0),(12.0,21.0),(8.0,21.0)]]))
,('9',(20.0,[[(4.0,3.0),(5.0,1.0),(8.0,0.0),(10.0,0.0),(13.0,1.0),(15.0,4.0)
,(16.0,9.0),(16.0,14.0),(15.0,18.0),(13.0,20.0),(10.0,21.0)
,(9.0,21.0),(6.0,20.0),(4.0,18.0),(3.0,15.0),(3.0,14.0),(4.0,11.0)
,(6.0,9.0),(9.0,8.0),(10.0,8.0),(13.0,9.0),(15.0,11.0),(16.0,14.0)]]))
,(':',(10.0,[[(5.0,2.0),(4.0,1.0),(5.0,0.0),(6.0,1.0),(5.0,2.0)],
[(5.0,14.0),(4.0,13.0),(5.0,12.0),(6.0,13.0),(5.0,14.0)]]))
,(';',(10.0,[[(4.0,4.0),(5.0,3.0),(6.0,1.0),(6.0,1.0),(5.0,2.0),(4.0,1.0)
,(5.0,0.0),(6.0,1.0)],[(5.0,14.0),(4.0,13.0),(5.0,12.0),(6.0,13.0)
,(5.0,14.0)]]))
,('<',(24.0,[[(20.0,0.0),(4.0,9.0),(20.0,18.0)]]))
,('=',(26.0,[[(4.0,6.0),(22.0,6.0)],[(22.0,12.0),(4.0,12.0)]]))
,('>',(24.0,[[(4.0,0.0),(20.0,9.0),(4.0,18.0)]]))
,('?',(18.0,[[(3.0,16.0),(3.0,17.0),(4.0,19.0),(5.0,20.0),(7.0,21.0),(11.0,21.0)
,(13.0,20.0),(14.0,19.0),(15.0,17.0),(15.0,15.0),(14.0,13.0)
,(13.0,12.0),(9.0,10.0),(9.0,7.0)]
,[(9.0,2.0),(8.0,1.0),(9.0,0.0),(10.0,1.0),(9.0,2.0)]]))
,('@',(27.0,[[(11.0,5.0),(10.0,6.0),(9.0,8.0),(9.0,11.0),(10.0,14.0),(12.0,16.0)]
,[(18.0,13.0),(17.0,15.0),(15.0,16.0),(12.0,16.0),(10.0,15.0),(9.0,14.0)
,(8.0,11.0),(8.0,8.0),(9.0,6.0),(11.0,5.0),(14.0,5.0),(16.0,6.0)
,(17.0,8.0)],[(19.0,5.0),(18.0,6.0),(18.0,8.0),(19.0,16.0)]
,[(18.0,16.0),(17.0,8.0),(17.0,6.0),(19.0,5.0),(21.0,5.0),(23.0,7.0)
,(24.0,10.0),(24.0,12.0),(23.0,15.0),(22.0,17.0),(20.0,19.0)
,(18.0,20.0),(15.0,21.0),(12.0,21.0),(9.0,20.0),(7.0,19.0)
,(5.0,17.0),(4.0,15.0),(3.0,12.0),(3.0,9.0),(4.0,6.0),(5.0,4.0)
,(7.0,2.0),(9.0,1.0),(12.0,0.0),(15.0,0.0),(18.0,1.0),(20.0,2.0),(21.0,3.0)]]))
,('A',(18.0,[[(1.0,0.0),(9.0,21.0),(17.0,0.0)],[(14.0,7.0),(4.0,7.0)]]))
,('B',(21.0,[[(4.0,11.0),(13.0,11.0),(16.0,10.0),(17.0,9.0),(18.0,7.0),(18.0,4.0)
,(17.0,2.0),(16.0,1.0),(13.0,0.0),(4.0,0.0),(4.0,21.0),(13.0,21.0)
,(16.0,20.0),(17.0,19.0),(18.0,17.0),(18.0,15.0),(17.0,13.0)
,(16.0,12.0),(13.0,11.0)]]))
,('C',(21.0,[[(18.0,5.0),(17.0,3.0),(15.0,1.0),(13.0,0.0),(9.0,0.0),(7.0,1.0)
,(5.0,3.0),(4.0,5.0),(3.0,8.0),(3.0,13.0),(4.0,16.0),(5.0,18.0)
,(7.0,20.0),(9.0,21.0),(13.0,21.0),(15.0,20.0),(17.0,18.0),(18.0,16.0)]]))
,('D',(21.0,[[(4.0,0.0),(4.0,21.0),(11.0,21.0),(14.0,20.0),(16.0,18.0),(17.0,16.0)
,(18.0,13.0),(18.0,8.0),(17.0,5.0),(16.0,3.0),(14.0,1.0),(11.0,0.0),(4.0,0.0)]]))
,('E',(19.0,[[(4.0,11.0),(12.0,11.0)],[(17.0,21.0),(4.0,21.0),(4.0,0.0),(17.0,0.0)]]))
,('F',(18.0,[[(12.0,11.0),(4.0,11.0)],[(4.0,0.0),(4.0,21.0),(17.0,21.0)]]))
,('G',(21.0,[[(13.0,8.0),(18.0,8.0),(18.0,5.0),(17.0,3.0),(15.0,1.0),(13.0,0.0)
,(9.0,0.0),(7.0,1.0),(5.0,3.0),(4.0,5.0),(3.0,8.0),(3.0,13.0)
,(4.0,16.0),(5.0,18.0),(7.0,20.0),(9.0,21.0),(13.0,21.0),(15.0,20.0)
,(17.0,18.0),(18.0,16.0)]]))
,('H',(22.0,[[(4.0,0.0),(4.0,21.0)],[(4.0,11.0),(18.0,11.0)],[(18.0,21.0),(18.0,0.0)]]))
,('I',(8.0,[[(4.0,0.0),(4.0,21.0)]]))
,('J',(16.0,[[(2.0,7.0),(2.0,5.0),(3.0,2.0),(4.0,1.0),(6.0,0.0),(8.0,0.0),(10.0,1.0)
,(11.0,2.0),(12.0,5.0),(12.0,21.0)]]))
,('K',(21.0,[[(18.0,0.0),(9.0,12.0)],[(4.0,21.0),(4.0,0.0)],[(4.0,7.0),(18.0,21.0)]]))
,('L',(17.0,[[(4.0,21.0),(4.0,0.0),(16.0,0.0)]]))
,('M',(24.0,[[(4.0,0.0),(4.0,21.0),(12.0,0.0),(20.0,21.0),(20.0,0.0)]]))
,('N',(22.0,[[(4.0,0.0),(4.0,21.0),(18.0,0.0),(18.0,21.0)]]))
,('O',(22.0,[[(9.0,21.0),(7.0,20.0),(5.0,18.0),(4.0,16.0),(3.0,13.0),(3.0,8.0)
,(4.0,5.0),(5.0,3.0),(7.0,1.0),(9.0,0.0),(13.0,0.0),(15.0,1.0)
,(17.0,3.0),(18.0,5.0),(19.0,8.0),(19.0,13.0),(18.0,16.0),(17.0,18.0)
,(15.0,20.0),(13.0,21.0),(9.0,21.0)]]))
,('P',(21.0,[[(4.0,0.0),(4.0,21.0),(13.0,21.0),(16.0,20.0),(17.0,19.0),(18.0,17.0)
,(18.0,14.0),(17.0,12.0),(16.0,11.0),(13.0,10.0),(4.0,10.0)]]))
,('Q',(22.0,[[(9.0,21.0),(7.0,20.0),(5.0,18.0),(4.0,16.0),(3.0,13.0),(3.0,8.0)
,(4.0,5.0),(5.0,3.0),(7.0,1.0),(9.0,0.0),(13.0,0.0),(15.0,1.0)
,(17.0,3.0),(18.0,5.0),(19.0,8.0),(19.0,13.0),(18.0,16.0),(17.0,18.0)
,(15.0,20.0),(13.0,21.0),(9.0,21.0)],[(12.0,4.0),(18.0,2.0)]]))
,('R',(21.0,[[(4.0,0.0),(4.0,21.0),(13.0,21.0),(16.0,20.0),(17.0,19.0),(18.0,17.0)
,(18.0,15.0),(17.0,13.0),(16.0,12.0),(13.0,11.0),(4.0,11.0)]
,[(11.0,11.0),(18.0,0.0)]]))
,('S',(20.0,[[(3.0,3.0),(5.0,1.0),(8.0,0.0),(12.0,0.0),(15.0,1.0),(17.0,3.0)
,(17.0,6.0),(16.0,8.0),(15.0,9.0),(13.0,10.0),(7.0,12.0),(5.0,13.0)
,(4.0,14.0),(3.0,16.0),(3.0,18.0),(5.0,20.0),(8.0,21.0),(12.0,21.0)
,(15.0,20.0),(17.0,18.0)]]))
,('T',(16.0,[[(1.0,21.0),(15.0,21.0)],[(8.0,21.0),(8.0,0.0)]]))
,('U',(22.0,[[(4.0,21.0),(4.0,6.0),(5.0,3.0),(7.0,1.0),(10.0,0.0),(12.0,0.0)
,(15.0,1.0),(17.0,3.0),(18.0,6.0),(18.0,21.0)]]))
,('V',(18.0,[[(1.0,21.0),(9.0,0.0),(17.0,21.0)]]))
,('W',(24.0,[[(2.0,21.0),(7.0,0.0),(12.0,21.0),(17.0,0.0),(22.0,21.0)]]))
,('X',(20.0,[[(3.0,0.0),(17.0,21.0)],[(3.0,21.0),(17.0,0.0)]]))
,('Y',(18.0,[[(1.0,21.0),(9.0,11.0),(9.0,0.0)],[(9.0,11.0),(17.0,21.0)]]))
,('Z',(20.0,[[(3.0,21.0),(17.0,21.0),(3.0,0.0),(17.0,0.0)]]))
,('[',(14.0,[[(5.0,7.0),(5.0,25.0)],[(11.0,25.0),(4.0,25.0),(4.0,7.0),(11.0,7.0)]]))
,(']',(14.0,[[(3.0,7.0),(10.0,7.0),(10.0,25.0),(3.0,25.0)],[(9.0,25.0),(9.0,7.0)]]))
,('^',(16.0,[[(2.0,12.0),(8.0,18.0),(14.0,12.0)],[(11.0,15.0),(8.0,19.0),(5.0,15.0)]]))
,('_',(16.0,[[(0.0,2.0),(16.0,2.0)]]))
,('`',(10.0,[[(5.0,17.0),(6.0,16.0),(5.0,15.0),(4.0,16.0),(4.0,18.0),(5.0,20.0),(6.0,21.0)]]))
,('a',(19.0,[[(15.0,0.0),(15.0,14.0)],[(15.0,11.0),(13.0,13.0),(11.0,14.0),(8.0,14.0)
,(6.0,13.0),(4.0,11.0),(3.0,8.0),(3.0,6.0),(4.0,3.0)
,(6.0,1.0),(8.0,0.0),(11.0,0.0),(13.0,1.0),(15.0,3.0)]]))
,('b',(19.0,[[(4.0,11.0),(6.0,13.0),(8.0,14.0),(11.0,14.0),(13.0,13.0),(15.0,11.0)
,(16.0,8.0),(16.0,6.0),(15.0,3.0),(13.0,1.0),(11.0,0.0),(8.0,0.0)
,(6.0,1.0),(4.0,3.0)],[(4.0,0.0),(4.0,21.0)]]))
,('c',(18.0,[[(15.0,3.0),(13.0,1.0),(11.0,0.0),(8.0,0.0),(6.0,1.0),(4.0,3.0),(3.0,6.0)
,(3.0,8.0),(4.0,11.0),(6.0,13.0),(8.0,14.0),(11.0,14.0),(13.0,13.0),(15.0,11.0)]]))
,('d',(19.0,[[(15.0,11.0),(13.0,13.0),(11.0,14.0),(8.0,14.0),(6.0,13.0),(4.0,11.0)
,(3.0,8.0),(3.0,6.0),(4.0,3.0),(6.0,1.0),(8.0,0.0),(11.0,0.0),(13.0,1.0)
,(15.0,3.0)],[(15.0,0.0),(15.0,21.0)]]))
,('e',(18.0,[[(3.0,8.0),(15.0,8.0),(15.0,10.0),(14.0,12.0),(13.0,13.0),(11.0,14.0)
,(8.0,14.0),(6.0,13.0),(4.0,11.0),(3.0,8.0),(3.0,6.0),(4.0,3.0),(6.0,1.0)
,(8.0,0.0),(11.0,0.0),(13.0,1.0),(15.0,3.0)]]))
,('f',(12.0,[[(2.0,14.0),(9.0,14.0)],[(10.0,21.0),(8.0,21.0),(6.0,20.0),(5.0,17.0)
,(5.0,0.0)]]))
,('g',(19.0,[[(6.0,6.0),(8.0,7.0),(11.0,7.0),(13.0,6.0),(14.0,5.0),(15.0,2.0)
,(15.0,14.0)],[(15.0,11.0),(13.0,13.0),(11.0,14.0),(8.0,14.0),(6.0,13.0)
,(4.0,11.0),(3.0,8.0),(3.0,6.0),(4.0,3.0),(6.0,1.0),(8.0,0.0)
,(11.0,0.0),(13.0,1.0),(15.0,3.0)]]))
,('h',(19.0,[[(4.0,21.0),(4.0,0.0)],[(4.0,10.0),(7.0,13.0),(9.0,14.0),(12.0,14.0)
,(14.0,13.0),(15.0,10.0),(15.0,0.0)]]))
,('i',(8.0,[[(3.0,21.0),(4.0,20.0),(5.0,21.0),(4.0,22.0),(3.0,21.0)]
,[(4.0,14.0),(4.0,0.0)]]))
,('j',(10.0,[[(1.0,7.0),(3.0,7.0),(5.0,6.0),(6.0,3.0),(6.0,14.0)]
,[(5.0,21.0),(6.0,20.0),(7.0,21.0),(6.0,22.0),(5.0,21.0)]]))
,('k',(17.0,[[(4.0,21.0),(4.0,0.0)],[(4.0,4.0),(14.0,14.0)],[(8.0,8.0),(15.0,0.0)]]))
,('l',(8.0,[[(4.0,0.0),(4.0,21.0)]]))
,('m',(30.0,[[(4.0,0.0),(4.0,14.0)],[(4.0,10.0),(7.0,13.0),(9.0,14.0),(12.0,14.0)
,(14.0,13.0),(15.0,10.0),(15.0,0.0)]
,[(15.0,10.0),(18.0,13.0),(20.0,14.0),(23.0,14.0),(25.0,13.0)
,(26.0,10.0),(26.0,0.0)]]))
,('n',(19.0,[[(4.0,0.0),(4.0,14.0)],[(4.0,10.0),(7.0,13.0),(9.0,14.0)
,(12.0,14.0),(14.0,13.0),(15.0,10.0),(15.0,0.0)]]))
,('o',(19.0,[[(8.0,14.0),(6.0,13.0),(4.0,11.0),(3.0,8.0),(3.0,6.0)
,(4.0,3.0),(6.0,1.0),(8.0,0.0),(11.0,0.0),(13.0,1.0),(15.0,3.0)
,(16.0,6.0),(16.0,8.0),(15.0,11.0),(13.0,13.0),(11.0,14.0),(8.0,14.0)]]))
,('p',(19.0,[[(4.0,7.0),(4.0,14.0)],[(4.0,11.0),(6.0,13.0),(8.0,14.0)
,(11.0,14.0),(13.0,13.0),(15.0,11.0)
,(16.0,8.0),(16.0,6.0),(15.0,3.0),(13.0,1.0)
,(11.0,0.0),(8.0,0.0),(6.0,1.0),(4.0,3.0)]]))
,('q',(19.0,[[(15.0,7.0),(15.0,14.0)],[(15.0,11.0),(13.0,13.0),(11.0,14.0)
,(8.0,14.0),(6.0,13.0),(4.0,11.0),(3.0,8.0)
,(3.0,6.0),(4.0,3.0),(6.0,1.0),(8.0,0.0)
,(11.0,0.0),(13.0,1.0),(15.0,3.0)]]))
,('r',(13.0,[[(4.0,0.0),(4.0,14.0)]
,[(4.0,8.0),(5.0,11.0),(7.0,13.0),(9.0,14.0),(12.0,14.0)]]))
,('s',(17.0,[[(3.0,3.0),(4.0,1.0),(7.0,0.0),(10.0,0.0),(13.0,1.0)
,(14.0,3.0),(14.0,4.0),(13.0,6.0),(11.0,7.0),(6.0,8.0),(4.0,9.0)
,(3.0,11.0),(4.0,13.0),(7.0,14.0),(10.0,14.0),(13.0,13.0)
,(14.0,11.0)]]))
,('t',(12.0,[[(9.0,14.0),(2.0,14.0)],[(5.0,21.0),(5.0,4.0),(6.0,1.0)
,(8.0,0.0),(10.0,0.0)]]))
,('u',(19.0,[[(4.0,14.0),(4.0,4.0),(5.0,1.0)
,(7.0,0.0),(10.0,0.0),(12.0,1.0),(15.0,4.0)],[(15.0,0.0),(15.0,14.0)]]))
,('v',(16.0,[[(2.0,14.0),(8.0,0.0),(14.0,14.0)]]))
,('w',(22.0,[[(3.0,14.0),(7.0,0.0),(11.0,14.0),(15.0,0.0),(19.0,14.0)]]))
,('x',(17.0,[[(3.0,0.0),(14.0,14.0)],[(3.0,14.0),(14.0,0.0)]]))
,('y',(16.0,[[(2.0,14.0),(8.0,0.0)],[(1.0,7.0),(2.0,7.0),(4.0,6.0)
,(6.0,4.0),(8.0,0.0),(14.0,14.0)]]))
,('z',(17.0,[[(3.0,14.0),(14.0,14.0),(3.0,0.0),(14.0,0.0)]]))
,('{',(14.0,[[(7.0,6.0),(6.0,4.0),(6.0,2.0),(7.0,0.0),(8.0,1.0)
,(9.0,3.0),(9.0,5.0),(8.0,7.0),(4.0,9.0),(8.0,11.0)
,(9.0,13.0),(9.0,15.0),(8.0,17.0),(7.0,18.0),(6.0,20.0)
,(6.0,22.0),(7.0,24.0)]
,[(9.0,25.0),(7.0,24.0),(6.0,23.0),(5.0,21.0),(5.0,19.0),(6.0,17.0)
,(7.0,16.0),(8.0,14.0),(8.0,12.0),(6.0,10.0)]
,[(6.0,8.0),(8.0,6.0),(8.0,4.0),(7.0,2.0),(6.0,1.0),(5.0,1.0)
,(5.0,3.0),(6.0,5.0),(7.0,6.0),(9.0,7.0)]]))
,('|',(8.0,[[(4.0,7.0),(4.0,25.0)]]))
,('}',(14.0,[[(5.0,7.0),(7.0,6.0),(8.0,5.0),(9.0,3.0),(9.0,1.0)
,(8.0,1.0),(7.0,2.0),(6.0,4.0),(6.0,6.0),(8.0,8.0)]
,[(8.0,10.0),(6.0,12.0),(6.0,14.0),(7.0,16.0),(8.0,17.0)
,(9.0,19.0),(9.0,21.0),(8.0,23.0),(7.0,24.0),(5.0,25.0)]
,[(7.0,24.0),(8.0,22.0),(8.0,20.0),(7.0,18.0),(6.0,17.0)
,(5.0,15.0),(5.0,13.0),(6.0,11.0),(10.0,9.0),(6.0,7.0)
,(5.0,5.0),(5.0,3.0),(6.0,1.0),(7.0,0.0),(8.0,2.0)
,(8.0,4.0),(7.0,6.0)]]))
,('~',(24.0,[[(3.0,6.0),(3.0,8.0),(4.0,11.0),(6.0,12.0),(8.0,12.0)
,(10.0,11.0),(14.0,8.0),(16.0,7.0),(18.0,7.0),(20.0,8.0)
,(21.0,10.0)]
,[(21.0,12.0),(21.0,10.0),(20.0,7.0),(18.0,6.0),(16.0,6.0)
,(14.0,7.0),(10.0,10.0),(8.0,11.0),(6.0,11.0),(4.0,10.0),(3.0,8.0)]]))
]