{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeSynonymInstances #-} module Hack.Utils where import Hack import Network.CGI hiding (Html) import Network.URI import Data.Default import Data.Monoid import Prelude hiding ((.), (^), (>)) import MPS import Control.Arrow ((>>>), (<<<)) (>) = (>>>) infixl 8 > not_found :: String -> IO Response not_found x = return $ Response { status = 404 , headers = [("Content-Type", "text/plain")] , body = x } empty_app :: Application empty_app = return def -- usage: app.use [content_type, cache] use :: [MiddleWare] -> MiddleWare use = reduce (<<<) not_found_app :: Application not_found_app = \env -> not_found [$here|Not Found: #{env.path_info}|]