Safe Haskell | None |
---|---|
Language | Haskell2010 |
Web.Route.Invertible.Internal
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
- class (Eq s, IsString s, Hashable s, Monoid s) => RouteString s where
- data Placeholder s a where
- PlaceholderFixed :: !s -> Placeholder s ()
- PlaceholderParameter :: Parameter s a => Placeholder s a
- data PlaceholderValue s where
- PlaceholderValueFixed :: !s -> PlaceholderValue s
- PlaceholderValueParameter :: Parameter s a => a -> PlaceholderValue s
- newtype Sequence s a = Sequence {
- freeSequence :: Free (Placeholder s) a
- newtype Path a = Path {}
- normalizePath :: [PathString] -> [PathString]
- pathValues :: Path a -> a -> [PlaceholderValue PathString]
- renderPath :: Path a -> a -> [PathString]
- urlPathBuilder :: Path a -> a -> Builder
- newtype Host a = HostRev {}
- splitHost :: ByteString -> [HostString]
- joinHost :: [HostString] -> ByteString
- renderHost :: Host a -> a -> ByteString
- class IsMethod m where
- toMethod :: m -> Method
- fromMethod :: Method -> Maybe m
- type QueryParams = HashMap QueryString [QueryString]
- paramsQuerySimple :: QueryParams -> SimpleQuery
- simpleQueryParams :: SimpleQuery -> QueryParams
- blankRequest :: Request
- data RoutePredicate a where
- RouteHost :: !(Host h) -> RoutePredicate h
- RouteSecure :: !Bool -> RoutePredicate ()
- RoutePath :: !(Path p) -> RoutePredicate p
- RouteMethod :: !Method -> RoutePredicate ()
- RouteQuery :: !QueryString -> !(Placeholder QueryString a) -> RoutePredicate a
- RouteAccept :: !ContentType -> RoutePredicate ()
- RouteCustom :: Typeable a => (Request -> Maybe a) -> (a -> Request -> Request) -> RoutePredicate a
- RoutePriority :: !Int -> RoutePredicate ()
- newtype Route a = Route {
- freeRoute :: Free RoutePredicate a
- normRoute :: Route a -> Route a
- foldRoute :: Monoid b => (forall a'. RoutePredicate a' -> a' -> b) -> Route a -> a -> b
- requestRoute' :: Route a -> a -> Request -> Request
- requestRoute :: Route a -> a -> Request
General
class (Eq s, IsString s, Hashable s, Monoid s) => RouteString s where Source #
Representions of request data that can be used in routing
Instances
RouteString String Source # | |
RouteString ByteString Source # | |
Defined in Web.Route.Invertible.String Methods toString :: ByteString -> String Source # | |
RouteString Text Source # | |
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
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.
Constructors
PlaceholderValueFixed :: !s -> PlaceholderValue s | |
PlaceholderValueParameter :: Parameter s a => a -> PlaceholderValue s |
Instances
Eq s => Eq (PlaceholderValue s) Source # | |
Defined in Web.Route.Invertible.Placeholder Methods (==) :: PlaceholderValue s -> PlaceholderValue s -> Bool # (/=) :: PlaceholderValue s -> PlaceholderValue s -> Bool # | |
Ord s => Ord (PlaceholderValue s) Source # | |
Defined in Web.Route.Invertible.Placeholder Methods compare :: PlaceholderValue s -> PlaceholderValue s -> Ordering # (<) :: PlaceholderValue s -> PlaceholderValue s -> Bool # (<=) :: PlaceholderValue s -> PlaceholderValue s -> Bool # (>) :: PlaceholderValue s -> PlaceholderValue s -> Bool # (>=) :: PlaceholderValue s -> PlaceholderValue s -> Bool # max :: PlaceholderValue s -> PlaceholderValue s -> PlaceholderValue s # min :: PlaceholderValue s -> PlaceholderValue s -> PlaceholderValue s # | |
(RouteString s, Show s) => Show (PlaceholderValue s) Source # | |
Defined in Web.Route.Invertible.Placeholder Methods showsPrec :: Int -> PlaceholderValue s -> ShowS # show :: PlaceholderValue s -> String # showList :: [PlaceholderValue s] -> ShowS # |
A parser/reverse-router isomorphism between sequences of strings (represented as [s]
) and a value a
.
These can be constructed using:
(or simplyfromString
ss
with OverloadedStrings), which matches a single literal component.
(orparameter
for an explicit type), which matches a place-holder component for aparam
(undefined :: T)Parameter
type.
Sequence values can then be composed using Monoidal
and MonoidalAlt
.
Constructors
Sequence | |
Fields
|
Instances
Parameterized s (Sequence s) Source # | |
Monoidal (Sequence s) Source # | |
MonoidalAlt (Sequence s) Source # | |
Functor (Sequence s) Source # | |
Show s => Show (Sequence s a) Source # | |
IsString s => IsString (Sequence s ()) Source # | |
Defined in Web.Route.Invertible.Sequence Methods fromString :: String -> Sequence s () # |
Path
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 | |
Fields |
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 #
Host
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 | |
Fields |
Instances
Monoidal Host Source # | |
MonoidalAlt Host Source # | |
Functor Host Source # | |
Parameterized HostString Host Source # | |
Defined in Web.Route.Invertible.Host | |
Show (Host a) Source # | |
IsString (Host ()) Source # | Since domain components cannot contain ".", |
Defined in Web.Route.Invertible.Host 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
class IsMethod m where Source #
Any types that represent an HTTP method.
Instances
IsMethod ByteString Source # | |
Defined in Web.Route.Invertible.Method | |
IsMethod StdMethod Source # | |
IsMethod Method Source # | |
IsMethod Method Source # | |
IsMethod (Either ByteString StdMethod) Source # | |
Defined in Web.Route.Invertible.Method Methods toMethod :: Either ByteString StdMethod -> Method Source # fromMethod :: Method -> Maybe (Either ByteString StdMethod) Source # |
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.
Constructors
RouteHost :: !(Host h) -> RoutePredicate h | |
RouteSecure :: !Bool -> RoutePredicate () | |
RoutePath :: !(Path p) -> RoutePredicate p | |
RouteMethod :: !Method -> RoutePredicate () | |
RouteQuery :: !QueryString -> !(Placeholder QueryString a) -> RoutePredicate a | |
RouteAccept :: !ContentType -> RoutePredicate () | |
RouteCustom :: Typeable a => (Request -> Maybe a) -> (a -> Request -> Request) -> RoutePredicate a | |
RoutePriority :: !Int -> RoutePredicate () |
Instances
Show (RoutePredicate a) Source # | |
Defined in Web.Route.Invertible.Route Methods showsPrec :: Int -> RoutePredicate a -> ShowS # show :: RoutePredicate a -> String # showList :: [RoutePredicate a] -> ShowS # |
A Monoidal
collection of routing predicates.
For example:
routeHost ("www" >* "domain.com") *< routePath ("object" *< parameter) :: Route Int
Constructors
Route | |
Fields
|
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 Source #
Apply requestRoute'
to blankRequest
.