Skip to content

Commit 6d90d48

Browse files
committed
http-media-0.8 changed mapAcceptMedia
1 parent b534a8c commit 6d90d48

File tree

2 files changed

+19
-5
lines changed

2 files changed

+19
-5
lines changed

servant/servant.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -161,6 +161,7 @@ test-suite spec
161161
, base-compat
162162
, aeson
163163
, bytestring
164+
, http-media
164165
, mtl
165166
, servant
166167
, string-conversions

servant/test/Servant/API/ContentTypesSpec.hs

Lines changed: 18 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE CPP #-}
12
{-# LANGUAGE DataKinds #-}
23
{-# LANGUAGE DeriveGeneric #-}
34
{-# LANGUAGE MultiParamTypeClasses #-}
@@ -20,7 +21,7 @@ import Data.Either
2021
import Data.Function
2122
(on)
2223
import Data.List
23-
(maximumBy)
24+
(sortBy)
2425
import qualified Data.List.NonEmpty as NE
2526
import Data.Maybe
2627
(fromJust, isJust, isNothing)
@@ -134,17 +135,29 @@ spec = describe "Servant.API.ContentTypes" $ do
134135
== Just ("application/json;charset=utf-8", encode x)
135136

136137
it "respects the Accept spec ordering" $ do
137-
let highest a b c = maximumBy (compare `on` snd)
138+
let highest a b c = last $ sortBy (compare `on` snd)
139+
-- when qualities are same, http-media-0.8 picks first; 0.7 last.
140+
#if MIN_VERSION_http_media(0,8,0)
141+
[ ("text/plain;charset=utf-8", c)
142+
, ("application/json;charset=utf-8", b)
143+
, ("application/octet-stream", a)
144+
]
145+
#else
138146
[ ("application/octet-stream", a)
139147
, ("application/json;charset=utf-8", b)
140148
, ("text/plain;charset=utf-8", c)
141149
]
150+
#endif
142151
let acceptH a b c = addToAccept (Proxy :: Proxy OctetStream) a $
143-
addToAccept (Proxy :: Proxy JSON) b $
144-
addToAccept (Proxy :: Proxy PlainText ) c ""
152+
addToAccept (Proxy :: Proxy JSON) b $
153+
addToAccept (Proxy :: Proxy PlainText ) c $
154+
""
145155
let val a b c i = handleAcceptH (Proxy :: Proxy '[OctetStream, JSON, PlainText])
146156
(acceptH a b c) (i :: Int)
147-
property $ \a b c i -> fst (fromJust $ val a b c i) == fst (highest a b c)
157+
property $ \a b c i ->
158+
let acc = acceptH a b c
159+
in counterexample (show acc) $
160+
fst (fromJust $ val a b c i) === fst (highest a b c)
148161

149162
describe "handleCTypeH" $ do
150163

0 commit comments

Comments
 (0)