blob: 53e63bf49273933d73aaac97d4fef3e3cc414c66 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
|
{-# 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 qualified View.Html.Design as 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 $ Design.price)
$ toHtml price
Nothing ->
H.span ""
if Resume.isPro resume
then
H.span
! A.class_ "pro"
! A.style (textValue . toStrict $ Design.pro)
$ "PRO"
else
""
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 $ Design.definitionList)
$ 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 $ Design.definitionDescription) $ (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)
|