apiary-2.1.2: Simple and type safe web framework that generate web API documentation.

Safe HaskellNone
LanguageHaskell2010

Data.Apiary.Routing

Contents

Description

>>> :set -XDataKinds -XPolyKinds -XOverloadedStrings
>>> data Proxy s = Proxy
>>> import Text.Read(readMaybe)
>>> import qualified Data.Text as T
  1. create path
>>> data Result = A | B T.Text | C | D Int | E T.Text deriving Show
>>> let key = Proxy :: Proxy "key"
>>> let a = root $ exact "foo" $ action Nothing (\_ -> Just A)
>>> let b = root $ exact "bar" $ fetch key Just $ action Nothing (\d -> Just . B $ D.get key d)
>>> let c = root $ exact "bar" $ any $ action (Just "GET") (\_ -> Just C)
>>> let d = root $ exact "bar" $ fetch key (\t -> readMaybe (T.unpack t) :: Maybe Int) $ action Nothing (\d -> Just . D $ D.get key d)
>>> let e = root $ exact "foo" $ fetch key Just $ exact "qux" $ action (Just "POST") (\d -> Just . E $ D.get key d)
>>> a
* /foo
>>> b
* /bar/:key
>>> c
GET /bar/**
>>> d
* /bar/:key
>>> e
POST /foo/:key/qux
  1. create router
>>> let r = e +| d +| a +| b +| c +| empty
  1. execute router
>>> let run = execute r
>>> run "GET" ["foo"]
Just A
>>> run "GET" ["foo", "bar"]
Nothing
>>> run "GET" ["bar", "12"]
Just (D 12)
>>> run "GET" ["bar", "baz"]
Just (B "baz")
>>> run "GET" ["bar", "baz", "qux"]
Just C
>>> run "POST" ["bar", "baz", "qux"]
Nothing
>>> run "POST" ["foo", "bar", "baz"]
Nothing
>>> run "POST" ["foo", "bar", "qux"]
Just (E "bar")

Synopsis

Documentation

Path

data Path d m a Source #

routing path

Instances

Show (Path d m a) Source # 

Methods

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

show :: Path d m a -> String #

showList :: [Path d m a] -> ShowS #

showPath :: Path d m a -> String Source #

show path. since v0.6.0.

getMethod :: Path d m a -> Maybe Method Source #

get method. since v0.6.0.

root :: Path '[] m a -> Path '[] m a Source #

root

root == id

children

exact :: Text -> Path d m a -> Path d m a Source #

exact matching path

action

action Source #

Arguments

:: Maybe Method

if Nothing, any method allowed

-> (Dict d -> m a)

action when route matching

-> Path d m a 

action

get parameter

type Raw m d d' Source #

Arguments

 = Store d

input dictionary

-> [Text]

input path information

-> m (Store d', [Text])

output dictionary and path information

raw Source #

Arguments

:: String

pretty print

-> Raw m d d' 
-> Path d' m a 
-> Path d m a 

get one directory as parameter.

raw get parameter function

if you want matching exact path, use exact for performance

fetch Source #

Arguments

:: (MonadPlus m, KnownSymbol k, k </ d) 
=> proxy k

dictionary key

-> (Text -> Maybe v)

reading function

-> Path ((k := v) ': d) m a 
-> Path d m a 

any :: Monad m => Path d m a -> Path d m a Source #

drop any pathes

rest Source #

Arguments

:: (KnownSymbol k, Monad m, k </ d) 
=> proxy k

dictionary key

-> Path ((k := [Text]) ': d) m a 
-> Path d m a 

take any pathes as [Text]

Router

data Router d m a Source #

router

empty :: MonadPlus m => Router '[] m a Source #

empty router

insert :: MonadPlus m => Path '[] m a -> Router '[] m a -> Router '[] m a infixr 9 Source #

insert path to router

(+|) :: MonadPlus m => Path '[] m a -> Router '[] m a -> Router '[] m a infixr 9 Source #

infix version of insert

execute

execute :: MonadPlus m => Router '[] m a -> Method -> [Text] -> m a Source #

execute router

reexport