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

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Apiary.Filter

Contents

Synopsis

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

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/foo::Int|] -- first path == "int" && get 2nd path as Int.
[capture|/bar::Int/baz::Double|] -- get first path as Int and get 2nd path as Double.
[capture|/**baz|] -- feed greedy and get all path as [Text] (since 0.17.0). 

this QQ can convert pure function easily.

[capture|foofoo::Int|]        == path "path" . fetch (Proxy :: Proxy ("foo" := Int)) . endPath
[capture|barbar::Int/**rest|] == path "path" . fetch (Proxy :: Proxy ("foo" := Int)) . restPath (Proxy :: Proxy "rest")

query matcher

(??) :: proxy key -> Html -> QueryKey key Source

add document to query parameter filter.

[key|key|] ?? "document" =: pInt

(=:) :: (HasDesc query, MonadIO actM, ReqParam v, KnownSymbol k, NotMember k prms) => query k -> proxy v -> ApiaryT exts ((k := v) : prms) actM m () -> ApiaryT exts prms actM m () Source

get first matched paramerer. since 0.5.0.0.

[key|key|] =: pInt

(=!:) :: (HasDesc query, MonadIO actM, ReqParam v, KnownSymbol k, NotMember k prms) => query k -> proxy v -> ApiaryT exts ((k := v) : 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|key|] =!: pInt

(=?:) :: (HasDesc query, MonadIO actM, ReqParam v, KnownSymbol k, NotMember k prms) => query k -> proxy v -> ApiaryT exts ((k := Maybe v) : 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|key|] =?: pInt

(=?!:) :: forall query k v exts prms actM m. (HasDesc query, MonadIO actM, Show v, ReqParam v, KnownSymbol k, NotMember k prms) => query k -> v -> ApiaryT exts ((k := v) : 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|key|] =!?: (0 :: Int)

(=*:) :: (HasDesc query, MonadIO actM, ReqParam v, KnownSymbol k, NotMember k prms) => query k -> proxy v -> ApiaryT exts ((k := [v]) : prms) actM m () -> ApiaryT exts prms actM m () Source

get many paramerer. since 0.5.0.0.

[key|key|] =*: pInt

(=+:) :: (HasDesc query, MonadIO actM, ReqParam v, KnownSymbol k, NotMember k prms) => query k -> proxy v -> ApiaryT exts ((k := [v]) : prms) actM m () -> ApiaryT exts prms actM m () Source

get some paramerer. since 0.5.0.0.

[key|key|] =+: pInt

switchQuery :: (HasDesc proxy, MonadIO actM, KnownSymbol k, NotMember k prms) => proxy k -> ApiaryT exts ((k := Bool) : prms) actM m () -> ApiaryT exts prms actM m () Source

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

header matcher

eqHeader :: (KnownSymbol k, Monad actM) => proxy k -> ByteString -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

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

header :: (KnownSymbol k, Monad actM, NotMember k prms) => proxy k -> ApiaryT exts ((k := ByteString) : prms) actM m () -> ApiaryT exts prms actM m () Source

filter by header and get first. 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.

not export from Web.Apiary

class HasDesc a where Source

Methods

queryDesc :: a key -> Maybe Html Source

newtype QueryKey key Source

Constructors

QueryKey 

Instances

query :: forall query strategy k v exts prms actM m. (NotMember k prms, MonadIO actM, KnownSymbol k, ReqParam v, HasDesc query, Strategy strategy) => query k -> strategy v -> ApiaryT exts (SNext strategy k v prms) actM m () -> ApiaryT exts prms actM m () Source

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

http version filter. since 0.5.0.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 :: forall proxy k p exts prms actM m. (NotMember k prms, KnownSymbol k, Path p, Monad actM) => proxy (k := p) -> Maybe Html -> ApiaryT exts ((k := p) : prms) actM m () -> ApiaryT exts prms actM m () Source

restPath :: (NotMember k prms, KnownSymbol k, Monad m, Monad actM) => proxy k -> Maybe Html -> ApiaryT exts ((k := [Text]) : prms) actM m () -> ApiaryT exts prms actM m () Source

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

function :: Monad actM => (Doc -> Doc) -> (Dict prms -> Request -> Maybe (Dict prms')) -> ApiaryT exts prms' actM m () -> ApiaryT exts prms actM m () Source

low level filter function.

function' :: (Monad actM, NotMember key prms) => (Doc -> Doc) -> (Request -> Maybe (proxy key, prm)) -> ApiaryT exts ((key := prm) : prms) actM m () -> ApiaryT exts prms actM m () Source

filter and append argument.

function_ :: Monad actM => (Doc -> Doc) -> (Request -> Bool) -> ApiaryT exts prms actM m () -> ApiaryT exts prms actM m () Source

filter only(not modify arguments).

focus :: Monad actM => (Doc -> Doc) -> ActionT exts prms actM (Dict prms') -> ApiaryT exts prms' actM m () -> ApiaryT exts prms actM m () Source

filter by action. since 0.6.1.0.