{-# LANGUAGE QuasiQuotes #-} -- | Stolen from rack: -- Rack::URLMap takes a hash mapping urls or paths to apps, and -- dispatches accordingly. -- -- URLMap modifies the SCRIPT_NAME and PATH_INFO such that the part -- relevant for dispatch is in the SCRIPT_NAME, and the rest in the -- PATH_INFO. This should be taken care of when you need to -- reconstruct the URL in order to create links. -- -- URLMap dispatches in such a way that the longest paths are tried -- first, since they are most specific. module Hack.Contrib.Middleware.SimpleRouter (route) where import Hack import MPSUTF8 import Prelude hiding ((.), (^), (>)) import List (find, isPrefixOf) type RoutePath = (String, Application) route :: [RoutePath] -> Middleware route h app = \env -> let path = env.path_info script = env.script_name mod_env location = env { script_name = script ++ location , path_info = path.drop (location.length) } in case h.find (fst > (`isPrefixOf` path) ) of Nothing -> app env Just (location, app') -> app' (mod_env location)