Compare commits

...

4 Commits

7 changed files with 151 additions and 39 deletions

View File

@ -5,7 +5,7 @@ cabal-version: 2.2
-- see: https://github.com/sol/hpack -- see: https://github.com/sol/hpack
name: gemcap name: gemcap
version: 0.0.0 version: 0.1.0
synopsis: a simple Gemini capsule (server) synopsis: a simple Gemini capsule (server)
description: a simple Gemini capsule (server) - see README.md for details description: a simple Gemini capsule (server) - see README.md for details
category: Gemini category: Gemini

View File

@ -1,5 +1,5 @@
name: gemcap name: gemcap
version: 0.0.0 version: 0.1.0
license: AGPL-3.0-or-later license: AGPL-3.0-or-later
author: "Jonathan Lamothe" author: "Jonathan Lamothe"
maintainer: "jonathan@jlamothe.net" maintainer: "jonathan@jlamothe.net"

View File

@ -97,18 +97,4 @@ adjustServerParams certRef params = let
hooks' = hooks { onClientCertificate = certHook' } hooks' = hooks { onClientCertificate = certHook' }
in params { serverHooks = hooks' } in params { serverHooks = hooks' }
runConnection
:: C.Connection a
-> GemHandler
-> Maybe Certificate
-> IO ()
runConnection conn handler mCert =
( readURL conn >>= \case
Nothing -> return $ newGemResponse
{ respStatus = 59
, respMeta = "bad request"
}
Just url -> handler (newGemRequest url) { reqCert = mCert }
) >>= sendResponse conn
--jl --jl

View File

@ -30,15 +30,21 @@ module Network.Gemini.Capsule.Encoding (
encodeGemURL, encodeGemURL,
decodeGemURL, decodeGemURL,
escapeString, escapeString,
unescapeString unescapeString,
encodeGemResponse
) where ) where
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.ByteString.Builder (charUtf8, stringUtf8, toLazyByteString) import Data.ByteString.Builder (
charUtf8,
lazyByteString,
stringUtf8,
toLazyByteString,
word8Dec)
import qualified Data.ByteString.Lazy as BSL import qualified Data.ByteString.Lazy as BSL
import Data.Char (chr, ord, toLower) import Data.Char (chr, ord, toLower)
import Data.List (find, intercalate) import Data.List (find, intercalate)
import Data.Maybe (fromJust) import Data.Maybe (fromJust, fromMaybe)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8') import Data.Text.Encoding (decodeUtf8')
@ -137,6 +143,25 @@ unescapeString str = case decodeUtf8' $ BS.pack $ toBytes str of
toNum ch = fst $ fromJust $ toNum ch = fst $ fromJust $
find (\x -> snd x == ch) $ zip [0..] hexDigits find (\x -> snd x == ch) $ zip [0..] hexDigits
-- | encodes a 'GemResponse' into a lazy ByteString
encodeGemResponse :: GemResponse -> BSL.ByteString
encodeGemResponse resp = let
code = respStatus resp
high = code `div` 10
low = code `mod` 10
meta = respMeta resp
body = fromMaybe "" $ respBody resp
builder
= word8Dec high
<> word8Dec low
<> charUtf8 ' '
<> stringUtf8 meta
<> stringUtf8 "\r\n"
<> lazyByteString body
in toLazyByteString builder
hexDigits :: String hexDigits :: String
hexDigits = ['0'..'9'] ++ ['a'..'f'] hexDigits = ['0'..'9'] ++ ['a'..'f']

View File

@ -33,8 +33,8 @@ time.
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
module Network.Gemini.Capsule.Internal ( module Network.Gemini.Capsule.Internal (
runConnection,
readURL, readURL,
sendResponse,
strFromConn, strFromConn,
readMax, readMax,
stripCRLF stripCRLF
@ -46,9 +46,10 @@ import Control.Monad.Trans.Maybe (MaybeT (..))
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.ByteString.Builder (Builder, byteString, toLazyByteString) import Data.ByteString.Builder (Builder, byteString, toLazyByteString)
import qualified Data.ByteString.Lazy as BSL import qualified Data.ByteString.Lazy as BSL
import Data.Connection (Connection, source) import Data.Connection (Connection, send, source)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8') import Data.Text.Encoding (decodeUtf8')
import Data.X509 (Certificate)
import qualified System.IO.Streams as S import qualified System.IO.Streams as S
import Network.Gemini.Capsule.Encoding import Network.Gemini.Capsule.Encoding
@ -60,6 +61,21 @@ import Network.Gemini.Capsule.Types
inBufSize :: Int inBufSize :: Int
inBufSize = 1026 inBufSize = 1026
-- | process a request and return a response over a 'Connection'
runConnection
:: Connection a
-> GemHandler
-> Maybe Certificate
-> IO ()
runConnection conn handler mCert =
( readURL conn >>= \case
Nothing -> return $ newGemResponse
{ respStatus = 59
, respMeta = "bad request"
}
Just url -> handler (newGemRequest url) { reqCert = mCert }
) >>= sendResponse conn
-- | Reads a 'GemURL' from a 'Connection' -- | Reads a 'GemURL' from a 'Connection'
readURL readURL
:: Connection a :: Connection a
@ -70,15 +86,6 @@ readURL conn =
Nothing -> Nothing Nothing -> Nothing
Just str -> decodeGemURL str Just str -> decodeGemURL str
-- | Sends a 'GemResponse' to a 'Connection'
sendResponse
:: Connection a
-- ^ the connection
-> GemResponse
-- ^ the response being sent
-> IO ()
sendResponse = undefined
-- | Reads up to a maxumum number of bytes from a 'Connection', UTF-8 -- | Reads up to a maxumum number of bytes from a 'Connection', UTF-8
-- decodes it, and returns the resulting string (if possible) without -- decodes it, and returns the resulting string (if possible) without
-- the trailing CR/LF -- the trailing CR/LF
@ -115,7 +122,10 @@ readMax maxLen conn = do
-- | Strips the CR/LF characters from the end of a string, retuning -- | Strips the CR/LF characters from the end of a string, retuning
-- Nothing if they are not present -- Nothing if they are not present
stripCRLF :: String -> Maybe String stripCRLF :: String -> Maybe String
stripCRLF = undefined stripCRLF = \case
"" -> Nothing
"\r\n" -> Just ""
c:str -> (c:) <$> stripCRLF str
readLoop :: Int -> S.InputStream BS.ByteString -> MaybeT IO Builder readLoop :: Int -> S.InputStream BS.ByteString -> MaybeT IO Builder
readLoop maxLen src = lift (S.read src) >>= \case readLoop maxLen src = lift (S.read src) >>= \case
@ -130,4 +140,12 @@ readLoop maxLen src = lift (S.read src) >>= \case
then return b then return b
else (b <>) <$> readLoop (maxLen - len) src else (b <>) <$> readLoop (maxLen - len) src
sendResponse
:: Connection a
-- ^ the connection
-> GemResponse
-- ^ the response being sent
-> IO ()
sendResponse conn resp = send conn $ encodeGemResponse resp
--jl --jl

View File

@ -20,6 +20,8 @@ License along with this program. If not, see
-} -}
{-# LANGUAGE OverloadedStrings #-}
module Network.Gemini.Capsule.EncodingSpec (spec) where module Network.Gemini.Capsule.EncodingSpec (spec) where
import Test.Hspec (Spec, context, describe, it, shouldBe) import Test.Hspec (Spec, context, describe, it, shouldBe)
@ -33,6 +35,7 @@ spec = describe "Encoding" $ do
decodeGemURLSpec decodeGemURLSpec
escapeStringSpec escapeStringSpec
unescapeStringSpec unescapeStringSpec
encodeGemResponseSpec
encodeGemURLSpec :: Spec encodeGemURLSpec :: Spec
encodeGemURLSpec = describe "encodeGemURL" $ mapM_ encodeGemURLSpec = describe "encodeGemURL" $ mapM_
@ -143,4 +146,12 @@ unescapeStringSpec = describe "unescapeString" $ mapM_
, ( "foo%ff", Nothing ) , ( "foo%ff", Nothing )
] ]
encodeGemResponseSpec :: Spec
encodeGemResponseSpec = describe "encodeGemResponse" $
it ("should be " ++ show expect) $
encodeGemResponse resp `shouldBe` expect
where
resp = newGemResponse { respBody = Just "Success!\r\n" }
expect = "20 text/gemini\r\nSuccess!\r\n"
--jl --jl

View File

@ -25,26 +25,70 @@ License along with this program. If not, see
module Network.Gemini.Capsule.InternalSpec (spec) where module Network.Gemini.Capsule.InternalSpec (spec) where
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import Data.Char (ord) import Data.Char (ord)
import Data.Connection (Connection (..)) import Data.Connection (Connection (..))
import Data.IORef (IORef, modifyIORef', newIORef, readIORef)
import Data.X509 (Certificate (..))
import System.IO.Streams (nullInput, unRead) import System.IO.Streams (nullInput, unRead)
import Test.Hspec (Spec, context, describe, it, shouldReturn, xit) import Test.Hspec (
Spec,
context,
describe,
it,
shouldBe,
shouldReturn)
import Network.Gemini.Capsule.Types import Network.Gemini.Capsule.Types
import Network.Gemini.Capsule.Internal import Network.Gemini.Capsule.Internal
spec :: Spec spec :: Spec
spec = describe "Internal" $ do spec = describe "Internal" $ do
runConnectionSpec
readURLSpec readURLSpec
sendResponseSpec
strFromConnSpec strFromConnSpec
readMaxSpec readMaxSpec
stripCRLFSpec stripCRLFSpec
runConnectionSpec :: Spec
runConnectionSpec = describe "runConnection" $ mapM_
( \(desc, ioConnRef, handler, mCert, expect) -> context desc $
it ("should return " ++ show expect) $ do
(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"
readURLSpec :: Spec readURLSpec :: Spec
readURLSpec = describe "readURL" $ mapM_ readURLSpec = describe "readURL" $ mapM_
( \(desc, ioConn, expect) -> context desc $ ( \(desc, ioConn, expect) -> context desc $
xit ("should return " ++ show expect) $ it ("should return " ++ show expect) $
do do
conn <- ioConn conn <- ioConn
readURL conn `shouldReturn` expect readURL conn `shouldReturn` expect
@ -70,13 +114,10 @@ readURLSpec = describe "readURL" $ mapM_
longDir = replicate (1024 - BS.length prefix) 'A' longDir = replicate (1024 - BS.length prefix) 'A'
prefix = "gemini://example.com/" prefix = "gemini://example.com/"
sendResponseSpec :: Spec
sendResponseSpec = describe "sendResponse" $ return ()
strFromConnSpec :: Spec strFromConnSpec :: Spec
strFromConnSpec = describe "strFromConn" $ mapM_ strFromConnSpec = describe "strFromConn" $ mapM_
( \(desc, maxLen, ioConn, expect) -> context desc $ ( \(desc, maxLen, ioConn, expect) -> context desc $
xit ("should return " ++ show expect) $ do it ("should return " ++ show expect) $ do
conn <- ioConn conn <- ioConn
strFromConn maxLen conn `shouldReturn` expect strFromConn maxLen conn `shouldReturn` expect
) )
@ -115,7 +156,26 @@ readMaxSpec = describe "readMax" $ mapM_
longBS = "ABCDEFGHIJKLMNOPQRSTUVWXYZ" longBS = "ABCDEFGHIJKLMNOPQRSTUVWXYZ"
stripCRLFSpec :: Spec stripCRLFSpec :: Spec
stripCRLFSpec = describe "stripCRLF" $ return () 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 "" )
]
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)
mkInConn :: [BS.ByteString] -> IO (Connection ()) mkInConn :: [BS.ByteString] -> IO (Connection ())
mkInConn bss = do mkInConn bss = do
@ -127,4 +187,16 @@ mkInConn bss = do
connExtraInfo = () connExtraInfo = ()
return Connection {..} return Connection {..}
sampleCert :: Certificate
sampleCert = Certificate
{ certVersion = undefined
, certSerial = undefined
, certSignatureAlg = undefined
, certIssuerDN = undefined
, certValidity = undefined
, certSubjectDN = undefined
, certPubKey = undefined
, certExtensions = undefined
}
--jl --jl