web-routes-0.27.5: Library for maintaining correctness and composability of URLs within an application.

Safe HaskellNone

Web.Routes.PathInfo

Contents

Synopsis

Documentation

stripOverlap :: Eq a => [a] -> [a] -> [a]Source

pToken :: tok -> (Text -> Maybe a) -> URLParser aSource

segment :: Text -> URLParser TextSource

match on a specific string

anySegment :: URLParser TextSource

match on any string

parseSegments :: URLParser a -> [Text] -> Either String aSource

run a URLParser on a list of path segments

returns Left parse error on failure.

returns Right a on success

class PathInfo url whereSource

Simple parsing and rendering for a type to and from URL path segments.

If you're using GHC 7.2 or later, you can use DeriveGeneric to derive instances of this class:

 {-# LANGUAGE DeriveGeneric #-}
 data Sitemap = Home | BlogPost Int deriving Generic
 instance PathInfo Sitemap

This results in the following instance:

 instance PathInfo Sitemap where
     toPathSegments Home = ["home"]
     toPathSegments (BlogPost x) = "blog-post" : toPathSegments x
     fromPathSegments = Home <$ segment "home"
                    <|> BlogPost <$ segment "blog-post" <*> fromPathSegments

And here it is in action:

>>> toPathInfo (BlogPost 123)
"/blog-post/123"
>>> fromPathInfo "/blog-post/123" :: Either String Sitemap
Right (BlogPost 123)

To instead derive instances using TemplateHaskell, see web-routes-th.

toPathInfo :: PathInfo url => url -> TextSource

convert url into the path info portion of a URL

toPathInfoParamsSource

Arguments

:: PathInfo url 
=> url

url

-> [(Text, Maybe Text)]

query string parameter

-> Text 

convert url + params into the path info portion of a URL + a query string

fromPathInfo :: PathInfo url => ByteString -> Either String urlSource

parse a String into url using PathInfo.

returns Left parse error on failure

returns Right url on success

mkSitePISource

Arguments

:: PathInfo url 
=> ((url -> [(Text, Maybe Text)] -> Text) -> url -> a)

a routing function

-> Site url a 

turn a routing function into a Site value using the PathInfo class

showParseError :: ParseError -> StringSource

show Parsec ParseError using terms that relevant to parsing a url

Re-exported for convenience

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic [a] 
Generic (Maybe a) 
Generic (Either a b) 
Generic (a, b) 
Generic (a, b, c) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g)