implemented readMax

This commit is contained in:
2021-11-19 20:58:41 -05:00
parent 4a99e5cb0b
commit 64444bbc81
4 changed files with 58 additions and 19 deletions

View File

@@ -20,7 +20,7 @@ License along with this program. If not, see
-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
module Network.Gemini.Capsule.InternalSpec (spec) where
@@ -28,7 +28,7 @@ import qualified Data.ByteString as BS
import Data.Char (ord)
import Data.Connection (Connection (..))
import System.IO.Streams (nullInput, unRead)
import Test.Hspec (Spec, context, describe, shouldReturn, xit)
import Test.Hspec (Spec, context, describe, it, shouldReturn, xit)
import Network.Gemini.Capsule.Types
import Network.Gemini.Capsule.Internal
@@ -89,24 +89,42 @@ strFromConnSpec = describe "strFromConn" $ mapM_
, ( "non-ASCII", 100, mkInConn ["\xc3\xa9\r\n"], Just "\xe9" )
]
mkInConn :: [BS.ByteString] -> IO (Connection a)
mkInConn bss = do
s <- nullInput
mapM_ (`unRead` s) (reverse bss)
return sampleConnection { source = s }
sampleConnection :: Connection a
sampleConnection = Connection
{ source = undefined
, send = const $ return ()
, close = return ()
, connExtraInfo = undefined
}
readMaxSpec :: Spec
readMaxSpec = describe "readMax" $ return ()
readMaxSpec = describe "readMax" $ mapM_
( \(desc, maxLen, ioConn, expect) -> context desc $
it ("should return " ++ show expect) $ do
conn <- ioConn
readMax maxLen conn `shouldReturn` expect
)
-- description, max length, connection, expected
[ ( "single input", 1024, singleConn, Just singleBS )
, ( "multi input", 1024, multiConn, Just multiBS )
, ( "long input", longLen, longConn, Just longBS )
, ( "too long", pred longLen, longConn, Nothing )
, ( "empty input", 1024, mkInConn [], Just "" )
]
where
singleConn = mkInConn ["foo"]
multiConn = mkInConn ["foo", "bar", "baz"]
longConn = mkInConn [longBS]
longLen = BS.length longBS
singleBS = "foo"
multiBS = "foobarbaz"
longBS = "ABCDEFGHIJKLMNOPQRSTUVWXYZ"
stripCRLFSpec :: Spec
stripCRLFSpec = describe "stripCRLF" $ return ()
mkInConn :: [BS.ByteString] -> IO (Connection ())
mkInConn bss = do
source <- nullInput
mapM_ (`unRead` source) (reverse bss)
let
send = const $ return ()
close = return ()
connExtraInfo = ()
return Connection {..}
--jl