{-# LANGUAGE TypeSynonymInstances #-} -- | Hack spec! Stolen from Rack with some simplification. module Hack where import Data.Default import System.IO import qualified Data.ByteString.Lazy as B version :: [Int] version = [2009, 5, 19] data RequestMethod = OPTIONS | GET | HEAD | POST | PUT | DELETE | TRACE | CONNECT deriving (Show, Read, Eq) data Hack_UrlScheme = HTTP | HTTPS deriving (Show, Eq) -- | customizable error stream type HackErrors = String -> IO () instance Show HackErrors where show _ = "HackErrors" data Env = Env { requestMethod :: RequestMethod -- ^ HTTP request method , scriptName :: String -- ^ The initial portion of the request URL's \"path\" that corresponds to the application object, so that the application knows its virtual \"location\". This may be an empty string, if the application corresponds to the \"root\" of the server. , pathInfo :: String -- ^ The remainder of the request URL's \"path\", designating the virtual \"location\" of the request's target within the application. This will always starts with \"/\" , queryString :: String -- ^ The portion of the request URL that follows the ?, if any. May be empty , serverName :: String -- ^ When combined with SCRIPT_NAME and PATH_INFO, these variables can be used to complete the URL. Note, however, that HTTP_HOST, if present, should be used , serverPort :: Int -- ^ preference to SERVER_NAME for reconstructing the request URL. SERVER_NAME and SERVER_PORT can never be empty strings, and so are always required. , http :: [(String, String)] -- ^ All http header variables. , hackVersion :: [Int] -- ^ The Array [0,1], representing this version of Hack , hackUrlScheme :: Hack_UrlScheme -- ^ HTTP or HTTPS, depending on the request URL , hackInput :: B.ByteString -- ^ body of the request , hackErrors :: HackErrors -- ^ error stream , hackHeaders :: [(String, String)] -- ^ custom headers, intended to be used by middleware } deriving (Show) -- careful with showing this, it now causes an infinite -- loop with certain handlers due to the use of a -- lazy bytestring data Response = Response { status :: Int -- ^ must be greater than or equal to 100. , headers :: [(String, String)] -- ^ The header must not contain a Status key, contain keys with : or newlines in their name, contain keys names that end in - or _, but only contain keys that consist of letters, digits, _ or - and start with a letter. The values of the header must be Strings, consisting of lines (for multiple header values) seperated by \"\\n\". The lines must not contain characters below 037. , body :: B.ByteString -- ^ body of the response } deriving (Show) instance Default RequestMethod where def = GET instance Default Hack_UrlScheme where def = HTTP instance Default Response where def = Response def def B.empty instance Default Env where def = Env def def def def def def def version def B.empty stderrStream def where stderrStream = hPutStr stderr type Application = Env -> IO Response type Middleware = Application -> Application