doco fixes and a build tool stanza

This commit is contained in:
Mark Wotton 2021-01-05 10:38:15 -05:00
parent df67dfc1c6
commit 900105a892
5 changed files with 52 additions and 43 deletions

View File

@ -2,7 +2,7 @@
Our api under test:
```haskell
``` haskell
-- Obligatory fancy-types pragma tax
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
@ -20,6 +20,7 @@ import Servant
import GHC.Generics
import Data.Typeable
import Data.Hashable
import Data.Maybe(isNothing, isJust)
newtype A = A Int
deriving (Generic, Eq, Show, Typeable)
@ -34,9 +35,7 @@ type Api =
:<|> "itemAdd" :> Capture "one" B :> Capture "two" B :> Get '[JSON] B
:<|> "item" :> Capture "itemId" B :> Get '[JSON] ()
goodServer = server (pure $ A 0)
badServer = server (pure $ A 1)
server :: Handler A -> Server Api
server introduce = introduce :<|> combine :<|> eliminate
where
combine (B i) (B j) = pure $ B (i + j)
@ -45,36 +44,55 @@ server introduce = introduce :<|> combine :<|> eliminate
| otherwise = pure ()
```
We have a "good" server, that never generates anything other than a 0. This means repeated application of
the combination/addition rule can never bring us to the dangerous state of numbers larger than 100.
``` haskell
goodServer, badServer :: Server Api
goodServer = server (pure $ A 0)
badServer = server (pure $ A 1)
```
In the test file, we first define the tests: the faulty server should fail and the good server should pass.
```haskell
main :: IO ()
main = hspec spec
spec :: Spec
spec = describe "example" $ do
it "good server should not fail" $ do
fuzz @Api goodServer config
>>= (`shouldSatisfy` isNothing)
it "bad server should fail" $ do
fuzz @Api badServer config
>>= (`shouldSatisfy` serverFailure)
config = defaultConfig
{
-- we expect to be able to cover the api from our starting point:
-- this will fail the test if we don't.
coverageThreshold = 0.99
}
-- there are other tweakable things in the config, like maximum runtime, reps,
-- per-request healthchecks, seeds, and verbose logging. Have a look at
-- Roboservant.Types.Config for details.
>>= (`shouldSatisfy` isJust)
```
And unless we want to ship roboservant and all its dependencies to production, we also need
We expect to be able to cover the whole api from our starting point, so let's set the coverage to 0.99.
There are other tweakable things in the config, like maximum runtime, reps,
per-request healthchecks, seeds, and verbose logging. Have a look at
Roboservant.Types.Config for details.
``` haskell
config :: Config
config = defaultConfig
{ coverageThreshold = 0.99
}
```
Unless we want to ship roboservant and all its dependencies to production, we also need
some orphan instances: because As are the only value we can get without
an input, we need to be able to break them down.
```haskell
``` haskell
deriving via (Compound A) instance Breakdown A
-- if we wanted to assemble As from parts as well, we'd derive using Compound
```
if we wanted to assemble As from parts as well, we'd derive using Compound, but in this case we don't care.
``` haskell
deriving via (Atom A) instance BuildFrom A
```
@ -86,20 +104,3 @@ build it up from components.
deriving via (Compound B) instance BuildFrom B
deriving via (Atom B) instance Breakdown B
```
finally some uninteresting utilities and the entrypoint
```haskell
main = hspec spec
serverFailure :: Maybe Report -> Bool
serverFailure c = case c of
Just Report{..} ->
let RoboservantException{..} = rsException
in failureReason /= NoPossibleMoves
_ -> False
isNothing x = case x of
Nothing -> True
_ -> False
```

View File

@ -19,9 +19,14 @@ sessions and verify properties that should hold over them.
In essence, ```fuzz @Api yourServer config``` will make a bunch of
calls to your API, and record the results in a type-indexed
dictionary. This means that they are now available for the
prerequisites of other call, so as you proceed, more and more api
prerequisites of other calls, so as you proceed, more and more api
calls become possible.
We explicitly do not try to come up with plausible values that haven't
somehow come back from the API. That's straying into QC/Hedgehog
territory: if you want that, come up with the values on that side, and
set them as seeds in the configuration.
### what does it mean to be "available"?
In a simple API, you may make a call and get back a `Foo`, which will
@ -65,7 +70,10 @@ Sometimes there are values we'd like to smuggle into the API that are
not derivable from within the API itself: sometimes this is a warning
sign that your API is incomplete, but it can be quite reasonable to
require identifying credentials within an API and not provide a way to
get them. For those cases, override the `seed` in the `Config` with a
get them. It might also be reasonable to have some sample values that
the user is expected to come up with.
For those cases, override the `seed` in the `Config` with a
list of seed values, suitably hashed:
``` haskell

View File

@ -63,5 +63,6 @@ tests:
dependencies:
- roboservant
- hspec
# build-depends: base, markdown-unlit
ghc-options: -pgmL markdown-unlit
build-tools: markdown-unlit

View File

@ -4,7 +4,7 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: 3eb8db6b6899ba904be853bb6865aba4f208077587e89f5377df3169743034b0
-- hash: 48773018ec618e9eba02a126e3aeb93781a1d68ce28e2c405c35e9536bf94f70
name: roboservant
version: 0.1.0.2
@ -33,7 +33,6 @@ library
Roboservant.Types.Breakdown
Roboservant.Types.BuildFrom
Roboservant.Types.Config
Roboservant.Types.Config.Internal
Roboservant.Types.FlattenServer
Roboservant.Types.Internal
Roboservant.Types.ReifiedApi
@ -72,6 +71,8 @@ test-suite example
hs-source-dirs:
./.
ghc-options: -Wall -fwrite-ide-info -hiedir=.hie -pgmL markdown-unlit
build-tool-depends:
markdown-unlit:markdown-unlit
build-depends:
base >=4.7 && <5
, bytestring

View File

@ -1,6 +1,4 @@
resolver: lts-16.27
# bit faster on ReifiedApi stuff which is unfortunately terribly slow.
# compiler: ghc-8.10.3
packages:
- .