2012-02-23 13:20:29 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
|
2012-02-22 22:03:31 +01:00
|
|
|
|
|
|
|
module Main where
|
|
|
|
|
2012-02-23 03:30:14 +01:00
|
|
|
import Control.Monad (msum, mzero)
|
|
|
|
import Data.Monoid (mempty)
|
|
|
|
import Data.ByteString.Char8 (ByteString)
|
|
|
|
import Data.Text hiding (map, length, zip, head)
|
|
|
|
import Data.Time
|
|
|
|
import Database.CouchDB
|
|
|
|
import Happstack.Server
|
2012-02-23 13:20:29 +01:00
|
|
|
import Network.CGI (liftIO)
|
2012-02-22 22:03:31 +01:00
|
|
|
import Text.Blaze (toValue, preEscapedString)
|
|
|
|
import Text.Blaze.Html5 (Html, (!), a, form, input, p, toHtml, label)
|
|
|
|
import Text.Blaze.Html5.Attributes (action, enctype, href, name, size, type_, value)
|
|
|
|
import qualified Text.Blaze.Html5 as H
|
|
|
|
import qualified Text.Blaze.Html5.Attributes as A
|
2012-02-23 03:30:14 +01:00
|
|
|
import Text.JSON.Generic
|
2012-02-22 22:03:31 +01:00
|
|
|
|
2012-02-23 03:30:14 +01:00
|
|
|
import Blog
|
2012-02-22 22:03:31 +01:00
|
|
|
|
|
|
|
tmpPolicy :: BodyPolicy
|
|
|
|
tmpPolicy = (defaultBodyPolicy "./tmp/" 0 1000 1000)
|
|
|
|
|
|
|
|
|
|
|
|
--TazBlog version
|
|
|
|
version = ("2.2b" :: String)
|
|
|
|
|
|
|
|
main :: IO()
|
|
|
|
main = do
|
2012-02-23 03:30:14 +01:00
|
|
|
putStrLn ("TazBlog " ++ version ++ " in Haskell starting")
|
|
|
|
simpleHTTP nullConf tazBlog
|
2012-02-22 22:03:31 +01:00
|
|
|
|
|
|
|
tazBlog :: ServerPart Response
|
|
|
|
tazBlog = do
|
2012-02-23 03:30:14 +01:00
|
|
|
msum [ dir "en" $ blogHandler EN
|
|
|
|
, dir "de" $ blogHandler DE
|
|
|
|
, do nullDir
|
|
|
|
ok $ showIndex DE
|
|
|
|
, do dir " " $ nullDir
|
|
|
|
seeOther ("https://plus.google.com/115916629925754851590" :: String) (toResponse ())
|
|
|
|
, dir "res" $ serveDirectory DisableBrowsing [] "../res"
|
|
|
|
, serveDirectory DisableBrowsing [] "../res"
|
|
|
|
]
|
2012-02-22 22:03:31 +01:00
|
|
|
|
|
|
|
blogHandler :: BlogLang -> ServerPart Response
|
|
|
|
blogHandler lang =
|
2012-02-23 03:30:14 +01:00
|
|
|
msum [ path $ \(year :: Int) -> path $ \(month :: Int) -> path $ --single entry
|
2012-02-23 13:20:29 +01:00
|
|
|
\(day :: Int) -> path $ \(id_ :: String) -> showEntry year month day id_
|
2012-02-23 03:30:14 +01:00
|
|
|
, do nullDir
|
|
|
|
ok $ showIndex lang
|
|
|
|
]
|
2012-02-22 22:03:31 +01:00
|
|
|
|
2012-02-23 13:20:29 +01:00
|
|
|
showEntry :: Int -> Int -> Int -> String -> ServerPart Response
|
|
|
|
showEntry y m d i = do
|
|
|
|
entryJS <- liftIO $ runCouchDB' $ getDoc (db "tazblog") (doc i)
|
|
|
|
let entry = maybeDoc entryJS
|
|
|
|
ok $ tryEntry entry
|
|
|
|
|
|
|
|
tryEntry :: Maybe Entry -> Response
|
|
|
|
tryEntry Nothing = toResponse $ showError NotFound
|
|
|
|
tryEntry (Just entry) = toResponse $ renderBlog eLang $ renderEntry entry
|
|
|
|
where
|
|
|
|
eLang = lang entry
|
2012-02-22 22:03:31 +01:00
|
|
|
|
|
|
|
showIndex :: BlogLang -> Response
|
|
|
|
showIndex lang = toResponse $ renderBlogHeader lang
|
|
|
|
|
2012-02-23 13:20:29 +01:00
|
|
|
renderBlog :: BlogLang -> Html -> Html
|
|
|
|
renderBlog DE body = blogTemplate "Tazjins Blog" "Wer mich kontaktieren will: " " oder " version DE body
|
|
|
|
renderBlog EN body = blogTemplate "Tazjin's Blog" "Get in touch with me: " " or " version EN body
|
|
|
|
|
2012-02-22 22:03:31 +01:00
|
|
|
renderBlogHeader :: BlogLang -> Html
|
2012-02-23 13:20:29 +01:00
|
|
|
renderBlogHeader DE = blogTemplate "Tazjins Blog" "Wer mich kontaktieren will: " " oder " version DE (emptyTest DE)
|
|
|
|
renderBlogHeader EN = blogTemplate "Tazjin's Blog" "Get in touch with me: " " or " version EN (emptyTest EN)
|
2012-02-22 22:03:31 +01:00
|
|
|
|
|
|
|
-- http://tazj.in/2012/02/10.155234
|
|
|
|
|
2012-02-23 13:20:29 +01:00
|
|
|
-- CouchDB functions
|
|
|
|
maybeDoc :: Data a => Maybe (Doc, Rev, JSValue) -> Maybe a
|
|
|
|
maybeDoc (Just(_,_,v)) = Just( stripResult $ fromJSON v)
|
|
|
|
maybeDoc Nothing = Nothing
|
|
|
|
|
|
|
|
stripResult :: Result a -> a
|
|
|
|
stripResult (Ok z) = z
|
|
|
|
stripResult (Error s) = error $ "JSON error: " ++ s
|
2012-02-22 22:03:31 +01:00
|
|
|
-- CouchDB View Setup
|
|
|
|
latestDEView = "function(doc){ if(doc.lang == \"de\"){ emit([doc.year, doc.month, doc.day, doc.id_], doc); } }"
|
|
|
|
latestENView = "function(doc){ if(doc.lang == \"en\"){ emit([doc.year, doc.month, doc.day, doc.id_]], doc); } }"
|
|
|
|
|
|
|
|
latestDE = ViewMap "latestDE" latestDEView
|
|
|
|
latestEN = ViewMap "latestEN" latestENView
|
|
|
|
|
2012-02-23 03:30:14 +01:00
|
|
|
setupBlogViews :: IO ()
|
2012-02-22 22:03:31 +01:00
|
|
|
setupBlogViews = runCouchDB' $
|
|
|
|
newView "tazblog" "entries" [latestDE, latestEN]
|