Twain and matching routes ending in slash

A while back I got a bunch of great help with combining the web framework Twain with postgresql-simple - so tonight I converted my small web-app from Spock to Twain, and it seems to have gone quite well, everything is working.

Well, except for one thing - routes that end with “/”. If make a route like this in Spock:

  get "about" about

It matches both https://example.org/about and https://example.org/about/ - which is what I want.

When I make a route like this in Twain:

                    , get "about" (about state pool)

it only matches https://example.org/about, and what’s worse: I cannot make Twain match https://example.org/about/(!) Eg going get "about/" (about state pool) doesn’t match, neither does get "/about/", so I am at a loss.

I could perhaps do some trickery in Apache, but I’d really rather like the framework to keep handling this.

The only workaround I have found so far is:

                    , get "/about/:wat" (about state pool)

but that feels kind of ugly. Especially when I want, say, a word-cloud of all keywords on /keyword/ (so one function) and a list of articles matching a specific keyword on /keyword/programming (another function), for instance.

Any ideas?

Cc: @gilmi

I think it’s a minor defect in the path matcher (or perhaps intentional behaviour). You could probably get away with something like

(warning, completely untested so there may be typos, bugs and missed imports)

import           Data.Text (Text)
import qualified Data.Text as T
import           Web.Twain
import           Web.Twain.Types

get' :: Text -> ResponderM a -> Middleware
get' = get . matchWithTrailingSlash

matchWithTrailingSlash :: Text -> PathPattern
matchWithTrailingSlash path = MatchPath (\req -> go (splitPath path) (pathInfo req) (Just []))
  where
    splitPath = filter (not . T.null) . T.split (== '/')
    go (p : ps) (r : rs) m@(Just pms)
      | T.head p == ':' = go ps rs (Just ((T.drop 1 p, r) : pms))
      | p == r = go ps rs m
    go [] [r] pms | T.null r = pms -- a single trailing slash
    go [] [] pms = pms
    go _ _ _ = Nothing

and then (hopefully) get' "about" (about state pool) will have the desired behaviour

2 Likes

After fixing two typos, it seems to work exactly as I wanted:

-import           Web.Train.Types
+import           Web.Twain.Types
-go [] [r] | T.null r = pms -- a single trailing slash
´go [] [r] pms | T.null r = pms -- a single trailing slash

Thanks for the help!

I will see if I can report this to the author of Twain.

After fixing two typos

I’ve edited the post so that they’re now fixed for the benefit of future readers

1 Like

Sweet - thanks again, hopefully my website will be leak free now :slight_smile: