| Portability | not portable, uses 2-rank types |
|---|---|
| Stability | experimental |
| Maintainer | johan.tibell@gmail.com |
Network.Wai
Contents
Description
Defines the interface implemented by all web applications.
Example application:
module Main where
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as C (pack, unpack)
import Network.Wai (Application(..), Enumerator(..))
import System.Directory (getCurrentDirectory)
import System.FilePath ((</>), makeRelative)
import System.IO
sendFile :: FilePath -> IO Enumerator
sendFile fname = do
cwd <- getCurrentDirectory
h <- openBinaryFile (cwd </> makeRelative "/" fname) ReadMode
let yieldBlock f z = do
block <- S.hGetNonBlocking h 1024
if S.null block then hClose h >> return z
else do
z' <- f z block
case z' of
Left z'' -> hClose h >> return z''
Right z'' -> yieldBlock f z''
return yieldBlock
fileServer :: Application
fileServer environ = do
-- Here you should add security checks, etc.
let contentType = (C.pack "Content-Type",
C.pack "application/octet-stream")
enumerator <- sendFile $ C.unpack $ pathInfo environ
return (200, pack "OK", [contentType], enumerator)
- type Application = Environment -> IO (Int, ByteString, Headers, Enumerator)
- type Enumerator = forall a. (a -> ByteString -> IO (Either a a)) -> a -> IO a
- data Environment = Environment {
- requestMethod :: Method
- scriptName :: ByteString
- pathInfo :: ByteString
- queryString :: Maybe ByteString
- requestProtocol :: (Int, Int)
- headers :: Headers
- input :: Enumerator
- errors :: String -> IO ()
- type Headers = [(ByteString, ByteString)]
- data Method
The Application type
type Application = Environment -> IO (Int, ByteString, Headers, Enumerator)Source
An application takes an environment and returns a HTTP status
code, a sequence of headers and an Enumerator containing the
response body.
type Enumerator = forall a. (a -> ByteString -> IO (Either a a)) -> a -> IO aSource
A left-fold enumerator.
data Environment Source
An environment providing information regarding the request.
Constructors
| Environment | |
Fields
| |
type Headers = [(ByteString, ByteString)]Source
The HTTP request headers.