<br><br><div class="gmail_quote">On Thu, Mar 18, 2010 at 2:07 PM, Jeremy Shaw <span dir="ltr">&lt;<a href="mailto:jeremy@n-heptane.com" target="_blank">jeremy@n-heptane.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">

<div>On Wed, Mar 17, 2010 at 5:47 PM, Michael Snoyman <span dir="ltr">&lt;<a href="mailto:michael@snoyman.com" target="_blank">michael@snoyman.com</a>&gt;</span> wrote:<br></div><div class="gmail_quote"><div>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">

<div><div></div><div><br>Now, as far as your concerns about boilerplate and hiding of types: you&#39;re correct on the small scale. When dealing with simple examples, it makes perfect sense to just pass in the 2 or 3 arguments directly instead of having a datatype declared. I see the advantage of having a unified typeclass/dispatch function for dealing with large, nested applications.</div>



</div></blockquote><div><br></div></div><div>I can see how declaring a datatype (typically a record) can be useful when you are passing a larger number of arguments to a subhandler. In fact, I already have real code based on URLT where I do that. In the existing example, I can call the version with the wrapped up arguments just fine with out dispatch:</div>



<div><br></div><div>     run 3000 $ handleWaiU (mySiteD (SiteArgs (BlogArgs now))) &quot;<a href="http://localhost:3000" target="_blank">http://localhost:3000</a>&quot;</div><div><div><br></div><div>If I call it using dispatch, then it is one token shorter:</div>



<div><br></div><div>     run 3000 $ handleWaiD (SiteArgs (BlogArgs now)) &quot;<a href="http://localhost:3000" target="_blank">http://localhost:3000</a>&quot;</div><div> </div><div>except I also am forced to add all these tokens:</div>


<div>
<div><br></div><div>instance Dispatch SiteArgs where</div><div>  type Routes SiteArgs = SiteURL</div><div>  type App SiteArgs    = Application</div><div>  dispatch             = mySiteD</div><div><br></div></div><div>even though I am only going to call dispatch on SiteArgs one place in my code.</div>



<div><br></div><div>So, without dispatch you get the option of using data-types to bundle up arguments if you want to. I don&#39;t see how dispatch improves on that portion.</div><div><br></div><div>With dispatch you are forced to whether you want to or not. The reason you are forced to is because dispatch requires a uniquely named type so it can determine which function to call.</div>



<div><br></div><div>One advantage of Dispatch, is that you can write polymorphic functions that call dispatch:</div><div><br></div><div>myFunc :: (Dispatch a) =&gt; a -&gt; ...</div><div><br></div><div>Is that something we are likely to exploit?</div>



<div> </div></div><div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div>That said, your example and my example are not exactly the same. I find the final line of mine to be *much* more concise than your Dispatch version. Let&#39;s compare them directly:</div>



<div><br></div>
<div>Mine:</div><div>    run 3000 $ plugToWai (MySite $ Blog now) &quot;<a href="http://localhost:3000/" target="_blank">http://localhost:3000/</a>&quot;</div><div>Your dispatch version:</div><div>     run 3000 $ handleWai mkAbs fromAbs (dispatch (SiteArgs (BlogArgs now)))</div>




<div>Your handleWai version:</div><div><div>     run 3000 $ handleWai mkAbs fromAbs (mySite now)</div></div></blockquote><div><br></div><div><br></div></div><div><div>True. If I had a version of handleWai that uses AsURL (similar to how plugToWai works). Then we have:</div>



<div><br></div></div><div><div>Yours:</div><div><div>    run 3000 $ plugToWai    (MySite $ Blog now) &quot;<a href="http://localhost:3000/" target="_blank">http://localhost:3000/</a>&quot;</div></div><div>Mine (no dispatch):</div>

<div>
    run 3000 $ handleWaiU (mySite now) &quot;<a href="http://localhost:3000" target="_blank">http://localhost:3000</a>&quot;</div>
<div>Mine (dispatch)</div><div>    run 3000 $ handleWaiD (MySite $ Blog now) &quot;<a href="http://localhost:3000" target="_blank">http://localhost:3000</a>&quot;</div><div><br></div></div><div>which are essentially the same. Without dispatch, mine could potentially be one token longer. Though in this case it is one token shorter. The version with dispatch is, of course, the same length.</div>

<div>
<div><br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<div><div>I think a lot of the boilerplate you experienced comes from your implementation of my idea, not the idea itself.</div></div></blockquote><div><br></div></div><div>I guess at this point I just feel like it is easier and more straightforward to call the handlers by unique names than to create an instance of Dispatch so I can call the handler using a general name. So, I am looking for some compelling examples where I am going to benefit from having a function like, dispatch :: (Dispatch a) =&gt; a -&gt; (Routes a -&gt; String) -&gt; Routes a -&gt; App a, hanging around.</div>



<div><br></div><div>Though, as I also mentioned. I don&#39;t mind having the Dispatch class in the library as long as I am not required to use it. </div><div><div> </div></div></div></blockquote><div>Based on everything you&#39;ve said, and some thought I&#39;ve had on my own, I agree that the base function should involve no typeclasses and not break up the path into pieces. Here&#39;s a proposal for the entire core:</div>
<div><br></div><div><div>newtype AbsPath = AbsPath { unAbsPath :: String }</div><div>newtype PathInfo = PathInfo { unPathInfo :: String }</div><div>handleWai :: (PathInfo -&gt; Failing url)</div><div>          -&gt; (url -&gt; PathInfo)</div>
<div>          -&gt; (PathInfo -&gt; AbsPath)</div><div>          -&gt; (url -&gt; (url -&gt; AbsPath) -&gt; Application)</div><div>          -&gt; Application</div><div>handleWai parsePI buildPI buildAbsPath dispatch req = do</div>
<div>    let pi = PathInfo $ S.unpack $ pathInfo req</div><div>    case parsePI pi of</div><div>        Success url -&gt; dispatch url (buildAbsPath . buildPI) req</div><div>        Failure errors -&gt; return $ Response Status404 [] $ Right $ fromLBS</div>
<div>                                 $ L.pack $ unlines errors</div><div><br></div><div>I&#39;ve gone ahead and gotten my previous plugToWai function to work on top of this (available in the gist), which should be enough of a proof-of-concept that this core is solid enough. I think it makes a lot of sense to define the two newtypes to keep a clear distinction between the two categories of &quot;URLs&quot;.</div>
<div><br></div><div>We could augment this further with a &quot;[String] -&gt; IO Response&quot; failure handling function. If we *really* want to go overboard, we could even redefine it as this:</div><div><div><br></div><div>
handleWai :: (PathInfo -&gt; Either err url)</div><div>          -&gt; (err -&gt; Application)</div><div>          -&gt; (url -&gt; PathInfo)</div><div>          -&gt; (PathInfo -&gt; AbsPath)</div><div>          -&gt; (url -&gt; (url -&gt; AbsPath) -&gt; Application)</div>
<div>          -&gt; Application</div><div><br></div></div><div><br></div></div>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div class="gmail_quote"><div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">



<div><div>However, let&#39;s try to deal with some of the other important issues. Firstly, Failing versus Maybe: I can&#39;t really see a case when you&#39;d need to specify why the path is not a valid URL. It would seem that either it&#39;s a theoretically valid path, or it&#39;s not. Issues like &quot;that object doesn&#39;t exist&quot; wouldn&#39;t be handled at the dispatch level usually.</div>



</div></blockquote><div><br></div></div><div>I have founding the Failing class to be very useful when using URLT for implementing a REST API. The links within my Haskell app won&#39;t fail, but links generated by non-Haskell clients can fail. For example, if some php programmer accidentally tries to get, /mysite/myblog/foobar/bolg/1 -- they are going to be a lot happier to see:</div>



<div><br></div><div>   expecting, &#39;blog&#39;, &#39;images&#39;, &#39;foo&#39;, but got &#39;bolg&#39;, than they would be if they just got &#39;invalid url&#39;. (Even better would be if it gave the character offset to the bogus path component).</div>



<div> </div><div>Also, if you are writing the toURL / fromURL functions by hand instead of deriving them automatically somehow, then you are going to get it wrong sometimes (in my experience, often). I provide a QuickCheck function that can be used to ensure that your toURL / fromURL functions are inverses. But when the test fails, it is nice to get a more specific error message.</div>

<div>

<div><br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div><div>I still think we need to reconsider relying on one or the other monad transformer library. I notice now that you&#39;re using mtl; Yesod uses transformers. I don&#39;t really have a strong preference on this, but it&#39;s immediately divisive.</div>



</div></blockquote><div><br></div></div><div>I refactored so that it does not really depend on either now. I did this by basically reimplementing URLT as a native Reader-like monad instead of wrapping around ReaderT. I added URLT.MTL and URLT.Transformers which contain the MonadTrans and MonadIO instances. But they are not used by any of the code.  </div>


<div><br></div><div>Happstack is currently mtl based. I think I like transformers better, though I am saddened to see they do not have the classes like MonadReader, MonadWriter, etc.</div><div>
<div> </div></div></div></blockquote><div>I see that Gregory already responded on monads-fd and monads-tf. Which only further splits the community unfortunately.</div><div> </div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<div class="gmail_quote"><div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div><div>There&#39;s one other major difference between URLT and my gist: my gist splits a path into pieces and hands that off for parsing. Your code allows each function to handle that itself. In your example, you use the default Read instance (I assume for simplicity). Splitting into pieces the way I did allowed for easy pattern matching; what would URLT code look like that handled &quot;real&quot; URLs?</div>



</div></blockquote><div><br></div></div><div>I like the String over the [String] because it is the most general form of representing a URL. If you wanted to use URLT to handle both the pathInfo and the query string parameters, then [String] isn&#39;t really the correct type. Though there could be something better than String as well...</div>



<div><br></div></div></blockquote><div>In some ways, ByteString is more appropriate, since that *is* the actual data available. But I doubt this really makes much of a difference, especially if we just internally use Char8 unpacking.</div>
<div> </div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div class="gmail_quote"><div></div><div>As for handling, &quot;real&quot; URLs, there are a variety of solutions. If you don&#39;t care too much about the prettiness of the URLs you can use template haskell to generate AsURL instances:</div>



<div><br></div><div><div>$(deriveAsURL &#39;&#39;BlogURL)</div><div>$(deriveAsURL &#39;&#39;SiteURL)</div><div><br></div><div>main1b :: IO ()</div><div>main1b =</div><div>  do now &lt;- getCurrentTime</div><div>     run 3000 $ handleWaiU (mySite now) &quot;<a href="http://localhost:3000" target="_blank">http://localhost:3000</a>&quot;</div>



<div><br></div><div>Or if you prefer Regular over TH you can do something like this (we can probably be cleaned up a little):</div><div><div><br>$(deriveAll &#39;&#39;BlogURL &quot;PFBlogURL&quot;)</div>
<div>type instance PF BlogURL = PFBlogURL</div><div><br></div><div>instance AsURL BlogURL where</div><div><div>  toURLS   = gtoURLS . from</div><div>  fromURLC = fmap (fmap to) gfromURLC</div></div><div><div><br>

$(deriveAll &#39;&#39;SiteURL &quot;PFSiteURL&quot;)</div><div>type instance PF SiteURL = PFSiteURL</div><div><br></div><div>instance AsURL SiteURL where</div><div><div>  toURLS   = gtoURLS . from</div><div>  fromURLC = fmap (fmap to) gfromURLC</div>



<div><br></div></div></div></div><div><div>that should also work with main1b.</div><div><br></div><div>Or you could do it without AsURL at all using syb:</div><div><br></div><div>gtoURL  :: (Data url) =&gt; url -&gt; String</div>


<div>gfromURL :: (Data url) =&gt; String -&gt; Failing url</div><div><br></div><div><div>     run 3000 $ handleWai gtoURL gfromURL (mySite now) &quot;<a href="http://localhost:3000" target="_blank">http://localhost:3000</a>&quot;</div>

<div>
<br></div><div>Or you could add an AsURL instance that just called gtoURL / gfromURL, and then you could use handleWaiU.</div><div><br></div><div>If you want to write parsers by hand, you could do it using parsec:</div><div>


<br></div><div><div>main1c :: IO ()</div><div>main1c =</div><div>  do now &lt;- getCurrentTime</div><div>     run 3000 $ handleWai toSiteURL (fromURLP pSiteURL) (mySite now) &quot;<a href="http://localhost:3000" target="_blank">http://localhost:3000</a>&quot;</div>


<div>       where</div><div>         pBlogURL :: Parser BlogURL</div><div>         pBlogURL = </div><div>           do char &#39;/&#39;</div><div>              (BlogPost &lt;$&gt; many1 (noneOf &quot;/&quot;)) &lt;|&gt; pure BlogHome</div>


<div>         pSiteURL :: Parser SiteURL</div><div>         pSiteURL =</div><div>           do char &#39;/&#39;</div><div>              MyBlog &lt;$&gt; (string &quot;blog&quot; *&gt; pBlogURL) &lt;|&gt; pure MyHome</div>


<div>         </div><div>         toBlogURL :: BlogURL -&gt; String</div><div>         toBlogURL BlogHome         = &quot;&quot;</div><div>         toBlogURL (BlogPost title) = title</div><div>         </div><div>         toSiteURL :: SiteURL -&gt; String</div>


<div>         toSiteURL MyHome           = &quot;&quot;</div><div>         toSiteURL (MyBlog blogURL) = &quot;blog/&quot; &lt;/&gt; (toBlogURL blogURL)</div><div><br></div><div>In this example,  I call handleWai. But I could also create AsURL instances and call handleWaiU.</div>


<div><br></div><div>Parsec is perhaps not the best choice of parser combinators. A more specialized URL parser combinator library might be nice.</div><div><br></div><div>We could also add a helper function so that it is easier to do things via straight pattern matching. But I think straight pattern patching may prove tedious rather quickly? </div>


<div><br></div><div>In general though, I am not a big fan of writing the converters by hand, because there is no assurance that they are inverses of each other, and it&#39;s annoying to have to basically express the same structure twice -- once to parse it, and once to print it. </div>


<div><br></div><div>But there does need to be someway where you can very explicitly map how the datatype and string representation of the URL are related.</div><div><br></div><div>It would be much better if there was a DSL that simultaneously expressed how to parse and how to print. I have not worked out how to do that yet though -- it is somewhat tricky.</div>


<div><br></div><div>However, the quasiquote stuff looks potentially promising as a way of expressing the parsing and printing in a single step...</div><div><br></div><font color="#888888"><div>- jeremy</div></font></div>

</div></div></div></div>
</blockquote></div><br>
<div>I&#39;m glad to hear someone else finds writing the same data twice to be error-prone and redundant. If we get this core out there, I&#39;ll happily split my mkResources quasi-quoter from Yesod and make it available as a standalone package.</div>
<div><br></div><div>By the way, should we think of something more descriptive than urlt?</div><div><br></div><div>Michael</div>