module FontProperty (fontProperty) where
import Font(FontProp(..))
import InternAtom(internAtom,atomName)
import Xtypes(Atom(..))
fontProperty :: [FontProp] -> String -> (Maybe String -> f hi ho) -> f hi ho
fontProperty [FontProp]
fsprops String
propn Maybe String -> f hi ho
cont =
let match :: Atom -> FontProp -> Bool
match Atom
an' (FontProp Atom
an Int
vn) = Atom
an' forall a. Eq a => a -> a -> Bool
== Atom
an
valatom :: FontProp -> Int
valatom (FontProp Atom
an Int
vn) = Int
vn
in forall {f :: * -> * -> *} {hi} {ho}.
FudgetIO f =>
String -> Bool -> (Atom -> f hi ho) -> f hi ho
internAtom String
propn Bool
True forall a b. (a -> b) -> a -> b
$ \Atom
pna ->
case Atom
pna of
Atom Int
0 -> Maybe String -> f hi ho
cont forall a. Maybe a
Nothing
Atom
a ->
case (forall a b. (a -> b) -> [a] -> [b]
map FontProp -> Int
valatom (forall a. (a -> Bool) -> [a] -> [a]
filter (Atom -> FontProp -> Bool
match Atom
a) [FontProp]
fsprops)) of
[] -> Maybe String -> f hi ho
cont forall a. Maybe a
Nothing
Int
vn:[Int]
_ -> forall {f :: * -> * -> *} {hi} {ho}.
FudgetIO f =>
Atom -> (Maybe String -> f hi ho) -> f hi ho
atomName (Int -> Atom
Atom (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
vn)) forall a b. (a -> b) -> a -> b
$ \Maybe String
vna -> Maybe String -> f hi ho
cont Maybe String
vna