cgi-3001.4.0.0: A library for writing CGI programs

Copyright(c) The University of Glasgow 2001
(c) Bjorn Bringert 2004-2006
(c) Ian Lynagh 2005
(c) Jeremy Shaw 2005
LicenseBSD-style
MaintainerJohn Chee <cheecheeo@gmail.com>
Stabilityexperimental
Portabilitynon-portable (uses Control.Monad.State)
Safe HaskellNone
LanguageHaskell98

Network.CGI

Contents

Description

Simple Library for writing CGI programs. See https://web.archive.org/web/20100109233524/http://hoohoo.ncsa.illinois.edu/cgi/interface.html for the CGI specification.

This version of the library is for systems with version 2.0 or greater of the network package. This includes GHC 6.6 and later. For older systems, see http://www.cs.chalmers.se/~bringert/darcs/cgi-compat/doc/

Based on the original Haskell binding for CGI:

Original Version by Erik Meijer mailto:erik@cs.ruu.nl. Further hacked on by Sven Panne mailto:sven.panne@aedion.de. Further hacking by Andy Gill mailto:andy@galconn.com. A new, hopefully more flexible, interface and support for file uploads by Bjorn Bringert mailto:bjorn@bringert.net.

Here is a simple example, including error handling (not that there is much that can go wrong with Hello World):

import Network.CGI

cgiMain :: CGI CGIResult
cgiMain = output "Hello World!"

main :: IO ()
main = runCGI (handleErrors cgiMain)
Synopsis

CGI monad

class Monad m => MonadCGI m Source #

The class of CGI monads. Most CGI actions can be run in any monad which is an instance of this class, which means that you can use your own monad transformers to add extra functionality.

Minimal complete definition

cgiAddHeader, cgiGet

Instances
Monad m => MonadCGI (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

cgiAddHeader :: HeaderName -> String -> CGIT m () Source #

cgiGet :: (CGIRequest -> a) -> CGIT m a Source #

data CGIT m a Source #

The CGIT monad transformer.

Instances
MonadTrans CGIT Source # 
Instance details

Defined in Network.CGI.Monad

Methods

lift :: Monad m => m a -> CGIT m a #

MonadCatch m => MonadError SomeException (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

throwError :: SomeException -> CGIT m a #

catchError :: CGIT m a -> (SomeException -> CGIT m a) -> CGIT m a #

Monad m => Monad (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

(>>=) :: CGIT m a -> (a -> CGIT m b) -> CGIT m b #

(>>) :: CGIT m a -> CGIT m b -> CGIT m b #

return :: a -> CGIT m a #

fail :: String -> CGIT m a #

Functor m => Functor (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

fmap :: (a -> b) -> CGIT m a -> CGIT m b #

(<$) :: a -> CGIT m b -> CGIT m a #

Applicative m => Applicative (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

pure :: a -> CGIT m a #

(<*>) :: CGIT m (a -> b) -> CGIT m a -> CGIT m b #

liftA2 :: (a -> b -> c) -> CGIT m a -> CGIT m b -> CGIT m c #

(*>) :: CGIT m a -> CGIT m b -> CGIT m b #

(<*) :: CGIT m a -> CGIT m b -> CGIT m a #

MonadIO m => MonadIO (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

liftIO :: IO a -> CGIT m a #

MonadThrow m => MonadThrow (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

throwM :: Exception e => e -> CGIT m a #

MonadCatch m => MonadCatch (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

catch :: Exception e => CGIT m a -> (e -> CGIT m a) -> CGIT m a #

MonadMask m => MonadMask (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

mask :: ((forall a. CGIT m a -> CGIT m a) -> CGIT m b) -> CGIT m b #

uninterruptibleMask :: ((forall a. CGIT m a -> CGIT m a) -> CGIT m b) -> CGIT m b #

generalBracket :: CGIT m a -> (a -> ExitCase b -> CGIT m c) -> (a -> CGIT m b) -> CGIT m (b, c) #

Monad m => MonadCGI (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

cgiAddHeader :: HeaderName -> String -> CGIT m () Source #

cgiGet :: (CGIRequest -> a) -> CGIT m a Source #

type CGI a = CGIT IO a Source #

A simple CGI monad with just IO.

class Monad m => MonadIO (m :: Type -> Type) #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Minimal complete definition

liftIO

Instances
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (CGIT m) Source # 
Instance details

Defined in Network.CGI.Monad

Methods

liftIO :: IO a -> CGIT m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

MonadIO m => MonadIO (ParsecT s u m) 
Instance details

Defined in Text.Parsec.Prim

Methods

liftIO :: IO a -> ParsecT s u m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a #

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

runCGI :: MonadIO m => CGIT m CGIResult -> m () Source #

Run a CGI action. Typically called by the main function. Reads input from stdin and writes to stdout. Gets CGI environment variables from the program environment.

Error handling

throwCGI :: MonadThrow m => SomeException -> m a Source #

Deprecated: Use Control.Monad.Catch.throwM instead.

Deprecated alias for throwM. Please use throwM instead.

catchCGI :: MonadCatch m => m a -> (SomeException -> m a) -> m a Source #

Deprecated: Use Control.Monad.Catch.catch instead.

Deprecated alias for catch. Please use catch instead.

tryCGI :: MonadCatch m => m a -> m (Either SomeException a) Source #

Deprecated: Use Control.Monad.Catch.try instead.

Deprecated alias for try. Please use try instead.

handleExceptionCGI :: MonadCatch m => m a -> (SomeException -> m a) -> m a Source #

Deprecated: Use Control.Monad.Catch.catch instead.

Deprecated alias for catch. Please use catch instead.

handleErrors :: (MonadCGI m, MonadCatch m, MonadIO m) => m CGIResult -> m CGIResult Source #

Catches any exception thrown by the given CGI action, returns an error page with a 500 Internal Server Error, showing the exception information, and logs the error.

Typical usage:

cgiMain :: CGI CGIResult
cgiMain = ...

main :: IO ()
main = runCGI (handleErrors cgiMain)

Logging

logCGI :: MonadIO m => String -> m () Source #

Logs some message using the server's logging facility. FIXME: does this have to be more general to support FastCGI etc? Maybe we should store log messages in the CGIState?

Output

output Source #

Arguments

:: MonadCGI m 
=> String

The string to output.

-> m CGIResult 

Output a String. The output is assumed to be text/html, encoded using ISO-8859-1. To change this, set the Content-type header using setHeader.

outputFPS Source #

Arguments

:: MonadCGI m 
=> ByteString

The string to output.

-> m CGIResult 

Output a ByteString. The output is assumed to be text/html, encoded using ISO-8859-1. To change this, set the Content-type header using setHeader.

outputNothing :: MonadCGI m => m CGIResult Source #

Do not output anything (except headers).

redirect Source #

Arguments

:: MonadCGI m 
=> String

A URL to redirect to.

-> m CGIResult 

Redirect to some location.

setHeader Source #

Arguments

:: MonadCGI m 
=> String

Header name.

-> String

Header value.

-> m () 

Add a response header. Example:

setHeader "Content-type" "text/plain"

setStatus Source #

Arguments

:: MonadCGI m 
=> Int

HTTP status code, e.g. 404

-> String

HTTP status message, e.g. "Not Found"

-> m () 

Set the HTTP response status.

Error pages

outputError Source #

Arguments

:: (MonadCGI m, MonadIO m) 
=> Int

HTTP Status code

-> String

Status message

-> [String]

Error information

-> m CGIResult 

Output an error page to the user, with the given HTTP status code in the response. Also logs the error information using logCGI.

outputException :: (MonadCGI m, MonadIO m) => SomeException -> m CGIResult Source #

Output a 500 Internal Server Error with information from an Exception.

outputNotFound Source #

Arguments

:: (MonadIO m, MonadCGI m) 
=> String

The name of the requested resource.

-> m CGIResult 

Use outputError to output and log a 404 Not Found error.

outputMethodNotAllowed Source #

Arguments

:: (MonadIO m, MonadCGI m) 
=> [String]

The allowed methods.

-> m CGIResult 

Use outputError to output and log a 405 Method Not Allowed error.

outputInternalServerError Source #

Arguments

:: (MonadIO m, MonadCGI m) 
=> [String]

Error information.

-> m CGIResult 

Use outputError to output and log a 500 Internal Server Error.

Input

getInput Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> m (Maybe String)

The value of the variable, or Nothing, if it was not set.

Get the value of an input variable, for example from a form. If the variable has multiple values, the first one is returned. Example:

query <- getInput "query"

getInputFPS Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> m (Maybe ByteString)

The value of the variable, or Nothing, if it was not set.

Like getInput, but returns a ByteString.

readInput Source #

Arguments

:: (Read a, MonadCGI m) 
=> String

The name of the variable.

-> m (Maybe a)

Nothing if the variable does not exist or if the value could not be interpreted at the desired type.

Same as getInput, but tries to read the value to the desired type.

getBody :: MonadCGI m => m String Source #

Get the uninterpreted request body as a String

getBodyFPS :: MonadCGI m => m ByteString Source #

Get the uninterpreted request body as lazy ByteString

getInputs :: MonadCGI m => m [(String, String)] Source #

Get the names and values of all inputs. Note: the same name may occur more than once in the output, if there are several values for the name.

getInputsFPS :: MonadCGI m => m [(String, ByteString)] Source #

Get the names and values of all inputs. Note: the same name may occur more than once in the output, if there are several values for the name.

getInputNames :: MonadCGI m => m [String] Source #

Get the names of all input variables.

getMultiInput Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> m [String]

The values of the variable, or the empty list if the variable was not set.

Get all the values of an input variable, for example from a form. This can be used to get all the values from form controls which allow multiple values to be selected. Example:

vals <- getMultiInput "my_checkboxes"

getMultiInputFPS Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> m [ByteString]

The values of the variable, or the empty list if the variable was not set.

Same as getMultiInput but using ByteStrings.

getInputFilename Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> m (Maybe String)

The file name corresponding to the input, if there is one.

Get the file name of an input.

getInputContentType Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> m (Maybe String)

The content type, formatted as a string.

Get the content-type of an input, if the input exists, e.g. "image/jpeg". For non-file inputs, this function returns "text/plain". You can use parseContentType to get a structured representation of the the content-type value.

Environment

getVar Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> m (Maybe String) 

Get the value of a CGI environment variable. Example:

remoteAddr <- getVar "REMOTE_ADDR"

getVarWithDefault Source #

Arguments

:: MonadCGI m 
=> String

The name of the variable.

-> String

Default value

-> m String 

getVars :: MonadCGI m => m [(String, String)] Source #

Get all CGI environment variables and their values.

Request information

serverName :: MonadCGI m => m String Source #

The server's hostname, DNS alias, or IP address as it would appear in self-referencing URLs.

serverPort :: MonadCGI m => m Int Source #

The port number to which the request was sent.

requestMethod :: MonadCGI m => m String Source #

The method with which the request was made. For HTTP, this is "GET", "HEAD", "POST", etc.

pathInfo :: MonadCGI m => m String Source #

The extra path information, as given by the client. This is any part of the request path that follows the CGI program path. If the string returned by this function is not empty, it is guaranteed to start with a '/'.

Note that this function returns an unencoded string. Make sure to percent-encode any characters that are not allowed in URI paths before using the result of this function to construct a URI. See progURI, queryURI and requestURI for a higher-level interface.

pathTranslated :: MonadCGI m => m String Source #

The path returned by pathInfo, but with virtual-to-physical mapping applied to it.

scriptName :: MonadCGI m => m String Source #

A virtual path to the script being executed, used for self-referencing URIs.

Note that this function returns an unencoded string. Make sure to percent-encode any characters that are not allowed in URI paths before using the result of this function to construct a URI. See progURI, queryURI and requestURI for a higher-level interface.

queryString :: MonadCGI m => m String Source #

The information which follows the ? in the URL which referenced this program. This is the percent-encoded query information. For most normal uses, getInput and friends are probably more convenient.

remoteHost :: MonadCGI m => m (Maybe String) Source #

The hostname making the request. If the server does not have this information, Nothing is returned. See also remoteAddr.

remoteAddr :: MonadCGI m => m String Source #

The IP address of the remote host making the request.

authType :: MonadCGI m => m (Maybe String) Source #

If the server supports user authentication, and the script is protected, this is the protocol-specific authentication method used to validate the user.

remoteUser :: MonadCGI m => m (Maybe String) Source #

If the server supports user authentication, and the script is protected, this is the username they have authenticated as.

requestContentType :: MonadCGI m => m (Maybe String) Source #

For queries which have attached information, such as HTTP POST and PUT, this is the content type of the data. You can use parseContentType to get a structured representation of the the content-type value.

requestContentLength :: MonadCGI m => m (Maybe Int) Source #

For queries which have attached information, such as HTTP POST and PUT, this is the length of the content given by the client.

requestHeader :: MonadCGI m => String -> m (Maybe String) Source #

Gets the value of the request header with the given name. The header name is case-insensitive. Example:

requestHeader "User-Agent"

Program and request URI

progURI :: MonadCGI m => m URI Source #

Attempts to reconstruct the absolute URI of this program. This does not include any extra path information or query parameters. See queryURI for that. If the server is rewriting request URIs, this URI can be different from the one requested by the client. See also requestURI.

Characters in the components of the returned URI are escaped when needed, as required by Network.URI.

queryURI :: MonadCGI m => m URI Source #

Like progURI, but the returned URI also includes any extra path information, and any query parameters. If the server is rewriting request URIs, this URI can be different from the one requested by the client. See also requestURI.

Characters in the components of the returned URI are escaped when needed, as required by Network.URI.

requestURI :: MonadCGI m => m URI Source #

Attempts to reconstruct the absolute URI requested by the client, including extra path information and query parameters. If no request URI rewriting is done, or if the web server does not provide the information needed to reconstruct the request URI, this function returns the same value as queryURI.

Characters in the components of the returned URI are escaped when needed, as required by Network.URI.

Content negotiation

class Eq a => Acceptable a Source #

Minimal complete definition

includes

Instances
Acceptable ContentType Source # 
Instance details

Defined in Network.CGI.Accept

Acceptable Language Source # 
Instance details

Defined in Network.CGI.Accept

Methods

includes :: Language -> Language -> Bool

Acceptable ContentEncoding Source # 
Instance details

Defined in Network.CGI.Accept

Acceptable Charset Source # 
Instance details

Defined in Network.CGI.Accept

Methods

includes :: Charset -> Charset -> Bool

data Accept a Source #

Instances
Show a => Show (Accept a) Source # 
Instance details

Defined in Network.CGI.Accept

Methods

showsPrec :: Int -> Accept a -> ShowS #

show :: Accept a -> String #

showList :: [Accept a] -> ShowS #

HeaderValue a => HeaderValue (Accept a) Source # 
Instance details

Defined in Network.CGI.Accept

newtype Charset Source #

Constructors

Charset String 
Instances
Eq Charset Source # 
Instance details

Defined in Network.CGI.Accept

Methods

(==) :: Charset -> Charset -> Bool #

(/=) :: Charset -> Charset -> Bool #

Ord Charset Source # 
Instance details

Defined in Network.CGI.Accept

Show Charset Source # 
Instance details

Defined in Network.CGI.Accept

HeaderValue Charset Source # 
Instance details

Defined in Network.CGI.Accept

Acceptable Charset Source # 
Instance details

Defined in Network.CGI.Accept

Methods

includes :: Charset -> Charset -> Bool

newtype Language Source #

Constructors

Language String 

negotiate :: Acceptable a => [a] -> Maybe (Accept a) -> [a] Source #

Content type

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.

Constructors

ContentType 

Fields

  • ctType :: String

    The top-level media type, the general type of the data. Common examples are "text", "image", "audio", "video", "multipart", and "application".

  • ctSubtype :: String

    The media subtype, the specific data format. Examples include "plain", "html", "jpeg", "form-data", etc.

  • ctParameters :: [(String, String)]

    Media type parameters. On common example is the charset parameter for the "text" top-level type, e.g. ("charset","ISO-8859-1").

parseContentType :: Monad m => String -> m ContentType #

Parse the standard representation of a content-type. If the input cannot be parsed, this function calls fail with a (hopefully) informative error message.

Cookies

data Cookie Source #

Contains all information about a cookie set by the server.

Constructors

Cookie 

Fields

Instances
Eq Cookie Source # 
Instance details

Defined in Network.CGI.Cookie

Methods

(==) :: Cookie -> Cookie -> Bool #

(/=) :: Cookie -> Cookie -> Bool #

Ord Cookie Source # 
Instance details

Defined in Network.CGI.Cookie

Read Cookie Source # 
Instance details

Defined in Network.CGI.Cookie

Show Cookie Source # 
Instance details

Defined in Network.CGI.Cookie

newCookie Source #

Arguments

:: String

Name

-> String

Value

-> Cookie

Cookie

Construct a cookie with only name and value set. This client will expire when the browser sessions ends, will only be sent to the server and path which set it and may be sent using any means.

getCookie Source #

Arguments

:: MonadCGI m 
=> String

The name of the cookie.

-> m (Maybe String)

Nothing if the cookie does not exist.

Get the value of a cookie.

readCookie Source #

Arguments

:: (Read a, MonadCGI m) 
=> String

The name of the cookie.

-> m (Maybe a)

Nothing if the cookie does not exist or if the value could not be interpreted at the desired type.

Same as getCookie, but tries to read the value to the desired type.

setCookie :: MonadCGI m => Cookie -> m () Source #

Set a cookie.

deleteCookie :: MonadCGI m => Cookie -> m () Source #

Delete a cookie from the client

URL encoding

formEncode :: [(String, String)] -> String Source #

Formats name-value pairs as application/x-www-form-urlencoded.

urlEncode :: String -> String Source #

Converts a single value to the application/x-www-form-urlencoded encoding.

formDecode :: String -> [(String, String)] Source #

Gets the name-value pairs from application/x-www-form-urlencoded data.

urlDecode :: String -> String Source #

Converts a single value from the application/x-www-form-urlencoded encoding.