module ImageF where import Control.Applicative import Fudgets import ParseURL(parseURL) import URL(URL,joinURL,url2str) import PixmapDisplayF(pixmapDisplayF',PixmapId) import StyleAttrs type ImageOutput = (URL,Maybe Size) type ImageInput = ((URL,Maybe Size),(Size,PixmapId)) imageF = imageF' 3 imageF' :: Size -> URL -> (Maybe String,TagAttrs) -> F ImageInput ImageOutput imageF' border purl (src,attrs) = maybe altF imgF (src >>= parseURL) where altF = sepF border $ labelF alt alt = maybe "??" id $ lookupAttr "ALT" attrs optSize = Point <$> lookupWidth attrs <*> lookupHeight attrs imgF rurl = sepF border $ putF (url,optSize) (pixmapDisplayF' optSize) >=^< snd' where snd' ((url',_),y) = ctrace "imageF" (url2str url,url2str url') $ y url = joinURL purl rurl --pick ((url',_),img) = if url'==url then Just img else Nothing