Add framingRender examples

This commit is contained in:
Oleg Grenrus 2018-11-10 01:20:57 +02:00
parent ce83e4b404
commit 17f9237980
2 changed files with 16 additions and 0 deletions

View File

@ -150,6 +150,7 @@ test-suite spec
, base-compat , base-compat
, aeson , aeson
, bytestring , bytestring
, mtl
, servant , servant
, string-conversions , string-conversions
, text , text

View File

@ -1,6 +1,8 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Servant.API.StreamSpec where module Servant.API.StreamSpec where
import Control.Monad.Except
(runExcept)
import qualified Data.Aeson as Aeson import qualified Data.Aeson as Aeson
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS import qualified Data.ByteString.Lazy as LBS
@ -32,6 +34,11 @@ spec = describe "Servant.API.Stream" $ do
describe "NewlineFraming" $ do describe "NewlineFraming" $ do
let tp = framingUnrender (Proxy :: Proxy NewlineFraming) (Right . LBS.toStrict) let tp = framingUnrender (Proxy :: Proxy NewlineFraming) (Right . LBS.toStrict)
let re = framingRender (Proxy :: Proxy NewlineFraming) id
it "framingRender examples" $ do
runRenderFrames re [] `shouldBe` Right ""
runRenderFrames re ["foo", "bar", "baz"] `shouldBe` Right "foo\nbar\nbaz"
it "framingUnrender examples" $ do it "framingUnrender examples" $ do
let expected n = map Right [fromString ("foo" ++ show (n :: Int)), "bar", "baz"] let expected n = map Right [fromString ("foo" ++ show (n :: Int)), "bar", "baz"]
@ -51,6 +58,11 @@ spec = describe "Servant.API.Stream" $ do
describe "NetstringFraming" $ do describe "NetstringFraming" $ do
let tp = framingUnrender (Proxy :: Proxy NetstringFraming) (Right . LBS.toStrict) let tp = framingUnrender (Proxy :: Proxy NetstringFraming) (Right . LBS.toStrict)
let re = framingRender (Proxy :: Proxy NetstringFraming) id
it "framingRender examples" $ do
runRenderFrames re [] `shouldBe` Right ""
runRenderFrames re ["foo", "bar", "baz"] `shouldBe` Right "3:foo,3:bar,3:baz,"
it "framingUnrender examples" $ do it "framingUnrender examples" $ do
let expected n = map Right [fromString ("foo" ++ show (n :: Int)), "bar", "baz"] let expected n = map Right [fromString ("foo" ++ show (n :: Int)), "bar", "baz"]
@ -74,6 +86,9 @@ roundtrip
roundtrip render unrender xs = roundtrip render unrender xs =
map Right xs === runUnrenderFrames (unrender . fmap LBS.toStrict . render) xs map Right xs === runUnrenderFrames (unrender . fmap LBS.toStrict . render) xs
runRenderFrames :: (SourceT Identity a -> SourceT Identity LBS.ByteString) -> [a] -> Either String LBS.ByteString
runRenderFrames f = fmap mconcat . runExcept . runSourceT . f . source
runUnrenderFrames :: (SourceT Identity b -> SourceT Identity a) -> [b] -> [Either String a] runUnrenderFrames :: (SourceT Identity b -> SourceT Identity a) -> [b] -> [Either String a]
runUnrenderFrames f = go . Effect . flip unSourceT return . f . source where runUnrenderFrames f = go . Effect . flip unSourceT return . f . source where
go :: StepT Identity a -> [Either String a] go :: StepT Identity a -> [Either String a]