iterIO-0.2.2: Iteratee-based IO with pipe operators

Safe HaskellTrustworthy

Data.IterIO.HttpRoute

Synopsis

Documentation

newtype HttpRoute m s Source

Simple HTTP request routing structure for inumHttpServer. This is a wrapper around a function on HttpReq structures. If the function accepts the HttpReq, it returns Just a response action. Otherwise it returns Nothing.

HttpRoute is a Monoid, and hence can be concatenated with mappend or mconcat. For example, you can say something like:

 simpleServer :: Iter L.ByteString IO ()  -- Output to web browser
              -> Onum L.ByteString IO ()  -- Input from web browser
              -> IO ()
 simpleServer iter enum = enum |$ inumHttpServer server .| iter
     where htdocs = "/var/www/htdocs"
           server = ioHttpServer $ runHttpRoute routing
           routing = mconcat [ routeTop $ routeConst $ resp301 "/start.html"
                             , routeName "apps" $ routeMap apps
                             , routeFileSys mimeMap "index.html" htdocs
                             ]
           apps = [ ("app1", routeFn app1)
                  , ("app2", routeFn app2) ]
 
 app1 :: (Monad m) => HttpReq -> Iter L.ByteString m (HttpResp m)
 app1 = ...

The above function will redirect requests for / to the URL /start.html using an HTTP 301 (Moved Permanently) response. Any request for a path under apps will be redirected to the functions app1, app2, etc. Finally, any other file name will be served out of the file system under the "/var/www/htdocs" directory. (This example assumes mimeMap has been constructed as discussed for mimeTypesI.)

Constructors

HttpRoute (HttpReq s -> Maybe (Iter ByteString m (HttpResp m))) 

Instances

addHeader :: Monad m => (ByteString, ByteString) -> HttpRoute m s -> HttpRoute m sSource

Prepend a header field to the response produced by an HttpRoute if that HttpRoute is successful. For example, to let clients cache static data for an hour, you might use:

   addHeader (pack "Cache-control", pack "max-age=3600") $
       routeFileSys mime (dirRedir "index.html") "/var/www/htdocs"

routeConst :: Monad m => HttpResp m -> HttpRoute m sSource

Route all requests to a constant response action that does not depend on the request. This route always succeeds, so anything mappended will never be used.

routeFn :: (HttpReq s -> Iter ByteString m (HttpResp m)) -> HttpRoute m sSource

Route all requests to a particular function. This route always succeeds, so anything mappended will never be used.

routeReq :: (HttpReq s -> HttpRoute m s) -> HttpRoute m sSource

Select a route based on some arbitrary function of the request. For most purposes, the existing predicates (routeName, routePath, etc.) should be fine, but occationally you might want to define a custom predicate. For example, to reject methods other then "GET" or "POST" at the top of your route, you could say:

      myRoute = mconcat [ rejectBadMethod
                        , otherRoute1
                        , ...
                        ]
      ...

rejectBadMethod :: HttpRoute m
rejectBadMethod =
      routeReq $ req ->
          case reqMethod req of
            s | s == pack "GET" || s == pack "PUT" ->
                  mempty                   {- reject route, falling through
                                                      to rest of myRoute -}
            _ -> routeConst $ resp405 req  {- reject request -}

routeMethodSource

Arguments

:: String

String method should match

-> HttpRoute m s

Target route to take if method matches

-> HttpRoute m s 

Route based on the method (GET, POST, HEAD, etc.) in a request.

routeHostSource

Arguments

:: String

String to compare against host (must be lower-case)

-> HttpRoute m s

Target route to follow if host matches

-> HttpRoute m s 

Route requests whose "Host:" header matches a particular string.

routeTop :: HttpRoute m s -> HttpRoute m sSource

Route the root directory (/).

type HttpMap m s = [(String, HttpRoute m s)]Source

Type alias for the argument of routeMap.

routeMap :: HttpMap m s -> HttpRoute m sSource

routeMap builds an efficient map out of a list of (directory_name, HttpRoute) pairs. If a name is not in the map, the request is not matched. Note that only the next directory component in the URL is matched.

routeAlwaysMap :: Monad m => HttpMap m s -> HttpRoute m sSource

routeAlwaysMap is like routeMap, but matches all requests and returns a 404 error for names that do not appear in the map.

routeName :: String -> HttpRoute m s -> HttpRoute m sSource

Routes a specific directory name, like routeMap for a singleton map.

routePath :: String -> HttpRoute m s -> HttpRoute m sSource

Routes a specific path, like routeName, except that the path can include several directories.

routeVar :: HttpRoute m s -> HttpRoute m sSource

Matches any directory name, but additionally pushes it onto the front of the reqPathParams list in the HttpReq structure. This allows the name to serve as a variable argument to the eventual handling function.

mimeTypesI :: Monad m => String -> Iter ByteString m (String -> ByteString)Source

Parses mime.types file data. Returns a function mapping file suffixes to mime types. The argument is a default mime type for suffixes that do not match any in the mime.types data. (Reasonable defaults might be "text/html", "text/plain", or, more pedantically but less usefully, "application/octet-stream".)

Since this likely doesn't change, it is convenient just to define it once in your program, for instance with something like:

 mimeMap :: String -> S8.ByteString
 mimeMap = unsafePerformIO $ do
             path <- findMimeTypes ["mime.types"
                                   , "/etc/mime.types"
                                   , "/var/www/conf/mime.types"]
             enumFile path |$ mimeTypesI "application/octet-stream"
     where
       findMimeTypes (h:t) = do exist <- fileExist h
                                if exist then return h else findMimeTypes t
       findMimeTypes []    = return "mime.types" -- cause error

dirRedir :: Monad m => FilePath -> FilePath -> HttpRoute m sSource

dirRedir indexFileName redirects requests to the URL formed by appending "/" ++ indexFileName to the requested URL.

routeFileSysSource

Arguments

:: MonadIO m 
=> (String -> ByteString)

Map of file suffixes to mime types (see mimeTypesI)

-> (FilePath -> HttpRoute m s)

Handler to invoke when the URL maps to a directory in the file system. Reasonable options include:

  • (const mempty) to do nothing, which results in a 403 forbidden,
  • (dirRedir "index.html") to redirect directory accesses to an index file, and
  • a recursive invocation such as (routeFileSys typemap . (++ "/index.html")) to re-route the request directly to an index file.
-> FilePath

Pathname of directory to serve from file system

-> HttpRoute m s 

Route a request to a directory tree in the file system. It gets the Content-Length from the target file's attributes (after opening the file). Thus, overwriting files on an active server could cause problems, while renaming new files into place should be safe.

data FileSystemCalls h m Source

An abstract representation of file system calls returning an opaque handle type h in an Iter parameterized by an arbitrary Monad m. This representation allows one to use routeGenFileSys in a monad that is not an instance of MonadIO.

Constructors

FileSystemCalls 

Fields

fs_stat :: !(FilePath -> Iter ByteString m FileStatus)

Return file attributes.

fs_open :: !(FilePath -> Iter ByteString m h)

Open file and return an opaque handle of type h.

fs_close :: !(h -> Iter ByteString m ())

Close an open file. You must call this unless you apply the enumerator returned by fs_enum.

fs_fstat :: !(h -> Iter ByteString m FileStatus)

Return the attributes of an open file.

fs_enum :: !(h -> Iter ByteString m (Onum ByteString m (IterR ByteString m ())))

Enumerate the contents of an open file, then close the file. If you apply the Onum returned by fs_enum, you do not need to call fs_close.

routeGenFileSys :: Monad m => FileSystemCalls h m -> (String -> ByteString) -> (FilePath -> HttpRoute m s) -> FilePath -> HttpRoute m sSource

A generalized version of routeFileSys that takes a FileSystemCalls object and can therefore work outside of the MonadIO monad. Other than the FileSystemCalls object, the arguments and their meaning are identical to routeFileSys.