Skip to content

Commit 293ff97

Browse files
authored
Merge pull request #42 from safareli/fix-userinfor-encoding
Fix userinfo encoding
2 parents fd6a5f3 + 2740b7c commit 293ff97

File tree

2 files changed

+49
-5
lines changed

2 files changed

+49
-5
lines changed

src/Data/URI/UserInfo.purs

Lines changed: 48 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,19 @@
1-
module Data.URI.UserInfo where
1+
module Data.URI.UserInfo
2+
( UserInfo(..)
3+
, parser
4+
, print
5+
)where
26

37
import Prelude
48

59
import Control.Alt ((<|>))
10+
import Data.Foldable (foldMap)
611
import Data.Generic.Rep (class Generic)
712
import Data.Generic.Rep.Show (genericShow)
813
import Data.Newtype (class Newtype)
9-
import Data.URI.Common (decodePCT, joinWith, parsePCTEncoded, parseSubDelims, parseUnreserved)
10-
import Global (encodeURI)
14+
import Data.String as Str
15+
import Data.URI.Common (decodePCTComponent, joinWith, parsePCTEncoded, parseSubDelims, parseUnreserved)
16+
import Global (encodeURIComponent)
1117
import Text.Parsing.StringParser (Parser)
1218
import Text.Parsing.StringParser.Combinators (many1)
1319
import Text.Parsing.StringParser.String (string)
@@ -25,9 +31,46 @@ parser ∷ Parser UserInfo
2531
parser = UserInfo <<< joinWith "" <$> many1 p
2632
where
2733
p = parseUnreserved
28-
<|> parsePCTEncoded decodePCT
34+
<|> parsePCTEncoded decodePCTComponent
2935
<|> parseSubDelims
3036
<|> string ":"
3137

3238
print UserInfo String
33-
print (UserInfo u) = encodeURI u
39+
print (UserInfo u) = encodeUserPassword u
40+
41+
42+
encodeUserPassword :: String -> String
43+
encodeUserPassword s = foldMap encodeChar $ Str.toCharArray s
44+
45+
shouldNotEscape :: Char -> Boolean
46+
shouldNotEscape c =
47+
{-
48+
https://tools.ietf.org/html/rfc3986#section-3.2.1
49+
userinfo = *( unreserved / pct-encoded / sub-delims / ":" )
50+
51+
https://tools.ietf.org/html/rfc3986#section-2.1
52+
pct-encoded = "%" HEXDIG HEXDIG
53+
54+
https://tools.ietf.org/html/rfc3986#section-2.3
55+
unreserved = ALPHA / DIGIT / "-" / "." / "_" / "~"
56+
57+
https://tools.ietf.org/html/rfc3986#section-2.1
58+
sub-delims = "!" / "$" / "&" / "'" / "(" / ")"
59+
/ "*" / "+" / "," / ";" / "="
60+
-}
61+
-- unreserved
62+
('A' <= c && c <= 'Z')
63+
|| ('a' <= c && c <= 'z')
64+
|| ('0' <= c && c <= '9')
65+
|| c == '-' || c == '_' || c == '.' || c == '~'
66+
-- sub-delims
67+
|| c == '!' || c == '$' || c == '&' || c == '\''
68+
|| c == '(' || c == ')' || c == '*' || c == '+'
69+
|| c == ',' || c == ';' || c == '='
70+
-- userinfo
71+
|| c == ':'
72+
73+
encodeChar :: Char -> String
74+
encodeChar c =
75+
let cStr = Str.singleton c
76+
in if shouldNotEscape c then cStr else encodeURIComponent cStr

test/Main.purs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -115,6 +115,7 @@ main = runTest $ suite "Data.URI" do
115115

116116
suite "UserInfo parser" do
117117
testRunParseSuccess UserInfo.parser "user" (UserInfo "user")
118+
testRunParseSuccess UserInfo.parser "u%40ser" (UserInfo "u@ser")
118119
testRunParseSuccess UserInfo.parser "spaced%20user" (UserInfo "spaced user")
119120
testRunParseSuccess UserInfo.parser "user:password" (UserInfo "user:password")
120121
testRunParseSuccess UserInfo.parser "spaced%20user:password%25%C2%A3" (UserInfo "spaced user:password%£")

0 commit comments

Comments
 (0)