{-# LANGUAGE OverloadedStrings #-} module View.Html.Ad ( renderAds ) where import Data.Text (Text) import qualified Data.Text as T import Data.Text.Lazy (toStrict) import Data.Maybe (catMaybes) import Data.List (intersperse) import Data.Map (Map) import qualified Data.Map as M import Text.Blaze.Html import Text.Blaze.Html5 (Html) import qualified Text.Blaze.Html5 as H import qualified Text.Blaze.Html5.Attributes as A import Text.Blaze.Html.Renderer.Text (renderHtml) import Text.Blaze.Internal (textValue) import Model.Ad (Ad) import qualified Model.Ad as Ad import Model.Resume (Resume) import qualified Model.Resume as Resume import Model.Detail (Detail) import qualified Model.Detail as Detail import Model.URL import Conf (Conf) import qualified Conf import View.Html.Design renderAds :: Conf -> [Ad] -> Text renderAds conf = toStrict . renderHtml . (adsHtml conf) adsHtml :: Conf -> [Ad] -> Html adsHtml conf ads = do mapM_ (adHtml conf) ads adHtml :: Conf -> Ad -> Html adHtml conf ad = let resume = Ad.resume ad detail = Ad.detail ad in do resumeHtml resume detailHtml conf detail resumeHtml :: Resume -> Html resumeHtml resume = do H.h1 $ do (toHtml . Resume.name $ resume) case Resume.price resume of Just price -> H.span ! A.class_ "price" ! A.style (textValue . toStrict $ priceDesign) $ toHtml price Nothing -> H.span "" linkHtml (Resume.url resume) detailHtml :: Conf -> Detail -> Html detailHtml conf detail = do propertiesHtml (Conf.properties conf) (Detail.properties detail) case Detail.description detail of Just description -> descriptionHtml description Nothing -> H.div "" mapM_ imageLinkHtml (Detail.images detail) propertiesHtml :: [Text] -> Map Text Text -> Html propertiesHtml keys properties = H.dl ! A.style (textValue . toStrict $ dlDesign) $ sequence_ (catMaybes $ map (propertyHtml properties) keys) propertyHtml :: Map Text Text -> Text -> Maybe Html propertyHtml properties key = fmap (\value -> do H.dt $ (toHtml key) H.dd ! A.style (textValue . toStrict $ ddDesign) $ (toHtml value) ) (M.lookup key properties) descriptionHtml :: Text -> Html descriptionHtml = H.p . sequence_ . intersperse H.br . fmap toHtml . T.lines linkHtml :: URL -> Html linkHtml url = H.a ! A.href (textValue url) $ (toHtml url) imageLinkHtml :: URL -> Html imageLinkHtml url = H.a ! A.href (textValue url) $ H.img ! A.src (textValue url) ! A.alt (textValue url)