More haddocks for Capture
This commit is contained in:
parent
407349c245
commit
e9ebb0f10b
2 changed files with 46 additions and 3 deletions
|
@ -58,7 +58,7 @@ instance (HasClient a, HasClient b) => HasClient (a :<|> b) where
|
||||||
clientWithRoute (Proxy :: Proxy a) req :<|>
|
clientWithRoute (Proxy :: Proxy a) req :<|>
|
||||||
clientWithRoute (Proxy :: Proxy b) req
|
clientWithRoute (Proxy :: Proxy b) req
|
||||||
|
|
||||||
-- | The generated docs for @a ':<|>' b@ just append the docs
|
-- | The generated docs for @a ':<|>' b@ just appends the docs
|
||||||
-- for @a@ with the docs for @b@.
|
-- for @a@ with the docs for @b@.
|
||||||
instance (HasDocs layout1, HasDocs layout2)
|
instance (HasDocs layout1, HasDocs layout2)
|
||||||
=> HasDocs (layout1 :<|> layout2) where
|
=> HasDocs (layout1 :<|> layout2) where
|
||||||
|
|
|
@ -4,7 +4,7 @@
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
module Servant.API.Capture where
|
module Servant.API.Capture (Capture) where
|
||||||
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import Data.Text
|
import Data.Text
|
||||||
|
@ -17,12 +17,34 @@ import Servant.Common.Text
|
||||||
import Servant.Docs
|
import Servant.Docs
|
||||||
import Servant.Server
|
import Servant.Server
|
||||||
|
|
||||||
-- * Captures
|
-- | Capture a value from the request path under a certain type @a@.
|
||||||
|
--
|
||||||
|
-- Example:
|
||||||
|
--
|
||||||
|
-- > -- GET /books/:isbn
|
||||||
|
-- > type MyApi = "books" :> Capture "isbn" Text :> Get Book
|
||||||
data Capture sym a
|
data Capture sym a
|
||||||
|
|
||||||
captured :: FromText a => proxy (Capture sym a) -> Text -> Maybe a
|
captured :: FromText a => proxy (Capture sym a) -> Text -> Maybe a
|
||||||
captured _ = fromText
|
captured _ = fromText
|
||||||
|
|
||||||
|
-- | If you use 'Capture' in one of the endpoints for your API,
|
||||||
|
-- this automatically requires your server-side handler to be a function
|
||||||
|
-- that takes an argument of the type specified by the 'Capture'.
|
||||||
|
-- This lets servant worry about getting it from the URL and turning
|
||||||
|
-- it into a value of the type you specify.
|
||||||
|
--
|
||||||
|
-- You can control how it'll be converted from 'Text' to your type
|
||||||
|
-- by simply providing an instance of 'FromText' for your type.
|
||||||
|
--
|
||||||
|
-- Example:
|
||||||
|
--
|
||||||
|
-- > type MyApi = "books" ':>' 'Capture' "isbn" 'Text' ':>' 'Get' Book
|
||||||
|
-- >
|
||||||
|
-- > server :: 'Server' MyApi
|
||||||
|
-- > server = getBook
|
||||||
|
-- > where getBook :: Text -> 'EitherT' (Int, String) IO Book
|
||||||
|
-- > getBook isbn = ...
|
||||||
instance (KnownSymbol capture, FromText a, HasServer sublayout)
|
instance (KnownSymbol capture, FromText a, HasServer sublayout)
|
||||||
=> HasServer (Capture capture a :> sublayout) where
|
=> HasServer (Capture capture a :> sublayout) where
|
||||||
|
|
||||||
|
@ -40,6 +62,25 @@ instance (KnownSymbol capture, FromText a, HasServer sublayout)
|
||||||
|
|
||||||
where captureProxy = Proxy :: Proxy (Capture capture a)
|
where captureProxy = Proxy :: Proxy (Capture capture a)
|
||||||
|
|
||||||
|
-- | If you use a 'Capture' in one of your endpoints in your API,
|
||||||
|
-- the corresponding querying function will automatically take
|
||||||
|
-- an additional argument of the type specified by your 'Capture'.
|
||||||
|
-- That function will take care of inserting a textual representation
|
||||||
|
-- of this value at the right place in the request path.
|
||||||
|
--
|
||||||
|
-- You can control how values for this type are turned into
|
||||||
|
-- text by specifying a 'ToText' instance for your type.
|
||||||
|
--
|
||||||
|
-- Example:
|
||||||
|
--
|
||||||
|
-- > type MyApi = "books" ':>' 'Capture' "isbn" 'Text' ':>' 'Get' Book
|
||||||
|
-- >
|
||||||
|
-- > myApi :: Proxy MyApi
|
||||||
|
-- > myApi = Proxy
|
||||||
|
-- >
|
||||||
|
-- > getBook :: Text -> BaseUrl -> EitherT String IO Book
|
||||||
|
-- > getBook = client myApi
|
||||||
|
-- > -- then you can just use "getBook" to query that endpoint
|
||||||
instance (KnownSymbol capture, ToText a, HasClient sublayout)
|
instance (KnownSymbol capture, ToText a, HasClient sublayout)
|
||||||
=> HasClient (Capture capture a :> sublayout) where
|
=> HasClient (Capture capture a :> sublayout) where
|
||||||
|
|
||||||
|
@ -52,6 +93,8 @@ instance (KnownSymbol capture, ToText a, HasClient sublayout)
|
||||||
|
|
||||||
where p = unpack (toText val)
|
where p = unpack (toText val)
|
||||||
|
|
||||||
|
-- | @"books" :> 'Capture' "isbn" Text@ will appear as
|
||||||
|
-- @/books/:isbn@ in the docs
|
||||||
instance (KnownSymbol sym, ToCapture (Capture sym a), HasDocs sublayout)
|
instance (KnownSymbol sym, ToCapture (Capture sym a), HasDocs sublayout)
|
||||||
=> HasDocs (Capture sym a :> sublayout) where
|
=> HasDocs (Capture sym a :> sublayout) where
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue