-- trying to merge this helper with the generic one results in cyclic imports {-# LANGUAGE NoMonomorphismRestriction#-} {-# LANGUAGE NoImplicitPrelude #-} module Panda.Helper.StateHelper where import Panda.Helper.Env import qualified Panda.Config.Global as G -- G.root = /blog -- raw_uri = blog/x -- full_uri = /blog/x -- uri = full_uri - (/blog/) remove_root s | G.root.is "/" = s | otherwise = s.slice (G.root.length) (s.length) uri = raw_uri ^ b2u ^ remove_root -- uri = raw_uri -- global parse_date format s = case maybe_d of Nothing -> Nothing Just d -> Just $ if d.ctYear < 1910 then d {ctYear = d.ctYear + 100} else d where maybe_d = parseCalendarTime defaultTimeLocale format s format_date = formatCalendarTime defaultTimeLocale default_date = parse_date "%Y-%m-%d %T" "2000-1-1 00:00:00".fromJust parse_post_date = parse_date G.post_date_format default_parse_date s = s.parse_post_date .fromMaybe default_date has_extension x = G.extensions.has x only_for ext x = if has_extension ext then x else toHtml "" -- controller paginate = length > full_paginate (G.per_page) cut = G.cut cut_re = "^\\s*" ++ cut match_cut = is_cut is_cut = isInfixOf cut split_cut = split cut_re -- model path id = G.flat_uri / id