{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Plugin.Photo.View where import Bamboo.Plugin.Photo.Model import MPSUTF8 import Prelude hiding ((.), (>), (^), (/), id, div) import Text.XHtml.Strict hiding (select, sub, meta) id :: String -> HtmlAttr id = identifier div_id :: String -> Html -> Html div_id s = thediv ! [id s] div_class :: String -> Html -> Html div_class s = thediv ! [theclass s] div_class_id :: String -> String -> Html -> Html div_class_id x y = thediv ! [theclass x, id y] span :: Html -> Html div :: Html -> Html d :: Html -> Html ul :: Html -> Html span = thespan div = thediv d = div ul = ulist klass :: String -> HtmlAttr klass = theclass c :: String -> Html -> Html c x = d ! [klass x] -- i x = d ! [id x] ic, ci:: String -> String -> Html -> Html ic x y = d ! [id x, klass y] ci x y = ic y x link :: String -> Html -> HotLink link = hotlink img :: Html space_html :: Html img = image space_html = primHtml " " render :: Album -> Html render = show_album empty_html :: Html empty_html = toHtml "" show_album :: Album -> Html show_album x = case x.album_type of Fade -> show_fade x Galleria -> show_galleria x SlideViewer -> show_slide_viewer x Popeye -> show_popeye x show_popeye :: Album -> Html show_popeye x = c "popeye" << ul << x.data_list.map picture_li where picture_li (l, t, i) = li << link l << img ! [src i, alt t] show_slide_viewer :: Album -> Html show_slide_viewer x = ul ! [id "slide-viewer", klass "svw"] << x.data_list.map picture_li where picture_li (_, t, i) = li << img ! [src i, alt t] show_galleria :: Album -> Html show_galleria x = ul ! [klass "gallery"] << x.data_list.map picture_li where picture_li (_, t, i) = li << img ! [src i, alt t] show_fade :: Album -> Html show_fade x = ul ! [klass "fade-album"] << x.data_list.map picture_li where picture_li (l, t, i) = li << [ toHtml $ link l << img ! [src i, alt t] , if x.show_description then p << t else empty_html ]