rowdy-0.0.1.0: An EDSL for web application routes.

Safe HaskellNone
LanguageHaskell2010

Rowdy

Description

Rowdy is a DSL for defining web routes. The DSL is only a nice syntax for expressing the tree-like structure of routes -- to actually interpret the route into something useful, you'll need another package.

rowdy-yesod provides a function that converts this representation into the Yesod route format, allowing you to drop the quasiquotater and use a plain Haskell DSL.

rowdy-servant provides a function that converts the DSL into Servant's type level DSL for defining routes. This allows you to work with a value-level DSL, taking full advantage of Haskell's value level programming, and then promote the DSL to the type level using Template Haskell.

Synopsis

Documentation

newtype RouteDsl nest capture terminal a Source #

A RouteDsl is a type useful for constructing web routes. At it's heart, it is a DSL for constructing a RouteTree, and is totally optional.

Routes are defined by how they handle nesting, what sorts of values are used to represent captures, and what values are used to represent endpoints.

Since: 0.0.1.0

Constructors

RouteDsl 

Fields

Instances

Monad (RouteDsl nest capture terminal) Source # 

Methods

(>>=) :: RouteDsl nest capture terminal a -> (a -> RouteDsl nest capture terminal b) -> RouteDsl nest capture terminal b #

(>>) :: RouteDsl nest capture terminal a -> RouteDsl nest capture terminal b -> RouteDsl nest capture terminal b #

return :: a -> RouteDsl nest capture terminal a #

fail :: String -> RouteDsl nest capture terminal a #

Functor (RouteDsl nest capture terminal) Source # 

Methods

fmap :: (a -> b) -> RouteDsl nest capture terminal a -> RouteDsl nest capture terminal b #

(<$) :: a -> RouteDsl nest capture terminal b -> RouteDsl nest capture terminal a #

Applicative (RouteDsl nest capture terminal) Source # 

Methods

pure :: a -> RouteDsl nest capture terminal a #

(<*>) :: RouteDsl nest capture terminal (a -> b) -> RouteDsl nest capture terminal a -> RouteDsl nest capture terminal b #

liftA2 :: (a -> b -> c) -> RouteDsl nest capture terminal a -> RouteDsl nest capture terminal b -> RouteDsl nest capture terminal c #

(*>) :: RouteDsl nest capture terminal a -> RouteDsl nest capture terminal b -> RouteDsl nest capture terminal b #

(<*) :: RouteDsl nest capture terminal a -> RouteDsl nest capture terminal b -> RouteDsl nest capture terminal a #

MonadWriter (DForest nest capture terminal) (RouteDsl nest capture terminal) Source # 

Methods

writer :: (a, DForest nest capture terminal) -> RouteDsl nest capture terminal a #

tell :: DForest nest capture terminal -> RouteDsl nest capture terminal () #

listen :: RouteDsl nest capture terminal a -> RouteDsl nest capture terminal (a, DForest nest capture terminal) #

pass :: RouteDsl nest capture terminal (a, DForest nest capture terminal -> DForest nest capture terminal) -> RouteDsl nest capture terminal a #

runRouteDsl :: RouteDsl n c e a -> Forest n c e Source #

Run the given RouteDsl and convert it into the Forest of routes. If you are defining an interpreter for a web framework, you will want to call this on the RouteDsl value.

Since: 0.0.1.0

runRouteDsl' :: RouteDsl n c e a -> DForest n c e Source #

Run the given RouteDsl and convert it into a DList of routes. This is useful when implementing combinators.

Since: 0.0.1.0

pathComponent :: capture -> RouteDsl nest capture endpoint () -> RouteDsl nest capture endpoint () Source #

Introduce a capture into all of the routes defined in the second argument. This function does not introduce nesting, so multiple distinct routes will be created.

As an example:

example :: RouteDsl nest String String ()
example =
    pathComponent "hello" $ do
        terminal "first route"
        terminal "second route"

Calling runRouteDsl example will give a data structure like:

[ PathComponent "hello" (Leaf "first route")
, PathComponent "hello" (Leaf "second route")
]

Since: 0.0.1.0

(//) :: capture -> RouteDsl nest capture endpoint () -> RouteDsl nest capture endpoint () infixr 5 Source #

An infix operator for pathComponent.

Since: 0.0.1.0

nest :: nest -> RouteDsl nest capture endpoint () -> RouteDsl nest capture endpoint () Source #

Introduce a nesting point in the route DSL. While the pathComponent function adds the capture to each route defined in the second argument, this one preserves the tree-like structure of the declaration.

example :: RouteDsl String String String ()
example =
    pathComponent "thing" $ nest "hello" $ do
         terminal "first"
         terminal "second"

Calling runRouteDsl example would give a data structure like:

[ PathComponent "thing" (Nest
    [ Leaf "first"
    , Leaf "second"
    ]
  )
]

In constrast, if nest were not called, you would see the PathComponent repeated and distributed to both endpoints.

Since: 0.0.1.0

(/:) :: nest -> RouteDsl nest capture endpoint () -> RouteDsl nest capture endpoint () infixr 7 Source #

An infix operator alias for nest.

Since: 0.0.1.0

terminal :: endpoint -> RouteDsl nest capture endpoint () Source #

Record the given endpoint as a route.

Since: 0.0.1.0

unnest :: RouteTree nest capture terminal -> [([capture], terminal)] Source #

Convert a RouteTree into a flattened list of routes. Each terminal is paired with the list of captures that preceeded it.

Since: 0.0.1.0

type ForestOf f n capture terminal = f (RouteTree n capture terminal) Source #

For efficiency's sake, we encode the route DSL as a DList while defining them, and (for convenience's sake) we present them as an ordinary list when you run it. To prevent type complexity, we parameterize the forest on how we're working with it.

Since: 0.0.1.0

type DForest n c t = ForestOf DList n c t Source #

A difference list (DList) of RouteTree values.

Since: 0.0.1.0

type Forest n c t = ForestOf [] n c t Source #

A list of RouteTree values.

Since: 0.0.1.0

data RouteTree nest capture terminal Source #

The core data type that is produced by the RouteDsl. If you'd prefer a non-monadic interface to creating these, you're welcome to use the constructors directly.

The DSL defined as example below has the route representation given by desugared:

example :: Forest String String String
example = runRouteDsl $ do
    "hello" // do
        terminal "world"
        terminal "friend"
        "nest" /: do
            terminal "nope"
            terminal "yes"

desugared :: Forest String String String
desugared =
    [ PathComponent "hello" (Leaf "world")
    , PathComponent "hello" (Leaf "friend")
    , PathComponent "hello" (Nest "nest"
        [ Leaf "nope"
        , Leaf "yes"
        ]
      )
    ]

Since: 0.0.1.0

Constructors

Leaf terminal 
PathComponent capture (RouteTree nest capture terminal) 
Nest nest [RouteTree nest capture terminal] 

Instances

Functor (RouteTree nest capture) Source # 

Methods

fmap :: (a -> b) -> RouteTree nest capture a -> RouteTree nest capture b #

(<$) :: a -> RouteTree nest capture b -> RouteTree nest capture a #

Foldable (RouteTree nest capture) Source # 

Methods

fold :: Monoid m => RouteTree nest capture m -> m #

foldMap :: Monoid m => (a -> m) -> RouteTree nest capture a -> m #

foldr :: (a -> b -> b) -> b -> RouteTree nest capture a -> b #

foldr' :: (a -> b -> b) -> b -> RouteTree nest capture a -> b #

foldl :: (b -> a -> b) -> b -> RouteTree nest capture a -> b #

foldl' :: (b -> a -> b) -> b -> RouteTree nest capture a -> b #

foldr1 :: (a -> a -> a) -> RouteTree nest capture a -> a #

foldl1 :: (a -> a -> a) -> RouteTree nest capture a -> a #

toList :: RouteTree nest capture a -> [a] #

null :: RouteTree nest capture a -> Bool #

length :: RouteTree nest capture a -> Int #

elem :: Eq a => a -> RouteTree nest capture a -> Bool #

maximum :: Ord a => RouteTree nest capture a -> a #

minimum :: Ord a => RouteTree nest capture a -> a #

sum :: Num a => RouteTree nest capture a -> a #

product :: Num a => RouteTree nest capture a -> a #

(Eq nest, Eq capture, Eq terminal) => Eq (RouteTree nest capture terminal) Source # 

Methods

(==) :: RouteTree nest capture terminal -> RouteTree nest capture terminal -> Bool #

(/=) :: RouteTree nest capture terminal -> RouteTree nest capture terminal -> Bool #

(Show nest, Show capture, Show terminal) => Show (RouteTree nest capture terminal) Source # 

Methods

showsPrec :: Int -> RouteTree nest capture terminal -> ShowS #

show :: RouteTree nest capture terminal -> String #

showList :: [RouteTree nest capture terminal] -> ShowS #

MonadWriter (DForest nest capture terminal) (RouteDsl nest capture terminal) Source # 

Methods

writer :: (a, DForest nest capture terminal) -> RouteDsl nest capture terminal a #

tell :: DForest nest capture terminal -> RouteDsl nest capture terminal () #

listen :: RouteDsl nest capture terminal a -> RouteDsl nest capture terminal (a, DForest nest capture terminal) #

pass :: RouteDsl nest capture terminal (a, DForest nest capture terminal -> DForest nest capture terminal) -> RouteDsl nest capture terminal a #