{-# OPTIONS -Wall #-} module Symbols where import Wumpus.Basic.Chains import Wumpus.Basic.Graphic import Wumpus.Basic.SafeFonts import Wumpus.Core -- package: wumpus-core import Data.AffineSpace -- package: vector-space import Control.Monad import Prelude hiding ( pi, product ) import System.Directory main :: IO () main = do createDirectoryIfMissing True "./out/" let pic1 = runDrawingU std_ctx symbols writeEPS "./out/symbols.eps" pic1 writeSVG "./out/symbols.svg" pic1 std_ctx :: DrawingContext std_ctx = fontface times_roman $ standardContext 12 -- Because the font changes, we draw the all the symbols in one -- run and all the labels in a second run. This helps Wumpus-Core -- generate better PostScript as there are less changes to the -- /graphics state/. -- symbols :: DDrawing symbols = drawTracing $ do localize (fontface symbol) $ zipWithM_ sdraw all_letters ps zipWithM_ ldraw all_letters ps where sdraw (s,_) pt = draw $ textline s `at` pt ldraw (_,name) pt = draw $ textline name `at` pt .+^ hvec 16 ps = unchain (coordinateScalingContext 100 20) $ tableDown 30 6 all_letters :: [(String, String)] all_letters = [ ("Α", "Alpha") , ("Β", "Beta") , ("Χ", "Chi") , ("Δ", "Delta") , ("Ε", "Epsilon") , ("Η", "Eta") , ("&Euro;", "Euro") , ("Γ", "Gamma") , ("&Ifraktur;", "Ifraktur") , ("Ι", "Iota") , ("Κ", "Kappa") , ("Λ", "Lambda") , ("Μ", "Mu") , ("Ν", "Nu") , ("Ω", "Omega") , ("Ο", "Omicron") , ("Φ", "Phi") , ("Π", "Pi") , ("Ψ", "Psi") , ("&Rfraktur;", "Rfraktur") , ("Ρ", "Rho") , ("Σ", "Sigma") , ("Τ", "Tau") , ("Θ", "Theta") , ("Υ", "Upsilon") , ("&Upsilon1;", "Upsilon1") , ("Ξ", "Xi") , ("Ζ", "Zeta") , ("ℵ", "aleph") , ("α", "alpha") , ("&ersand;", "ampersand") , ("∠", "angle") , ("&angleleft;", "angleleft") , ("&angleright;", "angleright") , ("&approxequal;", "approxequal") -- , ("&arrowboth;", "arrowboth") , ("&arrowdblboth;", "arrowdblboth") , ("&arrowdbldown;", "arrowdbldown") , ("&arrowdblleft;", "arrowdblleft") , ("&arrowdblright;", "arrowdblright") , ("&arrowdblup;", "arrowdblup") , ("&arrowdown;", "arrowdown") , ("&arrowleft;", "arrowleft") , ("&arrowright;", "arrowright") , ("&arrowup;", "arrowup") , ("&asteriskmath;", "asteriskmath") , ("&bar;", "bar") , ("β", "beta") , ("&braceleft;", "braceleft") , ("&braceright;", "braceright") , ("&bracketleft;", "bracketleft") , ("&bracketright;", "bracketright") , ("•", "bullet") , ("&carriagereturn;", "carriagereturn") , ("χ", "chi") -- , ("&circlemultiply;", "circlemultiply") , ("&circleplus;", "circleplus") , ("&club;", "club") , (":", "colon") , (",", "comma") , ("&congruent;", "congruent") , ("©rightsans;", "copyrightsans") , ("©rightserif;", "copyrightserif") , ("°ree;", "degree") , ("δ", "delta") , ("⋄", "diamond") , ("÷", "divide") , ("&dotmath;", "dotmath") , ("&eight;", "eight") , ("&element;", "element") , ("&ellipsis;", "ellipsis") , ("∅", "emptyset") , ("ε", "epsilon") , ("&equal;", "equal") , ("&equivalence;", "equivalence") , ("η", "eta") , ("&exclam;", "exclam") , ("&existential;", "existential") , ("&five;", "five") , ("&florin;", "florin") , ("&four;", "four") , ("&fraction;", "fraction") , ("γ", "gamma") , ("&gradient;", "gradient") , ("&greater;", "greater") , ("&greaterequal;", "greaterequal") , ("&heart;", "heart") , ("&infinity;", "infinity") , ("&integral;", "integral") -- , ("&intersection;", "intersection") , ("ι", "iota") , ("κ", "kappa") , ("λ", "lambda") , ("&less;", "less") , ("&lessequal;", "lessequal") , ("&logicaland;", "logicaland") , ("&logicalnot;", "logicalnot") , ("&logicalor;", "logicalor") , ("◊", "lozenge") , ("−", "minus") , ("&minute;", "minute") , ("μ", "mu") , ("&multiply;", "multiply") , ("&nine;", "nine") , ("¬element;", "notelement") , ("¬equal;", "notequal") , ("¬subset;", "notsubset") , ("ν", "nu") , ("&numbersign;", "numbersign") , ("ω", "omega") , ("&omega1;", "omega1") , ("ο", "omicron") , ("&one;", "one") , ("&parenleft;", "parenleft") , ("&parenright;", "parenright") -- , ("&partialdiff;", "partialdiff") , ("&percent;", "percent") , (".", "period") , ("&perpendicular;", "perpendicular") , ("φ", "phi") , ("&phi1;", "phi1") , ("π", "pi") , ("+", "plus") , ("&plusminus;", "plusminus") , ("&product;", "product") , ("&propersubset;", "propersubset") , ("&propersuperset;", "propersuperset") , ("&proportional;", "proportional") , ("ψ", "psi") , ("&question;", "question") , ("&radical;", "radical") , ("&radicalex;", "radicalex") , ("&reflexsubset;", "reflexsubset") , ("&reflexsuperset;", "reflexsuperset") , ("®istersans;", "registersans") , ("®isterserif;", "registerserif") , ("ρ", "rho") -- , ("&second;", "second") , ("&semicolon;", "semicolon") , ("&seven;", "seven") , ("σ", "sigma") , ("&sigma1;", "sigma1") , ("&similar;", "similar") , ("&six;", "six") , ("&slash;", "slash") , ("&space;", "space") , ("&spade;", "spade") , ("&suchthat;", "suchthat") , ("&summation;", "summation") , ("τ", "tau") , ("∴", "therefore") , ("θ", "theta") , ("&theta1;", "theta1") , ("&three;", "three") , ("&trademarksans;", "trademarksans") , ("&trademarkserif;", "trademarkserif") , ("&two;", "two") , ("&underscore;", "underscore") , ("&union;", "union") , ("&universal;", "universal") , ("υ", "upsilon") , ("&weierstrass;", "weierstrass") , ("ξ", "xi") , ("&zero;", "zero") , ("ζ", "zeta") ]