{-# OPTIONS -fno-monomorphism-restriction #-} module Panda.Model.Post where -- env import Panda.Helper.Env import Prelude hiding ((.), (/), id) import qualified Panda.Config.Global as Config data Post = Post { uid :: String -- blog/08-09-04 blog title , title :: String , body :: String , tags :: [String] } deriving (Show, Eq) list = do ids <- getDirectoryContents Config.blog_uri <.> (\\ [".", ".."]) <.> rsort <.> map ("" / Config.blog_id /) mapM get ids get id = liftM2 (Post id (get_title id) ) (get_body id) (return []) get_title id = id.fromUTF8.words.tail.join " " get_body id = (Config.flat_uri / id) .readFile parse_date = parseCalendarTime defaultTimeLocale "%Y-%m-%d" date x = case x.uid.fromUTF8.words.first.split "/".last.("20"++).parse_date of Nothing -> parse_date "2000-1-1".fromJust Just x -> x