{- gemcap Cooyright (C) Jonathan Lamothe 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 . -} {-# LANGUAGE OverloadedStrings #-} module Network.Gemini.Capsule.EncodingSpec (spec) where import Test.Hspec (Spec, context, describe, it, shouldBe) import Network.Gemini.Capsule.Encoding import Network.Gemini.Capsule.Types spec :: Spec spec = describe "Encoding" $ do encodeGemURLSpec decodeGemURLSpec escapeStringSpec unescapeStringSpec encodeGemResponseSpec encodeGemURLSpec :: Spec encodeGemURLSpec = describe "encodeGemURL" $ mapM_ ( \(desc, req, expected) -> context desc $ it ("should be " ++ show expected) $ encodeGemURL req `shouldBe` expected ) -- description, request, expected [ ( "simple", simpleURL, simpleExp ) , ( "with port", withPortURL, withPortExp ) , ( "with path", withPathURL, withPathExp ) , ( "with query", withQueryURL, withQueryExp ) , ( "blank query", blankQueryURL, blankQueryExp ) , ( "with escape", withEscapeURL, withEscapeExp ) ] where simpleURL = newGemURL "example.com" simpleExp = "gemini://example.com/" withPortURL = simpleURL { gemPort = Just 1965 } withPortExp = "gemini://example.com:1965/" withPathURL = simpleURL { gemPath = ["foo", "bar"] } withPathExp = "gemini://example.com/foo/bar" withQueryURL = simpleURL { gemQuery = Just "foo" } withQueryExp = "gemini://example.com/?foo" blankQueryURL = simpleURL { gemQuery = Just "" } blankQueryExp = "gemini://example.com/?" withEscapeURL = simpleURL { gemPath = ["foo bar"] , gemQuery = Just "baz quux" } withEscapeExp = "gemini://example.com/foo%20bar?baz%20quux" decodeGemURLSpec :: Spec decodeGemURLSpec = describe "decodeGemURL" $ mapM_ ( \(str, expected) -> context (show str) $ it ("should be " ++ show expected) $ decodeGemURL str `shouldBe` expected ) -- URL string, expected [ ( simpleStr, Just simpleURL ) , ( withSlashStr, Just simpleURL ) , ( withPathStr, Just withPathURL ) , ( withQueryStr, Just withQueryURL ) , ( pathQueryStr, Just pathQueryURL ) , ( blankQueryStr, Just blankQueryURL ) , ( withFragmentStr, Just simpleURL ) , ( escapedStr, Just escapedURL ) , ( httpStr, Nothing ) , ( malformed, Nothing ) , ( "", Nothing ) ] where simpleStr = "gemini://example.com" simpleURL = newGemURL "example.com" withSlashStr = simpleStr ++ "/" withPathStr = simpleStr ++ "/foo/bar" withPathURL = simpleURL { gemPath = ["foo", "bar"] } withQueryStr = simpleStr ++ "?foo" withQueryURL = simpleURL { gemQuery = Just "foo" } pathQueryStr = withPathStr ++ "?baz" pathQueryURL = withPathURL { gemQuery = Just "baz" } blankQueryStr = simpleStr ++"?" blankQueryURL = simpleURL { gemQuery = Just "" } withFragmentStr = simpleStr ++ "#foo" escapedStr = simpleStr ++ "/foo%20bar/baz?quux%20stuff" escapedURL = simpleURL { gemPath = ["foo bar", "baz"] , gemQuery = Just "quux stuff" } httpStr = "http://example.com" malformed = "foo" escapeStringSpec :: Spec escapeStringSpec = describe "escapeString" $ mapM_ ( \(input, expected) -> context (show input) $ it ("should be " ++ show expected) $ escapeString input `shouldBe` expected ) -- input, expected [ ( "~foo-bar_baz.quux", "~foo-bar_baz.quux" ) , ( "foo:/?=&#%", "foo%3a%2f%3f%3d%26%23%25" ) , ( "foo\xe9", "foo%c3%a9" ) ] unescapeStringSpec :: Spec unescapeStringSpec = describe "unescapeString" $ mapM_ ( \(input, expected) -> context (show input) $ it ("should be " ++ show expected) $ unescapeString input `shouldBe` expected ) -- input, expected [ ( "foo", Just "foo" ) , ( "foo%20bar", Just "foo bar" ) , ( "foo%7x", Just "foo%7x" ) , ( "foo%a", Just "foo%a" ) , ( "foo%", Just "foo%" ) , ( "foo%c3%a9", Just "foo\xe9" ) , ( "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