{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE NoImplicitPrelude #-} module Web.Geek.Type where import Air.Data.Record.SimpleLabel import Air.Env hiding (mod) import Air.Heavy (escape_xml) import Air.TH (mkDefault, here, mkLabel) import Data.Data import Data.IORef import Data.Map (Map) import Data.Text (Text, pack, unpack) import Data.Time import GHC.Exts( IsString(..) ) import Hack2.Contrib.Utils (escape_uri) import Prelude () import Text.Printf import Data.Aeson.Encode.Pretty (encodePretty) import Data.Aeson.Generic (toJSON) import Data.Text.Encoding (decodeUtf8) type Meta = [(Text, Text)] newtype HTMLText = HTMLText {unHTMLText :: Text} deriving (Show, Eq, Data, Typeable) instance IsString HTMLText where fromString = escape_xml > pack > HTMLText instance Default HTMLText where def = HTMLText def newtype URIEscapedText = URIEscapedText {unURIEscapedText :: Text} deriving (Show, Eq, Data, Typeable) instance IsString URIEscapedText where fromString = escape_uri > pack > URIEscapedText instance Default URIEscapedText where def = URIEscapedText def data Post = Post { title :: Text , path :: FilePath , meta :: Meta , date :: Maybe UTCTime , body :: HTMLText -- body must be HTML encoded , raw_body :: Text , link :: URIEscapedText , tags :: [Text] } deriving (Show, Eq, Data, Typeable) mkDefault ''Post mkLabel ''Post data MarkupEngine = MarkupEngine { markup_engine_name :: Text , extensions :: [Text] , transformer :: Text -> HTMLText } instance Default MarkupEngine where def = MarkupEngine { markup_engine_name = "plain" , extensions = [] , transformer = unpack > fromString } instance Show MarkupEngine where show a = printf "MarkupEngine for: %s" (a.extensions.map unpack.join ", ") data Config = Config { blog_directory :: FilePath , post_directory :: FilePath , post_date_format :: String , markup_engine_names :: [Text] , meta_tag_keyword :: Text , meta_date_keyword :: Text , server_port :: Int , static_serve :: Map Text [Text] , maximum_number_of_posts_per_page :: Integer , number_of_posts_per_feed :: Integer , index_file_path :: Text , full_text_search :: Bool , rss_site_title :: Text , rss_site_description :: Text , rss_site_link :: Text , rss_site_root_prefix :: Text } deriving (Show, Data, Typeable) mkDefault ''Config mkLabel ''Config pretty_print_config :: Config -> Text pretty_print_config x = decodeUtf8 - l2s - encodePretty - toJSON x data Runtime = Runtime { posts_ref :: IORef [Post] , markup_engines :: [MarkupEngine] , config :: Config , full_text_search_map_ref :: IORef (Map Text [Int]) } instance Default Runtime where def = Runtime { posts_ref = undefined , markup_engines = [] , config = def , full_text_search_map_ref = undefined } data TagCount = TagCount { tag_name :: Text , tag_count :: Integer } deriving (Show, Data, Typeable) mkDefault ''TagCount