-- trying to merge this helper with the generic one results in cyclic imports {-# LANGUAGE NoMonomorphismRestriction#-} {-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Helper.StateHelper where import Bamboo.Env hiding (path, cut) import qualified Bamboo.Type.Config as C import qualified Data.ByteString.Char8 as S import Data.ByteString (ByteString) import Hack.Contrib.Utils import Hack import System.Time -- static_config.root = /blog -- raw_uri = blog/x -- full_uri = /blog/x -- uri = full_uri - (/blog/) remove_root :: String -> String remove_root s | static_config.root.is "/" = s | otherwise = s.slice (static_config.root.length) (s.length) raw_uri :: Env -> String raw_uri env = ( env.script_name ++ env.path_info ) .(urlDecode > tail > remove_trailing_slash ) uri :: Env ->String uri env = raw_uri env .b2u .remove_root -- uri = raw_uri -- global parse_date :: String -> String -> Maybe CalendarTime 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_time :: String -> CalendarTime -> String format_time = formatCalendarTime defaultTimeLocale default_date :: CalendarTime default_date = parse_date "%Y-%m-%d %T" "2000-1-1 00:00:00".fromJust parse_post_date :: String -> Maybe CalendarTime parse_post_date = parse_date $ static_config.post_date_format default_parse_date :: String -> CalendarTime default_parse_date s = s.parse_post_date .fromMaybe default_date has_extension :: Extension -> Bool has_extension x = static_config.extensions.has x html_only_for :: Extension -> Html -> Html html_only_for ext x = if has_extension ext then x else toHtml "" -- controller cut :: ByteString cut = static_config.C.cut.to_sb match_cut :: ByteString -> Bool match_cut = S.lines > any (S.isPrefixOf cut) is_cut :: ByteString -> Bool is_cut = S.isPrefixOf cut -- not used for efficiency -- cut_re = "^\\s*" ++ cut -- split_cut = split cut_re -- model path :: String -> String path id = static_config.flat_uri / id id_to_path :: String -> String id_to_path = path {- etag_data :: String -> IO ByteString etag_data id = do let path = id.id_to_path mtime <- path.file_mtime ^ httpdate size <- path.file_size ^ show return $ [id, mtime, size] .join "," .pack -}