Difference between revisions of "HAppS tutorial2"

From HaskellWiki
Jump to navigation Jump to search
m (Fix url for methods example)
 
(22 intermediate revisions by 6 users not shown)
Line 6: Line 6:
   
 
Author's Note: This page will be in various states of disrepair for awhile. I'm creating this document as I am learning HAppS, so it may reflect my inaccurate perceptions. Some of the information on this page MAY EVEN BE WRONG. If you know it's wrong, I would be grateful for your help in improving it.
 
Author's Note: This page will be in various states of disrepair for awhile. I'm creating this document as I am learning HAppS, so it may reflect my inaccurate perceptions. Some of the information on this page MAY EVEN BE WRONG. If you know it's wrong, I would be grateful for your help in improving it.
  +
  +
Second Author's Note: This is by NO means a complete list. The best reference (that I've found so far) is, in the source, SimpleHTTP.hs - it has everything listed here, and more.
 
 
 
[http://happs.org/ HAppS] is a framework for developing Internet
 
[http://happs.org/ HAppS] is a framework for developing Internet
Line 21: Line 23:
 
biggest goal of this document is to provide a useful guide to the
 
biggest goal of this document is to provide a useful guide to the
 
ServerPart primitives that are available.
 
ServerPart primitives that are available.
  +
   
 
----
 
----
Line 73: Line 76:
   
 
The first argument is matched to the first directory element in the path URL. If it matches, then the ServerParts in the second argument are run.
 
The first argument is matched to the first directory element in the path URL. If it matches, then the ServerParts in the second argument are run.
  +
  +
<haskell>
  +
module Main where
  +
  +
import HAppS.Server
  +
  +
impl = [ dir "test" [ dir "me" [ anyRequest $ ok $ toResponse "/test/me matched." ]
  +
, anyRequest $ ok $ toResponse "/test matched."] ]
  +
  +
main = simpleHTTP nullConf { port = 8080 } impl
  +
</haskell>
  +
  +
===== compiling the "dir"-example =====
  +
Suppose you have saved the "dir"-example in the file dir_test.hs.
  +
Then you can compile with
  +
  +
ghc --make dir_test.hs -o dir_test
  +
  +
run it with ./dir_test and watch the result on your browser through
  +
http://localhost:8080/test/me
  +
   
 
====path====
 
====path====
Line 84: Line 108:
 
FromReqURI is a type class that facilitates the conversion of data in the URI to Haskell types. The basic types are are already members of the class.
 
FromReqURI is a type class that facilitates the conversion of data in the URI to Haskell types. The basic types are are already members of the class.
   
  +
<haskell>
  +
module Main where
  +
  +
import HAppS.Server
  +
  +
handleProjectById :: Int -> [ServerPart Response]
  +
handleProjectById id = [ anyRequest $ ok $ toResponse $ "Project num " ++ show id ++ " addressed."]
  +
  +
handleProjectByTag :: String -> [ServerPart Response]
  +
handleProjectByTag tag = [ anyRequest $ ok $ toResponse $ "Project tag " ++ show tag ++ " addressed."]
  +
  +
impl = [ dir "projects"
  +
[ path $ handleProjectById
  +
, path $ handleProjectByTag ]
  +
]
  +
  +
main = simpleHTTP nullConf { port = 8080 } impl
  +
  +
</haskell>
 
====multi====
 
====multi====
   
Line 94: Line 137:
   
 
====method====
 
====method====
  +
  +
<haskell>
  +
method :: (MatchMethod method, Monad m) => method -> WebT m a -> ServerPartT m a
  +
</haskell>
  +
  +
Filters for a specific request method.
  +
  +
An important note: '''method also prevents further matching on the request URL. This means you must capture (using path, dir, etc) the entire url before using method.''' This is useful, however, as method GET alone will match "/" (which cannot be matched with dir).
  +
  +
Below example illustrates handling different kind of request methods.
  +
  +
<haskell>
  +
module Main where
  +
  +
import HAppS.Server
  +
import Control.Monad (mplus)
  +
import Text.XHtml hiding (method, dir)
  +
import qualified Text.XHtml as H
  +
  +
-- a page for gathering comments
  +
commentPage :: Html
  +
commentPage = body <<
  +
(toHtml "Please give us your opinions:" +++
  +
(form ! [H.method "POST"] <<
  +
[ textarea ! [strAttr "name" "comment", strAttr "cols" "50", strAttr "rows" "12"] << ""
  +
, br, input ! [strAttr "type" "submit"]]))
  +
  +
resultPage :: String -> Html
  +
resultPage str = body <<
  +
(toHtml "Thank you for your comments." +++
  +
blockquote << (p << str))
  +
  +
processComment (Comment str) = [ anyRequest $ ok $ resultPage str ]
  +
  +
-- comment as a data type
  +
newtype Comment = Comment String
  +
instance FromData Comment where
  +
fromData = do c <- look "comment" `mplus` return "No comment."
  +
return (Comment c)
  +
  +
unauthMethods = (`elem` [CONNECT,TRACE,HEAD])
  +
impl = [ dir "comment" [ method GET $ ok commentPage
  +
, methodSP POST $ withData processComment
  +
, method () $ ok $ toHtml "Service not implemented for this type of method."]
  +
, method unauthMethods $ unauthorized $ toHtml "You're not authorized."]
  +
  +
main = simpleHTTP nullConf { port = 8080 } impl
  +
  +
</haskell>
  +
  +
We can see the behaviour from shell (note, html output omitted):
  +
<pre>
  +
quad% curl -X CONNECT http://localhost:8080/comment
  +
You're not authorized.
  +
  +
quad% curl -X OPTIONS http://localhost:8080/comment
  +
Service not implemented for this type of method.
  +
</pre>
  +
  +
====methodSP====
  +
identical to method, except for it takes a ServerPart T instead of a WebPart T
   
 
====withRequest====
 
====withRequest====
Line 138: Line 242:
 
return $ MyStructure str
 
return $ MyStructure str
   
main = do simpleHTTP nullConf
+
main = do simpleHTTP nullConf { port = 8080 }
 
 
[ withData $ \(MyStructure str) ->
 
[ withData $ \(MyStructure str) ->
 
 
[ anyRequest $ ok $ "You entered: " ++ str ]
 
[ anyRequest $ ok $ "You entered: " ++ str ]
 
 
, anyRequest $ ok "Sorry, I don't understand." ]
 
, anyRequest $ ok "Sorry, I don't understand." ]
 
 
</haskell>
 
</haskell>
   
 
In this example, the look function gets the contents of the variable "str" passed in the request.
 
In this example, the look function gets the contents of the variable "str" passed in the request.
  +
http://localhost:8080/?str=foo
   
 
====fileServe====
 
====fileServe====
Line 156: Line 257:
   
 
Creates a ServerPartT computation that serves files in the local filesystem. The first argument is a list of filenames to serve. The second argument is a path to the local directory where those files reside.
 
Creates a ServerPartT computation that serves files in the local filesystem. The first argument is a list of filenames to serve. The second argument is a path to the local directory where those files reside.
  +
  +
====seeOther====
  +
<haskell>
  +
seeOther :: (Monad m, ToSURI uri) => uri -> res -> WebT m res
  +
</haskell>
  +
preformes an http redirect to uri. returns res (a response).
   
 
===Error Codes===
 
===Error Codes===
Line 165: Line 272:
 
* movedPermanently
 
* movedPermanently
 
* tempRedirect
 
* tempRedirect
  +
  +
==Working with State==
  +
NOTE: This section is in progress.
  +
  +
* startSystemState - call this function to select an entry point
  +
* query - get the state
  +
* update - change the state
  +
  +
The query and update functions provide all the mechanisms needed to work with state.
  +
  +
HAppS works with state by working with functions that manipulate the state. Lemmih has described it as follows, "[Google's] BigTable pushes data on several machines in a parallel manner. HAppS pushes functions around on several machines in a parallel manner." On a single machine, HAppS keeps a transaction log by storing the functions that modified the state. In order to do this, those functions must be serialized.
  +
  +
Because of this, the query and update functions take QueryEvents and UpdateEvents as a parameter. These functions are typically generated by the TemplateHaskell mkMethods function to eliminate the need to write the above mentioned serialization code. Calls to mkMethods look like the following (taken from AllIn.hs):
  +
  +
<haskell>
  +
$(mkMethods ''UserComponent ['getComponent,'setComponent])
  +
$(mkMethods ''SingletonComponent ['setSingleton,'getSingleton])
  +
</haskell>
  +
  +
The lists in the second arguments are lists of the names of functions for which QueryEvents and UpdateEvents are to be created. QueryEvents and UpdateEvents are created from functions that return a MonadReader and MonadState respectively.
  +
  +
====Other Things To Check Out====
  +
Blog series by the first author, detailing the creation of an application to handle users:
  +
  +
[http://softwaresimply.blogspot.com/ Working with HAppS]
  +
  +
Blog post by second author, expanding upon what was in the first post series:
  +
  +
[http://dbpatterson.com/blog/4711386806 Building With HAppS - Part 1 - More User Functionality]
  +
  +
Thomas Hartman took ideas from both authors, added some of his own, and created:
  +
  +
[http://happstutorial.com:5001 Real World HAppS: The Cabalized, Self-Demoing HAppS Tutorial]

Latest revision as of 19:01, 16 January 2009


Most of the stuff on this page refers to HAppS 0.9.1.2 or greater. This is the most recent development version at the time of this writing. There is another tutorial for HAppS 0.8.8 at HAppS tutorial. Start there to get a background. This page is dedicated to the things that have changed in the newer versions.

Author's Note: This page will be in various states of disrepair for awhile. I'm creating this document as I am learning HAppS, so it may reflect my inaccurate perceptions. Some of the information on this page MAY EVEN BE WRONG. If you know it's wrong, I would be grateful for your help in improving it.

Second Author's Note: This is by NO means a complete list. The best reference (that I've found so far) is, in the source, SimpleHTTP.hs - it has everything listed here, and more.

HAppS is a framework for developing Internet services quickly, deploying them easily, scaling them massively, and managing them effortlessly. Web, persistence, mail, DNS and database servers are all built-in so you can focus on app development rather than integrating and babysitting lots of different servers/services (the Haskell type system keeps everything consistent).

Introduction

The basic web server framework in HAppS consists of a call to simpleHTTP that is passed a list of ServerParts that define the available pages. simpleHTTP searches through the ServerParts and returns the response generated by the first matching ServerPart. Typically ServerParts will match based on some part of the request URL.

The ServerPart is the workhorse of defining HAppS actions. The biggest goal of this document is to provide a useful guide to the ServerPart primitives that are available.



Fundamental Data Types

Need better explanations here.

Author's Note: Due to my inexperience with Monads, these explanations are probably lacking. Feel free to improve them.

These data types provide the framework for converting a Request into a Result in a structured way.

WebT

newtype WebT m a = WebT { unWebT :: m (Result a) }

A WebT is a computation that generates a result.

ServerPartT

newtype ServerPartT m a = ServerPartT { unServerPartT :: Request -> WebT m a }

A ServerPartT is a function that converts a Request into a WebT.

Basic ServerPart Functions

High-level description

Currently, these ServerPart primitives are defined in SimpleHTTP.hs. They were recently moved there from AlternativeHTTP.hs.

 * dir - match a directory at the front of the URL
 * path - another way to match a URL directory
 * multi - run a list of server parts
 * method - runs a server part if the request has the specified method
 * withRequest - builds a ServerPartT from a WebT
 * anyRequest - runs a ServerPartT no matter what the request was
 * withData - retrieve data from the input query or the cookies
 * withDataFn - retrieve data from the input query or the cookies
 * applyRequest
 * ok
 * toResponse
 * fileServe - a generic file server that returns files from the local file system as responses

dir

dir :: Monad m => String -> [ServerPartT m a] -> ServerPartT m a

The first argument is matched to the first directory element in the path URL. If it matches, then the ServerParts in the second argument are run.

module Main where

import HAppS.Server

impl = [ dir "test" [ dir "me" [ anyRequest $ ok $ toResponse "/test/me matched." ]
                    , anyRequest $ ok $ toResponse "/test matched."] ]

main = simpleHTTP nullConf { port = 8080 } impl
compiling the "dir"-example

Suppose you have saved the "dir"-example in the file dir_test.hs. Then you can compile with

ghc --make dir_test.hs -o dir_test

run it with ./dir_test and watch the result on your browser through

 http://localhost:8080/test/me


path

path :: (FromReqURI a, Monad m) => (a -> [ServerPartT m r]) -> ServerPartT m r

Similar to dir except instead of passing a String and a list of ServerParts, you pass a function that returns a list of ServerParts.

FromReqURI is a type class that facilitates the conversion of data in the URI to Haskell types. The basic types are are already members of the class.

module Main where

import HAppS.Server

handleProjectById :: Int -> [ServerPart Response]
handleProjectById id = [ anyRequest $ ok $ toResponse $ "Project num " ++ show id ++ " addressed."]

handleProjectByTag :: String -> [ServerPart Response]
handleProjectByTag tag = [ anyRequest $ ok $ toResponse $ "Project tag " ++ show tag ++ " addressed."]

impl = [ dir "projects"
                 [ path $ handleProjectById
                 , path $ handleProjectByTag ]
       ]

main = simpleHTTP nullConf { port = 8080 } impl

multi

multi :: Monad m => [ServerPartT m a] -> ServerPartT m a

Returns a ServerPart that runs the list of ServerParts supplied in the first argument.

method

method :: (MatchMethod method, Monad m) => method -> WebT m a -> ServerPartT m a

Filters for a specific request method.

An important note: method also prevents further matching on the request URL. This means you must capture (using path, dir, etc) the entire url before using method. This is useful, however, as method GET alone will match "/" (which cannot be matched with dir).

Below example illustrates handling different kind of request methods.

module Main where

import HAppS.Server
import Control.Monad (mplus)
import Text.XHtml hiding (method, dir)
import qualified Text.XHtml as H

-- a page for gathering comments
commentPage :: Html
commentPage = body <<
      (toHtml "Please give us your opinions:" +++
       (form ! [H.method "POST"] <<
        [ textarea ! [strAttr "name" "comment", strAttr "cols" "50", strAttr "rows" "12"] << ""
        , br, input ! [strAttr "type" "submit"]]))

resultPage :: String -> Html
resultPage str = body <<
                 (toHtml "Thank you for your comments." +++
                         blockquote << (p << str))

processComment (Comment str) = [ anyRequest $ ok $ resultPage str ]

-- comment as a data type
newtype Comment = Comment String
instance FromData Comment where
    fromData = do c <- look "comment" `mplus` return "No comment."
                  return (Comment c)

unauthMethods = (`elem` [CONNECT,TRACE,HEAD])
impl = [ dir "comment" [ method GET $ ok commentPage
                       , methodSP POST $ withData processComment
                       , method () $ ok $ toHtml "Service not implemented for this type of method."]
       , method unauthMethods $ unauthorized $ toHtml "You're not authorized."]

main = simpleHTTP nullConf { port = 8080 } impl

We can see the behaviour from shell (note, html output omitted):

quad% curl -X CONNECT http://localhost:8080/comment
You're not authorized.

quad% curl -X OPTIONS http://localhost:8080/comment
Service not implemented for this type of method.

methodSP

identical to method, except for it takes a ServerPart T instead of a WebPart T

withRequest

withRequest :: (Request -> WebT m a) -> ServerPartT m a

Since a ServerPartT is an encapsulation for a function (Request -> WebT), the withRequest function acts as a ServerPartT constructor.

anyRequest

anyRequest :: Monad m => WebT m a -> ServerPartT m a
anyRequest x = withRequest $ \_ -> x

anyRequest uses withRequest to construct a ServerPartT from the supplied WebT.

withData

withData provides a mechanism for retrieving structured data from a request. The first argument to withData is a function that takes a FromData instance in and returns [ServerPartT]. FromData is defined as follows.

class FromData a where
    fromData :: RqData a

So all you have to do to use withData is implement a fromData function for your data structure. fromData returns RqData which is a ReaderT that builds a computation that can get your type from the data in the request. HAppS provides several functions to use in constructing a fromData function for your data type. These functions are:

 * lookInput
 * lookBS
 * look
 * lookCookie
 * lookCookieValue
 * readCookieValue
 * lookRead
 * lookPairs

Here is an excerpt from one of the HAppS examples that illustrates the concept.

data MyStructure = MyStructure String
instance FromData MyStructure where
    fromData = do str <- look "str"
                  return $ MyStructure str

main = do simpleHTTP nullConf { port = 8080 }
              [ withData $ \(MyStructure str) ->
                    [ anyRequest $ ok $ "You entered: " ++ str ]
              , anyRequest $ ok "Sorry, I don't understand." ]

In this example, the look function gets the contents of the variable "str" passed in the request.

 http://localhost:8080/?str=foo

fileServe

fileServe :: MonadIO m => [FilePath] -> FilePath -> ServerPartT m Response

Creates a ServerPartT computation that serves files in the local filesystem. The first argument is a list of filenames to serve. The second argument is a path to the local directory where those files reside.

seeOther

seeOther :: (Monad m, ToSURI uri) => uri -> res -> WebT m res

preformes an http redirect to uri. returns res (a response).

Error Codes

 * badRequest
 * unauthorizied
 * notFound
 * seeOther
 * found
 * movedPermanently
 * tempRedirect

Working with State

NOTE: This section is in progress.

 * startSystemState - call this function to select an entry point
 * query - get the state
 * update - change the state

The query and update functions provide all the mechanisms needed to work with state.

HAppS works with state by working with functions that manipulate the state. Lemmih has described it as follows, "[Google's] BigTable pushes data on several machines in a parallel manner. HAppS pushes functions around on several machines in a parallel manner." On a single machine, HAppS keeps a transaction log by storing the functions that modified the state. In order to do this, those functions must be serialized.

Because of this, the query and update functions take QueryEvents and UpdateEvents as a parameter. These functions are typically generated by the TemplateHaskell mkMethods function to eliminate the need to write the above mentioned serialization code. Calls to mkMethods look like the following (taken from AllIn.hs):

$(mkMethods ''UserComponent ['getComponent,'setComponent])
$(mkMethods ''SingletonComponent ['setSingleton,'getSingleton])

The lists in the second arguments are lists of the names of functions for which QueryEvents and UpdateEvents are to be created. QueryEvents and UpdateEvents are created from functions that return a MonadReader and MonadState respectively.

Other Things To Check Out

Blog series by the first author, detailing the creation of an application to handle users:

Working with HAppS

Blog post by second author, expanding upon what was in the first post series:

Building With HAppS - Part 1 - More User Functionality

Thomas Hartman took ideas from both authors, added some of his own, and created:

Real World HAppS: The Cabalized, Self-Demoing HAppS Tutorial