-- 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, date)
import qualified MPS as MPS
import Prelude hiding ((.), (/), (^), id, readFile)
import qualified Panda.Config.Global as G
import Panda.Type.Reader
import Panda.Helper.StateHelper hiding (uri)
import Panda.Helper.Helper (date)

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 = title

instance Markable Post where
  markup x  = render_to_html (x.reader) (x.full)
  
instance Datable Post where
  date = uid >>> get_date

instance Addressable Post where
  uri = uid >>> id_to_uri

-- CRUD
list = ls G.post_uri ^ map from_utf8 ^ rsort ^ map (G.post_id /) >>= mapM get

get id        = liftM4 (Post id (get_title id) ) (get_body id) (return []) (return 0) (return $ get_reader id)
get_extension = takeExtension
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
get_date id   = id.words.first.split "/".last.default_parse_date

match s x = [title, body] .map (send_to x >>> lower >>> isInfixOf (s.lower)) .or
search "" = return []
search s  = list ^ filter (match s)

summary = body >>> split_cut >>> first >>> from_utf8
full x | x.body.match_cut.isNothing = x.body
full x = ( xs.takeWhile not_cut ++ xs.dropWhile not_cut .tail ).unlines where
  not_cut = is_cut >>> not
  xs = x.body.lines

has_continue = body >>> match_cut >>> isJust


-- extra
id_to_uri id = G.root / ( pretty_date ++ G.url_date_title_seperator ++ formatted_title ++ ext ) where
  formatted_title = G.url_title_subs.map (\(a,b) -> gsub a b).inject (id.get_title) apply
  pretty_date     = id.get_date.format_date G.url_date_format
  ext = id.get_extension

uri_to_id s = G.post_id / (d ++ " " ++ t) where
  (raw_d, (prefix, title_with_sep)) = s.MPS.match G.url_date_matcher.fromJust.fst
  raw_t = title_with_sep.drop (G.url_date_title_seperator.length)
  t = G.url_title_subs.map (\(a,b) -> gsub b a) .inject raw_t apply
  d = raw_d.parse_date G.url_date_format .fromJust.format_date G.post_date_format


-- summary
markup_summary x = post_summary x +++ next where
  post_summary = (reader &&& summary) >>> splash render_to_html
  next = if x.has_continue then toHtml $ hotlink (x.uri) << "Read the rest of the post ยป" else empty_html