[web-devel] Type-safe URL handling

Jeremy Shaw jeremy at n-heptane.com
Tue Mar 16 23:42:22 EDT 2010


On Tue, Mar 16, 2010 at 7:15 PM, Michael Snoyman <michael at snoyman.com>wrote:

> Firstly, I haven't read through all of URLT, so take anything I say with a
> grain of salt. I'll happily be corrected where I misspeak.
>
> I'm not sure if I really see the big advantages for URLT over the code that
> I posted. As an advantage to my code, it's *much* smaller and easier to
> digest. I understand the URLT is doing a lot of other stuff with TH and the
> like, but I'm trying to look at the core of URL dispatch here. I would
> imagine having a system like this:
>

The essence of URLT is pretty darn small. The TH, generics, and all that
other stuff is not required. This is the essence of URLT:

newtype URLT url m a = URLT { unURLT :: ReaderT  (url -> String) m a }
    deriving (Functor, Monad, MonadFix, MonadPlus, MonadIO, MonadTrans,
MonadReader (url -> String))

showURL :: (Monad m) => url -> URLT url m String
showURL u =
  do mkAbs <- ask
     return (mkAbs u)

-- |used to embed a URLT into a larger parent url
nestURL :: (Monad m) => (url2 -> url1) -> URLT url2 m a -> URLT url1 m a
nestURL b = withURLT (. b)

It's just one newtype wrapper around ReaderT and two very simple functions.
No classes, no generics, no nothing..

To 'run' the URLT monad transformer (ie. go from 'URLT url m a' to 'm a') we
simple supply a simple function of the type (url -> String).

That is all that is required.

To dispatch the incoming url we need a function that goes from (String ->
url). And then we just write a plain old function that takes the type 'url'
as an argument. So for the dispatch portion we don't require any classes or
anything from the library itself.

The Template Haskell, Generics, etc, are just there to provide some various
ways of automatically deriving the (url -> String) and (String -> url)
functions.

* An underlying typeclass/datatype/whatever for defining a set of URLs. For
> lack of a better term, let's call it a WebSubapp.
>

This would either refer to the monad URLT parameterized with a url type.

e.g., URLT WebURL m a

>
> * The ability to embed a WebSubapp within another WebSubapp.
>

the nestURL function.


> * The ability to convert a resource in a WebSubapp into a relative path,
> and vice-versa.
>

showURL converts a relative path to an absolute.


> * Dispatch a request to a specific resource, passing also (either via
> explicit argument or through a Reader monad) a function to convert a
> resource into an absolute path.
>

To dispatch a url you simple call the top-level handling function and pass
in the url. The URLT environment holds the function to convert a resource
into an absolute path.


> * Convert a WebSubapp into an Application. I'll assume for the moment that
> would be a Network.Wai.Application.
>

In the current URLT I have a function that does this for happstack. (that is
the entire reason why URLT depends on happstack, and why it would be easy to
split out). I can write a similar module for Wai tomorrow.


> Once we had that skeleton, we could dress it up however we want. For Yesod,
> I would change the mkResources quasi-quoter to produce an instance of
> WebSubapp. Others may wish to use the regular package, some might use TH,
> and others still may code it all directly.
>

In URLT mkResources would just need to return the two functions (String ->
url) and (url -> String).


> However, if we keep the same skeleton, then all of these will operate with
> each other seemlessly.
>

Yes. TH and Regular already operate seamless in URLT. If you add mkResource
it would as well.

Let's examine WebPlug more closely.

class WebPlug a where
    toRelPath :: a -> RelPath
    fromRelPath :: RelPath -> Maybe a
    dispatch :: a -> (a -> AbsPath) -> Application

now, I think that having dispatch be part of the WebPlug class itself is a
problem because it assumes that your dispatch function needs no other
arguments besides the URL. I find that  is often not the case. For an image
gallery library, the dispatch function might need to take a FilePath
argument which specifies where the image directory is. So I think it is
better that you write a dispatch handler with a unique name for url type and
call it by its unique name. Then there is no problem if you want to add
other arguments.

So, now you have a function like:

dispatchBlog :: a -> (a -> AbsPath) -> Application.

now in my function I might want to generate a url that I will use as an href
value. It's can't be a relative url (obviously) it needs to be an absolute
url. So I need to do something like this:

dispatchBlog Foo mkAbs =
         let u = mkAbs (BlogPost 1)
         in <a href=u>Blog Post 1</a>

Well, it can be a bit annoying to have to have to explicitly have that extra
mkAbs argument on every pattern. So we could just wrap it up in ReaderT
monad if we wanted:

dispatchBlog :: a -> Reader (a -> AbsPath) Application

and mkAbs can be:

mkAbs :: a -> Reader (a -> AbsPath) AbsPath
mkAbs url =
   do f <- ask
        return (f url)

and we can use it like:

dispatchBlog Foo =
       do u <- mkAbs (BlogPost 1)
            <a href=u>Blog Post 1</a>

and were you currently have this:

     dispatch (MyBlog b) toAbsPath req = dispatch b (toAbsPath . MyBlog) req

we would have something like:

dispatchMyBlog (MyBlog b) = withReader (MyBlog .) $ dispatchBlog b

we can rename withReader to make its intentions more clear:

dispatchSub c = withReader (c .)

and just write:

dispatchMyBlog (MyBlog b) = dispatchSub MyBlog $ dispatchBlog b

Since we got rid of the dispatch function in WebPlug we now have:

class WebPlug a where
    toRelPath :: a -> RelPath
    fromRelPath :: RelPath -> Maybe a

Personally, I think it should return Failure a instead of Maybe a, because
we can include information about why it failed.

class WebPlug a where
    toRelPath :: a -> RelPath
    fromRelPath :: RelPath -> Failing a

Now, this class is useful, but not required. It is also essentially the same
as AsURL

We have a low-level function:

plugToWai' :: (a -> ReaderT (a -> AbsPath) Application) -- ^ the dispatch
function
                  -> (a -> AbsPath) -- ^ function to convert url to an
AbsPath
                  -> (AbsPath -> a) -- ^ function to convert the AbsPath
back to a url
                  -> Application

We can that function from the higher-level:

plugToWai :: (WebPlug a) => (a -> ReaderT (a -> AbsPath) Application) ->
Application

if we have a dispatch function that takes argumens:

fooDispatch :: FilePath -> Int -> a -> ReaderT (a -> AbsPath) Application,
we just do something like:

plugToWai (fooDispatch "foo" 1)

So, to summerize:

 1. I don't think dispatch can be a member of the class, because the various
dispatch functions may need to take extra arguments, and you can't do that
if dispatch is in a class.
 2. if you pass the mkAbs function via the Reader monad instead of passing
it as an explicit argument then you have pretty much exactly reinvented
URLT.

Hence, I think you have no option but to agree that URLT is what you wanted
all along ;) I am happy to split the happstack and HSP portions out of the
core library. I would even be happy to split regular and TH so that we can
have:

urlt
urlt-regular
urlt-th
urlt-mkResource
urt-hsp
urlt-happstack
urlt-wai
urlt-all

so that you can only only the extensions you care about.

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


More information about the web-devel mailing list