webgear-server-0.2.0: Composable, type-safe library to build HTTP API servers

Copyright(c) Raghu Kaippully 2020
LicenseMPL-2.0
Maintainerrkaippully@gmail.com
Safe HaskellNone
LanguageHaskell2010

WebGear.Middlewares.Path

Description

Middlewares related to route paths.

Synopsis

Documentation

data Path (s :: Symbol) Source #

A path component which is literally matched against the request but discarded after that.

Instances
(KnownSymbol s, MonadState PathInfo m) => Trait (Path s :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Path

Associated Types

type Attribute (Path s) Request :: Type Source #

type Absence (Path s) Request :: Type Source #

type Attribute (Path s :: Type) Request Source # 
Instance details

Defined in WebGear.Middlewares.Path

type Attribute (Path s :: Type) Request = ()
type Absence (Path s :: Type) Request Source # 
Instance details

Defined in WebGear.Middlewares.Path

type Absence (Path s :: Type) Request = ()

data PathVar tag val Source #

A path variable that is extracted and converted to a value of type val. The tag is usually a type-level symbol (string) to uniquely identify this variable.

Instances
(FromHttpApiData val, MonadState PathInfo m) => Trait (PathVar tag val :: Type) Request m Source # 
Instance details

Defined in WebGear.Middlewares.Path

Associated Types

type Attribute (PathVar tag val) Request :: Type Source #

type Absence (PathVar tag val) Request :: Type Source #

Methods

toAttribute :: Request -> m (Result (PathVar tag val) Request) Source #

type Attribute (PathVar tag val :: Type) Request Source # 
Instance details

Defined in WebGear.Middlewares.Path

type Attribute (PathVar tag val :: Type) Request = val
type Absence (PathVar tag val :: Type) Request Source # 
Instance details

Defined in WebGear.Middlewares.Path

data PathEnd Source #

Trait to indicate that no more path components are present in the request

Instances
MonadState PathInfo m => Trait PathEnd Request m Source # 
Instance details

Defined in WebGear.Middlewares.Path

type Attribute PathEnd Request Source # 
Instance details

Defined in WebGear.Middlewares.Path

type Absence PathEnd Request Source # 
Instance details

Defined in WebGear.Middlewares.Path

path :: forall s ts m a. (KnownSymbol s, MonadRouter m) => RequestMiddleware' m ts (Path s ': ts) a Source #

A middleware that literally matches path s.

The symbol s could contain one or more parts separated by a forward slash character. The route will be rejected if there is no match.

For example, the following code could be used to match the URL path "a/b/c" and then invoke handler:

path @"a/b/c" handler

pathVar :: forall tag val ts m a. (FromHttpApiData val, MonadRouter m) => RequestMiddleware' m ts (PathVar tag val ': ts) a Source #

A middleware that captures a path variable from a single path component.

The value captured is converted to a value of type val via FromHttpApiData. The route will be rejected if the value is not found or cannot be converted.

For example, the following code could be used to read a path component as Int tagged with the symbol "objId", and then invoke handler:

pathVar @"objId" @Int handler

pathEnd :: MonadRouter m => RequestMiddleware' m ts (PathEnd ': ts) a Source #

A middleware that verifies that end of path is reached.

match :: QuasiQuoter Source #

Produces middleware(s) to match an optional HTTP method and some path components.

This middleware matches a prefix of path components, the remaining components can be matched by subsequent uses of match.

This quasiquoter can be used in several ways:

QuasiQuoter Equivalent Middleware
[match| /a/b/c |] path @"/a/b/c"
[match| /a/b/objId:Int/d |] path @"/a/b" . pathVar @"objId" @Int . path @"d"
[match| GET /a/b/c |] method @GET . path @"/a/b/c"
[match| GET /a/b/objId:Int/d |] method @GET . path @"/a/b" . pathVar @"objId" @Int . path @"d"

route :: QuasiQuoter Source #

Produces middleware(s) to match an optional HTTP method and the entire request path.

This middleware is intended to be used in cases where the entire path needs to be matched. Use match middleware to match only an initial portion of the path.

This quasiquoter can be used in several ways:

QuasiQuoter Equivalent Middleware
[route| /a/b/c |] path @"/a/b/c" . pathEnd
[route| /a/b/objId:Int/d |] path @"/a/b" . pathVar @"objId" @Int . path @"d" . pathEnd
[route| GET /a/b/c |] method @GET . path @"/a/b/c" . pathEnd
[route| GET /a/b/objId:Int/d |] method @GET . path @"/a/b" . pathVar @"objId" @Int . path @"d" . pathEnd