2012-03-07 17:31:42 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, GeneralizedNewtypeDeriving,
|
|
|
|
DeriveDataTypeable, FlexibleContexts, MultiParamTypeClasses, TemplateHaskell,
|
|
|
|
TypeFamilies, RecordWildCards #-}
|
2012-02-22 22:03:31 +01:00
|
|
|
|
|
|
|
module Main where
|
|
|
|
|
2012-03-07 12:59:44 +01:00
|
|
|
import Control.Applicative ((<$>), (<*>), optional, pure)
|
2012-03-08 11:42:10 +01:00
|
|
|
import Control.Exception (bracket)
|
|
|
|
import Control.Monad (msum, mzero, when, unless)
|
2012-03-07 17:31:42 +01:00
|
|
|
import Control.Monad.State (get, put)
|
|
|
|
import Control.Monad.Reader (ask)
|
|
|
|
import Data.Acid
|
|
|
|
import Data.Acid.Advanced
|
|
|
|
import Data.Acid.Local
|
2012-02-23 03:30:14 +01:00
|
|
|
import Data.ByteString.Char8 (ByteString)
|
2012-03-07 17:31:42 +01:00
|
|
|
import Data.Data (Data, Typeable)
|
|
|
|
import Data.Monoid (mempty)
|
2012-03-06 19:39:54 +01:00
|
|
|
import Data.Text (Text)
|
|
|
|
import qualified Data.Text as T
|
2012-02-23 03:30:14 +01:00
|
|
|
import Data.Time
|
2012-03-07 17:31:42 +01:00
|
|
|
import Data.SafeCopy (base, deriveSafeCopy)
|
2012-02-23 03:30:14 +01:00
|
|
|
import Database.CouchDB
|
|
|
|
import Happstack.Server
|
2012-02-23 13:20:29 +01:00
|
|
|
import Network.CGI (liftIO)
|
2012-02-23 03:30:14 +01:00
|
|
|
import Text.JSON.Generic
|
2012-03-07 12:59:44 +01:00
|
|
|
import System.Locale (defaultTimeLocale)
|
2012-02-22 22:03:31 +01:00
|
|
|
|
2012-02-23 03:30:14 +01:00
|
|
|
import Blog
|
2012-02-24 16:06:33 +01:00
|
|
|
import Locales
|
2012-02-22 22:03:31 +01:00
|
|
|
|
2012-03-07 17:31:42 +01:00
|
|
|
{-session handling functions-}
|
|
|
|
|
|
|
|
data SessionState = SessionState { sessions :: [(String, Integer)] } -- id/date
|
|
|
|
deriving (Eq, Ord, Read, Show, Data, Typeable)
|
|
|
|
|
|
|
|
$(deriveSafeCopy 0 'base ''SessionState)
|
|
|
|
|
|
|
|
initialSession :: SessionState
|
|
|
|
initialSession = SessionState []
|
|
|
|
|
|
|
|
addSession :: (String, Integer) -> Update SessionState [(String, Integer)]
|
|
|
|
addSession newS = do
|
|
|
|
s@SessionState{..} <- get
|
|
|
|
let newSessions = newS : sessions
|
|
|
|
put $ s{ sessions = newSessions }
|
|
|
|
return newSessions
|
|
|
|
|
|
|
|
querySessions :: Query SessionState [(String, Integer)]
|
|
|
|
querySessions = sessions <$> ask
|
|
|
|
|
|
|
|
$(makeAcidic ''SessionState ['addSession, 'querySessions])
|
|
|
|
|
2012-03-08 11:42:10 +01:00
|
|
|
guardSession :: AcidState SessionState -> ServerPartT IO ()
|
|
|
|
guardSession acid = do
|
|
|
|
sID <- lookCookieValue "session"
|
|
|
|
sDate <- readCookieValue "sdate"
|
|
|
|
cSessions <- query' acid QuerySessions
|
|
|
|
cDate <- liftIO $ currentSeconds
|
|
|
|
when (not $ elem (sID, sDate) cSessions)
|
|
|
|
mzero
|
|
|
|
when (32400 > (cDate - sDate))
|
|
|
|
mzero
|
|
|
|
|
|
|
|
{- Server -}
|
|
|
|
|
2012-02-22 22:03:31 +01:00
|
|
|
tmpPolicy :: BodyPolicy
|
|
|
|
tmpPolicy = (defaultBodyPolicy "./tmp/" 0 1000 1000)
|
|
|
|
|
|
|
|
main :: IO()
|
|
|
|
main = do
|
2012-02-23 03:30:14 +01:00
|
|
|
putStrLn ("TazBlog " ++ version ++ " in Haskell starting")
|
2012-03-08 11:42:10 +01:00
|
|
|
bracket (openLocalState initialSession)
|
|
|
|
(createCheckpointAndClose)
|
|
|
|
(\acid -> simpleHTTP nullConf $ tazBlog acid)
|
2012-02-22 22:03:31 +01:00
|
|
|
|
2012-03-08 11:42:10 +01:00
|
|
|
tazBlog :: AcidState SessionState -> ServerPart Response
|
|
|
|
tazBlog acid = do
|
2012-02-24 16:06:33 +01:00
|
|
|
msum [ dir (show DE) $ blogHandler DE
|
|
|
|
, dir (show EN) $ blogHandler EN
|
2012-02-23 03:30:14 +01:00
|
|
|
, do nullDir
|
2012-02-24 05:20:36 +01:00
|
|
|
showIndex DE
|
2012-02-23 03:30:14 +01:00
|
|
|
, do dir " " $ nullDir
|
|
|
|
seeOther ("https://plus.google.com/115916629925754851590" :: String) (toResponse ())
|
2012-03-07 12:59:44 +01:00
|
|
|
, path $ \(id_ :: Int) -> getEntryLink id_
|
2012-03-07 13:40:47 +01:00
|
|
|
, path $ \(year :: Int) -> path $ \(month :: Int) -> path $ \(id_ :: String) -> formatOldLink year month id_
|
2012-02-23 03:30:14 +01:00
|
|
|
, dir "res" $ serveDirectory DisableBrowsing [] "../res"
|
2012-03-06 23:34:04 +01:00
|
|
|
, dir "notice" $ ok $ toResponse showSiteNotice
|
2012-03-07 14:51:45 +01:00
|
|
|
, do adminSession <- lookCookieValue "session"
|
|
|
|
ok $ toResponse ("Eingeloggt" :: String)
|
|
|
|
, dir "admin" $ ok $ toResponse $ adminTemplate adminLogin "Login"
|
2012-02-23 03:30:14 +01:00
|
|
|
, 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-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_
|
2012-02-23 03:30:14 +01:00
|
|
|
, do nullDir
|
2012-02-24 05:20:36 +01:00
|
|
|
showIndex lang
|
2012-02-23 03:30:14 +01:00
|
|
|
]
|
2012-02-22 22:03:31 +01:00
|
|
|
|
2012-03-07 13:40:47 +01:00
|
|
|
formatOldLink :: Int -> Int -> String -> ServerPart Response
|
|
|
|
formatOldLink y m id_ =
|
|
|
|
flip seeOther (toResponse ()) $
|
|
|
|
concat $ intersperse' "/" ["de", show y, show m, replace '.' '/' id_]
|
|
|
|
|
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_)
|
2012-02-23 13:20:29 +01:00
|
|
|
let entry = maybeDoc entryJS
|
2012-03-06 23:34:04 +01:00
|
|
|
ok $ tryEntry entry lang
|
2012-02-23 13:20:29 +01:00
|
|
|
|
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
|
2012-02-23 13:20:29 +01:00
|
|
|
where
|
2012-03-06 19:39:54 +01:00
|
|
|
eTitle = T.pack $ ": " ++ title entry
|
2012-02-23 13:20:29 +01:00
|
|
|
eLang = lang entry
|
2012-02-22 22:03:31 +01:00
|
|
|
|
2012-03-07 12:59:44 +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
|
2012-03-03 16:39:15 +01:00
|
|
|
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
|
2012-03-03 16:39:15 +01:00
|
|
|
entries <- getLatest lang $ ("descending", showJSON True) : makeQuery startkey endkey
|
2012-03-02 09:12:09 +01:00
|
|
|
ok $ toResponse $ blogTemplate lang month
|
2012-03-03 16:39:15 +01:00
|
|
|
$ 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
|
2012-03-07 12:59:44 +01:00
|
|
|
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
|
|
|
|
|
2012-03-07 12:59:44 +01:00
|
|
|
currentSeconds :: IO Integer
|
|
|
|
currentSeconds = do
|
|
|
|
now <- getCurrentTime
|
|
|
|
let s = read (formatTime defaultTimeLocale "%s" now) :: Integer
|
|
|
|
return s
|
|
|
|
|
2012-02-23 13:20:29 +01:00
|
|
|
-- 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"
|
|
|
|
|
2012-03-07 12:59:44 +01:00
|
|
|
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
|
|
|
|
2012-02-23 13:20:29 +01:00
|
|
|
maybeDoc :: Data a => Maybe (Doc, Rev, JSValue) -> Maybe a
|
|
|
|
maybeDoc (Just(_,_,v)) = Just( stripResult $ fromJSON v)
|
|
|
|
maybeDoc Nothing = Nothing
|
|
|
|
|
2012-03-07 12:59:44 +01:00
|
|
|
updateDBDoc :: JSON a => Doc -> (a -> IO a) -> ServerPart (Maybe Rev)
|
|
|
|
updateDBDoc docn f = liftIO $ runCouchDB' $ getAndUpdateDoc (db "tazblog") docn f
|
|
|
|
|
2012-02-23 13:20:29 +01:00
|
|
|
stripResult :: Result a -> a
|
|
|
|
stripResult (Ok z) = z
|
|
|
|
stripResult (Error s) = error $ "JSON error: " ++ s
|
2012-02-24 17:01:36 +01:00
|
|
|
|
2012-03-07 12:59:44 +01:00
|
|
|
convertJSON :: Data a => JSValue -> a
|
|
|
|
convertJSON = stripResult . fromJSON
|
|
|
|
|
2012-03-03 03:47:11 +01:00
|
|
|
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
|
2012-03-03 03:47:11 +01:00
|
|
|
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); } }"
|
2012-03-03 03:47:11 +01:00
|
|
|
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
|
|
|
|
2012-02-23 03:30:14 +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]
|