implemented basic logic for readURL
This commit is contained in:
@@ -20,11 +20,70 @@ License along with this program. If not, see
|
||||
|
||||
-}
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Network.Gemini.Capsule.InternalSpec (spec) where
|
||||
|
||||
import Test.Hspec (Spec, describe)
|
||||
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 Network.Gemini.Capsule.Types
|
||||
import Network.Gemini.Capsule.Internal
|
||||
|
||||
spec :: Spec
|
||||
spec = describe "Internal" $ return ()
|
||||
spec = describe "Internal" $ do
|
||||
readURLSpec
|
||||
sendResponseSpec
|
||||
strFromConnSpec
|
||||
|
||||
readURLSpec :: Spec
|
||||
readURLSpec = describe "readURL" $ mapM_
|
||||
( \(desc, ioConn, expect) -> context desc $
|
||||
xit ("should return " ++ show expect) $
|
||||
do
|
||||
conn <- ioConn
|
||||
readURL conn `shouldReturn` expect
|
||||
)
|
||||
|
||||
-- description, connection, expected result
|
||||
[ ( "valid URL", validConn, Just validExp )
|
||||
, ( "long URL", longConn, Just longExp )
|
||||
, ( "too long URL", tooLongConn, Nothing )
|
||||
, ( "gibberish input", gibConn, Nothing )
|
||||
]
|
||||
|
||||
where
|
||||
validConn = mkConn "gemini://example.com/\r\n"
|
||||
longConn = mkConn longBS
|
||||
tooLongConn = mkConn tooLongBS
|
||||
gibConn = mkConn "aosidjfwoeinboijwefr"
|
||||
longBS = BS.pack (take 1024 bytes) <> "\r\n"
|
||||
tooLongBS = BS.pack (take 1025 bytes) <> "\r\n"
|
||||
bytes = BS.unpack prefix ++ repeat (fromIntegral $ ord 'A')
|
||||
validExp = newGemURL "example.com"
|
||||
longExp = validExp { gemPath = [longDir] }
|
||||
longDir = replicate (1024 - BS.length prefix) 'A'
|
||||
prefix = "gemini://example.com/"
|
||||
mkConn bs = do
|
||||
s <- nullInput
|
||||
unRead bs s
|
||||
return sampleConnection { source = s }
|
||||
|
||||
sendResponseSpec :: Spec
|
||||
sendResponseSpec = describe "sendResponse" $ return ()
|
||||
|
||||
sampleConnection :: Connection a
|
||||
sampleConnection = Connection
|
||||
{ source = undefined
|
||||
, send = const $ return ()
|
||||
, close = return ()
|
||||
, connExtraInfo = undefined
|
||||
}
|
||||
|
||||
strFromConnSpec :: Spec
|
||||
strFromConnSpec = describe "strFromConn" $ return ()
|
||||
|
||||
--jl
|
||||
|
||||
Reference in New Issue
Block a user