module HAppS.Helpers.Redirect where import HAppS.Server import qualified Data.ByteString.Char8 as B import Text.StringTemplate.Helpers import qualified Data.Map as M import Data.String.Utils (split) import Control.Monad.Trans import HAppS.Helpers.ParseRequest {- | redirectPath def path rq = ... eg, redirectPath (fail "horribly) "/path/to/page" will redirect to http://myserver.com/path/to/page or http://localhost:5001/path/to/page depending on whether it is servin in online environemnt or for local development on port 5001 Could produce an error if the hostname can't be determined for some reason (malformed headers?) -} redirectPath :: (MonadIO m) => WebT m Response -> String -> Request -> WebT m Response redirectPath def p rq = do case modRewriteAppUrl p rq of Left _ -> def Right au -> redirectToUrl au {- | Escape a serverPartT handler by redirecting somewhere Basically a wrapper around supplied seeOther function, which doesn't quite do what I want -} redirectToUrl :: MonadIO m => String -> WebT m Response redirectToUrl url = seeOther url $ toResponse ()