apiary-0.12.5: Simple and type safe web framework that can be automatically generate API documentation.

Safe HaskellNone

Control.Monad.Apiary.Filter

Contents

Synopsis

filters

http method

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

filter by HTTP method. since 0.1.0.0.

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

filter by HTTP method using StdMethod. since 0.1.0.0.

http version

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

http version filter. since 0.5.0.0.

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

http/0.9 only accepted fiter. since 0.5.0.0.

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

http/1.0 only accepted fiter. since 0.5.0.0.

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

http/1.1 only accepted fiter. since 0.5.0.0.

path matcher

root :: Monad n => ApiaryT c n m b -> ApiaryT c n 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.

path :: Monad n => Text -> ApiaryT c n m a -> ApiaryT c n m aSource

check first path and drill down. since 0.11.0.

endPath :: Monad n => ApiaryT c n m a -> ApiaryT c n m aSource

check consumed pathes. since 0.11.1.

fetch :: (Path a, Monad n) => proxy a -> Maybe Html -> ApiaryT (Snoc as a) n m b -> ApiaryT as n m bSource

get first path and drill down. since 0.11.0.

query matcher

data QueryKey Source

Constructors

QueryKey 

Instances

query :: forall a as w n m b proxy. (ReqParam a, Strategy w, MonadIO n) => QueryKey -> proxy (w a) -> ApiaryT (SNext w as a) n m b -> ApiaryT as n 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

(=:) :: (MonadIO n, ReqParam a) => QueryKey -> proxy a -> ApiaryT (Snoc as a) n m b -> ApiaryT as n m bSource

get first matched paramerer. since 0.5.0.0.

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

(=!:) :: (MonadIO n, ReqParam a) => QueryKey -> proxy a -> ApiaryT (Snoc as a) n m b -> ApiaryT as n 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))

(=?:) :: (MonadIO n, ReqParam a) => QueryKey -> proxy a -> ApiaryT (Snoc as (Maybe a)) n m b -> ApiaryT as n 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))

(?:) :: (MonadIO n, ReqParam a) => QueryKey -> proxy a -> ApiaryT as n m b -> ApiaryT as n 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))

(=*:) :: (MonadIO n, ReqParam a) => QueryKey -> proxy a -> ApiaryT (Snoc as [a]) n m b -> ApiaryT as n m bSource

get many paramerer. since 0.5.0.0.

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

(=+:) :: (MonadIO n, ReqParam a) => QueryKey -> proxy a -> ApiaryT (Snoc as [a]) n m b -> ApiaryT as n m bSource

get some paramerer. since 0.5.0.0.

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

hasQuery :: MonadIO n => QueryKey -> ApiaryT c n m a -> ApiaryT c n m aSource

query exists checker.

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

header matcher

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

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

eqHeaderSource

Arguments

:: Monad n 
=> HeaderName 
-> ByteString

header value

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

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

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

filter by headers up to 100 entries. since 0.6.0.0.

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

filter by header and get first. since 0.6.0.0.

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

low level header filter. since 0.6.0.0.

other

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

filter by ssl accessed. since 0.1.0.0.

Reexport

StdMethod(..)

Strategy Proxies