[web-devel] strange link behavior in yesod

Michael Snoyman michael at snoyman.com
Sun Apr 10 20:29:08 CEST 2011


Thank you, that was an actual bug caused by the switch from web-routes to
http-types. Firstly, in order to get the new code, run:

    ghc-pkg unregister yesod-core-0.8.0 --force && rm -rf
~/.cabal/packages/yesod-yackage && cabal update && cabal install yesod

What happens when you give Yesod a route like RootR is:

* It converts RootR into a list of path pieces, in this case, []
* It passes [] to the encodePath function from http-types. In previous
versions, it used encodePathSegments from web-routes, which has slightly
different semantics. http-types returns an empty string, will
encodePathSegments returns a forward slash.
* It concatenates the path just generated with the approot.

So in Yesod 0.7.0, the result will be "/" for your application, but in
0.8.0, the result is "". This bug won't show up in most real-life testing,
since most sites provide a proper approot. For example, this would cause a
home link on Haskellers to be "http://www.haskellers.com" instead of "
http://www.haskellers.com/".

The patch I just pushed tells Yesod to pass [""] to encodePath in the case
of a root link. I'm not sure if this was the right decision, or to modify
the behavior of encodePath. But either way, it fixes the issue.

Thanks again!
Michael

On Sun, Apr 10, 2011 at 7:55 PM, Chris Casinghino <
chris.casinghino at gmail.com> wrote:

> Hi all,
>
> I'm running the Yesod 0.8 beta on GHC 7.0.3 and seeing some strange
> behavior.  I'm a total Yesod newbie, so please forgive me if I'm
> missing something obvious.
>
> Below is a simplification of the Links example from the Yesod book.
> When I run the program with "runhaskell links.hs", the link on page1
> points back to page1, instead of home.
>
> I'd be very grateful if someone could explain what I'm doing wrong.
> Thanks!
>
> --Chris Casinghino
>
> > {-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses,
> TemplateHaskell, OverloadedStrings #-}
> > module Links where
> >
> > import Yesod
> >
> > data Links = Links
> >
> > mkYesod "Links" [parseRoutes|
> > / HomeR GET
> > /page1 Page1R GET
> > |]
> >
> > instance Yesod Links where
> >   approot _ = ""
> >
> > getHomeR  = defaultLayout [hamlet|<a href="@{Page1R}">Go to page 1!|]
> > getPage1R = defaultLayout [hamlet|<a href="@{HomeR}">Go home!|]
> >
> > main :: IO ()
> > main = warpDebug 3000 Links
>
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20110410/2f16cd33/attachment.htm>


More information about the web-devel mailing list