-- |
-- Module      : PlotFont.hs
-- Copyright   : (c) 2015, M J Oldfield
-- Stability   : Experimental
--
-- == Rationale
-- 
-- There are many good looking fonts which optimize for appearance. I wanted
-- some cruder fonts which had a simpler representation: a relatively small
-- number of straight lines which could easily be plotted by a machine, or
-- perhaps a person.
--
-- So this might be a good package for you if you're going to do something
-- with the coordinates afterwards, but not if you just want to render some
-- text.
--
--
-- == License discussion
--
-- My code is licensed under the GPL version 2 or later
-- see http://www.gnu.org/copyleft/gpl.html
--
-- The data in canvasText and fallbackGlyph come from Jim Studt's
-- canvastext.js: http://jim.studt.net/canvastext/ which he placed
-- in the public domain. He cites the original source as the
-- Hershey fonts: https://en.wikipedia.org/wiki/Hershey_fonts
--
-- The Hershey fonts appear to have this license:
--
--    1. The following acknowledgements must be distributed with
--       the font data:
--       - The Hershey Fonts were originally created by Dr.
--         A. V. Hershey while working at the U. S.
--         National Bureau of Standards.
--       - The format of the Font data in this distribution
--         was originally created by
--           James Hurt
--           Cognition, Inc.
--           900 Technology Park Drive
--           Billerica, MA 01821
--           (mit-eddie!ci-dandelion!hurt)
--
--	2. The font data in this distribution may be converted into
--         any other format *EXCEPT* the format distributed by
--	   the U.S. NTIS (which organization holds the rights
--	   to the distribution and use of the font data in that
--	   particular format). Not that anybody would really
--	   *want* to use their format... each point is described
--	   in eight bytes as "xxx yyy:", where xxx and yyy are
--	   the coordinate values as ASCII numbers.
--
-- It is not clear to me if Mr Studt used 'this distribution'.

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)

-- |'PFStroke' is the basic graphic element: a series of points
-- joined by straight lines.

type PFStroke = [PFPoint]

-- |'PFGlyph' is the basic element of the font: the symbol's width, plus
-- the strokes we need to draw it.
type PFGlyph  = (PFWidth, [PFStroke])

dist:: PFPoint -> PFPoint -> Double
dist (xa,ya) (xb,yb) = sqrt $ (xa - xb)^2 + (ya - yb)^2

-- |The 'PlotFont' type wraps the basic font: a map from 'Char' to 'PFGlyph'                      
data PlotFont = PlotFont (M.Map Char PFGlyph)

--
-- code to render strings into strokes
--

-- | Given a 'PlotFont' and a 'String', return
--
--   * 'Right' strokes if the 'String' can be rendered.
--
--   * 'Left' error otherwise.
--
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                   
              
-- this is like T.sequence but gives all the Lefts if any exist
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

-- | A varient of 'render' which replaces unknown characters with
-- a question mark.
--
-- It is guaranteed to render something, and thus
-- useful if you want to ignore the possibility of errors e.g.
-- because you're manually checking the output.
--
render' :: PlotFont -> String -> [PFStroke]
render' f = renderLine 0 . map (getGlyph' f)

getGlyph' :: PlotFont -> Char -> PFGlyph
getGlyph' (PlotFont m) c = M.findWithDefault fallbackGlyph c m

-- this is the ? from canvastextFont, duplicated here to avoid constraining
-- ctF to contain ?
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))

-- | Given a set of strokes, try to optimize their order and direction
-- so as to prefer:
--
--  *  fewer strokes;
--
--  *  smaller gaps between strokes;
--
--  *  left-most starting position;
--
--  *  bottom-most starting position.
--
-- The code does a reasonable job of improving fonts where no thought has
-- been given to this, but hand-tweaking is still better.
--
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]

-- given an arrangement of strokes, return a score (lower better),
-- preferring (in order):
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

------------------------------------------------------------------------
--
-- ex 
--
-- | The Hershey font used by <http://jim.studt.net/canvastext/canvastext.js canvastext.js>
-- which provides @!\"#$%&()*+,-.\/0123456789:;\<=>?\@ABCDEFGHIJKLMNOPQRSTUVWXYZ[]^_\`abcdefghijklmnopqrstuvwxyz{|}~@
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)]]))
       ]