{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Model.Static where -- env import Bamboo.Helper.Env hiding (match, body) import Bamboo.Type.Reader import Bamboo.Model.Helper import qualified Data.ByteString.Char8 as S import Bamboo.Type.Cache import Bamboo.Helper.StateHelper data Static = Static { uid :: String , body :: S.ByteString , reader :: Reader } deriving (Show, Eq) instance Resource Static where resource_title x = ("static" / x.uid.get_title) .spaced_url instance Markable Static where markup x = render_to_html (x.reader) (x.body) instance Default Static where def = Static def S.empty def -- CRUD instance FlatRead Static where flat_read x = do t <- x.cache etag_data get_body def {body = t, uid = x} .return instance Gettable Static where get id = do x <- flat_read id x { reader = get_reader id } .return get_title = id_to_resource > drop_known_extension > split "/" > last title = uid > get_title