web-inv-route-0.1.2: Composable, reversible, efficient web routing using invertible invariants and bijections

Safe HaskellNone
LanguageHaskell2010

Web.Route.Invertible.Internal

Contents

Description

This module exposes more of the inner workings of route construction for extensiblity and direct access. You may need interfaces like IsMethod or QueryParams to add support for a new web framework, for example. In particular, functions like foldRoute and pathValues can be used to extract low-level information about individual routes.

Synopsis

General

class (Eq s, IsString s, Hashable s, Monoid s) => RouteString s where Source #

Representions of request data that can be used in routing

Minimal complete definition

toString

Methods

toString :: s -> String Source #

Must be the inverse of fromString

data Placeholder s a where Source #

A segment of a parser over strings s, which may be a fixed string (usually created through IsString), only accepting a single fixed value, or a dynamic parameter (created through Parameterized), which encapsulates a Parameter type.

Constructors

PlaceholderFixed :: !s -> Placeholder s () 
PlaceholderParameter :: Parameter s a => Placeholder s a 

Instances

RouteString s => Parameterized s (Placeholder s) Source # 

Methods

parameter :: Parameter s a => Placeholder s a Source #

Eq s => Eq (Placeholder s a) Source # 

Methods

(==) :: Placeholder s a -> Placeholder s a -> Bool #

(/=) :: Placeholder s a -> Placeholder s a -> Bool #

Ord s => Ord (Placeholder s a) Source # 

Methods

compare :: Placeholder s a -> Placeholder s a -> Ordering #

(<) :: Placeholder s a -> Placeholder s a -> Bool #

(<=) :: Placeholder s a -> Placeholder s a -> Bool #

(>) :: Placeholder s a -> Placeholder s a -> Bool #

(>=) :: Placeholder s a -> Placeholder s a -> Bool #

max :: Placeholder s a -> Placeholder s a -> Placeholder s a #

min :: Placeholder s a -> Placeholder s a -> Placeholder s a #

Show s => Show (Placeholder s a) Source # 

Methods

showsPrec :: Int -> Placeholder s a -> ShowS #

show :: Placeholder s a -> String #

showList :: [Placeholder s a] -> ShowS #

IsString s => IsString (Placeholder s ()) Source # 

Methods

fromString :: String -> Placeholder s () #

data PlaceholderValue s where Source #

A concrete, untyped representation of a parsed Placeholder value, distinguishing fixed components from parameters but abstracting over the parsed type.

newtype Sequence s a Source #

A parser/reverse-router isomorphism between sequences of strings (represented as [s]) and a value a. These can be constructed using:

  • fromString s (or simply s with OverloadedStrings), which matches a single literal component.
  • parameter (or param (undefined :: T) for an explicit type), which matches a place-holder component for a Parameter type.

Sequence values can then be composed using Monoidal and MonoidalAlt.

Constructors

Sequence 

Fields

Instances

Parameterized s (Sequence s) Source # 

Methods

parameter :: Parameter s a => Sequence s a Source #

Monoidal (Sequence s) Source # 

Methods

unit :: Sequence s () #

(>*<) :: Sequence s a -> Sequence s b -> Sequence s (a, b) #

MonoidalAlt (Sequence s) Source # 

Methods

zero :: Sequence s Void #

(>|<) :: Sequence s a -> Sequence s b -> Sequence s (Either a b) #

Functor (Sequence s) Source # 

Methods

fmap :: (a <-> b) -> Sequence s a -> Sequence s b #

Show s => Show (Sequence s a) Source # 

Methods

showsPrec :: Int -> Sequence s a -> ShowS #

show :: Sequence s a -> String #

showList :: [Sequence s a] -> ShowS #

IsString s => IsString (Sequence s ()) Source # 

Methods

fromString :: String -> Sequence s () #

Path

newtype Path a Source #

A URL path parser/generator. These should typically be constructed using the IsString and Parameterized instances. Note that the individual components are decoded path segments, so a literal slash in a component (e.g., as produced with fromString) will match "%2F". Example:

"get" *< parameter >*< "value" *< parameter :: Path (String, Int)

matches (or generates) /get/$x/value/$y for any string $x and any int $y and returns those values.

Constructors

Path 

Instances

Monoidal Path Source # 

Methods

unit :: Path () #

(>*<) :: Path a -> Path b -> Path (a, b) #

MonoidalAlt Path Source # 

Methods

zero :: Path Void #

(>|<) :: Path a -> Path b -> Path (Either a b) #

Functor Path Source # 

Methods

fmap :: (a <-> b) -> Path a -> Path b #

Parameterized PathString Path Source # 
Show (Path a) Source # 

Methods

showsPrec :: Int -> Path a -> ShowS #

show :: Path a -> String #

showList :: [Path a] -> ShowS #

IsString (Path ()) Source # 

Methods

fromString :: String -> Path () #

normalizePath :: [PathString] -> [PathString] Source #

Remove double- and trailing-slashes (i.e., empty path segments).

pathValues :: Path a -> a -> [PlaceholderValue PathString] Source #

Render a Path as instantiated by a value to a list of placeholder values.

renderPath :: Path a -> a -> [PathString] Source #

Render a Path as instantiated by a value to a list of string segments.

urlPathBuilder :: Path a -> a -> Builder Source #

Build a Path as applied to a value into a bytestring Builder by encoding the segments with urlEncodePath and joining them with "/".

Host

newtype Host a Source #

A hostname matcher. These should typically be constructed using the IsString and Parameterized instances. This matches hostnames in reverse order (from TLD down), but the Monoidal instance and splitHost automatically deal with this for you. Example:

parameter >* "domain" >* "com" :: Host String

matches (or generates) *.domain.com and returns the * component.

Constructors

HostRev 

Instances

Monoidal Host Source # 

Methods

unit :: Host () #

(>*<) :: Host a -> Host b -> Host (a, b) #

MonoidalAlt Host Source # 

Methods

zero :: Host Void #

(>|<) :: Host a -> Host b -> Host (Either a b) #

Functor Host Source # 

Methods

fmap :: (a <-> b) -> Host a -> Host b #

Parameterized HostString Host Source # 
Show (Host a) Source # 

Methods

showsPrec :: Int -> Host a -> ShowS #

show :: Host a -> String #

showList :: [Host a] -> ShowS #

IsString (Host ()) Source #

Since domain components cannot contain ".", "foo.com" is equivalent to "foo" *< "com" (unlike other Sequences).

Methods

fromString :: String -> Host () #

splitHost :: ByteString -> [HostString] Source #

Split (and reverse) a domainname on "." for use with Host.

joinHost :: [HostString] -> ByteString Source #

Reverse and join a hostname with ".".

renderHost :: Host a -> a -> ByteString Source #

Instantiate a host with a value and render it as a domainname.

Method

Query

type QueryParams = HashMap QueryString [QueryString] Source #

A map from query variables to values, based on SimpleQuery.

Route

blankRequest :: Request Source #

A blank/unknown request; effectively the default value

data RoutePredicate a where Source #

A term, qualifier, or component of a route, each specifying one filterattributeparser/generator for a request.

newtype Route a Source #

A Monoidal collection of routing predicates. For example:

routeHost ("www" >* "domain.com") *< routePath ("object" *< parameter) :: Route Int

Constructors

Route 

Instances

Monoidal Route Source # 

Methods

unit :: Route () #

(>*<) :: Route a -> Route b -> Route (a, b) #

MonoidalAlt Route Source # 

Methods

zero :: Route Void #

(>|<) :: Route a -> Route b -> Route (Either a b) #

Functor Route Source # 

Methods

fmap :: (a <-> b) -> Route a -> Route b #

Show (Route a) Source # 

Methods

showsPrec :: Int -> Route a -> ShowS #

show :: Route a -> String #

showList :: [Route a] -> ShowS #

normRoute :: Route a -> Route a Source #

By default, route predicates are matched in the order they are specified, so each test is done only if all preceding tests succeed. However, in most cases routing rules should be tested in a specific order in order to produce sensible errors (e.g., a 405 error that offers available methods should only apply to other routes with the same path). This re-orders the predicates in a route in order of the constructors in RoutePredicate (i.e., host, secure, path, method, ...), allowing you to construct your routes in any order but still produce sensible matching behavior. Alternatively, since there are cases you may watch to match in a different order (e.g., for routePriority), you can specify your routes in specific order and avoid this function (which would also be more efficient). Note that there are some "de-normalized" cases that this will not correct, such as having duplicate routeMethod specifications (in which case all must match, but each is done independently).

foldRoute :: Monoid b => (forall a'. RoutePredicate a' -> a' -> b) -> Route a -> a -> b Source #

Fold over the predicates in an instatiated route.

requestRoute' :: Route a -> a -> Request -> Request Source #

Given an instantiation of a Route with its value, add the relevant reverse-route information to a Request.