Difference between revisions of "HAppS tutorial"

From HaskellWiki
Jump to navigation Jump to search
(more smaller incremental examples)
(switch to headings)
Line 46: Line 46:
   
   
=== Simple stateless example ===
+
==== Simple stateless example ====
   
 
Start with a trivial stateleless example. We define a very trivial handler function that ingnores its arguments and
 
Start with a trivial stateleless example. We define a very trivial handler function that ingnores its arguments and
Line 72: Line 72:
 
For this custom handler, any GET request will return "Hello". The specifics here are that ok is shorthand for sending back an HTTP 200 response, and plain formats the response value as text rather than applying some sort of formatting.
 
For this custom handler, any GET request will return "Hello". The specifics here are that ok is shorthand for sending back an HTTP 200 response, and plain formats the response value as text rather than applying some sort of formatting.
   
  +
==== add "val" for simplicity ====
 
The concept of just returning a value is so common that we defined a function "val" to make it nicer:
 
The concept of just returning a value is so common that we defined a function "val" to make it nicer:
 
<haskell>
 
<haskell>
Line 82: Line 83:
 
</haskell>
 
</haskell>
   
  +
==== choose your method ====
 
You really want to pick which method a handler responds to so you can do this:
 
You really want to pick which method a handler responds to so you can do this:
 
<haskell>
 
<haskell>
Line 93: Line 95:
 
</haskell>
 
</haskell>
   
  +
==== respond by path ====
 
Then specify getting a particular path. Notice that the path is a regex!
 
Then specify getting a particular path. Notice that the path is a regex!
 
<haskell>
 
<haskell>
Line 104: Line 107:
 
]
 
]
 
</haskell>
 
</haskell>
  +
==== default error handlers ====
 
 
Now cleanup so that the last ones are actually error handlers. Note that you can pass a list of methods. A bunch of
 
Now cleanup so that the last ones are actually error handlers. Note that you can pass a list of methods. A bunch of
 
standard status functions are defined in the SimpleHTTP2 module (ok,notFound,notIplemented,etc). We'll cover the ones
 
standard status functions are defined in the SimpleHTTP2 module (ok,notFound,notIplemented,etc). We'll cover the ones
Line 120: Line 123:
 
]
 
]
 
</haskell>
 
</haskell>
  +
==== serve files ====
 
 
Now serve some files and note that happs actually defines those automatically so you only need to have them if you want
 
Now serve some files and note that happs actually defines those automatically so you only need to have them if you want
 
customized error messages.
 
customized error messages.
Line 132: Line 135:
 
]
 
]
 
</haskell>
 
</haskell>
  +
==== block dot files ====
   
  +
Now we observe that we actually want to block dot files as well so we do. (There's probably a nicer way to do this
  +
using regex). Notice that the fileServe code actually does IO. So you can write responses that do IO. Conceptually
  +
you can serve content out of an external database or a proxy server.
  +
  +
<haskell>
  +
import HAppS
  +
main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
  +
noState : -- our application has no state
  +
[
  +
h "/$" GET $ ok plain $ val "GETting root hello"
  +
,h "/s/" GET $ forbidden plain $ \path req -> if isDot path then respond "Dot files not alloed" else req
  +
,h "/s/" GET $ fileServe2 mimeTypes staticPath
  +
]
  +
</haskell>
 
=== Serve static files ===
 
=== Serve static files ===
 
Another common task is to serve files from the file system.
 
Another common task is to serve files from the file system.
Line 153: Line 171:
 
</haskell>
 
</haskell>
   
  +
Now we observe that we actually want to block dot files as well so we do. (There's probably a nicer way to do this
  +
using regex). Notice that the fileServe code does IO. It's easy to write responses that do IO. You can just as easily
  +
serve content out of an external database or a proxy server.
  +
  +
<haskell>
  +
main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
  +
noState : -- our application has no state
  +
[
  +
h "/$" GET $ ok plain $ val "GETting root hello"
  +
,h "/s/" GET $ forbidden plain $ \path req -> if isDot path then respond "Dot files not alloed" else req
  +
,h "/s/" GET $ fileServe2 mimeTypes staticPath
  +
]
  +
</haskell>
  +
  +
<code>hs</code> let us consolidate these. Because of that, SimpleHTTP2 defines basicFileServe as:
  +
<haskell>
  +
basicFileServe staticPath path meth= multi
  +
[
  +
,h path meth GET $ forbidden plain $ \path req -> if isDot path then respond "Dot files not alloed" else req
  +
,h path meth $ fileServe2 mimeTypes staticPath
  +
]
  +
</haskell>
 
=== XSLT and State change ===
 
=== XSLT and State change ===
   

Revision as of 21:36, 18 January 2007


Installing

To install HAppS the following packages are needed:

  • HaXml 1.13.X ( http://www.haskell.org/HaXml, libghc6-haxml-dev in Debian )
  • base
  • cabal (for installation)
  • mtl ( Monad Template Library, libghc6-mtl-dev in Debian )
  • network ( libghc6-network-dev in Debian )
  • stm ( Software Transactional Memory, comes with GHC 6.6 )
  • template-haskell ( http://www.haskell.org/th, comes with GHC 6.6 )

The quick way to see what's missing is to get the darcs repository, change into that directory, and run runghc Setup.hs configure. If you don't get an error, try runghc Setup.hs build and then as root runghc Setup.hs install.

Overview

The application model in HAppS is to help separate state, application logic, wire formats, protocols, and presentation layer:

State

State is just a haskell data type you define. ACID [2] Consistency enforced by Haskell's type system. ACID Durability is handled by MACID write-ahead logging and checkpointing.

Application

Incoming events are gathered in individual haskell threads and then pushed onto a single application queue for processing. The queue model gives you ACID Atomicity and Isolation and lets your app be simply a set of functions with types like:

SomeInputType -> MACID SomeOutputType


The MACID monad lets you update your state and *schedule* side-effects. To be clear, MACID is not in the IO monad so you cannot execute side effects, you can only schedule them. The framework takes care of making sure they are executed at-least-once (if they can be completed by a deadline you specify).

Wire formats

Since your app consists of a set of functions with various haskell input and output types, somewhere you need a place to convert between those internal haskell types and external protocol event types; e.g. from URL Encoded HTTP requests to SomeInputType and from SomeOutputType to XML encoded HTTP responses.

Protocols

HAppS currently provides support for HTTP Requests/Responses and SMTP Envelopes. To be clear HAppS provides ACID Atomicity at the protocol event level. So if you write a protocol with SMTP envelopes being the arriving event type then your app will have atomicity in processing incoming SMTP envelopes. If you write a protocol with SMTP commands being the arriving event type, then your app will have atomicity at the level of individual smtp commands.

Presentation

If your application outputs XML as its wire format, HAppS provides a lot of support for using XSLT to transform it for presentation purposes. For example, you can send XML mail and HAppS will take care of applying the relevant XSLT stylesheet before it is delivered. If you output XML HTTP responses, HAppS takes care of applying the XSLT stylesheet server side for user-agents that don't support doing so on the client. The value here is that you can have designer types who know XSLT modify presentation stuff without touching your application code.

First steps

This chapter will run you through some first simple programs written in HAppS. For other programs have a look at the directory named 'examples'.

First of all, default HAppS applications run their own webserver on port 8000, so you probably want to try out these examples at http://localhost:8000/

If you'd rather access these applications on some other port, use ./myapp --default-port=8001 obviously substituting the name of your binary for myapp.

How to build these examples

Cut'n'paste this into a file named Hello.hs and run ghc --make Hello.hs -o hello to compile and then ./hello to execute the resulting binary.


Simple stateless example

Start with a trivial stateleless example. We define a very trivial handler function that ingnores its arguments and returns a value. We will explain why we use () instead of _ later.

tutorial1.hs

import HAppS
main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
       noState : -- our application has no state
       [
        h () () $ ok plain $ \() () -> respond "Hello" -- any request will return "Hello"
       ]

First you import HAppS, then you pass your list of request handlers to stdHTTP. Handlers are tried in order. Handlers can do one of two things, they can modify the request and pass it on to the next handler, or they can handle the request.

The h handler takes three arguments, the url it should handle, the request type it should handle and the action it should take if it matches.

This example uses two included system handlers, debugFilter and noState, and one custom handler inside the list.

debugFilter does not modify the request, but it does log lots of information about the request to the console. If you don't want see debug information in your console, you can take this out.

noState tells HAppS that this application doesn't have any state.

For this custom handler, any GET request will return "Hello". The specifics here are that ok is shorthand for sending back an HTTP 200 response, and plain formats the response value as text rather than applying some sort of formatting.

add "val" for simplicity

The concept of just returning a value is so common that we defined a function "val" to make it nicer:

import HAppS
 main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
                  noState : -- our application has no state
       [
        h () () $ ok plain $ val "Hello" -- any request will return "Hello"
       ]

choose your method

You really want to pick which method a handler responds to so you can do this:

import HAppS
  main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
                  noState : -- our application has no state
       [
         h () GET $ ok plain $ val "GETting hello"
        ,h () () $ ok plain $ val "Hello" -- any other request will return "Hello"
       ]

respond by path

Then specify getting a particular path. Notice that the path is a regex!

import HAppS
main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
                  noState : -- our application has no state
       [
         h "/$" GET $ ok plain $ val "GETting root hello"
        ,h () GET $ ok plain $ val "GETting hello" -- GET any other path
        ,h () () $ ok plain $ val "Hello" -- any other request will return "Hello"
       ]

default error handlers

Now cleanup so that the last ones are actually error handlers. Note that you can pass a list of methods. A bunch of standard status functions are defined in the SimpleHTTP2 module (ok,notFound,notIplemented,etc). We'll cover the ones that involve redirects later.

import HAppS
  main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
                  noState : -- our application has no state
       [
         h "/$" GET $ ok plain $ val "GETting root hello"
        --these are error handlers
        ,h () [GET,POST] $ notFound plain $ val "not found"
        ,h () () $ notImplemented plain $ val "not implemented"
       ]

serve files

Now serve some files and note that happs actually defines those automatically so you only need to have them if you want customized error messages.

import HAppS
  main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
                  noState : -- our application has no state
       [
         h "/$" GET $ ok plain $ val "GETting root hello"
        ,h "/s/" GET $ fileServe2 mimeTypes staticPath
       ]

block dot files

Now we observe that we actually want to block dot files as well so we do. (There's probably a nicer way to do this using regex). Notice that the fileServe code actually does IO. So you can write responses that do IO. Conceptually you can serve content out of an external database or a proxy server.

import HAppS
  main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
                  noState : -- our application has no state
    [
     h "/$" GET $ ok plain $ val "GETting root hello"
    ,h "/s/" GET  $ forbidden plain $ \path req -> if isDot path then respond "Dot files not alloed" else req
    ,h "/s/" GET $ fileServe2 mimeTypes staticPath
   ]

Serve static files

Another common task is to serve files from the file system.

The HAppS code to do this is basicFileServe. This example sets clientPath and staticPath to the same values as they are by default, so those two lines are optional.

import HAppS hiding (clientPath, staticPath)

-- serve from the filesystem

clientPath = "/s/"
staticPath = "static/"

main = stdHTTP $ debugFilter :
       noState :
       [
        hs clientPath  GET $ basicFileServe staticPath
       ,h () GET $ ok plain $ val "Hello" -- http://localhost:8000/hello
       ]

Now we observe that we actually want to block dot files as well so we do. (There's probably a nicer way to do this using regex). Notice that the fileServe code does IO. It's easy to write responses that do IO. You can just as easily serve content out of an external database or a proxy server.

  main = stdHTTP $ debugFilter : -- we want to see debug messages in the console
                  noState : -- our application has no state
    [
     h "/$" GET $ ok plain $ val "GETting root hello"
    ,h "/s/" GET  $ forbidden plain $ \path req -> if isDot path then respond "Dot files not alloed" else req
    ,h "/s/" GET $ fileServe2 mimeTypes staticPath
   ]

hs let us consolidate these. Because of that, SimpleHTTP2 defines basicFileServe as:

   basicFileServe staticPath path meth= multi
    [
    ,h path meth  GET  $ forbidden plain $ \path req -> if isDot path then respond "Dot files not alloed" else req
    ,h path       meth $ fileServe2 mimeTypes staticPath
    ]

XSLT and State change

{-# OPTIONS -fglasgow-exts -fth #-}
import Data.Typeable
import Control.Monad.State
import HAppS 

--define your application state. If you don't use application state, use noState in your list
data MyState = MySt { appVal :: Int } deriving (Read,Show,Typeable)
$(inferStartState ''MyState) -- boilerplate that will eventually by SYB
 
--Here are some trivial application functions
{-- all application functions take 2 arguments
* a value that is an instance of FromReqURI -- so you can grab stuff from the inbound URI 
 (see FromReqURI above for example instances and see how fileServe2 consumes the pathInfo not consumed by the match)
* a value that is an instance of FromMessage -- so you can grab stuff from the message body or querystring
 (see the FromMessage instance below for an example of how to implement)
--}
-- exampleGetVal :: (MonadState MyApp m) => Int -> () -> m (Either a MyApp)
exampleGetVal x () = do (MySt y) <- get; respond $ MySt (x+y)
examplePostVal () (MySt x) = modify (\ (MySt y)->MySt (y+x)) >> get >>= respond
exampleHelloWorld () () = respond "Hello there world!"
 
-- since you wantto expose functions that return MyApp as XML you need to implement ToElement
instance ToElement MyState where toElement = textElem "MySt" [] . show . appVal
-- since you want people to be able to Post MyApp to your app you need to implement fromMessage
instance FromMessage MyState where fromMessageM m = maybeM $ lookMbRead m "myst" >>= return . MySt
 

main = stdHTTP $ debugFilter: -- we want to see debug messages in the console
      -- noState:   --put this in if your app doesn't use state
      [h "/$"           GET  $ ok xml $ val Index
      ,hs clientPath    GET  $ basicFileServe staticPath

      ,h "/hello1" GET $ ok plain $ val "Hello"  -- val is a handler that ignores arguments
      ,h "/hello2" GET $ ok plain $ \() () -> respond "hello world" -- the most trivial handler
      ,h "/hello3" GET $ ok plain exampleHelloWorld -- put it in a function to make is prettier

      ,h "/val1/" GET $ ok plain_xml exampleGetVal -- produce raw unstyled XML
      ,h "/val1$" POST $ ok plain_xml examplePostVal

      ,h "/val2/" GET $ ok xml exampleGetVal ---- adds an xslt stylesheet at /s/style.xsl for templating
      ,h "/val2$" POST $ ok xml examplePostVal
      ]

For the code above, the file below should be saved in static/style.xsl

<?xml version="1.0"?>
<!DOCTYPE xsl:stylesheet PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "libxslt/xslt2.dtd">

<xsl:stylesheet xmlns:xsl="http://www.w3.org/1999/XSL/Transform" version="1.0"
xmlns:html='http://www.w3.org/TR/REC-html40'
>
<xsl:template match="*">
  1. view source to see server output.
  2. make templates for each of your output types. 
  3.use the xsl lib that handles all sorts of standard template issues
to make it all nice!
</xsl:stylesheet>