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

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Apiary.Filter

Contents

Synopsis

filters

http method

method :: Monad actM => Method -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

filter by HTTP method. since 0.1.0.0.

method GET      -- stdmethod
method "HOGE" -- non standard method

http version

httpVersion :: Monad actM => HttpVersion -> Html -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

http version filter. since 0.5.0.0.

http09 :: Monad actM => ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

http/0.9 only accepted fiter. since 0.5.0.0.

http10 :: Monad actM => ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

http/1.0 only accepted fiter. since 0.5.0.0.

http11 :: Monad actM => ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

http/1.1 only accepted fiter. since 0.5.0.0.

path matcher

root :: (Monad m, Monad actM) => ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

capture :: QuasiQuoter Source

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.
[capture|/**|] -- feed greedy and get all path as [Text] (since 0.17.0). 

path :: Monad actM => Text -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

check first path and drill down. since 0.11.0.

endPath :: Monad actM => ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

check consumed paths. since 0.11.1.

fetch :: (Path p, Monad actM) => proxy p -> Maybe Html -> ApiaryT exts (p : prms) actM m () -> ApiaryT exts prms actM m () Source

get first path and drill down. since 0.11.0.

query matcher

data QueryKey Source

Constructors

QueryKey 

Instances

query :: forall exts prms actM a w m. (ReqParam a, Strategy w, MonadIO actM) => QueryKey -> w a -> ApiaryT exts (SNext w prms a) actM m () -> ApiaryT exts prms actM m () Source

low level query getter. since 0.5.0.0.

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

examples:

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

specified operators

(=:) :: (MonadIO actM, ReqParam p) => QueryKey -> proxy p -> ApiaryT exts (p : prms) actM m () -> ApiaryT exts prms actM m () Source

get first matched paramerer. since 0.5.0.0.

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

(=!:) :: (MonadIO actM, ReqParam p) => QueryKey -> proxy p -> ApiaryT exts (p : prms) actM m () -> ApiaryT exts prms actM m () Source

get one matched paramerer. since 0.5.0.0.

when more one parameger given, not matched.

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

(=?:) :: (MonadIO actM, ReqParam p) => QueryKey -> proxy p -> ApiaryT exts (Maybe p : prms) actM m () -> ApiaryT exts prms actM m () Source

get optional first paramerer. since 0.5.0.0.

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

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

(=?!:) :: (MonadIO actM, ReqParam p, Show p) => QueryKey -> p -> ApiaryT exts (p : prms) actM m () -> ApiaryT exts prms actM m () Source

get optional first paramerer with default. since 0.16.0.

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

"key" =: (0 :: Int) == query "key" (pOptional (0 :: Int)) == query "key" (Optional 0 :: Optional Int)

(?:) :: (MonadIO actM, ReqParam p) => QueryKey -> proxy p -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

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" (Check :: Check Int)

(=*:) :: (MonadIO actM, ReqParam p) => QueryKey -> proxy p -> ApiaryT exts ([p] : prms) actM m () -> ApiaryT exts prms actM m () Source

get many paramerer. since 0.5.0.0.

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

(=+:) :: (MonadIO actM, ReqParam p) => QueryKey -> proxy p -> ApiaryT exts ([p] : prms) actM m () -> ApiaryT exts prms actM m () Source

get some paramerer. since 0.5.0.0.

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

hasQuery :: MonadIO actM => QueryKey -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

query exists checker.

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

switchQuery :: Monad actM => QueryKey -> ApiaryT exts (Bool : prms) actM m () -> ApiaryT exts prms actM m () Source

get existance of key only query parameter. since v0.17.0.

header matcher

hasHeader :: Monad actM => HeaderName -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

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

eqHeader Source

Arguments

:: Monad actM 
=> HeaderName 
-> ByteString

header value

-> ApiaryT exts prms actM m () 
-> ApiaryT exts prms actM m () 

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

headers :: Monad actM => HeaderName -> ApiaryT exts ([ByteString] : prms) actM m () -> ApiaryT exts prms actM m () Source

filter by headers up to 100 entries. since 0.6.0.0.

header :: Monad actM => HeaderName -> ApiaryT exts (ByteString : prms) actM m () -> ApiaryT exts prms actM m () Source

filter by header and get first. since 0.6.0.0.

header' :: (Strategy w, Monad actM) => (forall x. Proxy x -> w x) -> (Header -> Bool) -> Maybe Html -> ApiaryT exts (SNext w prms ByteString) actM m () -> ApiaryT exts prms actM m () Source

low level header filter. since 0.6.0.0.

accept :: Monad actM => ContentType -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

require Accept header and set response Content-Type. since 0.16.0.

other

ssl :: Monad actM => ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

filter by ssl accessed. since 0.1.0.0.

deprecated

stdMethod :: Monad actM => Method -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

Deprecated: use method

filter by HTTP method using StdMethod. since 0.1.0.0.

anyPath :: (Monad m, Monad actM) => ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

Deprecated: use greedy filter [capture|/**|] or use restPath.

match all subsequent path. since 0.15.0.