-- what about the performance? -- Haskell takes care of that, since IOs are also lazy. -- Posts are not read unless specifically required, i.e. after pagination module Panda.Model.Post where -- env import Panda.Helper.Env hiding (match, title, body) import Prelude hiding ((.), (/), (^), id, readFile) import qualified Panda.Config.Global as G import Panda.Type.Reader data Post = Post { uid :: String -- blog/08-09-04 blog title , title :: String , body :: String , tags :: [String] , comment_size :: Int , reader :: Reader } deriving (Show, Eq) instance Resource Post where resource_title = uid >>> id_to_resource list = ls G.blog_uri ^ map from_utf8 ^ rsort ^ map (G.blog_id /) >>= mapM get get id = liftM4 (Post id (get_title id) ) (get_body id) (return []) (return 0) (return $ get_reader id) get_title id = id.words.tail.unwords.dropExtension get_body id = (G.flat_uri / id.to_utf8) .readFile get_reader id = id.take_extension.guess_reader.fromMaybe G.default_reader parse_date = parseCalendarTime defaultTimeLocale "%Y-%m-%d" date x = x.uid.words.first.split "/".last.("20"++).parse_date.fromMaybe (parse_date "2000-1-1".fromJust) match s x = [title, body] .map (send_to x >>> lower >>> isInfixOf (s.lower)) .or search "" = return [] search s = list ^ filter (match s) markup x = render_to_html (x.reader) (x.body)