Compare commits

...

3 Commits

Author SHA1 Message Date
Jonathan Lamothe 64444bbc81 implemented readMax 2021-11-19 20:58:41 -05:00
Jonathan Lamothe 4a99e5cb0b implemented high-level logic for strFromConn 2021-11-19 19:30:54 -05:00
Jonathan Lamothe 489d0fdb78 linting of readURL function
I disagree with the use of `<$>` in place of `.`, but not enough to fight hlint on it.
2021-11-19 19:28:46 -05:00
4 changed files with 113 additions and 23 deletions

View File

@ -40,6 +40,7 @@ library
, tcp-streams >=1.0.1.1 && <1.1 , tcp-streams >=1.0.1.1 && <1.1
, text >=1.2.4.1 && <1.3 , text >=1.2.4.1 && <1.3
, tls , tls
, transformers
, x509 , x509
default-language: Haskell2010 default-language: Haskell2010
autogen-modules: Paths_gemcap autogen-modules: Paths_gemcap
@ -65,6 +66,7 @@ test-suite gemcap-test
, tcp-streams >=1.0.1.1 && <1.1 , tcp-streams >=1.0.1.1 && <1.1
, text >=1.2.4.1 && <1.3 , text >=1.2.4.1 && <1.3
, tls , tls
, transformers
, x509 , x509
default-language: Haskell2010 default-language: Haskell2010
autogen-modules: Paths_gemcap autogen-modules: Paths_gemcap

View File

@ -31,6 +31,7 @@ dependencies:
- io-streams - io-streams
- network - network
- tls - tls
- transformers
- x509 - x509
library: library:

View File

@ -34,10 +34,21 @@ time.
module Network.Gemini.Capsule.Internal ( module Network.Gemini.Capsule.Internal (
readURL, readURL,
sendResponse sendResponse,
strFromConn,
readMax,
stripCRLF
) where ) where
import Data.Connection (Connection) import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Maybe (MaybeT (..))
import qualified Data.ByteString as BS
import Data.ByteString.Builder (Builder, byteString, toLazyByteString)
import qualified Data.ByteString.Lazy as BSL
import Data.Connection (Connection, source)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8')
import System.IO.Streams as S
import Network.Gemini.Capsule.Encoding import Network.Gemini.Capsule.Encoding
import Network.Gemini.Capsule.Types import Network.Gemini.Capsule.Types
@ -54,7 +65,7 @@ readURL
-- ^ the connection -- ^ the connection
-> IO (Maybe GemURL) -> IO (Maybe GemURL)
readURL conn = readURL conn =
strFromConn inBufSize conn >>= return . \case strFromConn inBufSize conn >>= return <$> \case
Nothing -> Nothing Nothing -> Nothing
Just str -> decodeGemURL str Just str -> decodeGemURL str
@ -76,6 +87,41 @@ strFromConn
-> Connection a -> Connection a
-- ^ The connection to read from -- ^ The connection to read from
-> IO (Maybe String) -> IO (Maybe String)
strFromConn = undefined strFromConn maxLen conn = do
mbs <- readMax maxLen conn
return $ do
bs <- mbs
txt <- case decodeUtf8' bs of
Left _ -> Nothing
Right s -> Just s
stripCRLF $ T.unpack txt
-- | Reads from a connection up to a maximum number of bytes,
-- returning 'Nothing' if the limit is exceeded
readMax
:: Int
-- ^ the maximum number of bytes
-> Connection a
-- ^ the 'Connection' to read from
-> IO (Maybe BS.ByteString)
readMax maxLen conn = do
let src = source conn
runMaybeT $
BS.pack . BSL.unpack . toLazyByteString
<$> readLoop maxLen src
-- | Strips the CR/LF characters from the end of a string, retuning
-- Nothing if they are not present
stripCRLF :: String -> Maybe String
stripCRLF = undefined
readLoop :: Int -> S.InputStream BS.ByteString -> MaybeT IO Builder
readLoop maxLen src =
lift (S.read src) >>= \case
Nothing -> return mempty
Just bs -> let len = BS.length bs in
if len > maxLen
then MaybeT $ return Nothing
else (byteString bs <>) <$> readLoop (maxLen - len) src
--jl --jl

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 module Network.Gemini.Capsule.InternalSpec (spec) where
@ -28,7 +28,7 @@ import qualified Data.ByteString as BS
import Data.Char (ord) import Data.Char (ord)
import Data.Connection (Connection (..)) import Data.Connection (Connection (..))
import System.IO.Streams (nullInput, unRead) 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.Types
import Network.Gemini.Capsule.Internal import Network.Gemini.Capsule.Internal
@ -38,6 +38,8 @@ spec = describe "Internal" $ do
readURLSpec readURLSpec
sendResponseSpec sendResponseSpec
strFromConnSpec strFromConnSpec
readMaxSpec
stripCRLFSpec
readURLSpec :: Spec readURLSpec :: Spec
readURLSpec = describe "readURL" $ mapM_ readURLSpec = describe "readURL" $ mapM_
@ -56,10 +58,10 @@ readURLSpec = describe "readURL" $ mapM_
] ]
where where
validConn = mkConn "gemini://example.com/\r\n" validConn = mkInConn ["gemini://example.com/\r\n"]
longConn = mkConn longBS longConn = mkInConn [longBS]
tooLongConn = mkConn tooLongBS tooLongConn = mkInConn [tooLongBS]
gibConn = mkConn "aosidjfwoeinboijwefr" gibConn = mkInConn ["aosidjfwoeinboijwefr"]
longBS = BS.pack (take 1024 bytes) <> "\r\n" longBS = BS.pack (take 1024 bytes) <> "\r\n"
tooLongBS = BS.pack (take 1025 bytes) <> "\r\n" tooLongBS = BS.pack (take 1025 bytes) <> "\r\n"
bytes = BS.unpack prefix ++ repeat (fromIntegral $ ord 'A') bytes = BS.unpack prefix ++ repeat (fromIntegral $ ord 'A')
@ -67,23 +69,62 @@ readURLSpec = describe "readURL" $ mapM_
longExp = validExp { gemPath = [longDir] } longExp = validExp { gemPath = [longDir] }
longDir = replicate (1024 - BS.length prefix) 'A' longDir = replicate (1024 - BS.length prefix) 'A'
prefix = "gemini://example.com/" prefix = "gemini://example.com/"
mkConn bs = do
s <- nullInput
unRead bs s
return sampleConnection { source = s }
sendResponseSpec :: Spec sendResponseSpec :: Spec
sendResponseSpec = describe "sendResponse" $ return () sendResponseSpec = describe "sendResponse" $ return ()
sampleConnection :: Connection a
sampleConnection = Connection
{ source = undefined
, send = const $ return ()
, close = return ()
, connExtraInfo = undefined
}
strFromConnSpec :: Spec strFromConnSpec :: Spec
strFromConnSpec = describe "strFromConn" $ return () strFromConnSpec = describe "strFromConn" $ mapM_
( \(desc, maxLen, ioConn, expect) -> context desc $
xit ("should return " ++ show expect) $ do
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
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 --jl