salvia-1.0.0: Modular web application framework.

Network.Salvia.Interface

Description

This interface module contains all the basic operations to access the server context. The interface is just of bunch of type classes that allow access to the request and response objects. Most type classes allow access to the context information through lifted state computations. To dig deeper into the context object you would probably want to use the derived fclabels accessors.

Example 1: To get the entire request object:

 do r <- request get  -- Control.Monad.State.get

Example 2: To get the request URI as a string:

 do r <- request (getM uri) -- getM from Data.Record.Label

Example 3: To get the query parameters and the User-Agent header:

 do request $
      do q <- getM (queryParams . asUri)  -- composed labels using the (.) from Control.Category.
         u <- header "user-agent"
         return (q, u)

Example 4: To set the Content-Type and response status and send some string.

 do response $
      do status =: BadRequest    -- the (=:) operator from Data.Record.Label
         header "content-type" =: "text/plain"
    send "hello, world"

Synopsis

Documentation

class ForkM n m whereSource

Methods

forkM :: m a -> m (n a)Source

Instances

class (Applicative m, Monad m) => HttpM dir m whereSource

The HttpM type class indicates is parametrized with the directon (Request or Response) for which the implementation should be able to supply and modify the values. The http method allow for running arbitrary state computations over the request or response objects.

Methods

http :: State (Http dir) a -> m aSource

class (Applicative m, Monad m) => RawHttpM dir m whereSource

Methods

rawHttp :: State (Http dir) a -> m aSource

forRequest :: RequestSource

Stub request and response used to fill in type level gaps for message directions.

class (HttpM Request m, HttpM Response m) => HttpM' m Source

Type class alias indicating an HttpM instance for both requests and responses.

Instances

request :: HttpM Request m => State (Http Request) a -> m aSource

Direction specific aliases for the http method.

class (Applicative m, Monad m) => SocketM m whereSource

The SocketM type class allows access to the raw socket.

Methods

socket :: m SocketSource

Instances

class (Applicative m, Monad m) => HandleM m whereSource

The HandleM type class allows access to the file handle, probabaly associated with the socket to the peer.

Methods

handle :: m HandleSource

Instances

class (Applicative m, Monad m) => ClientAddressM m whereSource

The ClientAddressM type class gives access to socket address of the client part of the connection.

Instances

class (Applicative m, Monad m) => ServerAddressM m whereSource

The ServerAddressM type class gives access to socket address of the client part of the connection.

Instances

class (ClientAddressM m, ServerAddressM m) => AddressM' m Source

Type class alias indicating an instances for both ClientAddressM and ServerAddressM.

Instances

type SendQueue = [SendAction]Source

The send queue is an abstraction to make sure all data that belongs to the message body is sent after the response headers have been sent. Instead of sending data to client directly over the socket from the context it is preferable to queue send actions in the context's send queue. The entire send queue can be flushed to the client at once after the HTTP headers have been sent at the end of a request handler.

data SendAction Source

Constructors

SendAction ((Socket, Handle) -> IO ()) 

Instances

class (Applicative m, Monad m) => HandleQueueM m whereSource

todo: comment: The QueueM type class allows for queing actions for sending data values over the wire. Using a queue for collecting send actions instead of directly sending values over the socket allows for a more modular client or server layout.

Methods

enqueueHandle :: (Handle -> IO ()) -> m ()Source

Instances

class (Applicative m, Monad m) => SocketQueueM m whereSource

Methods

enqueueSock :: (Socket -> IO ()) -> m ()Source

Instances

class (Applicative m, Monad m) => QueueM m whereSource

Instances

class (Applicative m, Monad m) => SendM m whereSource

Methods

send :: String -> m ()Source

Enqueue the action of sending one regular Haskell String over the wire to the other endpoint.

sendBs :: ByteString -> m ()Source

Enqueue the action of sending one ByteString over the wire to the other endpoint.

spoolWith :: (String -> String) -> Handle -> m ()Source

Like the spool function but allows a custom filter over the contents. the wire to the other endpoint.

spoolWithBs :: (ByteString -> ByteString) -> Handle -> m ()Source

Like the spoolWith function but uses a direct ByteString filter which might be more efficient.

Instances

spool :: SendM m => Handle -> m ()Source

Enqueue the action of spooling the entire contents of a file handle over the wire to the other endpoint.

class (Applicative m, Monad m) => FlushM dir m whereSource

The FlushM type class can be used to flush the message headers and the message body directly over the wire to the other endpoint.

Methods

flushHeaders :: dir -> m ()Source

flushQueue :: dir -> m ()Source

class (Applicative m, Monad m) => BodyM dir m whereSource

Methods

body :: dir -> m ByteStringSource

class (Applicative m, Monad m) => ServerM m whereSource

The ServerM type class can be used to acesss the static server configuration like the address/port combination the server listens on and the related hostname.

Instances

class (Applicative m, Monad m, Contains p (TVar q)) => PayloadM p q m | m -> p whereSource

The PayloadM type class provides access to the server payload. The payload can be an arbitrary piece of data that gets shared between all the handlers. Can be used to implement sessions and such. Heterogeneous lists implemented as right associated nested tuples can be used to store multiple pieces of information and still let individual handlers pick out the right thing they need. Picking the right pieces of information from the payload can be done with the select function from the Contains type class.

Methods

payload :: State q a -> m aSource

Instances

Contains p (TVar q) => PayloadM p q (Handler p) 

(&) :: a -> b -> (a, b)Source

class Contains a b whereSource

Methods

select :: a :-> bSource

Instances

a ~ a' => Contains a a' 
(b ~ b', Contains a b') => Contains (c, a) b' 
Contains (a, c) a