2021-11-10 15:04:00 -05:00
|
|
|
{-
|
|
|
|
|
2021-11-17 13:15:36 -05:00
|
|
|
gemcap
|
2021-11-10 15:04:00 -05:00
|
|
|
|
|
|
|
Cooyright (C) Jonathan Lamothe <jonathan@jlamothe.net>
|
|
|
|
|
|
|
|
This program is free software: you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU Affero General Public License as
|
|
|
|
published by the Free Software Foundation, either version 3 of the
|
|
|
|
License, or (at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful, but
|
|
|
|
WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
|
|
|
|
Affero General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU Affero General Public
|
|
|
|
License along with this program. If not, see
|
|
|
|
<https://www.gnu.org/licenses/>.
|
|
|
|
|
|
|
|
-}
|
|
|
|
|
2021-11-19 20:58:41 -05:00
|
|
|
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
|
2021-11-18 20:00:52 -05:00
|
|
|
|
2021-11-17 13:15:36 -05:00
|
|
|
module Network.Gemini.Capsule.InternalSpec (spec) where
|
2021-11-10 15:04:00 -05:00
|
|
|
|
2021-11-18 20:00:52 -05:00
|
|
|
import qualified Data.ByteString as BS
|
2021-11-24 18:56:12 -05:00
|
|
|
import qualified Data.ByteString.Lazy as BSL
|
2021-11-18 20:00:52 -05:00
|
|
|
import Data.Char (ord)
|
|
|
|
import Data.Connection (Connection (..))
|
2021-11-24 18:56:12 -05:00
|
|
|
import Data.IORef (IORef, modifyIORef', newIORef, readIORef)
|
|
|
|
import Data.X509 (Certificate (..))
|
2021-11-18 20:00:52 -05:00
|
|
|
import System.IO.Streams (nullInput, unRead)
|
2021-11-24 19:07:58 -05:00
|
|
|
import Test.Hspec (
|
|
|
|
Spec,
|
|
|
|
context,
|
|
|
|
describe,
|
|
|
|
it,
|
|
|
|
shouldBe,
|
2021-11-24 19:43:16 -05:00
|
|
|
shouldReturn)
|
2021-11-18 20:00:52 -05:00
|
|
|
|
|
|
|
import Network.Gemini.Capsule.Types
|
|
|
|
import Network.Gemini.Capsule.Internal
|
2021-11-10 15:04:00 -05:00
|
|
|
|
|
|
|
spec :: Spec
|
2021-11-18 20:00:52 -05:00
|
|
|
spec = describe "Internal" $ do
|
2021-11-24 18:56:12 -05:00
|
|
|
runConnectionSpec
|
2021-11-18 20:00:52 -05:00
|
|
|
readURLSpec
|
|
|
|
strFromConnSpec
|
2021-11-19 19:30:54 -05:00
|
|
|
readMaxSpec
|
|
|
|
stripCRLFSpec
|
2021-11-18 20:00:52 -05:00
|
|
|
|
2021-11-24 18:56:12 -05:00
|
|
|
runConnectionSpec :: Spec
|
|
|
|
runConnectionSpec = describe "runConnection" $ mapM_
|
|
|
|
( \(desc, ioConnRef, handler, mCert, expect) -> context desc $
|
2021-11-24 19:43:16 -05:00
|
|
|
it ("should return " ++ show expect) $ do
|
2021-11-24 18:56:12 -05:00
|
|
|
(conn, outRef) <- ioConnRef
|
|
|
|
runConnection conn handler mCert
|
|
|
|
readIORef outRef `shouldReturn` expect
|
|
|
|
)
|
|
|
|
|
|
|
|
-- description, connection, handler, certificate, expectation
|
|
|
|
[ ( "basic connection", basicConn, basicH, Nothing, basicExp )
|
|
|
|
, ( "no certificate", basicConn, certH, Nothing, noCertExp )
|
|
|
|
, ( "with certificate", basicConn, certH, Just sampleCert, basicExp )
|
|
|
|
, ( "gibberish with CR/LF", gibConnCRLF, basicH, Nothing, gibExp )
|
|
|
|
, ( "gibberish w/o CR/LF", gibConn, basicH, Nothing, gibExp )
|
|
|
|
]
|
|
|
|
|
|
|
|
where
|
|
|
|
basicConn = mkIOConn ["gemini://example.com/\r\n"]
|
|
|
|
gibConnCRLF = mkIOConn ["aosidjgfoeribjeworifj\r\n"]
|
|
|
|
gibConn = mkIOConn ["sodifjboije"]
|
|
|
|
basicH _ = return newGemResponse { respBody = Just success }
|
|
|
|
|
|
|
|
certH req = return $ case reqCert req of
|
|
|
|
Nothing -> newGemResponse
|
|
|
|
{ respStatus = 60
|
|
|
|
, respMeta = "certificate required"
|
|
|
|
}
|
|
|
|
Just _ -> newGemResponse { respBody = Just success }
|
|
|
|
|
|
|
|
basicExp = ["20 text/gemini\r\nSuccess!\r\n"]
|
|
|
|
noCertExp = ["60 certificate required\r\n"]
|
|
|
|
gibExp = ["59 bad request\r\n"]
|
|
|
|
success = "Success!\r\n"
|
|
|
|
|
2021-11-18 20:00:52 -05:00
|
|
|
readURLSpec :: Spec
|
|
|
|
readURLSpec = describe "readURL" $ mapM_
|
|
|
|
( \(desc, ioConn, expect) -> context desc $
|
2021-11-24 19:07:58 -05:00
|
|
|
it ("should return " ++ show expect) $
|
2021-11-18 20:00:52 -05:00
|
|
|
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
|
2021-11-19 19:30:54 -05:00
|
|
|
validConn = mkInConn ["gemini://example.com/\r\n"]
|
|
|
|
longConn = mkInConn [longBS]
|
|
|
|
tooLongConn = mkInConn [tooLongBS]
|
|
|
|
gibConn = mkInConn ["aosidjfwoeinboijwefr"]
|
2021-11-18 20:00:52 -05:00
|
|
|
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/"
|
|
|
|
|
2021-11-19 19:30:54 -05:00
|
|
|
strFromConnSpec :: Spec
|
|
|
|
strFromConnSpec = describe "strFromConn" $ mapM_
|
|
|
|
( \(desc, maxLen, ioConn, expect) -> context desc $
|
2021-11-24 19:07:58 -05:00
|
|
|
it ("should return " ++ show expect) $ do
|
2021-11-19 19:30:54 -05:00
|
|
|
conn <- ioConn
|
|
|
|
strFromConn maxLen conn `shouldReturn` expect
|
|
|
|
)
|
|
|
|
|
|
|
|
-- description, max size, connection, expected
|
|
|
|
[ ( "valid string", 100, mkInConn ["foo\r\n"], Just "foo" )
|
|
|
|
, ( "long string", 5, mkInConn ["too long\r\n"], Nothing )
|
|
|
|
, ( "no CR/LF", 100, mkInConn ["foo"], Nothing )
|
|
|
|
, ( "bad UTF-8", 100, mkInConn ["foo\xff\r\n"], Nothing )
|
|
|
|
, ( "non-ASCII", 100, mkInConn ["\xc3\xa9\r\n"], Just "\xe9" )
|
|
|
|
]
|
|
|
|
|
|
|
|
readMaxSpec :: Spec
|
2021-11-19 20:58:41 -05:00
|
|
|
readMaxSpec = describe "readMax" $ mapM_
|
|
|
|
( \(desc, maxLen, ioConn, expect) -> context desc $
|
|
|
|
it ("should return " ++ show expect) $ do
|
|
|
|
conn <- ioConn
|
|
|
|
readMax maxLen conn `shouldReturn` expect
|
|
|
|
)
|
|
|
|
|
2021-11-20 11:43:11 -05:00
|
|
|
-- description, max length, connection, expected
|
2021-11-19 20:58:41 -05:00
|
|
|
[ ( "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"
|
2021-11-19 19:30:54 -05:00
|
|
|
|
|
|
|
stripCRLFSpec :: Spec
|
2021-11-24 19:07:58 -05:00
|
|
|
stripCRLFSpec = describe "stripCRLF" $ mapM_
|
|
|
|
( \(input, expected) -> context (show input) $
|
|
|
|
it ("should be" ++ show expected) $
|
|
|
|
stripCRLF input `shouldBe` expected
|
|
|
|
)
|
|
|
|
|
|
|
|
-- input, expectation
|
|
|
|
[ ( "foo\r\n", Just "foo" )
|
|
|
|
, ( "foo\n", Nothing )
|
|
|
|
, ( "foo", Nothing )
|
|
|
|
, ( "\r\n", Just "" )
|
|
|
|
]
|
2021-11-10 15:04:00 -05:00
|
|
|
|
2021-11-24 18:56:12 -05:00
|
|
|
mkIOConn :: [BS.ByteString] -> IO (Connection (), IORef [BSL.ByteString])
|
|
|
|
mkIOConn input = do
|
|
|
|
ref <- newIORef []
|
|
|
|
conn <-
|
|
|
|
( \c -> c { send = \bs -> modifyIORef' ref (++[bs]) }
|
|
|
|
) <$> mkInConn input
|
|
|
|
return (conn, ref)
|
|
|
|
|
2021-11-19 20:58:41 -05:00
|
|
|
mkInConn :: [BS.ByteString] -> IO (Connection ())
|
|
|
|
mkInConn bss = do
|
|
|
|
source <- nullInput
|
|
|
|
mapM_ (`unRead` source) (reverse bss)
|
|
|
|
let
|
|
|
|
send = const $ return ()
|
|
|
|
close = return ()
|
|
|
|
connExtraInfo = ()
|
|
|
|
return Connection {..}
|
|
|
|
|
2021-11-24 18:56:12 -05:00
|
|
|
sampleCert :: Certificate
|
|
|
|
sampleCert = Certificate
|
|
|
|
{ certVersion = undefined
|
|
|
|
, certSerial = undefined
|
|
|
|
, certSignatureAlg = undefined
|
|
|
|
, certIssuerDN = undefined
|
|
|
|
, certValidity = undefined
|
|
|
|
, certSubjectDN = undefined
|
|
|
|
, certPubKey = undefined
|
|
|
|
, certExtensions = undefined
|
|
|
|
}
|
|
|
|
|
2021-11-10 15:04:00 -05:00
|
|
|
--jl
|