Safe Haskell | None |
---|
- method :: Method -> Apiary c a -> Apiary c a
- stdMethod :: StdMethod -> Apiary c a -> Apiary c a
- httpVersion :: HttpVersion -> Apiary c b -> Apiary c b
- http09 :: Apiary c b -> Apiary c b
- http10 :: Apiary c b -> Apiary c b
- http11 :: Apiary c b -> Apiary c b
- root :: Apiary c b -> Apiary c b
- capture :: QuasiQuoter
- query :: (Query a, Strategy w) => ByteString -> Proxy (w a) -> Apiary (SNext w as a) b -> Apiary as b
- (=:) :: Query a => ByteString -> Proxy a -> Apiary (Snoc as a) b -> Apiary as b
- (=!:) :: Query a => ByteString -> Proxy a -> Apiary (Snoc as a) b -> Apiary as b
- (=?:) :: Query a => ByteString -> Proxy a -> Apiary (Snoc as (Maybe a)) b -> Apiary as b
- (?:) :: Query a => ByteString -> Proxy a -> Apiary as b -> Apiary as b
- (=*:) :: Query a => ByteString -> Proxy a -> Apiary (Snoc as [a]) b -> Apiary as b
- (=+:) :: Query a => ByteString -> Proxy a -> Apiary (Snoc as [a]) b -> Apiary as b
- hasQuery :: ByteString -> Apiary c a -> Apiary c a
- hasHeader :: HeaderName -> Apiary as b -> Apiary as b
- eqHeader :: HeaderName -> ByteString -> Apiary as b -> Apiary as b
- headers :: HeaderName -> Apiary (Snoc as [ByteString]) b -> Apiary as b
- header :: HeaderName -> Apiary (Snoc as ByteString) b -> Apiary as b
- header' :: Strategy w => (forall x. Proxy x -> Proxy (w x)) -> (Header -> Bool) -> Apiary (SNext w as ByteString) b -> Apiary as b
- ssl :: Apiary c a -> Apiary c a
- module Network.HTTP.Types
- module Control.Monad.Apiary.Filter.Internal.Strategy
filters
http method
stdMethod :: StdMethod -> Apiary c a -> Apiary c aSource
filter by HTTP method using StdMethod. since 0.1.0.0.
http version
httpVersion :: HttpVersion -> Apiary c b -> Apiary c bSource
http version filter. since 0.5.0.0.
path matcher
root :: Apiary c b -> Apiary c bSource
filter by rootPattern
of ApiaryConfig
.
query matcher
query :: (Query a, Strategy w) => ByteString -> Proxy (w a) -> Apiary (SNext w as a) b -> Apiary as 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
hasQuery :: ByteString -> Apiary c a -> Apiary c aSource
query exists checker.
hasQuery q =query
q (Proxy :: Proxy (Check
()))
header matcher
hasHeader :: HeaderName -> Apiary as b -> Apiary as bSource
check whether to exists specified header or not. since 0.6.0.0.
:: HeaderName | |
-> ByteString | header value |
-> Apiary as b | |
-> Apiary as b |
check whether to exists specified valued header or not. since 0.6.0.0.
headers :: HeaderName -> Apiary (Snoc as [ByteString]) b -> Apiary as bSource
filter by headers up to 100 entries. since 0.6.0.0.
header :: HeaderName -> Apiary (Snoc as ByteString) b -> Apiary as bSource
filter by header and get first. since 0.6.0.0.
header' :: Strategy w => (forall x. Proxy x -> Proxy (w x)) -> (Header -> Bool) -> Apiary (SNext w as ByteString) b -> Apiary as bSource
low level header filter. since 0.6.0.0.
other
Reexport
StdMethod(..)
module Network.HTTP.Types
Strategy Proxies