Difference between revisions of "UrlDisp"

From HaskellWiki
Jump to navigation Jump to search
(Added categories Web and Packages)
(added extensions)
Line 50: Line 50:
   
 
<hask>
 
<hask>
  +
{-# LANGUAGE FlexibleInstances, ScopedTypeVariables #-}
 
import Network.UrlDisp
 
import Network.UrlDisp
 
import Database.HDBC
 
import Database.HDBC

Revision as of 04:50, 5 February 2009

What is UrlDisp

Problem statement

URLs are everywhere on the web. Most of them, however, are hard to remember, because they are meaningless for humans. This is wrong: URLs are a part of user interface, and therefore should be kept simple, meaningful and memorizeable.

Solution

UrlDisp provides (Fast)CGI programs a minimalistic domain-specific parser for URLs.

Hierarchical part of the URL is tokenized and matched against rules defined using UrlDisp combinators. Every rule consists of, basically, a predicate and a CGI action. Once a predicate is satisfied, an action is performed; otherwise, alternatives are tried in order. The matching algorithm is backtracking.

Usage examples

Basics

A regular CGI action looks like this:

output "hello, world!"

Adding a predicate:

-- if URL matches /hello, then output "hello, world!" h |/ "hello" *> output "hello, world!"

More examples:

-- if URL contains /hello, output "woot, it works!", otherwise check for -- /foo (h |/ "hello" *> output "woot, it works!") <|> (h |/ "foo" *> output "foo")

As you can see, the |/ combinator matches current token against it's right operand. h is a special predicate that matches anything, it is used to begin a string of combinators.

One can also match against

  • URL parameters,
  • HTTP methods,
  • and also convert token into a variable which is an instance of Read

There's also an API which is believed to be more human-readable.

Extending UrlDisp

The examples given above are not very interesting since one wants to interact with outside world. Let's see how to extend UrlDisp to handle database access.

Wrapping UrlDisp around a ReaderT will do the trick.

{-# LANGUAGE FlexibleInstances, ScopedTypeVariables #-} import Network.UrlDisp import Database.HDBC import Database.HDBC.ODBC import Control.Exception (bracket) import Network.CGI import Network.CGI.Monad instance MonadCGI (ReaderT Connection (CGIT IO)) where cgiAddHeader n v = lift $ cgiAddHeader n v cgiGet = lift . cgiGet -- once a request to "/db/" is sent, -- execute an SQL query and show it's results main :: IO () main = bracket (connectODBC connStr) disconnect (\c -> runCGI $ (flip runReaderT) c $ evalUrlDisp $ ((h |/ "db" *> m) <|> output "not found")) m :: UrlDisp (ReaderT Connection (CGIT IO)) CGIResult m = do v <- lift ask >>= \c -> liftIO (quickQuery' c "select * from ..." []) output $ show v