module Panda.Config.Global where import Panda.Helper.Helper import MPS import Prelude hiding ((.), (/), (^), id, readFile) import System.FilePath hiding ((<.>)) import Control.Arrow ((>>>), (&&&), (***)) import Data.Maybe import System.Directory import Data.Default import Panda.Type.Reader import Panda.Type.StaticWidget import Panda.Type.Theme ( to_theme ) import Panda.Type.Extension db_id = "db" flat_id = "." post_id = "blog" config_id = "config" tag_id = "tag" comment_id = "comment" sidebar_id = "sidebar" theme_id = "theme" config_file_id = "site.txt" db_uri = db_id flat_uri = db_uri / flat_id config_uri = flat_uri / config_id / config_file_id sidebar_uri = flat_uri / config_id / sidebar_id footer_uri = flat_uri / config_id post_uri = flat_uri / post_id tag_uri = flat_uri / tag_id comment_uri = flat_uri / comment_id theme_uri = flat_uri / config_id / theme_id data ConfigData = BlogTitle | BlogSubtitle | HostName | AuthorEmail | PerPage | Navigation | Root | Sidebar | Footer | Favicon | AnalyticsAccountId | Extensions | Theme | PostDateFormat | CommentDateFormat | UrlDateFormat | UrlDateMatcher | UrlTitleSubs | UrlDateTitleSeperator | Cut | SummaryForRoot | SummaryForTag | SummaryForRss deriving (Show) -- unsafe, must restart server after changing config file, sorry about that ... -- but these configs are read only, and keep the view pure, so no monad headaches involved. user_config = parse_config config_uri for' x d = user_config.lookup (x.show_data) .fromMaybe d for_int' x d = for' x d .read :: Int for_list' x d = for' x d .parse_list for x = for' x (x.show_data) blog_title = for BlogTitle blog_subtitle = for BlogSubtitle host_name = for HostName author_email = for AuthorEmail per_page = for_int' PerPage "7" navigation = for_list' Navigation "About" .("Home" :) panda_url = "http://www.haskell.org/haskellwiki/Panda" root | user_root.belongs_to ["/", ""] = "/" | otherwise = user_root.("/" /).remove_trailing_slash where user_root = for' Root "/" default_reader = def load_widget = read_static_widget default_reader >>> purify sidebar = for_list' Sidebar "" .map (sidebar_uri /).select (to_utf8 >>> doesFileExist >>> purify ) .map load_widget footer = for Footer .(footer_uri / ) .(\x -> if x.to_utf8.doesFileExist.purify then Just $ load_widget x else Nothing) favicon = for' Favicon "/favicon.ico" -- extensions analytics_account_id = for AnalyticsAccountId extensions = for_list' Extensions "search, comment, analytics" .read_data_list :: [Extension] -- theme default_theme = def user_theme_name = for Theme user_theme_uri = (theme_uri / user_theme_name) ++ ".txt" theme = if user_theme_uri.doesFileExist.purify then parse_config user_theme_uri .(("name", user_theme_name) : ) .to_theme else default_theme -- custom as_l s = "[" ++ s ++ "]" post_date_format = for' PostDateFormat "%y-%m-%d" comment_date_format = for' CommentDateFormat "%y-%m-%d %T" url_date_format = for' UrlDateFormat "%y-%m-%d" url_date_matcher = for' UrlDateMatcher "\\d{2}-\\d{2}-\\d{2}" url_title_subs = for' UrlTitleSubs "" .as_l .read :: [(String, String)] url_date_title_seperator = for' UrlDateTitleSeperator " " -- summary cut = for' Cut "✂-----" .to_utf8 parse_boolean = belongs_to ["true", "1", "y", "yes", "yeah"] summary_for_root = for SummaryForRoot .parse_boolean summary_for_tag = for SummaryForTag .parse_boolean summary_for_rss = for SummaryForRss .parse_boolean