module Panda.Model.Comment where -- env import Panda.Helper.Env hiding (match, title, body) import Prelude hiding ((.), (/), (^), id, readFile, writeFile) import qualified Panda.Config.Global as G import Panda.Type.Reader import qualified Panda.Model.Post as Post import System.Directory import Panda.Helper.StateHelper data Comment = Comment { uid :: String -- comment/08-09-04 blog title , author :: String , body :: String , author_email :: String , author_link :: String } deriving (Show, Eq) instance Resource Comment where resource_title = uid >>> spaced_url instance Markable Comment where markup x = render_to_html Markdown (x.body) instance Datable Comment where date x = x.uid.split "/".last.default_parse_date -- CRUD list_for post_id = do has_comments <- doesDirectoryExist d if has_comments then ls d ^ rsort ^ map (G.comment_id / r /) >>= mapM (from_utf8 >>> get) else return [] where d = (G.comment_uri / r) r = post_id.id_to_resource.to_utf8 get id = do xs <- (G.flat_uri / id.to_utf8) .readFile ^ lines let author = xs.first let author_email = "" let author_link = xs.drop 2.first let body = xs.drop 4.unlines return $ Comment id author body author_email author_link create h = do let author = at "author" let author_link = at "author_link" -- let author_email = at "author_email" let body = at "comment" let post_id = at "post_id" timestamp <- ( getClockTime >>= toCalendarTime ) ^ format_date G.comment_date_format let comment_path = post_id_to_uid post_id .to_utf8 createDirectoryIfMissing True comment_path let uid = comment_path / timestamp let content = [author, author_link, body].join "\n\n" writeFile uid content where at s = h.lookup s .fromJust -- extra from_post_id x = Comment (post_id_to_uid x) "" "" "" "" post_id_to_uid x = G.flat_uri / G.comment_id / x.split "/" .last uid_to_post_id x = G.post_id / x.split "/" .last fill_comment_size x = do size <- x.Post.uid.list_for ^ length return $ x { Post.comment_size = size }