tvl-depot/src/Main.hs

188 lines
7 KiB
Haskell
Raw Normal View History

{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
2012-02-22 22:03:31 +01:00
module Main where
import Control.Applicative ((<$>), (<*>), optional, pure)
import Control.Monad (msum)
import Data.Monoid (mempty)
import Data.ByteString.Char8 (ByteString)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time
import Database.CouchDB
import Happstack.Server
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
import Text.JSON.Generic
import System.Locale (defaultTimeLocale)
2012-02-22 22:03:31 +01:00
import Blog
2012-02-24 16:06:33 +01:00
import Locales
2012-02-22 22:03:31 +01:00
tmpPolicy :: BodyPolicy
tmpPolicy = (defaultBodyPolicy "./tmp/" 0 1000 1000)
main :: IO()
main = do
putStrLn ("TazBlog " ++ version ++ " in Haskell starting")
simpleHTTP nullConf tazBlog
2012-02-22 22:03:31 +01:00
tazBlog :: ServerPart Response
tazBlog = do
2012-02-24 16:06:33 +01:00
msum [ dir (show DE) $ blogHandler DE
, dir (show EN) $ blogHandler EN
, do nullDir
2012-02-24 05:20:36 +01:00
showIndex DE
, do dir " " $ nullDir
seeOther ("https://plus.google.com/115916629925754851590" :: String) (toResponse ())
, path $ \(id_ :: Int) -> getEntryLink id_
, dir "res" $ serveDirectory DisableBrowsing [] "../res"
2012-03-06 23:34:04 +01:00
, dir "notice" $ ok $ toResponse showSiteNotice
, serveDirectory DisableBrowsing [] "../res"
]
2012-02-22 22:03:31 +01:00
blogHandler :: BlogLang -> ServerPart Response
blogHandler lang =
msum [ path $ \(year :: Int) -> path $ \(month :: Int) -> path $ --single entry
2012-03-06 23:34:04 +01:00
\(day :: Int) -> path $ \(id_ :: String) -> showEntry lang id_
2012-02-24 17:01:36 +01:00
, path $ \(year :: Int ) -> path $ \(month :: Int) -> showMonth year month lang
2012-03-06 00:50:53 +01:00
, do
decodeBody tmpPolicy
dir "postcomment" $ path $ \(id_ :: String) -> addComment id_
, do nullDir
2012-02-24 05:20:36 +01:00
showIndex lang
]
2012-02-22 22:03:31 +01:00
2012-03-06 23:34:04 +01:00
showEntry :: BlogLang -> String -> ServerPart Response
showEntry lang id_ = do
entryJS <- liftIO $ runCouchDB' $ getDoc (db "tazblog") (doc id_)
let entry = maybeDoc entryJS
2012-03-06 23:34:04 +01:00
ok $ tryEntry entry lang
2012-03-06 23:34:04 +01:00
tryEntry :: Maybe Entry -> BlogLang -> Response
tryEntry Nothing lang = toResponse $ showError NotFound lang
tryEntry (Just entry) _ = toResponse $ blogTemplate eLang eTitle $ renderEntry entry
where
eTitle = T.pack $ ": " ++ title entry
eLang = lang entry
2012-02-22 22:03:31 +01:00
getEntryLink :: Int -> ServerPart Response
getEntryLink id_ = do
entryJS <- liftIO $ runCouchDB' $ getDoc (db "tazblog") (doc $ show id_)
let entry = maybeDoc entryJS
seeOther (makeLink entry) (toResponse())
where
makeLink :: Maybe Entry -> String
makeLink (Just e) = concat $ intersperse' "/" [show $ lang e, show $ year e, show $ month e, show $ day e, show id_]
makeLink Nothing = "/"
2012-02-24 05:20:36 +01:00
showIndex :: BlogLang -> ServerPart Response
showIndex lang = do
entries <- getLatest lang [("descending", showJSON True)]
(page :: Maybe Int) <- optional $ lookRead "page"
ok $ toResponse $ blogTemplate lang "" $
renderEntries False (eDrop page entries) (topText lang) (Just $ showLinks page lang)
where
eDrop :: Maybe Int -> [a] -> [a]
eDrop (Just i) = drop ((i-1) * 6)
eDrop Nothing = drop 0
2012-02-24 17:01:36 +01:00
showMonth :: Int -> Int -> BlogLang -> ServerPart Response
showMonth y m lang = do
entries <- getLatest lang $ ("descending", showJSON True) : makeQuery startkey endkey
2012-03-02 09:12:09 +01:00
ok $ toResponse $ blogTemplate lang month
$ renderEntries True entries month Nothing
2012-02-24 05:20:36 +01:00
where
2012-03-02 09:12:09 +01:00
month = getMonth lang y m
2012-02-24 17:01:36 +01:00
startkey = JSArray [toJSON y, toJSON m]
endkey = JSArray [toJSON y, toJSON m, JSObject (toJSObject [] )]
2012-03-06 00:50:53 +01:00
addComment :: String -> ServerPart Response
addComment id_ = do
rda <- liftIO $ currentSeconds >>= return
nComment <- Comment <$> look "cname"
<*> look "ctext"
<*> pure rda
rev <- updateDBDoc (doc id_) $ insertComment nComment
liftIO $ putStrLn $ show rev
seeOther ("/" ++ id_) (toResponse())
2012-03-06 00:50:53 +01:00
2012-02-22 22:03:31 +01:00
-- http://tazj.in/2012/02/10.155234
currentSeconds :: IO Integer
currentSeconds = do
now <- getCurrentTime
let s = read (formatTime defaultTimeLocale "%s" now) :: Integer
return s
-- CouchDB functions
2012-02-24 05:20:36 +01:00
getLatest :: BlogLang -> [(String, JSValue)] -> ServerPart [Entry]
getLatest lang arg = do
queryResult <- queryDB view arg
let entries = map (stripResult . fromJSON . snd) queryResult
return entries
where
view = case lang of
EN -> "latestEN"
DE -> "latestDE"
insertComment :: Comment -> JSValue -> IO JSValue
insertComment c jEntry = return $ toJSON $ e { comments = c : (comments e)}
where
e = convertJSON jEntry :: Entry
2012-02-24 17:01:36 +01:00
makeQuery :: JSON a => a -> a -> [(String, JSValue)]
makeQuery qsk qek = [("startkey", (showJSON qsk))
,("endkey", (showJSON qek))]
2012-02-24 05:20:36 +01:00
queryDB :: JSON a => String -> [(String, JSValue)] -> ServerPart [(Doc, a)]
2012-03-03 03:35:20 +01:00
queryDB view arg = liftIO . runCouchDB' $ queryView (db "tazblog") (doc "entries") (doc view) arg
2012-02-24 05:20:36 +01:00
maybeDoc :: Data a => Maybe (Doc, Rev, JSValue) -> Maybe a
maybeDoc (Just(_,_,v)) = Just( stripResult $ fromJSON v)
maybeDoc Nothing = Nothing
updateDBDoc :: JSON a => Doc -> (a -> IO a) -> ServerPart (Maybe Rev)
updateDBDoc docn f = liftIO $ runCouchDB' $ getAndUpdateDoc (db "tazblog") docn f
stripResult :: Result a -> a
stripResult (Ok z) = z
stripResult (Error s) = error $ "JSON error: " ++ s
2012-02-24 17:01:36 +01:00
convertJSON :: Data a => JSValue -> a
convertJSON = stripResult . fromJSON
getMonthCount :: BlogLang -> Int -> Int -> ServerPart Int
getMonthCount lang y m = do
count <- queryDB (view lang) $ makeQuery startkey endkey
2012-03-03 03:42:44 +01:00
return . stripCount $ map (stripResult . fromJSON . snd) count
2012-03-03 03:35:20 +01:00
where
startkey = JSArray [toJSON ("count" :: String), toJSON y, toJSON m]
endkey = JSArray [toJSON ("count" :: String), toJSON y, toJSON m, JSObject (toJSObject [] )]
stripCount :: [Int] -> Int
stripCount [x] = x
stripCount [] = 0
view DE = "countDE"
view EN = "countEN"
2012-03-03 03:35:20 +01:00
2012-02-22 22:03:31 +01:00
-- CouchDB View Setup
2012-03-02 09:12:09 +01:00
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); } }"
countDEView = "function(doc){ if(doc.lang == 'DE'){ emit(['count', doc.year, doc.month, doc.day, doc._id], 1); } }"
countENView = "function(doc){ if(doc.lang == 'EN'){ emit(['count', doc.year, doc.month, doc.day, doc._id], 1); } }"
2012-03-03 03:35:20 +01:00
countReduce = "function(keys, values, rereduce) { return sum(values); }"
2012-02-22 22:03:31 +01:00
latestDE = ViewMap "latestDE" latestDEView
latestEN = ViewMap "latestEN" latestENView
2012-03-02 09:12:09 +01:00
countDE = ViewMapReduce "countDE" countDEView countReduce
countEN = ViewMapReduce "countEN" countENView countReduce
2012-02-22 22:03:31 +01:00
setupBlogViews :: IO ()
2012-02-22 22:03:31 +01:00
setupBlogViews = runCouchDB' $
2012-03-02 09:12:09 +01:00
newView "tazblog" "entries" [latestDE, latestEN, countDE, countEN]