Changelog for servant-0.17
The latest version of this document is on GitHub.
0.17
Significant changes
-
Add NoContentVerb #1028 #1219 #1228
The
NoContent
API endpoints should now useNoContentVerb
combinator. The API type changes are usually of the kind- :<|> PostNoContent '[JSON] NoContent + :<|> PostNoContent
i.e. one doesn't need to specify the content-type anymore. There is no content.
-
Capture
can beLenient
#1155 #1156You can specify a lenient capture as
:<|> "capture-lenient" :> Capture' '[Lenient] "foo" Int :> GET
which will make the capture always succeed. Handlers will be of the type
Either String CapturedType
, whereLeft err
represents the possible parse failure. -
servant-client Added a function to create Client.Request in ClientEnv #1213 #1255
The new member
makeClientRequest
ofClientEnv
is used to createhttp-client
Request
fromservant-client-core
Request
. This functionality can be used for example to set dynamic timeouts for each request. -
servant-server use queryString to parse QueryParam, QueryParams and QueryFlag #1249 #1262
Some APIs need query parameters rewriting, e.g. in order to support for multiple casing (camel, snake, etc) or something to that effect.
This could be easily achieved by using WAI Middleware and modyfing request's
Query
. But QueryParam, QueryParams and QueryFlag userawQueryString
. By usingqueryString
rather thenrawQueryString
we can enable such rewritings. -
servant servant-server Make packages
build-type: Simple
#1263We used
build-type: Custom
, but it's problematic e.g. for cross-compiling. The benefit is small, as the doctests can be run other ways too (though not so conviniently). -
servant Remove deprecated modules 1268#
Servant.Utils.Links
isServant.Links
Servant.API.Internal.Test.ComprehensiveAPI
isServant.Test.ComprehensiveAPI
Other changes
-
servant-client servant-client-core servant-http-streams Fix Verb with headers checking content type differently #1200 #1204
For
Verb
s with responseHeaders
, the implementation didn't check for the content-type of the response. Now it does. -
servant-docs Merge documentation from duplicate routes #1240 #1241
Servant supports defining the same route multiple times with different content-types and result-types, but servant-docs was only documenting the first of copy of such duplicated routes. It now combines the documentation from all the copies.
Unfortunately, it is not yet possible for the documentation to specify multiple status codes.
-
Add sponsorship button #1190
Well-Typed is a consultancy which could help you with
servant
issues (See consultancies section on https://www.servant.dev/). -
Try changelog-d for changelog management #1230
Check the CONTRIBUTING.md for details
-
CI and testing tweaks. #1154 #1157 #1182 #1214 #1229 #1233 #1242 #1247 #1250 #1258
We are experiencing some bitrotting of cookbook recipe dependencies, therefore some of them aren't build as part of our CI anymore.
-
servant-jsaddle Progress on servant-jsaddle #1216
-
servant-docs Prevent race-conditions in testing #1194
-
servant-client servant-http-streams
HasClient
instance forStream
withHeaders
#1170 #1197 -
servant Remove unused extensions from cabal file #1201
-
servant-client Redact the authorization header in Show and exceptions #1238
-
Dependency upgrades #1173 #1181 #1183 #1188 #1224 #1245 #1257
0.16.2
singleton-bool-0.1.5
(SBool
is re-exported)- Add
discreteBool :: Dec (a :~: b)
(GHC-7.8+) - Add
Show
,Eq
,Ord
SBool b
instances.
- Add
- dependencies update
0.16.1
- Add
Semigroup
andMonoid
SourceT
instances #1158 #1159 - Use
http-api-data-0.4.1
#1181 - Allow newer dependencies
0.16.0.1
- Make tests work with
http-media-0.8
0.16
Significant changes
-
Rename
ServantError
toClientError
,ServantErr
toServerError
#1131 -
servant-client-core Rearrange modules. No more
Internal
modules, whole API is versioned. #1130 -
servant-http-streams New package #1117
-
servant-client-core
RequestBody
is now= RequestBodyLBS LBS.ByteString | RequestBodyBS BS.ByteString | RequestBodySource (SourceIO LBS.ByteString)
i.e. no more replicates
http-client
s API. #1117 -
servant-client-core Keep structured exceptions in
ConnectionError
constructor ofClientError
#1115-| ConnectionError Text +| ConnectionError SomeException
-
servant-client-core Preserve failing request in
FailureResponse
constructor ofClientError
#1114-FailureResponse Response +-- | The server returned an error response including the +-- failing request. 'requestPath' includes the 'BaseUrl' and the +-- path of the request. +FailureResponse (RequestF () (BaseUrl, BS.ByteString)) Response
-
servant-client Fix (implement)
StreamBody
instance #1110
Other changes
-
servant-client Update CookieJar with intermediate request/responses (redirects) #1104
-
servant-server Reorder HTTP failure code priorities #1103
-
servant-server Re-organise internal modules #1139
-
Allow
network-3.0
#1107 -
Add
NFData NoContent
instance #1090
0.15
Significant changes
-
Streaming refactoring. #991 #1076 #1077
The streaming functionality (
Servant.API.Stream
) is refactored to useservant
's ownSourceIO
type (seeServant.Types.SourceT
documentation), which replaces bothStreamGenerator
andResultStream
types.New conversion type-classes are
ToSourceIO
andFromSourceIO
(replacingToStreamGenerator
andBuildFromStream
). There are instances for conduit, pipes and machines in new packages: servant-conduit servant-pipes and servant-machines respectively.Writing new framing strategies is simpler. Check existing strategies for examples.
This change shouldn't affect you, if you don't use streaming endpoints.
-
servant-client Separate streaming client. #1066
We now have two
http-client
based clients, inServant.Client
andServant.Client.Streaming
.Their API is the same, except for
Servant.Client
cannot requestStream
endpoints.Servant.Client
is run by directrunClientM :: ClientM a -> ClientEnv -> IO (Either ServantError a)
Servant.Client.Streaming
can requestStream
endpoints.Servant.Client.Streaming
is used by CPSisedwithClientM :: ClientM a -> ClientEnv -> (Either ServantError a -> IO b) -> IO b
To access
Stream
endpoints useServant.Client.Streaming
withwithClientM
; otherwise you can continue usingServant.Client
withrunClientM
. You can use both too,ClientEnv
andBaseUrl
types are same for both.Note:
Servant.Client.Streaming
doesn't stream non-Stream
endpoints. Requesting ordinaryVerb
endpoints (e.g.Get
) will block until the whole response is received.There is
Servant.Client.Streaming.runClientM
function, but it has restricted type.NFData a
constraint prevents using it withSourceT
,Conduit
etc. response types.runClientM :: NFData a => ClientM a -> ClientEnv -> IO (Either ServantError a)
This change shouldn't affect you, if you don't use streaming endpoints.
-
servant-client-core Related to the previous:
streamingResponse
is removed fromRunClient
. We have a new type-class:class RunClient m => RunStreamingClient m where withStreamingRequest :: Request -> (StreamingResponse -> IO a) -> m a
-
servant
ComprehensiveAPI
is a part of public API inServant.Test.ComprehensiveAPI
module. This API type is used to verify that libraries implement all core combinators. Now we won't change this type between major versions. (This has been true for some time already). #1070 -
servant Remove
Servant.Utils.Enter
module (deprecated inservant-0.12
in favour ofhoistServer
) #996 -
servant-foreign Add support so
HasForeign
can be implemented forMultipartForm
fromservant-multipart
#1035
Other changes
-
servant-client-core Add
NFData (GenResponse a)
andNFData ServantError
instances. #1076 -
servant NewlineFraming encodes newline after each element (i.e last) #1079 #1011
-
servant Add
lookupResponseHeader :: ... => Headers headers r -> ResponseHeader h a
#1064 -
servant-server Add
MonadMask Handler
#1068 -
servant-docs Fix markdown indentation #1043
-
servant Export
GetHeaders'
#1052 -
servant Add
Bitraversable
and otherBi-
instances for:<|>
#1032 -
servant Add
PutCreated
method type alias #1024 -
servant-client-core Add
aeson
andLift BaseUrl
instances #1037 -
servant Add
ToSourceIO (NonEmpty a)
instance #988 -
Development process improvements
-
Documentation Tutorial and new recipes
- Using free client #1005
- Generating mock curl calls #1033
- Error logging with Sentry #987
- Hoist Server With Context for Custom Monads #1044
- How To Test Servant Applications #1050
genericServeT
: using custom monad withServant.API.Generic
in Using generics #1058- Tutorial #974 #1007
- miscellanea: fixed typos etc. #1030 #1020 #1059
-
Documentation README #1010
-
servant-client-ghcjs updates. note package is not released on Hackage #938
0.14.1
-
Merge in (and slightly refactor)
servant-generic
(by Patrick Chilton) intoservant
(Servant.API.Generic
),servant-client-code
(Servant.Client.Generic
) andservant-server
(Servant.Server.Generic
). -
Deprecate
Servant.Utils.Links
, useServant.Links
. #998 -
servant-server Deprecate
Servant.Utils.StaticUtils
, useServant.Server.StaticUtils
.
0.14
Significant changes
-
Stream
takes a status code argument-Stream method framing ctype a +Stream method status framing ctype a
-
ToStreamGenerator
definition changed, so it's possible to write an instance for conduits.-class ToStreamGenerator f a where - toStreamGenerator :: f a -> StreamGenerator a +class ToStreamGenerator a b | a -> b where + toStreamGenerator :: a -> StreamGenerator b
(#959)
-
Added
NoFraming
streaming strategy (#959) -
servant-client-core Free
Client
implementation. Useful for testingHasClient
instances. (#920) -
servant-client-core Add
hoistClient
toHasClient
. Just likehoistServer
allows us to change the monad in which request handlers of a web application live in, we also havehoistClient
for changing the monad in which client functions live. Read tutorial section for more information. (#936)iF you have own combinators, you'll need to define a new method of
HasClient
class, for example:type Client m (MyCombinator :> api) = MyValue :> Client m api hoistClientMonad pm _ nt cl = hoistClientMonad pm (Proxy :: Proxy api) nt . cl
-
servant Add
safeLink' :: (Link -> a) -> ... -> MkLink endpoint a
, which allows to create helpers returning something else thanLink
. (#968) -
servant-server File serving in polymorphic monad. i.e. Generalised types of
serveDirectoryFileServer
etc functions inServant.Utils.StaticFiles
(#953) -
servant-server
ReqBody
content type check is recoverable. This allows writing APIs like:ReqBody '[JSON] Int :> Post '[PlainText] Int :<|> ReqBody '[PlainText] Int :> Post '[PlainText] Int
which is useful when handlers are subtly different, for example may do less work. (#937)
-
servant-client Add more constructors to
RequestBody
, includingRequestBodyStream
. Note: we are looking for http-library agnostic API, so the might change again soon. Tell us which constructors are useful for you! (#913)
Other changes
-
GetHeaders
instances implemented withoutOverlappingInstances
(#971) -
Added tests or enabled tests (#975)
-
Add
servant-flatten
"spice" to the structuring api recipe (#929)
Note
(VIM) Regular-expression to link PR numbers: s/\v#(\d+)/[#\1](https:\/\/github.com\/haskell-servant\/servant\/pull\/\1)/
0.13.0.1
- Support
base-compat-0.10
0.13
Significant changes
-
Streaming endpoint support. (#836)
type StreamApi f = "streamGetNewline" :> StreamGet NewlineFraming JSON (f Person)
See tutorial for more details
-
servant Add
Servant.API.Modifiers
(#873 #903)QueryParam
,Header
andReqBody
understand modifiers:Required
orOptional
(resulting ina
orMaybe a
in handlers)Strict
orLenient
(resulting ina
orEither String a
in handlers)
Also you can use
Description
as a modifier, but it doesn't yet work withservant-docs
, onlyservant-swagger
. There is an issue. -
servant-client Support
http-client
’sCookieJar
(#897 #883)ClientM
preserves cookies between requests, if given initialCookieJar
. To migrate from older code, changeClientEnv
constructor tomkClientEnv
which makesClientEnv
withoutCookieJar
. -
servant Mono-kind-ise modifiers, resulting in better error messages. (#887 #890)
-
servant Add
TypeError ... => HasServer
s instances in GHC-8.2 for not saturated modifiers (Capture "foo" :> ...
) or->
in place of:>
. (#893) -
Cookbook example projects at http://docs.servant.dev/en/master/cookbook/index.html (#867 #892)
Other changes
-
servant Links aren't double escaped (#878)
0.12.1
Bug fixes
0.12
Significant changes
-
servant-client servant-client-core Factored out of
servant-client
all the functionality that was independent of thehttp-client
backend. (#803 #821)If you have own combinators, you'll need to add an additional
m
argument inHasClient
,Client
andclientWithRoute
:-class HasClient api - type Client (api :: *) :: * - clientWithRoute :: Proxy api -> Req -> Client api +class HasClient m api + type Client (m :: * -> *) (api :: *) :: * + clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api
See https://github.com/haskell-servant/servant-auth/pull/67/commits/f777818e3cc0fa3ed2346baff8328e96d62b1790 for a real world example.
-
servant-server Added
hoistServer
member to theHasServer
class, which isHasServer
specificenter
. (#804 #824)enter
isn't exported fromServant
module anymore. You can changeenter
tohoistServer
in a straight forward way. Unwrap natural transformation and add a api typeProxy
:-server = enter (NT nt) impl +server = hoistServer (Proxy :: Proxy MyApi) nt impl
If you have own combinators, you'll need to define a new method of
HasServer
class, for example:type ServerT (MyCombinator :> api) m = MyValue -> ServerT api m hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt . s
See https://github.com/haskell-servant/servant-auth/pull/67/commits/8ee3b6315247ac076516213fd7cfcdbfdb583ac9 for a real world example.
-
Add
Description
andSummary
combinators (#767)It's possible to annotate endpoints with free form text. This information is used by e.g. by
servant-swagger
, see screenshot in https://github.com/phadej/servant-swagger-ui -
Lower
:>
and:<|>
infix precedence to 4 and 3 respectively (#761)This shouldn't affect you, except if you define your own infix operators for Servant type-level DSL.
Other changes
- servant-foreign Derive
Data
for all types (#809) - servant-docs Add authentication lenses (#787)
- servant-docs Generated markdown improvements (#813 #767 #790 #788)
- Add
addLinks
to generate all links for unnested APIs. (#851) - Allow newest dependencies (#772 #842)
- Documentation improvements and typo fixes (#757 #771 #775 #790 #791 #806)
- Development process improvements (#764 #839)
0.11
Breaking changes
Other changes
- Add a type representing an empty API (#753)
- Add
linkURI'
andLink
accessors (#745 , #717 , #715) - Prepare for GHC-8.2 (#722)
- Add
HasLink AuthProtect
instance (#720) AllCTRender [] ()
TypeError
(useNoContent
) (#671)- Documentation improvements and typo fixes (#702 , #709 , #716 , #725 , #727)
0.10
Breaking changes
-
Use
NT
fromnatural-transformation
forEnter
(#616) -
Change to
MkLink (Verb ...) = Link
(previouslyURI
). To consumeLink
use itsToHttpApiData
instance orlinkURI
. (#527)
Other changes
-
Add
Servant.API.TypeLevel
module with type families to work with API types. (#345 , #305) -
Default JSON content type change to
application/json;charset=utf-8
. (#263) Related browser bugs: Chromium and Firefox -
Accept
class may accept multiple content-types.MimeUnrender
adopted as well. (#613 , #615)
0.9.1
- Added 'noHeader' function for not adding response headers.
0.9
- Added Eq, Show, Read, Generic and Ord instances to IsSecure
- BACKWARDS INCOMPATIBLE: replace use of
ToFromByteString
withTo/FromHttpApiData
forGetHeaders/BuildHeadersTo
- BACKWARDS INCOMPATIBLE: Moved
From/ToFormUrlEncoded
classes, which were renamed toFrom/ToForm
tohttp-api-data
0.8.1
- Add
CaptureAll
combinator. Captures all of the remaining segments in a URL. - Add
Servant.API.TypeLevel
module, with frequently used type-level functionaliy.
0.8
- Minor fixes, documentation changes and cabal tweaks
0.7.1
- Add module
Servant.Utils.Enter
(https://github.com/haskell-servant/servant/pull/478) - Allow to set the same header multiple times in responses.
0.5
- Add
WithNamedConfig
combinator. - Add
HttpVersion
,IsSecure
,RemoteHost
andVault
combinators - Fix safeLink, so Header is not in fact required.
- Add more instances for (:<|>)
- Use
http-api-data
instead ofServant.Common.Text
- Remove matrix params.
- Add PlainText String MimeRender and MimeUnrender instances.
- Add new
Verbs
combinator, and make all existing and new verb combinators type synonyms of it. - Add
BasicAuth
combinator to support Basic authentication - Add generalized authentication support
0.4.2
- Fix missing cases for
Patch
insafeLink
0.4.1
- Allow whitespace after parsing JSON
- Stricter matching for
safeLink
forCapture
0.4
Delete
now is likeGet
,Post
,Put
, andPatch
and returns a response body- Multiple content-type/accept support for all the relevant combinators
- Provide JSON, PlainText, OctetStream and FormUrlEncoded content types out of the box
- Type-safe link generation to API endpoints
- Support for the PATCH HTTP method
- Removed the home-made QuasiQuote for writing API types in a more human-friendly format until we come up with a better design for it
- Make most if not all of the haddock code examples run through doctest
- Some general code cleanup
- Add response headers