[web-devel] Type-safe URL handling

Jeremy Shaw jeremy at n-heptane.com
Tue Mar 16 18:35:11 EDT 2010


On Tue, Mar 16, 2010 at 11:51 AM, Gregory Collins
<greg at gregorycollins.net>wrote:

> Michael Snoyman <michael at snoyman.com> writes:
>


> Yes, this approach smells a lot better to me: the types are types and
> the data are data. Just a brainstorm: if each handler monad were to
> carry its routing table around with it, you could define something like:
>
>    match :: ByteString
>          -> (WhateverYourWebMonadIsCalled a)
>          -> (WhateverYourWebMonadIsCalled a)

And write
>
>    handler = match "/foo/:bar/#int/" $ do ...
>
> without the template haskell quasiquotation (i.e. do the checking at
> runtime.)


Well, that is pretty much exactly how the ServerMonad in happstack works.
That is why I wanted to free ServerMonad  so that it is not happstack
specific.

I am not sure what :bar is supposed to mean, but let's pretend it means
match on the type Bar.

In the current code today you would could match on "/foo/:bar/#int/" like
this:

 dir "foo" $ path $ \(bar :: Bar) -> path $ \(i :: Int) -> ...

Now, one issue with your runtime match function is that it returns two
parameters, in that example, but might return a different number of
arguments in other cases. So the type would have to be something vararg-ish.

match :: (MonadPlus m, ServerMonad m, MatchArgs c) => String -> (c -> m a)
-> m a

Where the type 'c' hopefully matches up with the values that
"/foo/:bar/#int/" returns. Despite this annoyance, this could be implemented
using ServerMonad today.

One advantage of using the QuasiQuote method instead of a plain string is
that the QuasiQuote method would parse the string at compile time and
generate a matcher with a specific type signature. If the handler function
had different arguments you would get a compile time error.

I would very much like to see a QuasiQuote version of match added to the
ServerMonad library. It's basically just syntactic sugar for using dir /
path /etc. But it is very nice sugar.



> Is it always true that compile-time link checking is
> possible/desirable? All of these solutions also imply that each handler
> knows where it's hung on the routing table so that it can resolve
> relative URLs, etc.


With URLT, the handler 'knows where it is hung' because it is stored
transparently by the URLT monad, and accessed via showURL. So in the blog
library, for example, you would just write:

 u <- showURL (ViewPost 1)

showURL magically knows where it is hung. If the blog was incorporated into
a master site:

data App = Blog BlogURL

it would be told like:

app (Blog blogURL) = nestURL Blog $ blogHandler blogURL


> IMO no matter what a link-checker should be lightweight enough that you
> can refactor easily without rewriting a bunch of static tables; you
> should be able to move an entire "subtree" to another place in the
> routing table in O(1) time.
>

That should be easy with URLT. You could just change the type:

data App = MyBlog BlogURL

Now, if you forget to update the nestURL handler from Blog to MyBlog, you
will get a compile time error.

Or, might might not change the type at all. You might just change the AsURL
instance so that

 (Blog (ViewPost 1))

generates:

/myblog/viewpost/1

So, you have the flexibility to change the way your urls look by modifying
two functions and leaving everything else alone.


> This rabbit hole goes pretty deep though; if you're serious about the
> bondage and discipline approach you'd want to ensure that you can check
> query parameters; i.e. "'/foo' takes a mandatory 'bar' integer parameter
> on the queryString and an optional 'sort' parameter which must be either
> 'asc' or 'desc'", etc. At some point I have to wonder: is the medicine
> worse than the disease?
>

Using the the URLT, the issue of the mandatory and optional arguments is
simple.

You would have types like:

data Sort = Asc | Desc
data WebURL = Foo Int (Maybe Sort)

instance AsURL Foo where
   toURLS (Foo i mSort) = showString "Foo?" . showString "bar=" . shows n .
showString ";" . (case mSort of Nothing -> id ; (Just Asc) -> showString
"sort=asc;" ; (Just Desc) -> showString "sort=desc;")
   fromURLC = -- skipped for brevity

It seems like the medicine is quite nice here. Instead of having to remember
if the 'bar' is a parameter or a path component, we just do:

showURL (Foo 1 (Just Asc))

The details of how that looks are centralized in a single spot. if we decide
that we want the url to instead look like:

 /foo/1?sort=desc

We can change it in one spot instead of having to:
  1. change it everywhere
  2. tell everyone about the change and get them to remember that it changed

Additionally, with the typed version you can never forget the mandatory
'bar' parameter because the compiler will tell you.

Writing the toURLS and fromURLC instances by hand gives you very precise
control over how the URLs look -- though it can be a bit tedious. However I
think some simple combinators could help with that. Either a DSL for
constructing things by hand, or something based on a yesod style
quasiquoter.

- jeremy
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/web-devel/attachments/20100316/7f1db20a/attachment.html


More information about the web-devel mailing list