breve/src/Views.hs

52 lines
1.6 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
module Views where
import Data.Text (Text)
import Data.Text.Lazy (toStrict)
import Text.Blaze.Html.Renderer.Text (renderHtml)
import Text.Blaze.Html5 as H
import Text.Blaze.Html5.Attributes as A
import qualified Web.Spock.Core as S
render :: Html -> S.ActionT IO ()
render = S.html . toStrict . renderHtml
done :: Text -> Html
done url = template $ do
"here's your new link: "
a ! href (toValue url) $ (toHtml url)
index :: Html
index = template $ do
H.form ! method "POST" $ do
"your url:"
input ! type_ "text" ! name "url"
input ! type_ "submit" ! value "go"
message :: Text -> Html
message = template . toHtml
template :: Html -> Html
template fill =
docTypeHtml $ do
H.head $ do
H.title "breve: url shortener"
meta ! name "description" ! content "url shortener"
meta ! name "keywords" ! content "url, shortener"
meta ! name "author" ! content "Michele Guerini Rocco"
meta ! charset "utf-8"
link ! rel "stylesheet" ! href "main.css" ! type_ "text/css"
link ! rel "apple-touch-icon" ! href "icon-big.png"
link ! rel "icon" ! type_ "image/png" ! href "/icon-medium.png" ! sizes "96x96"
link ! rel "icon" ! type_ "image/png" ! href "/icon-small.png" ! sizes "16x16"
body $ do
header $ do
h1 $ a ! href "/" $ "BREVE"
h2 "a url shortener"
H.div ! A.id "center" $ fill
footer $ do
"breve is open "
a ! href "https://github.com/rnhmjoj/breve" $ "source"
H.span "© Rnhmjoj"