apiary-0.6.0.0: Simple web framework inspired by scotty.

Safe HaskellNone

Control.Monad.Apiary.Filter

Contents

Synopsis

filters

http method

method :: Monad m => Method -> ApiaryT c m a -> ApiaryT c m aSource

filter by HTTP method. since 0.1.0.0.

stdMethod :: Monad m => StdMethod -> ApiaryT c m a -> ApiaryT c m aSource

filter by HTTP method using StdMethod. since 0.1.0.0.

http version

httpVersion :: Monad m => HttpVersion -> ApiaryT c m b -> ApiaryT c m bSource

http version filter. since 0.5.0.0.

http09 :: Monad m => ApiaryT c m b -> ApiaryT c m bSource

http/0.9 only accepted fiter. since 0.5.0.0.

http10 :: Monad m => ApiaryT c m b -> ApiaryT c m bSource

http/1.0 only accepted fiter. since 0.5.0.0.

http11 :: Monad m => ApiaryT c m b -> ApiaryT c m bSource

http/1.1 only accepted fiter. since 0.5.0.0.

path matcher

root :: Monad m => ApiaryT c m b -> ApiaryT c m bSource

filter by rootPattern of ApiaryConfig.

capture :: QuasiQuoterSource

capture QuasiQuoter. since 0.1.0.0.

example:

 [capture|/path|] -- first path == path
 [capture|/int/:Int|] -- first path == int && get 2nd path as Int.
 [capture|/:Int/:Double|] -- get first path as Int and get 2nd path as Double.

query matcher

query :: (Query a, Strategy w, Monad m) => ByteString -> Proxy (w a) -> ApiaryT (SNext w as a) m b -> ApiaryT as m bSource

low level query getter. since 0.5.0.0.

 query key (Proxy :: Proxy (fetcher type))

examples:

 query key (Proxy :: Proxy (First Int)) -- get first 'key' query parameter as Int.
 query key (Proxy :: Proxy (Option (Maybe Int)) -- get first 'key' query parameter as Int. allow without param or value.
 query key (Proxy :: Proxy (Many String) -- get all 'key' query parameter as String.

specified operators

(=:) :: (Query a, Monad m) => ByteString -> Proxy a -> ApiaryT (Snoc as a) m b -> ApiaryT as m bSource

get first matched paramerer. since 0.5.0.0.

 key =: pInt == query key (pFirst pInt) == query key (Proxy :: Proxy (First Int))

(=!:) :: (Query a, Monad m) => ByteString -> Proxy a -> ApiaryT (Snoc as a) m b -> ApiaryT as m bSource

get one matched paramerer. since 0.5.0.0.

when more one parameger given, not matched.

 key =: pInt == query key (pOne pInt) == query key (Proxy :: Proxy (One Int))

(=?:) :: (Query a, Monad m) => ByteString -> Proxy a -> ApiaryT (Snoc as (Maybe a)) m b -> ApiaryT as m bSource

get optional first paramerer. since 0.5.0.0.

when illegal type parameter given, fail mather(don't give Nothing).

 key =: pInt == query key (pOption pInt) == query key (Proxy :: Proxy (Option Int))

(?:) :: (Query a, Monad m) => ByteString -> Proxy a -> ApiaryT as m b -> ApiaryT as m bSource

check parameger given and type. since 0.5.0.0.

If you wan't to allow any type, give pVoid.

 key =: pInt == query key (pCheck pInt) == query key (Proxy :: Proxy (Check Int))

(=*:) :: (Query a, Monad m) => ByteString -> Proxy a -> ApiaryT (Snoc as [a]) m b -> ApiaryT as m bSource

get many paramerer. since 0.5.0.0.

 key =: pInt == query key (pMany pInt) == query key (Proxy :: Proxy (Many Int))

(=+:) :: (Query a, Monad m) => ByteString -> Proxy a -> ApiaryT (Snoc as [a]) m b -> ApiaryT as m bSource

get some paramerer. since 0.5.0.0.

 key =: pInt == query key (pSome pInt) == query key (Proxy :: Proxy (Some Int))

hasQuery :: Monad m => ByteString -> ApiaryT c m a -> ApiaryT c m aSource

query exists checker.

 hasQuery q = query q (Proxy :: Proxy (Check ()))

header matcher

hasHeader :: Monad m => HeaderName -> ApiaryT as m b -> ApiaryT as m bSource

check whether to exists specified header or not. since 0.6.0.0.

eqHeaderSource

Arguments

:: Monad m 
=> HeaderName 
-> ByteString

header value

-> ApiaryT as m b 
-> ApiaryT as m b 

check whether to exists specified valued header or not. since 0.6.0.0.

headers :: Monad m => HeaderName -> ApiaryT (Snoc as [ByteString]) m b -> ApiaryT as m bSource

filter by headers up to 100 entries. since 0.6.0.0.

header :: Monad m => HeaderName -> ApiaryT (Snoc as ByteString) m b -> ApiaryT as m bSource

filter by header and get first. since 0.6.0.0.

header' :: (Strategy w, Monad m) => (forall x. Proxy x -> Proxy (w x)) -> (Header -> Bool) -> ApiaryT (SNext w as ByteString) m b -> ApiaryT as m bSource

low level header filter. since 0.6.0.0.

other

ssl :: Monad m => ApiaryT c m a -> ApiaryT c m aSource

filter by ssl accessed. since 0.1.0.0.

Reexport

StdMethod(..)

Strategy Proxies