module FontSpec where import Fudgets(argReadKey,argKey) import Data.Ix data FontSpec = F { charset :: CharSet, weight :: Weight, spacing :: Spacing, serif :: Serif, slant :: Slant, fontsize :: FontSize } deriving (Bounded,Eq,Ord,Ix) defaultFont = F IsoLatin1 Medium Proportional Serif Roman fontsize where fontsize = FontSize (argReadKey "fontsize" 4) bigger = adjsize 1 smaller = adjsize (-1) adjsize n fs@(F {fontsize=fontsize}) = fs{fontsize=adjsize' n fontsize} adjsize' n (FontSize s) = FontSize (s+n) setsize n fs = fs{fontsize=n} setWeight w fs = fs{weight=w} setCharset s fs = fs{charset=s} setSlant s fs = fs{slant=s} setSpacing s fs = fs{spacing=s} setSerif s fs = fs{serif=s} data CharSet = IsoLatin1 | AdobeSymbol deriving (Bounded,Eq,Ord,Ix) data Weight = Medium | Bold deriving (Bounded,Eq,Ord,Ix) data Spacing = Fixed | Proportional deriving (Bounded,Eq,Ord,Ix) data Serif = Serif | SansSerif deriving (Bounded,Eq,Ord,Ix) data Slant = Roman | Italic deriving (Bounded,Eq,Ord,Ix) newtype FontSize = FontSize Int deriving (Eq,Ord,Ix) fontname (F {charset=charset,weight=weight,spacing=spacing,serif=serif,slant=slant,fontsize=fontsize}) = "-*-"++fmly++wght++slnt++"-*-*"++pxlsz++"-*-*-*-*-*-"++encdng where (fmly,encdng) = case charset of AdobeSymbol -> ("symbol","*-*") _ -> (case (spacing,serif) of (Fixed,Serif) -> fixedFamily (Fixed,SansSerif) -> fixedsansFamily (Proportional,SansSerif) -> sansFamily (Proportional,Serif) -> serifFamily, normalcharset) wght = case weight of Bold -> "-bold"; _ -> "-medium" slnt = case slant of Italic -> italic; _ -> "-r" pxlsz = "-"++show (pixelsize fontsize) italic = if fmly `elem` ["courier","helvetica"] then "-o" else "-i" serifFamily = argKey "serif" "new century schoolbook" sansFamily = argKey "sans" "helvetica" fixedFamily = argKey "fixed" "courier" fixedsansFamily = argKey "fixedsans" fixedFamily --"lucidatypewriter" normalcharset = argKey "charset" "iso8859-1" pixelsize (FontSize n) = case n of 3 -> 12 4 -> 14 5 -> 18 6 -> 24 7 -> 34 8 -> 40 2 -> 10 1 -> 8 _ -> if n<3 then 7 else 50 instance Bounded FontSize where minBound = FontSize 0 maxBound = FontSize 9