
On Mon, Jun 20, 2011 at 2:50 PM, Christopher Done
On 20 June 2011 20:05, Jeremy Shaw
wrote: Hello,
How is this actually different from web-routes (which already supports automatic url deriving via Template Haskell, generics, or quasi-quotation)?
1) Erm, it's actually documented? ;-)
I am planning to write documentation for web-routes this week or next week. There is an additional web-routes extension I need to finish up first. In fact, I was working on that code when I got distracted by this thread :p
You suggest that web-routes requires a single URL type for all the routes and that your code allows for multiple types. But I do not see how that is actually done.
The same approach can be done with the existing web-routes code. Here is a conversion: {-# LANGUAGE RecordWildCards, DeriveDataTypeable, TemplateHaskell #-} import Data.Data import Data.List import Data.Maybe import Web.Routes import Web.Routes.TH data Event = Event { eventId :: Integer -- ^ The event id. , eventScope :: Bool -- ^ Show the scope? , eventLayout :: Layout -- ^ Layout for the page. } deriving (Data,Typeable,Show) data Layout = Wide | Thin | Collapsed deriving (Typeable,Data,Show,Enum) data Home = Home deriving (Data,Typeable,Show) $(derivePathInfo ''Bool) $(derivePathInfo ''Layout) $(derivePathInfo ''Home) $(derivePathInfo ''Event) router :: String -> IO String router url = fromMaybe (error "404!") (listToMaybe $ mapMaybe ($ url) routes) routes :: [String -> Maybe (IO String)] routes = [route eventPage ,route homePage] route :: (PathInfo a) => (a -> IO String) -> (String -> Maybe (IO String)) route handler url = case fromPathInfo url of Right a -> Just $ handler a Left e -> Nothing eventPage :: Event -> IO String eventPage Event{..} = return $ "Event page! Layout: " ++ show eventLayout homePage :: Home -> IO String homePage Home = return $ "Home page! Click here to go to the event page: " ++ toPathInfo Event { eventId = 1, eventScope = False, eventLayout = Thin } Here I am using the existing template haskell code to derive the printer/parser pair. The template haskell code uses a different set of formatting rules than your SYB code. But there is no reason why the syb code could not be used with web-routes. In fact, it only requires a few small modifications to your existing code. I have made the changes here: http://hpaste.org/48039 The essence of the change is that it should work using [String] rather than String. Where [String] is the list of / separated path segments. That version will actually do the right thing if your record contains a String and the String contains special characters like / or non-ascii unicode characters. Plus it can be easily integrated with the rest of the web-routes framework. It is just another way of generating the printers/parsers. That was one of the goals of the web-routes library -- the base package does not provide any rules for how the urls should be formatted. Instead we provide extension packages that provide various methods and schemes. Or people can write their own -- there is nothing sacred about methods we provide. So, I would be happy to work with you to create a web-routes-syb package that uses your set of encoding rules. (Actually, that modified code on hpaste plus a little extra glue code is all you really need). That said, I do have a complaint about the particular set of rules you use. You allow the fields to be specified in any order -- but that makes it difficult to support record types that contain other record types, doesn't it? I am not sure why arbitrary ordering is more valuable than nested records. If you are using the library to generate the urls, then you already know the order. If you wanted to extend Layout with a constructor that takes an argument; data Layout = Wide | Thin | Collapsed | Arbitrary Integer Then you are kind of stuck? If you get rid of variable field ordering, then you can encode a much larger range of URL types. Anyway, I highly recommend you build on top of web-routes. web-routes is a pretty lightweight dependency and it already solves the problems of low-level URL encoding, escaping, etc. It also provides integration with yesod, happstack, hsp, and more. That means you can just focus on the high-level issue of deriving a nice looking URL scheme using SYB. If there is someway in which web-routes in not suitable to build on, I would love to fix it. - jeremy