Replace all occurances of () with NoContent

We use NoContent to signify an empty response nowadays. This commit
replaces all occurences of () with NoContent so that all packages use
the new semantics.
This commit is contained in:
Arian van Putten 2016-07-08 09:11:34 +02:00
parent d45c7c5897
commit 05379ed7e3
18 changed files with 81 additions and 70 deletions

View File

@ -81,7 +81,7 @@ type TestApi =
:<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] (Headers '[Header "X-Example" Int] Greet) :<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] (Headers '[Header "X-Example" Int] Greet)
-- DELETE /greet/:greetid -- DELETE /greet/:greetid
:<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] () :<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] NoContent
testApi :: Proxy TestApi testApi :: Proxy TestApi
testApi = Proxy testApi = Proxy
@ -91,7 +91,7 @@ testApi = Proxy
-- notes. -- notes.
extra :: ExtraInfo TestApi extra :: ExtraInfo TestApi
extra = extra =
extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete '[JSON] ())) $ extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete '[JSON] NoContent)) $
defAction & headers <>~ ["unicorns"] defAction & headers <>~ ["unicorns"]
& notes <>~ [ DocNote "Title" ["This is some text"] & notes <>~ [ DocNote "Title" ["This is some text"]
, DocNote "Second secton" ["And some more"] , DocNote "Second secton" ["And some more"]

View File

@ -833,7 +833,7 @@ instance (ToAuthInfo (BasicAuth realm usr), HasDocs api) => HasDocs (BasicAuth r
action' = over authInfo (|> toAuthInfo authProxy) action action' = over authInfo (|> toAuthInfo authProxy) action
-- ToSample instances for simple types -- ToSample instances for simple types
instance ToSample () instance ToSample NoContent
instance ToSample Bool instance ToSample Bool
instance ToSample Ordering instance ToSample Ordering

View File

@ -169,11 +169,11 @@ type family Elem (a :: *) (ls::[*]) :: Constraint where
-- > getEndpoints api = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy Text) api -- > getEndpoints api = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy Text) api
-- --
-- > -- If language __X__ is dynamically typed then you can use -- > -- If language __X__ is dynamically typed then you can use
-- > -- a predefined NoTypes parameter with the () output type: -- > -- a predefined NoTypes parameter with the NoContent output type:
-- --
-- > getEndpoints :: (HasForeign NoTypes () api, GenerateList Text (Foreign () api)) -- > getEndpoints :: (HasForeign NoTypes NoContent api, GenerateList Text (Foreign NoContent api))
-- > => Proxy api -> [Req ()] -- > => Proxy api -> [Req NoContent]
-- > getEndpoints api = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy ()) api -- > getEndpoints api = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) api
-- > -- >
-- --
class HasForeignType lang ftype a where class HasForeignType lang ftype a where
@ -181,8 +181,8 @@ class HasForeignType lang ftype a where
data NoTypes data NoTypes
instance HasForeignType NoTypes () ftype where instance HasForeignType NoTypes NoContent ftype where
typeFor _ _ _ = () typeFor _ _ _ = NoContent
class HasForeign lang ftype (api :: *) where class HasForeign lang ftype (api :: *) where
type Foreign ftype api :: * type Foreign ftype api :: *

View File

@ -26,7 +26,7 @@ camelCaseSpec = describe "camelCase" $ do
data LangX data LangX
instance HasForeignType LangX String () where instance HasForeignType LangX String NoContent where
typeFor _ _ _ = "voidX" typeFor _ _ _ = "voidX"
instance HasForeignType LangX String Int where instance HasForeignType LangX String Int where
@ -43,9 +43,9 @@ instance OVERLAPPABLE_ HasForeignType LangX String a => HasForeignType LangX Str
type TestApi type TestApi
= "test" :> Header "header" [String] :> QueryFlag "flag" :> Get '[JSON] Int = "test" :> Header "header" [String] :> QueryFlag "flag" :> Get '[JSON] Int
:<|> "test" :> QueryParam "param" Int :> ReqBody '[JSON] [String] :> Post '[JSON] () :<|> "test" :> QueryParam "param" Int :> ReqBody '[JSON] [String] :> Post '[JSON] NoContent
:<|> "test" :> QueryParams "params" Int :> ReqBody '[JSON] String :> Put '[JSON] () :<|> "test" :> QueryParams "params" Int :> ReqBody '[JSON] String :> Put '[JSON] NoContent
:<|> "test" :> Capture "id" Int :> Delete '[JSON] () :<|> "test" :> Capture "id" Int :> Delete '[JSON] NoContent
testApi :: [Req String] testApi :: [Req String]
testApi = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy String) (Proxy :: Proxy TestApi) testApi = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy String) (Proxy :: Proxy TestApi)

View File

@ -46,6 +46,7 @@ library
, charset >= 0.3 , charset >= 0.3
, lens >= 4 , lens >= 4
, servant-foreign == 0.7.* , servant-foreign == 0.7.*
, servant == 0.7.*
, text >= 1.2 && < 1.3 , text >= 1.2 && < 1.3
hs-source-dirs: src hs-source-dirs: src

View File

@ -118,6 +118,7 @@ import Prelude hiding (writeFile)
import Data.Proxy import Data.Proxy
import Data.Text import Data.Text
import Data.Text.IO (writeFile) import Data.Text.IO (writeFile)
import Servant.API.ContentTypes
import Servant.JS.Angular import Servant.JS.Angular
import Servant.JS.Axios import Servant.JS.Axios
import Servant.JS.Internal import Servant.JS.Internal
@ -128,22 +129,22 @@ import Servant.Foreign (listFromAPI)
-- | Generate the data necessary to generate javascript code -- | Generate the data necessary to generate javascript code
-- for all the endpoints of an API, as ':<|>'-separated values -- for all the endpoints of an API, as ':<|>'-separated values
-- of type 'AjaxReq'. -- of type 'AjaxReq'.
javascript :: HasForeign NoTypes () api => Proxy api -> Foreign () api javascript :: HasForeign NoTypes NoContent api => Proxy api -> Foreign NoContent api
javascript p = foreignFor (Proxy :: Proxy NoTypes) (Proxy :: Proxy ()) p defReq javascript p = foreignFor (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) p defReq
-- | Directly generate all the javascript functions for your API -- | Directly generate all the javascript functions for your API
-- from a 'Proxy' for your API type. You can then write it to -- from a 'Proxy' for your API type. You can then write it to
-- a file or integrate it in a page, for example. -- a file or integrate it in a page, for example.
jsForAPI :: (HasForeign NoTypes () api, GenerateList () (Foreign () api)) jsForAPI :: (HasForeign NoTypes NoContent api, GenerateList NoContent (Foreign NoContent api))
=> Proxy api -- ^ proxy for your API type => Proxy api -- ^ proxy for your API type
-> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others) -> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others)
-> Text -- ^ a text that you can embed in your pages or write to a file -> Text -- ^ a text that you can embed in your pages or write to a file
jsForAPI p gen = gen (listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy ()) p) jsForAPI p gen = gen (listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) p)
-- | Directly generate all the javascript functions for your API -- | Directly generate all the javascript functions for your API
-- from a 'Proxy' for your API type using the given generator -- from a 'Proxy' for your API type using the given generator
-- and write the resulting code to a file at the given path. -- and write the resulting code to a file at the given path.
writeJSForAPI :: (HasForeign NoTypes () api, GenerateList () (Foreign () api)) writeJSForAPI :: (HasForeign NoTypes NoContent api, GenerateList NoContent (Foreign NoContent api))
=> Proxy api -- ^ proxy for your API type => Proxy api -- ^ proxy for your API type
-> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others) -> JavaScriptGenerator -- ^ js code generator to use (angular, vanilla js, jquery, others)
-> FilePath -- ^ path to the file you want to write the resulting javascript code into -> FilePath -- ^ path to the file you want to write the resulting javascript code into

View File

@ -54,12 +54,12 @@ import qualified Data.Text as T
import Data.Text (Text) import Data.Text (Text)
import Servant.Foreign import Servant.Foreign
type AjaxReq = Req () type AjaxReq = Req NoContent
-- A 'JavascriptGenerator' just takes the data found in the API type -- A 'JavascriptGenerator' just takes the data found in the API type
-- for each endpoint and generates Javascript code in a Text. Several -- for each endpoint and generates Javascript code in a Text. Several
-- generators are available in this package. -- generators are available in this package.
type JavaScriptGenerator = [Req ()] -> Text type JavaScriptGenerator = [Req NoContent] -> Text
-- | This structure is used by specific implementations to let you -- | This structure is used by specific implementations to let you
-- customize the output -- customize the output

View File

@ -21,6 +21,7 @@ import Prelude.Compat
import Test.Hspec hiding (shouldContain, shouldNotContain) import Test.Hspec hiding (shouldContain, shouldNotContain)
import Servant.API.Internal.Test.ComprehensiveAPI import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.API.ContentTypes
import Servant.JS import Servant.JS
import Servant.JS.Internal import Servant.JS.Internal
import qualified Servant.JS.Angular as NG import qualified Servant.JS.Angular as NG
@ -105,7 +106,7 @@ a `shouldNotContain` b = shouldNotSatisfy a (T.isInfixOf b)
axiosSpec :: Spec axiosSpec :: Spec
axiosSpec = describe specLabel $ do axiosSpec = describe specLabel $ do
let reqList = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy ()) (Proxy :: Proxy TestAPI) let reqList = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) (Proxy :: Proxy TestAPI)
it "should add withCredentials when needed" $ do it "should add withCredentials when needed" $ do
let jsText = genJS withCredOpts $ reqList let jsText = genJS withCredOpts $ reqList
output jsText output jsText
@ -129,7 +130,7 @@ axiosSpec = describe specLabel $ do
angularSpec :: TestNames -> Spec angularSpec :: TestNames -> Spec
angularSpec test = describe specLabel $ do angularSpec test = describe specLabel $ do
let reqList = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy ()) (Proxy :: Proxy TestAPI) let reqList = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) (Proxy :: Proxy TestAPI)
it "should implement a service globally" $ do it "should implement a service globally" $ do
let jsText = genJS reqList let jsText = genJS reqList
output jsText output jsText

View File

@ -16,6 +16,7 @@ import Data.Monoid
import Data.Proxy import Data.Proxy
import Data.Text (pack) import Data.Text (pack)
import GHC.TypeLits import GHC.TypeLits
import Servant.API.ContentTypes
import Servant.JS.Internal import Servant.JS.Internal
-- | This is a hypothetical combinator that fetches an Authorization header. -- | This is a hypothetical combinator that fetches an Authorization header.
@ -23,13 +24,13 @@ import Servant.JS.Internal
-- using -- Basic, Digest, whatever. -- using -- Basic, Digest, whatever.
data Authorization (sym :: Symbol) a data Authorization (sym :: Symbol) a
instance (KnownSymbol sym, HasForeign lang () api) instance (KnownSymbol sym, HasForeign lang NoContent api)
=> HasForeign lang () (Authorization sym a :> api) where => HasForeign lang NoContent (Authorization sym a :> api) where
type Foreign () (Authorization sym a :> api) = Foreign () api type Foreign NoContent (Authorization sym a :> api) = Foreign NoContent api
foreignFor lang ftype Proxy req = foreignFor lang ftype (Proxy :: Proxy api) $ foreignFor lang ftype Proxy req = foreignFor lang ftype (Proxy :: Proxy api) $
req & reqHeaders <>~ req & reqHeaders <>~
[ ReplaceHeaderArg (Arg "Authorization" ()) [ ReplaceHeaderArg (Arg "Authorization" NoContent)
$ tokenType (pack . symbolVal $ (Proxy :: Proxy sym)) ] $ tokenType (pack . symbolVal $ (Proxy :: Proxy sym)) ]
where where
tokenType t = t <> " {Authorization}" tokenType t = t <> " {Authorization}"
@ -37,23 +38,23 @@ instance (KnownSymbol sym, HasForeign lang () api)
-- | This is a combinator that fetches an X-MyLovelyHorse header. -- | This is a combinator that fetches an X-MyLovelyHorse header.
data MyLovelyHorse a data MyLovelyHorse a
instance (HasForeign lang () api) instance (HasForeign lang NoContent api)
=> HasForeign lang () (MyLovelyHorse a :> api) where => HasForeign lang NoContent (MyLovelyHorse a :> api) where
type Foreign () (MyLovelyHorse a :> api) = Foreign () api type Foreign NoContent (MyLovelyHorse a :> api) = Foreign NoContent api
foreignFor lang ftype Proxy req = foreignFor lang ftype (Proxy :: Proxy api) $ foreignFor lang ftype Proxy req = foreignFor lang ftype (Proxy :: Proxy api) $
req & reqHeaders <>~ [ ReplaceHeaderArg (Arg "X-MyLovelyHorse" ()) tpl ] req & reqHeaders <>~ [ ReplaceHeaderArg (Arg "X-MyLovelyHorse" NoContent) tpl ]
where where
tpl = "I am good friends with {X-MyLovelyHorse}" tpl = "I am good friends with {X-MyLovelyHorse}"
-- | This is a combinator that fetches an X-WhatsForDinner header. -- | This is a combinator that fetches an X-WhatsForDinner header.
data WhatsForDinner a data WhatsForDinner a
instance (HasForeign lang () api) instance (HasForeign lang NoContent api)
=> HasForeign lang () (WhatsForDinner a :> api) where => HasForeign lang NoContent (WhatsForDinner a :> api) where
type Foreign () (WhatsForDinner a :> api) = Foreign () api type Foreign NoContent (WhatsForDinner a :> api) = Foreign NoContent api
foreignFor lang ftype Proxy req = foreignFor lang ftype (Proxy :: Proxy api) $ foreignFor lang ftype Proxy req = foreignFor lang ftype (Proxy :: Proxy api) $
req & reqHeaders <>~ [ ReplaceHeaderArg (Arg "X-WhatsForDinner" ()) tpl ] req & reqHeaders <>~ [ ReplaceHeaderArg (Arg "X-WhatsForDinner" NoContent) tpl ]
where where
tpl = "I would like {X-WhatsForDinner} with a cherry on top." tpl = "I would like {X-WhatsForDinner} with a cherry on top."

View File

@ -180,3 +180,6 @@ instance Arbitrary (HList '[]) where
instance (Arbitrary a, Arbitrary (HList hs)) instance (Arbitrary a, Arbitrary (HList hs))
=> Arbitrary (HList (Header h a ': hs)) where => Arbitrary (HList (Header h a ': hs)) where
arbitrary = HCons <$> fmap Header arbitrary <*> arbitrary arbitrary = HCons <$> fmap Header arbitrary <*> arbitrary
instance Arbitrary NoContent where
arbitrary = pure NoContent

View File

@ -34,7 +34,7 @@ type TestApi =
:<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet :<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet
-- DELETE /greet/:greetid -- DELETE /greet/:greetid
:<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] () :<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] NoContent
testApi :: Proxy TestApi testApi :: Proxy TestApi
testApi = Proxy testApi = Proxy
@ -54,7 +54,7 @@ server = helloH :<|> postGreetH :<|> deleteGreetH
postGreetH greet = return greet postGreetH greet = return greet
deleteGreetH _ = return () deleteGreetH _ = return NoContent
-- Turn the server into a WAI app. 'serve' is provided by servant, -- Turn the server into a WAI app. 'serve' is provided by servant,
-- more precisely by the Servant.Server module. -- more precisely by the Servant.Server module.

View File

@ -147,7 +147,7 @@ serveWithContext p context server =
-- For the following API -- For the following API
-- --
-- > type API = -- > type API =
-- > "a" :> "d" :> Get '[JSON] () -- > "a" :> "d" :> Get '[JSON] NoContent
-- > :<|> "b" :> Capture "x" Int :> Get '[JSON] Bool -- > :<|> "b" :> Capture "x" Int :> Get '[JSON] Bool
-- > :<|> "c" :> Put '[JSON] Bool -- > :<|> "c" :> Put '[JSON] Bool
-- > :<|> "a" :> "e" :> Get '[JSON] Int -- > :<|> "a" :> "e" :> Get '[JSON] Int

View File

@ -74,7 +74,7 @@ makeTrivialRouter :: (HasServer layout '[]) => Proxy layout -> Router ()
makeTrivialRouter p = makeTrivialRouter p =
route p EmptyContext (emptyDelayed (FailFatal err501)) route p EmptyContext (emptyDelayed (FailFatal err501))
type End = Get '[JSON] () type End = Get '[JSON] NoContent
-- The latter version looks more efficient, -- The latter version looks more efficient,
-- but the former should be compiled to the -- but the former should be compiled to the

View File

@ -340,19 +340,23 @@ reqBodySpec = describe "Servant.API.ReqBody" $ do
-- * headerSpec {{{ -- * headerSpec {{{
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
type HeaderApi a = Header "MyHeader" a :> Delete '[JSON] () type HeaderApi a = Header "MyHeader" a :> Delete '[JSON] NoContent
headerApi :: Proxy (HeaderApi a) headerApi :: Proxy (HeaderApi a)
headerApi = Proxy headerApi = Proxy
headerSpec :: Spec headerSpec :: Spec
headerSpec = describe "Servant.API.Header" $ do headerSpec = describe "Servant.API.Header" $ do
let expectsInt :: Maybe Int -> Handler () let expectsInt :: Maybe Int -> Handler NoContent
expectsInt (Just x) = when (x /= 5) $ error "Expected 5" expectsInt (Just x) = do
when (x /= 5) $ error "Expected 5"
return NoContent
expectsInt Nothing = error "Expected an int" expectsInt Nothing = error "Expected an int"
let expectsString :: Maybe String -> Handler () let expectsString :: Maybe String -> Handler NoContent
expectsString (Just x) = when (x /= "more from you") $ error "Expected more from you" expectsString (Just x) = do
when (x /= "more from you") $ error "Expected more from you"
return NoContent
expectsString Nothing = error "Expected a string" expectsString Nothing = error "Expected a string"
with (return (serve headerApi expectsInt)) $ do with (return (serve headerApi expectsInt)) $ do
@ -410,7 +414,7 @@ type AlternativeApi =
:<|> "foo" :> Get '[PlainText] T.Text :<|> "foo" :> Get '[PlainText] T.Text
:<|> "bar" :> Post '[JSON] Animal :<|> "bar" :> Post '[JSON] Animal
:<|> "bar" :> Put '[JSON] Animal :<|> "bar" :> Put '[JSON] Animal
:<|> "bar" :> Delete '[JSON] () :<|> "bar" :> Delete '[JSON] NoContent
alternativeApi :: Proxy AlternativeApi alternativeApi :: Proxy AlternativeApi
alternativeApi = Proxy alternativeApi = Proxy
@ -422,7 +426,7 @@ alternativeServer =
:<|> return "a string" :<|> return "a string"
:<|> return jerry :<|> return jerry
:<|> return jerry :<|> return jerry
:<|> return () :<|> return NoContent
alternativeSpec :: Spec alternativeSpec :: Spec
alternativeSpec = do alternativeSpec = do

View File

@ -319,7 +319,7 @@ instance MimeRender OctetStream BS.ByteString where
-- | A type for responses without content-body. -- | A type for responses without content-body.
data NoContent = NoContent data NoContent = NoContent
deriving (Show, Eq, Read) deriving (Show, Eq, Read, Generic)
-------------------------------------------------------------------------- --------------------------------------------------------------------------

View File

@ -10,7 +10,7 @@ import Data.Proxy
import Servant.API import Servant.API
type GET = Get '[JSON] () type GET = Get '[JSON] NoContent
type ComprehensiveAPI = type ComprehensiveAPI =
GET :<|> GET :<|>
@ -25,10 +25,10 @@ type ComprehensiveAPI =
-- Raw :<|> -- Raw :<|>
RemoteHost :> GET :<|> RemoteHost :> GET :<|>
ReqBody '[JSON] Int :> GET :<|> ReqBody '[JSON] Int :> GET :<|>
Get '[JSON] (Headers '[Header "foo" Int] ()) :<|> Get '[JSON] (Headers '[Header "foo" Int] NoContent) :<|>
"foo" :> GET :<|> "foo" :> GET :<|>
Vault :> GET :<|> Vault :> GET :<|>
Verb 'POST 204 '[JSON] () :<|> Verb 'POST 204 '[JSON] NoContent :<|>
Verb 'POST 204 '[JSON] Int :<|> Verb 'POST 204 '[JSON] Int :<|>
WithNamedContext "foo" '[] GET WithNamedContext "foo" '[] GET

View File

@ -21,7 +21,7 @@
-- >>> -- >>>
-- >>> -- >>>
-- >>> type Hello = "hello" :> Get '[JSON] Int -- >>> type Hello = "hello" :> Get '[JSON] Int
-- >>> type Bye = "bye" :> QueryParam "name" String :> Delete '[JSON] () -- >>> type Bye = "bye" :> QueryParam "name" String :> Delete '[JSON] NoContent
-- >>> type API = Hello :<|> Bye -- >>> type API = Hello :<|> Bye
-- >>> let api = Proxy :: Proxy API -- >>> let api = Proxy :: Proxy API
-- --
@ -47,11 +47,11 @@
-- If the API has an endpoint with parameters then we can generate links with -- If the API has an endpoint with parameters then we can generate links with
-- or without those: -- or without those:
-- --
-- >>> let with = Proxy :: Proxy ("bye" :> QueryParam "name" String :> Delete '[JSON] ()) -- >>> let with = Proxy :: Proxy ("bye" :> QueryParam "name" String :> Delete '[JSON] NoContent)
-- >>> print $ safeLink api with (Just "Hubert") -- >>> print $ safeLink api with (Just "Hubert")
-- bye?name=Hubert -- bye?name=Hubert
-- --
-- >>> let without = Proxy :: Proxy ("bye" :> Delete '[JSON] ()) -- >>> let without = Proxy :: Proxy ("bye" :> Delete '[JSON] NoContent)
-- >>> print $ safeLink api without -- >>> print $ safeLink api without
-- bye -- bye
-- --
@ -69,7 +69,7 @@
-- Attempting to construct a link to an endpoint that does not exist in api -- Attempting to construct a link to an endpoint that does not exist in api
-- will result in a type error like this: -- will result in a type error like this:
-- --
-- >>> let bad_link = Proxy :: Proxy ("hello" :> Delete '[JSON] ()) -- >>> let bad_link = Proxy :: Proxy ("hello" :> Delete '[JSON] NoContent)
-- >>> safeLink api bad_link -- >>> safeLink api bad_link
-- ... -- ...
-- ...Could not deduce... -- ...Could not deduce...

View File

@ -12,16 +12,16 @@ import Servant.API
type TestApi = type TestApi =
-- Capture and query params -- Capture and query params
"hello" :> Capture "name" String :> QueryParam "capital" Bool :> Delete '[JSON] () "hello" :> Capture "name" String :> QueryParam "capital" Bool :> Delete '[JSON] NoContent
-- Flags -- Flags
:<|> "balls" :> QueryFlag "bouncy" :> QueryFlag "fast" :> Delete '[JSON] () :<|> "balls" :> QueryFlag "bouncy" :> QueryFlag "fast" :> Delete '[JSON] NoContent
-- All of the verbs -- All of the verbs
:<|> "get" :> Get '[JSON] () :<|> "get" :> Get '[JSON] NoContent
:<|> "put" :> Put '[JSON] () :<|> "put" :> Put '[JSON] NoContent
:<|> "post" :> ReqBody '[JSON] 'True :> Post '[JSON] () :<|> "post" :> ReqBody '[JSON] 'True :> Post '[JSON] NoContent
:<|> "delete" :> Header "ponies" String :> Delete '[JSON] () :<|> "delete" :> Header "ponies" String :> Delete '[JSON] NoContent
:<|> "raw" :> Raw :<|> "raw" :> Raw
@ -38,26 +38,26 @@ shouldBeURI link expected =
spec :: Spec spec :: Spec
spec = describe "Servant.Utils.Links" $ do spec = describe "Servant.Utils.Links" $ do
it "generates correct links for capture query params" $ do it "generates correct links for capture query params" $ do
let l1 = Proxy :: Proxy ("hello" :> Capture "name" String :> Delete '[JSON] ()) let l1 = Proxy :: Proxy ("hello" :> Capture "name" String :> Delete '[JSON] NoContent)
apiLink l1 "hi" `shouldBeURI` "hello/hi" apiLink l1 "hi" `shouldBeURI` "hello/hi"
let l2 = Proxy :: Proxy ("hello" :> Capture "name" String let l2 = Proxy :: Proxy ("hello" :> Capture "name" String
:> QueryParam "capital" Bool :> QueryParam "capital" Bool
:> Delete '[JSON] ()) :> Delete '[JSON] NoContent)
apiLink l2 "bye" (Just True) `shouldBeURI` "hello/bye?capital=true" apiLink l2 "bye" (Just True) `shouldBeURI` "hello/bye?capital=true"
it "generates correct links for query flags" $ do it "generates correct links for query flags" $ do
let l1 = Proxy :: Proxy ("balls" :> QueryFlag "bouncy" let l1 = Proxy :: Proxy ("balls" :> QueryFlag "bouncy"
:> QueryFlag "fast" :> Delete '[JSON] ()) :> QueryFlag "fast" :> Delete '[JSON] NoContent)
apiLink l1 True True `shouldBeURI` "balls?bouncy&fast" apiLink l1 True True `shouldBeURI` "balls?bouncy&fast"
apiLink l1 False True `shouldBeURI` "balls?fast" apiLink l1 False True `shouldBeURI` "balls?fast"
it "generates correct links for all of the verbs" $ do it "generates correct links for all of the verbs" $ do
apiLink (Proxy :: Proxy ("get" :> Get '[JSON] ())) `shouldBeURI` "get" apiLink (Proxy :: Proxy ("get" :> Get '[JSON] NoContent)) `shouldBeURI` "get"
apiLink (Proxy :: Proxy ("put" :> Put '[JSON] ())) `shouldBeURI` "put" apiLink (Proxy :: Proxy ("put" :> Put '[JSON] NoContent)) `shouldBeURI` "put"
apiLink (Proxy :: Proxy ("post" :> Post '[JSON] ())) `shouldBeURI` "post" apiLink (Proxy :: Proxy ("post" :> Post '[JSON] NoContent)) `shouldBeURI` "post"
apiLink (Proxy :: Proxy ("delete" :> Delete '[JSON] ())) `shouldBeURI` "delete" apiLink (Proxy :: Proxy ("delete" :> Delete '[JSON] NoContent)) `shouldBeURI` "delete"
apiLink (Proxy :: Proxy ("raw" :> Raw)) `shouldBeURI` "raw" apiLink (Proxy :: Proxy ("raw" :> Raw)) `shouldBeURI` "raw"
@ -93,9 +93,9 @@ spec = describe "Servant.Utils.Links" $ do
-- sanity check -- sanity check
-- >>> apiLink (Proxy :: Proxy AllGood) -- >>> apiLink (Proxy :: Proxy AllGood)
-- get -- get
type WrongPath = "getTypo" :> Get '[JSON] () type WrongPath = "getTypo" :> Get '[JSON] NoContent
type WrongReturnType = "get" :> Get '[JSON] Bool type WrongReturnType = "get" :> Get '[JSON] Bool
type WrongContentType = "get" :> Get '[OctetStream] () type WrongContentType = "get" :> Get '[OctetStream] NoContent
type WrongMethod = "get" :> Post '[JSON] () type WrongMethod = "get" :> Post '[JSON] NoContent
type NotALink = "hello" :> ReqBody '[JSON] 'True :> Get '[JSON] Bool type NotALink = "hello" :> ReqBody '[JSON] 'True :> Get '[JSON] Bool
type AllGood = "get" :> Get '[JSON] () type AllGood = "get" :> Get '[JSON] NoContent