web-routes-quasi-0.4.0: Define data types and parse/build functions for web-routes via a quasi-quoted DSL

Web.Routes.Quasi

Contents

Synopsis

Quasi quoter

parseRoutes :: QuasiQuoterSource

A quasi-quoter to parse a string into a list of Resources. Checks for overlapping routes, failing if present; use parseRoutesNoCheck to skip the checking. See documentation site for details on syntax.

parseRoutesNoCheck :: QuasiQuoterSource

Same as parseRoutes, but performs no overlap checking.

Template haskell

Low level

createQuasiDispatch :: QuasiSiteSettings -> Q [Clause]Source

Generate the set of clauses necesary to dispatch the given Resources. See quasiDispatch.

createRender :: QuasiSiteSettings -> [Resource] -> Q [Clause]Source

Generates the set of clauses necesary to render the given Resources. See quasiRender.

createParse :: QuasiSiteSettings -> [Resource] -> Q [Clause]Source

Generates the set of clauses necesary to parse the given Resources. See quasiParse.

High level for QuasiSites

createQuasiSite :: QuasiSiteSettings -> Q QuasiSiteDecsSource

Template haskell code to convert a list of Resources into appropriate declarations for a QuasiSite. See the QuasiSiteSettings and QuasiSiteDecs data types for an explanation for the input and output, respectively, of this function.

data QuasiSiteSettings Source

The arguments passed to createQuasiSite for generating applications based on the QuasiSite datatype.

Constructors

QuasiSiteSettings 

Fields

crRoutes :: Name

The name for the URL data type to be created.

crApplication :: Type

The type for underlying applications.

crArgument :: Type

The type for the argument value to be passed to dispatch functions.

crExplode :: Exp

Underlying applications will often want to program against some datatype. The explode function converts that datatype into a function that will generate an application (crApplication). In particular, the value of crExplode should have a type signature of:

 explode :: handler
         -> ('Routes' master -> String)
         -> 'Routes' sub
         -> ('Routes' sub -> 'Routes' master)
         -> master
         -> (master -> sub)
         -> app
         -> String
         -> app

handler is some datatype handled by the calling application; web-routes-quasi needn't know about it. sub and master are the arguments for the subsite and master site, respectively. app is the datatype for the underlying application; the app argument above is the handler for unsupported method. The String argument is the request method.

crResources :: [Resource]

The Resources upon which we are building the set of URLs and dispatches. Usually generated by parseRoutes.

crSite :: Name

The name for the resulting function which will return the QuasiSite.

crMaster :: Either Type [(String, [Name])]

Describes the type of the master argument. This can either be a Left concrete datatype, or Right a list of Preds describing the context for master.

data QuasiSiteDecs Source

The template Haskell declarations returned from createQuasiSite.

Constructors

QuasiSiteDecs 

Fields

decRoutes :: Dec

Defines the actual URL datatype, with all its constructors.

decRoutesSyn :: Dec

Defines the Routes type synonym instance between the argument (crArgument) and URL datatype.

decSiteType :: Dec

The type signature for the site function (decSite).

decSite :: Dec

Function which returns a QuasiSite. The type parameters for the QuasiSite will be crApplication, crArgument and a forall master.

Quasi site

type QuasiDispatch app sub masterSource

Arguments

 = (Routes master -> String) 
-> Routes sub 
-> (Routes sub -> Routes master) 
-> master 
-> (master -> sub) 
-> app

bad method handler

-> String

method

-> app 

The type for quasiDispatch; separated out for clarity of Haddock docs.

data QuasiSite app sub master Source

Very similar in principle to Site, but with special support for arguments and subsites.

Constructors

QuasiSite 

Fields

quasiDispatch :: QuasiDispatch app sub master
 
quasiRender :: Routes sub -> [String]
 
quasiParse :: [String] -> Either String (Routes sub)
 

quasiFromSite :: Site surl app -> QuasiSite app (BlankArgs surl) masterSource

Convert a Site to a QuasiSite. quasiRender and quasiParse are identical to formatPathSegments and parsePathSegments; for the quasiDispatch function, we just ignore the extra arguments that Site does not use.

quasiToSiteSource

Arguments

:: QuasiSite app sub sub 
-> ((String -> app) -> app)

grab method

-> app

bad method

-> sub 
-> Site (Routes sub) app 

Convert a QuasiSite to a Site. quasiRender and quasiParse are identical to formatPathSegments and parsePathSegments; for the handleSite function, we need some extra information passed to this function. We also restrict the resulting QuasiSite to cases where subsite and master site are the same.

type family Routes a Source

data BlankArgs routes Source

Used for applications with no arguments. In particular, this facilitates a translation from a Site to a QuasiSite via quasiFromSite.

Constructors

BlankArgs 

Underlying data types

data Resource Source

A single resource pattern.

First argument is the name of the constructor, second is the URL pattern to match, third is how to dispatch.

Constructors

Resource String [Piece] Handler 

data Handler Source

Defines how to dispatch a request for a specific resource.

ByMethod allows a different function to be called for each request method. The first value in each pair is the method, the second is the name of the handler.

Single dispatches to a single function for all methods.

SubSite passes dispatch to a different site. The first argument is the name of the datatype for the routes. The second is a function returning a QuasiSite for that type of routes. The third is a function converting the master argument to the subsite argument.

Constructors

ByMethod [(String, String)]

(method, handler)

Single String 
SubSite String String String 

data Piece Source

A single piece of a URL, delimited by slashes.

In the case of StaticPiece, the argument is the value of the piece; for the other constructors, it is the name of the parameter represented by this piece. That value is not used here, but may be useful elsewhere.

FIXME