Safe Haskell | None |
---|---|
Language | Haskell98 |
happstack-lite
provides a simplied introduction to
happstack-server
. (Nearly) all the functions in happstack-lite
are simple re-exports from the happstack-server
package. happstack-lite
offers two
key advantages over happstack-server
:
- it only contains the most commonly used functions, gathered in one convenient location.
- the type signatures have been simplified to remove most references to type classes, monad transformers, and other potentially confusing type signatures.
The beautiful part about happstack-lite
is that because it merely re-exports
functions and types from happstack-server
it is possible to gradually import extra functionality from happstack-server
on an as-need basis.
There is a brief introduction to happstack-lite
located here:
http://www.happstack.com/C/ViewPage/9
More detailed examples and information can be found in the Happstack Crash Course:
http://www.happstack.com/docs/crashcourse/index.html
The Happstack Crash Course is written against happstack-server
but the behavior of the functions available in happstack-lite
is almost identical.
Synopsis
- data Request
- data Response
- type ServerPart a = ServerPartT IO a
- data ServerConfig = ServerConfig {}
- defaultServerConfig :: ServerConfig
- serve :: Maybe ServerConfig -> ServerPart Response -> IO ()
- method :: MatchMethod method => method -> ServerPart ()
- data Method
- class MatchMethod m where
- matchMethod :: m -> Method -> Bool
- dir :: String -> ServerPart a -> ServerPart a
- path :: FromReqURI a => (a -> ServerPart b) -> ServerPart b
- class FromReqURI a where
- fromReqURI :: String -> Maybe a
- nullDir :: ServerPart ()
- guardRq :: (Request -> Bool) -> ServerPart ()
- class ToMessage a where
- toContentType :: a -> ByteString
- toMessage :: a -> ByteString
- toResponse :: a -> Response
- toResponseBS :: ByteString -> ByteString -> Response
- ok :: a -> ServerPart a
- internalServerError :: a -> ServerPart a
- unauthorized :: a -> ServerPart a
- notFound :: a -> ServerPart a
- seeOther :: ToSURI uri => uri -> a -> ServerPart a
- setResponseCode :: Int -> ServerPart ()
- lookBS :: String -> ServerPart ByteString
- lookBSs :: String -> ServerPart [ByteString]
- lookText :: String -> ServerPart Text
- lookTexts :: String -> ServerPart [Text]
- lookFile :: String -> ServerPart (FilePath, FilePath, ContentType)
- data ContentType = ContentType {}
- data Cookie = Cookie {
- cookieVersion :: String
- cookiePath :: String
- cookieDomain :: String
- cookieName :: String
- cookieValue :: String
- secure :: Bool
- httpOnly :: Bool
- data CookieLife
- mkCookie :: String -> String -> Cookie
- addCookies :: [(CookieLife, Cookie)] -> ServerPart ()
- expireCookie :: String -> ServerPart ()
- lookCookieValue :: String -> ServerPart String
- addHeaderM :: String -> String -> ServerPart ()
- setHeaderM :: String -> String -> ServerPart ()
- getHeaderM :: String -> ServerPart (Maybe ByteString)
- data Browsing
- serveDirectory :: Browsing -> [FilePath] -> FilePath -> ServerPart Response
- serveFile :: (FilePath -> ServerPart String) -> FilePath -> ServerPart Response
- asContentType :: String -> FilePath -> ServerPart String
- type MimeMap = Map String String
- guessContentTypeM :: MimeMap -> FilePath -> ServerPart String
- mimeTypes :: MimeMap
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
Core Types
an HTTP request
Instances
Show Request | |
HasHeaders Request | |
Defined in Happstack.Server.Internal.Types |
an HTTP Response
Instances
Show Response | |
HasHeaders Response | |
Defined in Happstack.Server.Internal.Types | |
ToMessage Response | |
Defined in Happstack.Server.Response toContentType :: Response -> ByteString # toMessage :: Response -> ByteString # toResponse :: Response -> Response # | |
Error Response | |
Monad m => FilterMonad Response (ServerPartT m) | |
Defined in Happstack.Server.Internal.Monads setFilter :: (Response -> Response) -> ServerPartT m () # composeFilter :: (Response -> Response) -> ServerPartT m () # getFilter :: ServerPartT m b -> ServerPartT m (b, Response -> Response) # | |
Monad m => FilterMonad Response (WebT m) | |
Monad m => WebMonad Response (ServerPartT m) | |
Defined in Happstack.Server.Internal.Monads finishWith :: Response -> ServerPartT m b # | |
Monad m => WebMonad Response (WebT m) | |
Defined in Happstack.Server.Internal.Monads finishWith :: Response -> WebT m b # |
type ServerPart a = ServerPartT IO a #
An alias for ServerPartT
IO
Starting the Server
data ServerConfig Source #
configuration to be used with serve
function
defaultServerConfig :: ServerConfig Source #
a reasonable default ServerConfig
ServerConfig { port = 8000 , ramQuota = 1 * 10^6 , diskQuota = 20 * 10^6 , tmpDir = "/tmp/" }
:: Maybe ServerConfig | if Nothing, then use |
-> ServerPart Response | request handler |
-> IO () |
start the server and handle requests using the supplied ServerPart
Routing an Incoming Request
method :: MatchMethod method => method -> ServerPart () Source #
Guard against the request method
Example:
handler :: ServerPart Response handler = do method [GET, HEAD] ...
HTTP request method
Instances
Eq Method | |
Data Method | |
Defined in Happstack.Server.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Method -> c Method # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Method # toConstr :: Method -> Constr # dataTypeOf :: Method -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Method) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Method) # gmapT :: (forall b. Data b => b -> b) -> Method -> Method # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Method -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Method -> r # gmapQ :: (forall d. Data d => d -> u) -> Method -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Method -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Method -> m Method # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Method -> m Method # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Method -> m Method # | |
Ord Method | |
Read Method | |
Show Method | |
MatchMethod Method | |
Defined in Happstack.Server.Routing matchMethod :: Method -> Method -> Bool # | |
MatchMethod [Method] | |
Defined in Happstack.Server.Routing matchMethod :: [Method] -> Method -> Bool # | |
MatchMethod (Method -> Bool) | |
Defined in Happstack.Server.Routing |
class MatchMethod m where #
instances of this class provide a variety of ways to match on the Request
method.
Examples:
method GET -- match GET or HEAD method [GET, POST] -- match GET, HEAD or POST method HEAD -- match HEAD /but not/ GET method (== GET) -- match GET or HEAD method (not . (==) DELETE) -- match any method except DELETE method () -- match any method
As you can see, GET implies that HEAD should match as well. This is to make it harder to write an application that uses HTTP incorrectly. Happstack handles HEAD requests automatically, but we still need to make sure our handlers don't mismatch or a HEAD will result in a 404.
If you must, you can still do something like this to match GET without HEAD:
guardRq ((== GET) . rqMethod)
matchMethod :: m -> Method -> Bool #
Instances
MatchMethod () | |
Defined in Happstack.Server.Routing matchMethod :: () -> Method -> Bool # | |
MatchMethod Method | |
Defined in Happstack.Server.Routing matchMethod :: Method -> Method -> Bool # | |
MatchMethod [Method] | |
Defined in Happstack.Server.Routing matchMethod :: [Method] -> Method -> Bool # | |
MatchMethod (Method -> Bool) | |
Defined in Happstack.Server.Routing |
dir :: String -> ServerPart a -> ServerPart a Source #
Pop a path element and run the supplied handler if it matches the given string.
handler :: ServerPart Response handler = dir "foo" $ dir "bar" $ subHandler
The path element can not contain '/'. See also dirs
.
path :: FromReqURI a => (a -> ServerPart b) -> ServerPart b Source #
Pop a path element and parse it using the fromReqURI
in the
FromReqURI
class.
class FromReqURI a where #
This class is used by path
to parse a path component into a
value.
The instances for number types (Int
, Float
, etc) use readM
to
parse the path component.
The instance for String
, on the other hand, returns the
unmodified path component.
See the following section of the Happstack Crash Course for
detailed instructions using and extending FromReqURI
:
http://www.happstack.com/docs/crashcourse/RouteFilters.html#FromReqURI
fromReqURI :: String -> Maybe a #
Instances
nullDir :: ServerPart () Source #
guard which only succeeds if there are no remaining path segments
Often used if you want to explicitly assign a route for /
guardRq :: (Request -> Bool) -> ServerPart () Source #
Guard using an arbitrary function on the Request
.
Creating a Response
toResponse
will convert a value into a Response
body,
set the content-type
, and set the default response code for that type.
happstack-server
Example:
main = simpleHTTP nullConf $ toResponse "hello, world!"
will generate a Response
with the content-type text/plain
,
the response code 200 OK
, and the body: hello, world!
.
simpleHTTP
will call toResponse
automatically, so the above can be shortened to:
main = simpleHTTP nullConf $ "hello, world!"
happstack-lite
Example:
main = serve Nothing $ toResponse "hello, world!"
Minimal definition: toMessage
(and usually toContentType
).
Nothing
Instances
:: ByteString | content-type |
-> ByteString | response body |
-> Response |
A low-level function to build a Response
from a content-type
and a ByteString
.
Creates a Response
in a manner similar to the ToMessage
class,
but without requiring an instance declaration.
example:
import Data.ByteString.Char8 as C import Data.ByteString.Lazy.Char8 as L import Happstack.Lite main = serve Nothing $ ok $ toResponseBS (C.pack "text/plain") (L.pack "hello, world")
(note: pack
and pack
only work for ascii. For unicode strings you would need to use utf8-string
, text
, or something similar to create a valid ByteString
).
Setting the Response Code
ok :: a -> ServerPart a Source #
Respond with 200 OK
.
main = serve Nothing $ ok "Everything is OK"
internalServerError :: a -> ServerPart a Source #
Respond with 500 Internal Server Error
.
main = serve Nothing $ internalServerError "Sorry, there was an internal server error."
unauthorized :: a -> ServerPart a Source #
Respond with 401 Unauthorized
.
main = serve Nothing $ unauthorized "You are not authorized."
notFound :: a -> ServerPart a Source #
Respond with 404 Not Found
.
main = serve Nothing $ notFound "What you are looking for has not been found."
seeOther :: ToSURI uri => uri -> a -> ServerPart a Source #
Respond with 303 See Other
.
main = serve Nothing $ seeOther "http://example.org/" "What you are looking for is now at http://example.org/"
NOTE: The second argument of seeOther
is the message body which will sent to the browser. According to the HTTP 1.1 spec,
the entity of the response SHOULD contain a short hypertext note with a hyperlink to the new URI(s).
This is because pre-HTTP/1.1 user agents do not support 303. However, in practice you can probably just use ""
as the second argument.
:: Int | response code |
-> ServerPart () |
Looking up Request Parameters
lookBS :: String -> ServerPart ByteString Source #
Gets the first matching named input parameter as a lazy ByteString
Searches the QUERY_STRING followed by the Request body.
see also: lookBSs
lookBSs :: String -> ServerPart [ByteString] Source #
Gets all matches for the named input parameter as lazy ByteString
s
Searches the QUERY_STRING followed by the Request body.
see also: lookBS
:: String | name of input field to search for |
-> ServerPart (FilePath, FilePath, ContentType) | (temporary file location, uploaded file name, content-type) |
Gets the first matching named file
Files can only appear in the request body. Additionally, the form must set enctype="multipart/form-data".
This function returns a tuple consisting of:
- The temporary location of the uploaded file
- The local filename supplied by the browser
- The content-type supplied by the browser
NOTE: You must move the file from the temporary location before the
Response
is sent. The temporary files are automatically removed
after the Response
is sent.
data ContentType #
A MIME media type value.
The Show
instance is derived automatically.
Use showContentType
to obtain the standard
string representation.
See http://www.ietf.org/rfc/rfc2046.txt for more
information about MIME media types.
ContentType | |
|
Instances
Eq ContentType | |
Defined in Happstack.Server.Internal.RFC822Headers (==) :: ContentType -> ContentType -> Bool # (/=) :: ContentType -> ContentType -> Bool # | |
Ord ContentType | |
Defined in Happstack.Server.Internal.RFC822Headers compare :: ContentType -> ContentType -> Ordering # (<) :: ContentType -> ContentType -> Bool # (<=) :: ContentType -> ContentType -> Bool # (>) :: ContentType -> ContentType -> Bool # (>=) :: ContentType -> ContentType -> Bool # max :: ContentType -> ContentType -> ContentType # min :: ContentType -> ContentType -> ContentType # | |
Read ContentType | |
Defined in Happstack.Server.Internal.RFC822Headers readsPrec :: Int -> ReadS ContentType # readList :: ReadS [ContentType] # readPrec :: ReadPrec ContentType # readListPrec :: ReadPrec [ContentType] # | |
Show ContentType | |
Defined in Happstack.Server.Internal.RFC822Headers showsPrec :: Int -> ContentType -> ShowS # show :: ContentType -> String # showList :: [ContentType] -> ShowS # |
Cookies
a type for HTTP cookies. Usually created using mkCookie
.
Cookie | |
|
Instances
Eq Cookie | |
Data Cookie | |
Defined in Happstack.Server.Internal.Cookie gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cookie -> c Cookie # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cookie # toConstr :: Cookie -> Constr # dataTypeOf :: Cookie -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cookie) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cookie) # gmapT :: (forall b. Data b => b -> b) -> Cookie -> Cookie # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cookie -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cookie -> r # gmapQ :: (forall d. Data d => d -> u) -> Cookie -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cookie -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cookie -> m Cookie # | |
Read Cookie | |
Show Cookie | |
MonadReader RqEnv RqData | |
data CookieLife #
Specify the lifetime of a cookie.
Note that we always set the max-age and expires headers because
internet explorer does not honor max-age. You can specific MaxAge
or Expires
and the other will be calculated for you. Choose which
ever one makes your life easiest.
Session | session cookie - expires when browser is closed |
MaxAge Int | life time of cookie in seconds |
Expires UTCTime | cookie expiration date |
Expired | cookie already expired |
Instances
Eq CookieLife | |
Defined in Happstack.Server.Internal.Cookie (==) :: CookieLife -> CookieLife -> Bool # (/=) :: CookieLife -> CookieLife -> Bool # | |
Ord CookieLife | |
Defined in Happstack.Server.Internal.Cookie compare :: CookieLife -> CookieLife -> Ordering # (<) :: CookieLife -> CookieLife -> Bool # (<=) :: CookieLife -> CookieLife -> Bool # (>) :: CookieLife -> CookieLife -> Bool # (>=) :: CookieLife -> CookieLife -> Bool # max :: CookieLife -> CookieLife -> CookieLife # min :: CookieLife -> CookieLife -> CookieLife # | |
Read CookieLife | |
Defined in Happstack.Server.Internal.Cookie readsPrec :: Int -> ReadS CookieLife # readList :: ReadS [CookieLife] # readPrec :: ReadPrec CookieLife # readListPrec :: ReadPrec [CookieLife] # | |
Show CookieLife | |
Defined in Happstack.Server.Internal.Cookie showsPrec :: Int -> CookieLife -> ShowS # show :: CookieLife -> String # showList :: [CookieLife] -> ShowS # |
Creates a cookie with a default version of 1, empty domain, a path of "/", secure == False and httpOnly == False
see also: addCookie
addCookies :: [(CookieLife, Cookie)] -> ServerPart () Source #
expireCookie :: String -> ServerPart () Source #
Expire the named cookie immediately and set the cookie value to ""
main = serve Nothing $ do expireCookie "name" ok $ "The cookie has been expired."
lookCookieValue :: String -> ServerPart String Source #
gets the named cookie as a string
HTTP Headers
addHeaderM :: String -> String -> ServerPart () Source #
Add headers into the response. This method does not overwrite
any existing header of the same name, hence the name addHeaderM
.
If you want to replace a header use setHeaderM
.
setHeaderM :: String -> String -> ServerPart () Source #
Set a header into the response. This will replace an existing
header of the same name. Use addHeaderM
if you want to add more
than one header of the same name.
getHeaderM :: String -> ServerPart (Maybe ByteString) Source #
Get a header out of the request.
File Serving
see serveDirectory
Instances
Enum Browsing | |
Defined in Happstack.Server.FileServe.BuildingBlocks | |
Eq Browsing | |
Data Browsing | |
Defined in Happstack.Server.FileServe.BuildingBlocks gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Browsing -> c Browsing # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Browsing # toConstr :: Browsing -> Constr # dataTypeOf :: Browsing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Browsing) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Browsing) # gmapT :: (forall b. Data b => b -> b) -> Browsing -> Browsing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Browsing -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Browsing -> r # gmapQ :: (forall d. Data d => d -> u) -> Browsing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Browsing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Browsing -> m Browsing # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Browsing -> m Browsing # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Browsing -> m Browsing # | |
Ord Browsing | |
Defined in Happstack.Server.FileServe.BuildingBlocks | |
Read Browsing | |
Show Browsing | |
:: Browsing | allow directory browsing |
-> [FilePath] | index file names, in case the requested path is a directory |
-> FilePath | file/directory to serve |
-> ServerPart Response |
Serve files and directories from a directory and its subdirectories using sendFile
.
Usage:
serveDirectory EnableBrowsing ["index.html"] "path/to/files/on/disk"
If the requested path does not match a file or directory on the
disk, then serveDirectory
calls mzero
.
If the requested path is a file then the file is served normally.
If the requested path is a directory, then the result depends on what the first two arguments to the function are.
The first argument controls whether directory browsing is enabled.
The second argument is a list of index files (such as index.html).
When a directory is requested, serveDirectory
will first try to
find one of the index files (in the order they are listed). If that
fails, it will show a directory listing if EnableBrowsing
is set,
otherwise it will return forbidden "Directory index forbidden"
.
Here is an explicit list of all the possible outcomes when the argument is a (valid) directory:
DisableBrowsing
, empty index file list
This will always return, forbidden "Directory index forbidden"
DisableBrowsing
, non-empty index file list
- If an index file is found it will be shown.
- Otherwise returns, forbidden "Directory index forbidden"
EnableBrowsing
, empty index file list
Always shows a directory index.
EnableBrowsing
, non-empty index file list
- If an index file is found it will be shown
- Otherwise shows a directory index
see also: serveFile
:: (FilePath -> ServerPart String) | function for determining content-type of file. Typically |
-> FilePath | path to the file to serve |
-> ServerPart Response |
Serve a single, specified file. The name of the file being served is specified explicity. It is not derived automatically from the Request
url.
example 1:
Serve as a specific content-type:
serveFile (asContentType "image/jpeg") "/srv/data/image.jpg"
example 2:
Serve guessing the content-type from the extension:
serveFile (guessContentTypeM mimeTypes) "/srv/data/image.jpg"
If the specified path does not exist or is not a file, this function will return mzero
.
WARNING: No security checks are performed.
NOTE: alias for serveFileUsing
filePathSendFile
:: String | the content-type to return |
-> FilePath -> ServerPart String |
:: MimeMap | map from file extensions to mime-types (usually |
-> FilePath -> ServerPart String |
Ready collection of common mime types. Except for the first two entries, the mappings come from http://svn.apache.org/viewvc/httpd/httpd/branches/2.4.x/docs/conf/mime.types?view=co
Other
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Monads that also support choice and failure.
Nothing
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
An associative operation. The default definition is
mplus = (<|>
)
Instances
MonadPlus [] | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
MonadPlus IO | Since: base-4.9.0.0 |
MonadPlus ReadP | Since: base-2.1 |
MonadPlus RqData | |
MonadPlus P | Since: base-2.1 |
Defined in Text.ParserCombinators.ReadP | |
MonadPlus m => MonadPlus (ServerPartT m) | |
Defined in Happstack.Server.Internal.Monads mzero :: ServerPartT m a # mplus :: ServerPartT m a -> ServerPartT m a -> ServerPartT m a # | |
(Monad m, MonadPlus m) => MonadPlus (WebT m) | |
(Monad m, Error e) => MonadPlus (ErrorT e m) | |
(Error e, Monoid e) => MonadPlus (ReaderError r e) | |
Defined in Happstack.Server.RqData |