File 4141-base64-Add-selectable-alphabet.patch of Package erlang

From 05e61dc7eb568cc5a5db965dcc3534fb6c9aa66d Mon Sep 17 00:00:00 2001
From: Jan Uhlig <juhlig@hnc-agency.org>
Date: Thu, 15 Sep 2022 12:28:33 +0200
Subject: [PATCH] base64: Add selectable alphabet

RFC 4648 defines two possible alphabets that may be used for
encoding and decoding, the standard alphabet in Section 4 and
an alternative URL and Filename safe alphabet in Section 5.

This commit adds the ability to specify one of the alphabets
for encoding and decoding.

Co-authored-by: Maria Scott <maria-12648430@hnc-agency.org>
---
 lib/stdlib/doc/src/base64.xml                 |  85 ++-
 lib/stdlib/src/base64.erl                     | 658 ++++++++++--------
 lib/stdlib/test/base64_SUITE.erl              |  98 ++-
 .../test/base64_property_test_SUITE.erl       | 108 ++-
 lib/stdlib/test/property_test/base64_prop.erl | 375 ++++++----
 5 files changed, 856 insertions(+), 468 deletions(-)

diff --git a/lib/stdlib/doc/src/base64.xml b/lib/stdlib/doc/src/base64.xml
index bb45927c3f..b58e7394f2 100644
--- a/lib/stdlib/doc/src/base64.xml
+++ b/lib/stdlib/doc/src/base64.xml
@@ -40,7 +40,17 @@
   <datatypes>
     <datatype>
       <name name="base64_alphabet"/>
-      <desc><p>Base 64 Encoding alphabet, see <url href="https://www.ietf.org/rfc/rfc4648.txt">RFC 4648</url>.</p>
+      <desc><p>Base 64 Encoding alphabet, see
+        <url href="https://datatracker.ietf.org/doc/html/rfc4648">RFC 4648</url>.</p>
+      </desc>
+    </datatype>
+    <datatype>
+      <name name="base64_mode"/>
+      <desc>
+        <p>Selector for the Base 64 Encoding alphabet used for encoding and decoding,
+         see <url href="https://datatracker.ietf.org/doc/html/rfc4648">RFC 4648</url>
+         Sections <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-4">4</url>
+         and <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-5">5</url>.</p>
       </desc>
     </datatype>
     <datatype>
@@ -67,18 +77,54 @@
       <name name="mime_decode" arity="1"/>
       <name name="mime_decode_to_string" arity="1"/>
       <fsummary>Decode a base64 encoded string to data.</fsummary>
-      <type variable="Base64" name_i="1"/>
+      <type variable="Base64"/>
       <type variable="Data" name_i="1"/>
       <type variable="DataString" name_i="2"/>
       <desc>
-        <p>Decodes a base64-encoded string to plain ASCII. See
-          <url href="https://www.ietf.org/html/rfc4648">RFC 4648</url>.</p>
+        <p>Decodes a base64 string encoded using the standard alphabet according
+          to <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-4">RFC 4648
+          Section 4</url> to plain ASCII.</p>
         <p><c>mime_decode/1</c> and <c>mime_decode_to_string/1</c> strip away
           illegal characters, while <c>decode/1</c> and
           <c>decode_to_string/1</c> only strip away whitespace characters.</p>
       </desc>
     </func>
 
+    <func>
+      <name name="decode" arity="2"/>
+      <name name="decode_to_string" arity="2"/>
+      <name name="mime_decode" arity="2"/>
+      <name name="mime_decode_to_string" arity="2"/>
+      <fsummary>Decode a base64 encoded string to data.</fsummary>
+      <type variable="Base64"/>
+      <type variable="Mode" name_i="1"/>
+      <type variable="Data" name_i="1"/>
+      <type variable="DataString" name_i="2"/>
+      <desc>
+        <p>Decodes a base64 string encoded using the alphabet indicated by the
+          <c><anno>Mode</anno></c> parameter to plain ASCII.</p>
+        <p><c>mime_decode/2</c> and <c>mime_decode_to_string/2</c> strip away
+          illegal characters, while <c>decode/2</c> and
+          <c>decode_to_string/2</c> only strip away whitespace characters.</p>
+        <p>The <c><anno>Mode</anno></c> parameter can be one of the following:</p>
+        <taglist>
+          <tag><c>standard</c></tag>
+          <item>Decode the given string using the standard base64 alphabet according
+            to <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-4">RFC 4648
+            Section 4</url>, that is <c>"+"</c> and <c>"/"</c> are representing bytes <c>62</c>
+            and <c>63</c> respectively, while <c>"-"</c> and <c>"_"</c> are illegal
+            characters.</item>
+          <tag><c>urlsafe</c></tag>
+          <item>Decode the given string using the alternative "URL and Filename safe" base64
+            alphabet according to
+            <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-5">RFC 4648
+            Section 5</url>, that is <c>"-"</c> and <c>"_"</c> are representing bytes <c>62</c>
+            and <c>63</c> respectively, while <c>"+"</c> and <c>"/"</c> are illegal
+            characters.</item>
+        </taglist>
+      </desc>
+    </func>
+
     <func>
       <name name="encode" arity="1"/>
       <name name="encode_to_string" arity="1"/>
@@ -87,8 +133,35 @@
       <type variable="Base64" name_i="1"/>
       <type variable="Base64String"/>
       <desc>
-        <p>Encodes a plain ASCII string into base64. The result is 33% larger
-          than the data.</p>
+        <p>Encodes a plain ASCII string into base64 using the standard alphabet
+          according to <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-4">RFC 4648
+          Section 4</url>. The result is 33% larger than the data.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="encode" arity="2"/>
+      <name name="encode_to_string" arity="2"/>
+      <fsummary>Encode data into base64.</fsummary>
+      <type variable="Data"/>
+      <type variable="Mode"/>
+      <type variable="Base64" name_i="1"/>
+      <type variable="Base64String"/>
+      <desc>
+        <p>Encodes a plain ASCII string into base64 using the alphabet indicated by
+          the <c><anno>Mode</anno></c> parameter. The result is 33% larger than the data.</p>
+        <p>The <c><anno>Mode</anno></c> parameter can be one of the following:</p>
+        <taglist>
+          <tag><c>standard</c></tag>
+          <item>Encode the given string using the standard base64 alphabet according
+            to <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-4">RFC 4648
+            Section 4</url>.</item>
+          <tag><c>urlsafe</c></tag>
+          <item>Encode the given string using the alternative "URL and Filename safe" base64
+            alphabet according to
+            <url href="https://datatracker.ietf.org/doc/html/rfc4648#section-5">RFC 4648
+            Section 5</url>.</item>
+        </taglist>
       </desc>
     </func>
   </funcs>
diff --git a/lib/stdlib/src/base64.erl b/lib/stdlib/src/base64.erl
index 600f73a4cb..eae9527a2d 100644
--- a/lib/stdlib/src/base64.erl
+++ b/lib/stdlib/src/base64.erl
@@ -21,12 +21,19 @@
 
 -module(base64).
 
--export([encode/1, decode/1, mime_decode/1,
-	 encode_to_string/1, decode_to_string/1, mime_decode_to_string/1]).
-
+-export([encode/1, encode/2,
+	 decode/1, decode/2,
+	 mime_decode/1, mime_decode/2,
+	 encode_to_string/1, encode_to_string/2,
+	 decode_to_string/1, decode_to_string/2,
+	 mime_decode_to_string/1, mime_decode_to_string/2]).
 
 %% RFC 4648: Base 64 Encoding alphabet
--type base64_alphabet() :: $A..$Z | $a..$z | $0..$9 | $+ | $/ | $=.
+-type base64_alphabet() :: $A..$Z | $a..$z | $0..$9 | $+ | $/ | $- | $_ | $=.
+
+%% Selector for the Base 64 alphabet, `standard'  for RFC 4648
+%% Section 4, `urlsafe'  for RFC 4648 Section 5.
+-type base64_mode() :: 'standard' | 'urlsafe'.
 
 %% The following type is a subtype of string() for return values
 %% of encoding functions.
@@ -40,76 +47,95 @@
       Data :: byte_string() | binary(),
       Base64String :: base64_string().
 
-encode_to_string(Bin) when is_binary(Bin) ->
-    encode_to_string(binary_to_list(Bin));
-encode_to_string(List) when is_list(List) ->
-    encode_list_to_string(List).
+encode_to_string(Data) ->
+    encode_to_string(Data, standard).
+
+-spec encode_to_string(Data, Mode) -> Base64String when
+      Data :: byte_string() | binary(),
+      Mode :: base64_mode(),
+      Base64String :: base64_string().
+
+encode_to_string(Bin, Mode) when is_binary(Bin) ->
+    encode_to_string(binary_to_list(Bin), Mode);
+encode_to_string(List, Mode) when is_list(List) ->
+    encode_list_to_string(get_encoding_offset(Mode), List).
 
 -spec encode(Data) -> Base64 when
       Data :: byte_string() | binary(),
       Base64 :: base64_binary().
 
-encode(Bin) when is_binary(Bin) ->
-    encode_binary(Bin, <<>>);
-encode(List) when is_list(List) ->
-    encode_list(List, <<>>).
+encode(Data) ->
+    encode(Data, standard).
 
-encode_list_to_string([]) ->
+-spec encode(Data, Mode) -> Base64 when
+      Data :: byte_string() | binary(),
+      Mode :: base64_mode(),
+      Base64 :: base64_binary().
+
+encode(Bin, Mode) when is_binary(Bin) ->
+    encode_binary(get_encoding_offset(Mode), Bin, <<>>);
+encode(List, Mode) when is_list(List) ->
+    encode_list(get_encoding_offset(Mode), List, <<>>).
+
+encode_list_to_string(_ModeOffset, []) ->
     [];
-encode_list_to_string([B1]) ->
-    [b64e(B1 bsr 2),
-     b64e((B1 band 3) bsl 4), $=, $=];
-encode_list_to_string([B1,B2]) ->
-    [b64e(B1 bsr 2),
-     b64e(((B1 band 3) bsl 4) bor (B2 bsr 4)),
-     b64e((B2 band 15) bsl 2), $=];
-encode_list_to_string([B1,B2,B3|Ls]) ->
+encode_list_to_string(ModeOffset, [B1]) ->
+    [b64e(B1 bsr 2, ModeOffset),
+     b64e((B1 band 3) bsl 4, ModeOffset), $=, $=];
+encode_list_to_string(ModeOffset, [B1,B2]) ->
+    [b64e(B1 bsr 2, ModeOffset),
+     b64e(((B1 band 3) bsl 4) bor (B2 bsr 4), ModeOffset),
+     b64e((B2 band 15) bsl 2, ModeOffset), $=];
+encode_list_to_string(ModeOffset, [B1,B2,B3|Ls]) ->
     BB = (B1 bsl 16) bor (B2 bsl 8) bor B3,
-    [b64e(BB bsr 18),
-     b64e((BB bsr 12) band 63), 
-     b64e((BB bsr 6) band 63),
-     b64e(BB band 63) | encode_list_to_string(Ls)].
-
-encode_binary(<<B1:6, B2:6, B3:6, B4:6, B5:6, B6:6, B7:6, B8:6, Ls/bits>>, A) ->
-    encode_binary(Ls,
+    [b64e(BB bsr 18, ModeOffset),
+     b64e((BB bsr 12) band 63, ModeOffset), 
+     b64e((BB bsr 6) band 63, ModeOffset),
+     b64e(BB band 63, ModeOffset) | encode_list_to_string(ModeOffset, Ls)].
+
+encode_binary(ModeOffset, <<B1:6, B2:6, B3:6, B4:6, B5:6, B6:6, B7:6, B8:6, Ls/bits>>, A) ->
+    encode_binary(ModeOffset,
+                  Ls,
                   <<A/bits,
-                    (b64e(B1)):8,
-                    (b64e(B2)):8,
-                    (b64e(B3)):8,
-                    (b64e(B4)):8,
-                    (b64e(B5)):8,
-                    (b64e(B6)):8,
-                    (b64e(B7)):8,
-                    (b64e(B8)):8>>);
-encode_binary(<<>>, A) ->
+                    (b64e(B1, ModeOffset)):8,
+                    (b64e(B2, ModeOffset)):8,
+                    (b64e(B3, ModeOffset)):8,
+                    (b64e(B4, ModeOffset)):8,
+                    (b64e(B5, ModeOffset)):8,
+                    (b64e(B6, ModeOffset)):8,
+                    (b64e(B7, ModeOffset)):8,
+                    (b64e(B8, ModeOffset)):8>>);
+encode_binary(_ModeOffset, <<>>, A) ->
     A;
-encode_binary(<<B1:6, B2:6, B3:6, B4:6, Ls/bits>>, A) ->
-    encode_binary(Ls,
+encode_binary(ModeOffset, <<B1:6, B2:6, B3:6, B4:6, Ls/bits>>, A) ->
+    encode_binary(ModeOffset,
+		  Ls,
                   <<A/bits,
-                    (b64e(B1)):8,
-                    (b64e(B2)):8,
-                    (b64e(B3)):8,
-                    (b64e(B4)):8>>);
-encode_binary(<<B1:6, B2:2>>, A) ->
-    <<A/bits,(b64e(B1)):8,(b64e(B2 bsl 4)):8,$=:8,$=:8>>;
-encode_binary(<<B1:6, B2:6, B3:4>>, A) ->
-    <<A/bits,(b64e(B1)):8,(b64e(B2)):8,(b64e(B3 bsl 2)):8, $=:8>>.
-
-encode_list([], A) ->
+                    (b64e(B1, ModeOffset)):8,
+                    (b64e(B2, ModeOffset)):8,
+                    (b64e(B3, ModeOffset)):8,
+                    (b64e(B4, ModeOffset)):8>>);
+encode_binary(ModeOffset, <<B1:6, B2:2>>, A) ->
+    <<A/bits,(b64e(B1, ModeOffset)):8,(b64e(B2 bsl 4, ModeOffset)):8,$=:8,$=:8>>;
+encode_binary(ModeOffset, <<B1:6, B2:6, B3:4>>, A) ->
+    <<A/bits,(b64e(B1, ModeOffset)):8,(b64e(B2, ModeOffset)):8,(b64e(B3 bsl 2, ModeOffset)):8, $=:8>>.
+
+encode_list(_ModeOffset, [], A) ->
     A;
-encode_list([B1], A) ->
-    <<A/bits,(b64e(B1 bsr 2)):8,(b64e((B1 band 3) bsl 4)):8,$=:8,$=:8>>;
-encode_list([B1,B2], A) ->
-    <<A/bits,(b64e(B1 bsr 2)):8,
-      (b64e(((B1 band 3) bsl 4) bor (B2 bsr 4))):8,
-      (b64e((B2 band 15) bsl 2)):8, $=:8>>;
-encode_list([B1,B2,B3|Ls], A) ->
+encode_list(ModeOffset, [B1], A) ->
+    <<A/bits,(b64e(B1 bsr 2, ModeOffset)):8,(b64e((B1 band 3) bsl 4, ModeOffset)):8,$=:8,$=:8>>;
+encode_list(ModeOffset, [B1,B2], A) ->
+    <<A/bits,(b64e(B1 bsr 2, ModeOffset)):8,
+      (b64e(((B1 band 3) bsl 4) bor (B2 bsr 4), ModeOffset)):8,
+      (b64e((B2 band 15) bsl 2, ModeOffset)):8, $=:8>>;
+encode_list(ModeOffset, [B1,B2,B3|Ls], A) ->
     BB = (B1 bsl 16) bor (B2 bsl 8) bor B3,
-    encode_list(Ls,
-                <<A/bits,(b64e(BB bsr 18)):8,
-                  (b64e((BB bsr 12) band 63)):8,
-                  (b64e((BB bsr 6) band 63)):8,
-                  (b64e(BB band 63)):8>>).
+    encode_list(ModeOffset,
+		Ls,
+                <<A/bits,(b64e(BB bsr 18, ModeOffset)):8,
+                  (b64e((BB bsr 12) band 63, ModeOffset)):8,
+                  (b64e((BB bsr 6) band 63, ModeOffset)):8,
+                  (b64e(BB band 63, ModeOffset)):8>>).
 
 %% mime_decode strips away all characters not Base64 before
 %% converting, whereas decode crashes if an illegal character is found
@@ -118,19 +144,35 @@ encode_list([B1,B2,B3|Ls], A) ->
       Base64 :: base64_string() | base64_binary(),
       Data :: binary().
 
-decode(Bin) when is_binary(Bin) ->
-    decode_binary(Bin, <<>>);
-decode(List) when is_list(List) ->
-    decode_list(List, <<>>).
+decode(Base64) ->
+    decode(Base64, standard).
+
+-spec decode(Base64, Mode) -> Data when
+      Base64 :: base64_string() | base64_binary(),
+      Mode :: base64_mode(),
+      Data :: binary().
+
+decode(Bin, Mode) when is_binary(Bin) ->
+    decode_binary(get_decoding_offset(Mode), Bin, <<>>);
+decode(List, Mode) when is_list(List) ->
+    decode_list(get_decoding_offset(Mode), List, <<>>).
 
 -spec mime_decode(Base64) -> Data when
       Base64 :: base64_string() | base64_binary(),
       Data :: binary().
 
-mime_decode(Bin) when is_binary(Bin) ->
-    mime_decode_binary(Bin, <<>>);
-mime_decode(List) when is_list(List) ->
-    mime_decode_list(List, <<>>).
+mime_decode(Base64) ->
+    mime_decode(Base64, standard).
+
+-spec mime_decode(Base64, Mode) -> Data when
+      Base64 :: base64_string() | base64_binary(),
+      Mode :: base64_mode(),
+      Data :: binary().
+
+mime_decode(Bin, Mode) when is_binary(Bin) ->
+    mime_decode_binary(get_decoding_offset(Mode), Bin, <<>>);
+mime_decode(List, Mode) when is_list(List) ->
+    mime_decode_list(get_decoding_offset(Mode), List, <<>>).
 
 %% mime_decode_to_string strips away all characters not Base64 before
 %% converting, whereas decode_to_string crashes if an illegal
@@ -140,352 +182,338 @@ mime_decode(List) when is_list(List) ->
       Base64 :: base64_string() | base64_binary(),
       DataString :: byte_string().
 
-decode_to_string(Bin) when is_binary(Bin) ->
-    decode_to_string(binary_to_list(Bin));
-decode_to_string(List) when is_list(List) ->
-    decode_list_to_string(List).
+decode_to_string(Base64) ->
+    decode_to_string(Base64, standard).
+
+-spec decode_to_string(Base64, Mode) -> DataString when
+      Base64 :: base64_string() | base64_binary(),
+      Mode :: base64_mode(),
+      DataString :: byte_string().
+
+decode_to_string(Bin, Mode) when is_binary(Bin) ->
+    decode_to_string(binary_to_list(Bin), Mode);
+decode_to_string(List, Mode) when is_list(List) ->
+    decode_list_to_string(get_decoding_offset(Mode), List).
 
 -spec mime_decode_to_string(Base64) -> DataString when
       Base64 :: base64_string() | base64_binary(),
       DataString :: byte_string().
 
-mime_decode_to_string(Bin) when is_binary(Bin) ->
-    mime_decode_to_string(binary_to_list(Bin));
-mime_decode_to_string(List) when is_list(List) ->
-    mime_decode_list_to_string(List).
+mime_decode_to_string(Base64) ->
+    mime_decode_to_string(Base64, standard).
+
+-spec mime_decode_to_string(Base64, Mode) -> DataString when
+      Base64 :: base64_string() | base64_binary(),
+      Mode :: base64_mode(),
+      DataString :: byte_string().
+
+mime_decode_to_string(Bin, Mode) when is_binary(Bin) ->
+    mime_decode_to_string(binary_to_list(Bin), Mode);
+mime_decode_to_string(List, Mode) when is_list(List) ->
+    mime_decode_list_to_string(get_decoding_offset(Mode), List).
 
 %% Skipping pad character if not at end of string. Also liberal about
 %% excess padding and skipping of other illegal (non-base64 alphabet)
 %% characters. See section 3.3 of RFC4648
-mime_decode_list([0 | Cs], A) ->
-    mime_decode_list(Cs, A);
-mime_decode_list([C1 | Cs], A) ->
-    case b64d(C1) of
-        B1 when is_integer(B1) -> mime_decode_list(Cs, A, B1);
-        _ -> mime_decode_list(Cs, A)  % eq is padding
+mime_decode_list(ModeOffset, [C1 | Cs], A) ->
+    case b64d(C1, ModeOffset) of
+        B1 when is_integer(B1) -> mime_decode_list(ModeOffset, Cs, A, B1);
+        _ -> mime_decode_list(ModeOffset, Cs, A)  % eq is padding
     end;
-mime_decode_list([], A) ->
+mime_decode_list(_ModeOffset, [], A) ->
     A.
 
-mime_decode_list([0 | Cs], A, B1) ->
-    mime_decode_list(Cs, A, B1);
-mime_decode_list([C2 | Cs], A, B1) ->
-    case b64d(C2) of
+mime_decode_list(ModeOffset, [C2 | Cs], A, B1) ->
+    case b64d(C2, ModeOffset) of
         B2 when is_integer(B2) ->
-            mime_decode_list(Cs, A, B1, B2);
-        _ -> mime_decode_list(Cs, A, B1) % eq is padding
+            mime_decode_list(ModeOffset, Cs, A, B1, B2);
+        _ -> mime_decode_list(ModeOffset, Cs, A, B1) % eq is padding
     end.
 
-mime_decode_list([0 | Cs], A, B1, B2) ->
-    mime_decode_list(Cs, A, B1, B2);
-mime_decode_list([C3 | Cs], A, B1, B2) ->
-    case b64d(C3) of
+mime_decode_list(ModeOffset, [C3 | Cs], A, B1, B2) ->
+    case b64d(C3, ModeOffset) of
         B3 when is_integer(B3) ->
-            mime_decode_list(Cs, A, B1, B2, B3);
+            mime_decode_list(ModeOffset, Cs, A, B1, B2, B3);
         eq=B3 ->
-            mime_decode_list_after_eq(Cs, A, B1, B2, B3);
-        _ -> mime_decode_list(Cs, A, B1, B2)
+            mime_decode_list_after_eq(ModeOffset, Cs, A, B1, B2, B3);
+        _ -> mime_decode_list(ModeOffset, Cs, A, B1, B2)
     end.
 
-mime_decode_list([0 | Cs], A, B1, B2, B3) ->
-    mime_decode_list(Cs, A, B1, B2, B3);
-mime_decode_list([C4 | Cs], A, B1, B2, B3) ->
-    case b64d(C4) of
+mime_decode_list(ModeOffset, [C4 | Cs], A, B1, B2, B3) ->
+    case b64d(C4, ModeOffset) of
         B4 when is_integer(B4) ->
-            mime_decode_list(Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>);
+            mime_decode_list(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>);
         eq ->
-            mime_decode_list_after_eq(Cs, A, B1, B2, B3);
-        _ -> mime_decode_list(Cs, A, B1, B2, B3)
+            mime_decode_list_after_eq(ModeOffset, Cs, A, B1, B2, B3);
+        _ -> mime_decode_list(ModeOffset, Cs, A, B1, B2, B3)
     end.
 
-mime_decode_list_after_eq([0 | Cs], A, B1, B2, B3) ->
-    mime_decode_list_after_eq(Cs, A, B1, B2, B3);
-mime_decode_list_after_eq([C | Cs], A, B1, B2, B3) ->
-    case b64d(C) of
+mime_decode_list_after_eq(ModeOffset, [C | Cs], A, B1, B2, B3) ->
+    case b64d(C, ModeOffset) of
         B when is_integer(B) ->
             %% More valid data, skip the eq as invalid
             case B3 of
-                eq -> mime_decode_list(Cs, A, B1, B2, B);
-                _ -> mime_decode_list(Cs, <<A/bits,B1:6,B2:6,B3:6,B:6>>)
+                eq -> mime_decode_list(ModeOffset, Cs, A, B1, B2, B);
+                _ -> mime_decode_list(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B:6>>)
             end;
-        _ -> mime_decode_list_after_eq(Cs, A, B1, B2, B3)
+        _ -> mime_decode_list_after_eq(ModeOffset, Cs, A, B1, B2, B3)
     end;
-mime_decode_list_after_eq([], A, B1, B2, eq) ->
+mime_decode_list_after_eq(_ModeOffset, [], A, B1, B2, eq) ->
     <<A/bits,B1:6,(B2 bsr 4):2>>;
-mime_decode_list_after_eq([], A, B1, B2, B3) ->
+mime_decode_list_after_eq(_ModeOffset, [], A, B1, B2, B3) ->
     <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>.
 
-mime_decode_binary(<<0:8, Cs/bits>>, A) ->
-    mime_decode_binary(Cs, A);
-mime_decode_binary(<<C1:8, Cs/bits>>, A) ->
-    case b64d(C1) of
-        B1 when is_integer(B1) -> mime_decode_binary(Cs, A, B1);
-        _ -> mime_decode_binary(Cs, A)  % eq is padding
+mime_decode_binary(ModeOffset, <<C1:8, Cs/bits>>, A) ->
+    case b64d(C1, ModeOffset) of
+        B1 when is_integer(B1) -> mime_decode_binary(ModeOffset, Cs, A, B1);
+        _ -> mime_decode_binary(ModeOffset, Cs, A)  % eq is padding
     end;
-mime_decode_binary(<<>>, A) ->
+mime_decode_binary(_ModeOffset, <<>>, A) ->
     A.
 
-mime_decode_binary(<<0:8, Cs/bits>>, A, B1) ->
-    mime_decode_binary(Cs, A, B1);
-mime_decode_binary(<<C2:8, Cs/bits>>, A, B1) ->
-    case b64d(C2) of
+mime_decode_binary(ModeOffset, <<C2:8, Cs/bits>>, A, B1) ->
+    case b64d(C2, ModeOffset) of
         B2 when is_integer(B2) ->
-            mime_decode_binary(Cs, A, B1, B2);
-        _ -> mime_decode_binary(Cs, A, B1) % eq is padding
+            mime_decode_binary(ModeOffset, Cs, A, B1, B2);
+        _ -> mime_decode_binary(ModeOffset, Cs, A, B1) % eq is padding
     end.
 
-mime_decode_binary(<<0:8, Cs/bits>>, A, B1, B2) ->
-    mime_decode_binary(Cs, A, B1, B2);
-mime_decode_binary(<<C3:8, Cs/bits>>, A, B1, B2) ->
-    case b64d(C3) of
+mime_decode_binary(ModeOffset, <<C3:8, Cs/bits>>, A, B1, B2) ->
+    case b64d(C3, ModeOffset) of
         B3 when is_integer(B3) ->
-            mime_decode_binary(Cs, A, B1, B2, B3);
+            mime_decode_binary(ModeOffset, Cs, A, B1, B2, B3);
         eq=B3 ->
-            mime_decode_binary_after_eq(Cs, A, B1, B2, B3);
-        _ -> mime_decode_binary(Cs, A, B1, B2)
+            mime_decode_binary_after_eq(ModeOffset, Cs, A, B1, B2, B3);
+        _ -> mime_decode_binary(ModeOffset, Cs, A, B1, B2)
     end.
 
-mime_decode_binary(<<0:8, Cs/bits>>, A, B1, B2, B3) ->
-    mime_decode_binary(Cs, A, B1, B2, B3);
-mime_decode_binary(<<C4:8, Cs/bits>>, A, B1, B2, B3) ->
-    case b64d(C4) of
+mime_decode_binary(ModeOffset, <<C4:8, Cs/bits>>, A, B1, B2, B3) ->
+    case b64d(C4, ModeOffset) of
         B4 when is_integer(B4) ->
-            mime_decode_binary(Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>);
+            mime_decode_binary(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>);
         eq ->
-            mime_decode_binary_after_eq(Cs, A, B1, B2, B3);
-        _ -> mime_decode_binary(Cs, A, B1, B2, B3)
+            mime_decode_binary_after_eq(ModeOffset, Cs, A, B1, B2, B3);
+        _ -> mime_decode_binary(ModeOffset, Cs, A, B1, B2, B3)
     end.
 
-mime_decode_binary_after_eq(<<0:8, Cs/bits>>, A, B1, B2, B3) ->
-    mime_decode_binary_after_eq(Cs, A, B1, B2, B3);
-mime_decode_binary_after_eq(<<C:8, Cs/bits>>, A, B1, B2, B3) ->
-    case b64d(C) of
+mime_decode_binary_after_eq(ModeOffset, <<C:8, Cs/bits>>, A, B1, B2, B3) ->
+    case b64d(C, ModeOffset) of
         B when is_integer(B) ->
             %% More valid data, skip the eq as invalid
             case B3 of
-                eq -> mime_decode_binary(Cs, A, B1, B2, B);
-                _ -> mime_decode_binary(Cs, <<A/bits,B1:6,B2:6,B3:6,B:6>>)
+                eq -> mime_decode_binary(ModeOffset, Cs, A, B1, B2, B);
+                _ -> mime_decode_binary(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B:6>>)
             end;
-        _ -> mime_decode_binary_after_eq(Cs, A, B1, B2, B3)
+        _ -> mime_decode_binary_after_eq(ModeOffset, Cs, A, B1, B2, B3)
     end;
-mime_decode_binary_after_eq(<<>>, A, B1, B2, eq) ->
+mime_decode_binary_after_eq(_ModeOffset, <<>>, A, B1, B2, eq) ->
     <<A/bits,B1:6,(B2 bsr 4):2>>;
-mime_decode_binary_after_eq(<<>>, A, B1, B2, B3) ->
+mime_decode_binary_after_eq(_ModeOffset, <<>>, A, B1, B2, B3) ->
     <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>.
 
-mime_decode_list_to_string([0 | Cs]) ->
-    mime_decode_list_to_string(Cs);
-mime_decode_list_to_string([C1 | Cs]) ->
-    case b64d(C1) of
-        B1 when is_integer(B1) -> mime_decode_list_to_string(Cs, B1);
-        _ -> mime_decode_list_to_string(Cs) % eq is padding
+mime_decode_list_to_string(ModeOffset, [C1 | Cs]) ->
+    case b64d(C1, ModeOffset) of
+        B1 when is_integer(B1) -> mime_decode_list_to_string(ModeOffset, Cs, B1);
+        _ -> mime_decode_list_to_string(ModeOffset, Cs) % eq is padding
     end;
-mime_decode_list_to_string([]) ->
+mime_decode_list_to_string(_ModeOffset, []) ->
     [].
 
-mime_decode_list_to_string([0 | Cs], B1) ->
-    mime_decode_list_to_string(Cs, B1);
-mime_decode_list_to_string([C2 | Cs], B1) ->
-    case b64d(C2) of
+mime_decode_list_to_string(ModeOffset, [C2 | Cs], B1) ->
+    case b64d(C2, ModeOffset) of
         B2 when is_integer(B2) ->
-            mime_decode_list_to_string(Cs, B1, B2);
-        _ -> mime_decode_list_to_string(Cs, B1) % eq is padding
+            mime_decode_list_to_string(ModeOffset, Cs, B1, B2);
+        _ -> mime_decode_list_to_string(ModeOffset, Cs, B1) % eq is padding
     end.
 
-mime_decode_list_to_string([0 | Cs], B1, B2) ->
-    mime_decode_list_to_string(Cs, B1, B2);
-mime_decode_list_to_string([C3 | Cs], B1, B2) ->
-    case b64d(C3) of
+mime_decode_list_to_string(ModeOffset, [C3 | Cs], B1, B2) ->
+    case b64d(C3, ModeOffset) of
         B3 when is_integer(B3) ->
-            mime_decode_list_to_string(Cs, B1, B2, B3);
-        eq=B3 -> mime_decode_list_to_string_after_eq(Cs, B1, B2, B3);
-        _ -> mime_decode_list_to_string(Cs, B1, B2)
+            mime_decode_list_to_string(ModeOffset, Cs, B1, B2, B3);
+        eq=B3 -> mime_decode_list_to_string_after_eq(ModeOffset, Cs, B1, B2, B3);
+        _ -> mime_decode_list_to_string(ModeOffset, Cs, B1, B2)
     end.
 
-mime_decode_list_to_string([0 | Cs], B1, B2, B3) ->
-    mime_decode_list_to_string(Cs, B1, B2, B3);
-mime_decode_list_to_string([C4 | Cs], B1, B2, B3) ->
-    case b64d(C4) of
+mime_decode_list_to_string(ModeOffset, [C4 | Cs], B1, B2, B3) ->
+    case b64d(C4, ModeOffset) of
         B4 when is_integer(B4) ->
             Bits4x6 = (B1 bsl 18) bor (B2 bsl 12) bor (B3 bsl 6) bor B4,
             Octet1 = Bits4x6 bsr 16,
             Octet2 = (Bits4x6 bsr 8) band 16#ff,
             Octet3 = Bits4x6 band 16#ff,
-            [Octet1, Octet2, Octet3 | mime_decode_list_to_string(Cs)];
+            [Octet1, Octet2, Octet3 | mime_decode_list_to_string(ModeOffset, Cs)];
         eq ->
-            mime_decode_list_to_string_after_eq(Cs, B1, B2, B3);
-        _ -> mime_decode_list_to_string(Cs, B1, B2, B3)
+            mime_decode_list_to_string_after_eq(ModeOffset, Cs, B1, B2, B3);
+        _ -> mime_decode_list_to_string(ModeOffset, Cs, B1, B2, B3)
     end.
 
-mime_decode_list_to_string_after_eq([0 | Cs], B1, B2, B3) ->
-    mime_decode_list_to_string_after_eq(Cs, B1, B2, B3);
-mime_decode_list_to_string_after_eq([C | Cs], B1, B2, B3) ->
-    case b64d(C) of
+mime_decode_list_to_string_after_eq(ModeOffset, [C | Cs], B1, B2, B3) ->
+    case b64d(C, ModeOffset) of
         B when is_integer(B) ->
             %% More valid data, skip the eq as invalid
             case B3 of
-                eq -> mime_decode_list_to_string(Cs, B1, B2, B);
+                eq -> mime_decode_list_to_string(ModeOffset, Cs, B1, B2, B);
                 _ ->
                     Bits4x6 = (B1 bsl 18) bor (B2 bsl 12) bor (B3 bsl 6) bor B,
                     Octet1 = Bits4x6 bsr 16,
                     Octet2 = (Bits4x6 bsr 8) band 16#ff,
                     Octet3 = Bits4x6 band 16#ff,
-                    [Octet1, Octet2, Octet3 | mime_decode_list_to_string(Cs)]
+                    [Octet1, Octet2, Octet3 | mime_decode_list_to_string(ModeOffset, Cs)]
             end;
-        _ -> mime_decode_list_to_string_after_eq(Cs, B1, B2, B3)
+        _ -> mime_decode_list_to_string_after_eq(ModeOffset, Cs, B1, B2, B3)
     end;
-mime_decode_list_to_string_after_eq([], B1, B2, eq) ->
+mime_decode_list_to_string_after_eq(_ModeOffset, [], B1, B2, eq) ->
     binary_to_list(<<B1:6,(B2 bsr 4):2>>);
-mime_decode_list_to_string_after_eq([], B1, B2, B3) ->
+mime_decode_list_to_string_after_eq(_ModeOffset, [], B1, B2, B3) ->
     binary_to_list(<<B1:6,B2:6,(B3 bsr 2):4>>).
 
-decode_list([C1 | Cs], A) ->
-    case b64d(C1) of
-        ws -> decode_list(Cs, A);
-        B1 -> decode_list(Cs, A, B1)
+decode_list(ModeOffset, [C1 | Cs], A) ->
+    case b64d(C1, ModeOffset) of
+        ws -> decode_list(ModeOffset, Cs, A);
+        B1 -> decode_list(ModeOffset, Cs, A, B1)
     end;
-decode_list([], A) ->
+decode_list(_ModeOffset, [], A) ->
     A.
 
-decode_list([C2 | Cs], A, B1) ->
-    case b64d(C2) of
-        ws -> decode_list(Cs, A, B1);
-        B2 -> decode_list(Cs, A, B1, B2)
+decode_list(ModeOffset, [C2 | Cs], A, B1) ->
+    case b64d(C2, ModeOffset) of
+        ws -> decode_list(ModeOffset, Cs, A, B1);
+        B2 -> decode_list(ModeOffset, Cs, A, B1, B2)
     end.
 
-decode_list([C3 | Cs], A, B1, B2) ->
-    case b64d(C3) of
-        ws -> decode_list(Cs, A, B1, B2);
-        B3 -> decode_list(Cs, A, B1, B2, B3)
+decode_list(ModeOffset, [C3 | Cs], A, B1, B2) ->
+    case b64d(C3, ModeOffset) of
+        ws -> decode_list(ModeOffset, Cs, A, B1, B2);
+        B3 -> decode_list(ModeOffset, Cs, A, B1, B2, B3)
     end.
 
-decode_list([C4 | Cs], A, B1, B2, B3) ->
-    case b64d(C4) of
-        ws                -> decode_list(Cs, A, B1, B2, B3);
-        eq when B3 =:= eq -> only_ws(Cs, <<A/bits,B1:6,(B2 bsr 4):2>>);
-        eq                -> only_ws(Cs, <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>);
-        B4                -> decode_list(Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>)
+decode_list(ModeOffset, [C4 | Cs], A, B1, B2, B3) ->
+    case b64d(C4, ModeOffset) of
+        ws                -> decode_list(ModeOffset, Cs, A, B1, B2, B3);
+        eq when B3 =:= eq -> only_ws(ModeOffset, Cs, <<A/bits,B1:6,(B2 bsr 4):2>>);
+        eq                -> only_ws(ModeOffset, Cs, <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>);
+        B4                -> decode_list(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>)
     end.
 
-decode_binary(<<C1:8, C2:8, C3:8, C4:8, Cs/bits>>, A) ->
-    case {b64d(C1), b64d(C2), b64d(C3), b64d(C4)} of
+decode_binary(ModeOffset, <<C1:8, C2:8, C3:8, C4:8, Cs/bits>>, A) ->
+    case {b64d(C1, ModeOffset), b64d(C2, ModeOffset), b64d(C3, ModeOffset), b64d(C4, ModeOffset)} of
         {B1, B2, B3, B4} when is_integer(B1), is_integer(B2),
                               is_integer(B3), is_integer(B4) ->
-            decode_binary(Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>);
+            decode_binary(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>);
         {B1, B2, B3, B4} ->
-            dec_bin(Cs, B1, B2, B3, B4, A)
+            dec_bin(ModeOffset, Cs, B1, B2, B3, B4, A)
     end;
-decode_binary(<<>>, A) ->
+decode_binary(_ModeOffset, <<>>, A) ->
     A;
-decode_binary(<<C1:8, Cs/bits>>, A) ->
-    case b64d(C1) of
-        ws -> decode_binary(Cs, A);
-        B1 -> decode_binary(Cs, A, B1)
+decode_binary(ModeOffset, <<C1:8, Cs/bits>>, A) ->
+    case b64d(C1, ModeOffset) of
+        ws -> decode_binary(ModeOffset, Cs, A);
+        B1 -> decode_binary(ModeOffset, Cs, A, B1)
     end.
 
-dec_bin(Cs, ws, B2, B3, B4, A) ->
-    dec_bin(Cs, B2, B3, B4, A);
-dec_bin(Cs, B1, ws, B3, B4, A) ->
-    dec_bin(Cs, B1, B3, B4, A);
-dec_bin(Cs, B1, B2, ws, B4, A) ->
-    dec_bin(Cs, B1, B2, B4, A);
-dec_bin(Cs, B1, B2, B3, B4, A) ->
+dec_bin(ModeOffset, Cs, ws, B2, B3, B4, A) ->
+    dec_bin(ModeOffset, Cs, B2, B3, B4, A);
+dec_bin(ModeOffset, Cs, B1, ws, B3, B4, A) ->
+    dec_bin(ModeOffset, Cs, B1, B3, B4, A);
+dec_bin(ModeOffset, Cs, B1, B2, ws, B4, A) ->
+    dec_bin(ModeOffset, Cs, B1, B2, B4, A);
+dec_bin(ModeOffset, Cs, B1, B2, B3, B4, A) ->
     case B4 of
-        ws                -> decode_binary(Cs, A, B1, B2, B3);
-        eq when B3 =:= eq -> only_ws_binary(Cs, <<A/bits,B1:6,(B2 bsr 4):2>>);
-        eq                -> only_ws_binary(Cs, <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>);
-        B4                -> decode_binary(Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>)
+        ws                -> decode_binary(ModeOffset, Cs, A, B1, B2, B3);
+        eq when B3 =:= eq -> only_ws_binary(ModeOffset, Cs, <<A/bits,B1:6,(B2 bsr 4):2>>);
+        eq                -> only_ws_binary(ModeOffset, Cs, <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>);
+        B4                -> decode_binary(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>)
     end.
 
-dec_bin(Cs, ws, B2, B3, A) ->
-    dec_bin(Cs, B2, B3, A);
-dec_bin(Cs, B1, ws, B3, A) ->
-    dec_bin(Cs, B1, B3, A);
-dec_bin(Cs, B1, B2, ws, A) ->
-    dec_bin(Cs, B1, B2, A);
-dec_bin(Cs, B1, B2, B3, A) ->
-    decode_binary(Cs, A, B1, B2, B3).
-
-dec_bin(Cs, ws, B2, A) ->
-    dec_bin(Cs, B2, A);
-dec_bin(Cs, B1, ws, A) ->
-    dec_bin(Cs, B1, A);
-dec_bin(Cs, B1, B2, A) ->
-    decode_binary(Cs, A, B1, B2).
-
-dec_bin(Cs, ws, A) ->
-    decode_binary(Cs, A);
-dec_bin(Cs, B1, A) ->
-    decode_binary(Cs, A, B1).
-
-decode_binary(<<C2:8, Cs/bits>>, A, B1) ->
-    case b64d(C2) of
-        ws -> decode_binary(Cs, A, B1);
-        B2 -> decode_binary(Cs, A, B1, B2)
+dec_bin(ModeOffset, Cs, ws, B2, B3, A) ->
+    dec_bin(ModeOffset, Cs, B2, B3, A);
+dec_bin(ModeOffset, Cs, B1, ws, B3, A) ->
+    dec_bin(ModeOffset, Cs, B1, B3, A);
+dec_bin(ModeOffset, Cs, B1, B2, ws, A) ->
+    dec_bin(ModeOffset, Cs, B1, B2, A);
+dec_bin(ModeOffset, Cs, B1, B2, B3, A) ->
+    decode_binary(ModeOffset, Cs, A, B1, B2, B3).
+
+dec_bin(ModeOffset, Cs, ws, B2, A) ->
+    dec_bin(ModeOffset, Cs, B2, A);
+dec_bin(ModeOffset, Cs, B1, ws, A) ->
+    dec_bin(ModeOffset, Cs, B1, A);
+dec_bin(ModeOffset, Cs, B1, B2, A) ->
+    decode_binary(ModeOffset, Cs, A, B1, B2).
+
+dec_bin(ModeOffset, Cs, ws, A) ->
+    decode_binary(ModeOffset, Cs, A);
+dec_bin(ModeOffset, Cs, B1, A) ->
+    decode_binary(ModeOffset, Cs, A, B1).
+
+decode_binary(ModeOffset, <<C2:8, Cs/bits>>, A, B1) ->
+    case b64d(C2, ModeOffset) of
+        ws -> decode_binary(ModeOffset, Cs, A, B1);
+        B2 -> decode_binary(ModeOffset, Cs, A, B1, B2)
     end.
 
-decode_binary(<<C3:8, Cs/bits>>, A, B1, B2) ->
-    case b64d(C3) of
-        ws -> decode_binary(Cs, A, B1, B2);
-        B3 -> decode_binary(Cs, A, B1, B2, B3)
+decode_binary(ModeOffset, <<C3:8, Cs/bits>>, A, B1, B2) ->
+    case b64d(C3, ModeOffset) of
+        ws -> decode_binary(ModeOffset, Cs, A, B1, B2);
+        B3 -> decode_binary(ModeOffset, Cs, A, B1, B2, B3)
     end.
 
-decode_binary(<<C4:8, Cs/bits>>, A, B1, B2, B3) ->
-    case b64d(C4) of
-        ws                -> decode_binary(Cs, A, B1, B2, B3);
-        eq when B3 =:= eq -> only_ws_binary(Cs, <<A/bits,B1:6,(B2 bsr 4):2>>);
-        eq                -> only_ws_binary(Cs, <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>);
-        B4                -> decode_binary(Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>)
+decode_binary(ModeOffset, <<C4:8, Cs/bits>>, A, B1, B2, B3) ->
+    case b64d(C4, ModeOffset) of
+        ws                -> decode_binary(ModeOffset, Cs, A, B1, B2, B3);
+        eq when B3 =:= eq -> only_ws_binary(ModeOffset, Cs, <<A/bits,B1:6,(B2 bsr 4):2>>);
+        eq                -> only_ws_binary(ModeOffset, Cs, <<A/bits,B1:6,B2:6,(B3 bsr 2):4>>);
+        B4                -> decode_binary(ModeOffset, Cs, <<A/bits,B1:6,B2:6,B3:6,B4:6>>)
     end.
 
-only_ws_binary(<<>>, A) ->
+only_ws_binary(_ModeOffset, <<>>, A) ->
     A;
-only_ws_binary(<<C:8, Cs/bits>>, A) ->
-    case b64d(C) of
-        ws -> only_ws_binary(Cs, A)
+only_ws_binary(ModeOffset, <<C:8, Cs/bits>>, A) ->
+    case b64d(C, ModeOffset) of
+        ws -> only_ws_binary(ModeOffset, Cs, A)
     end.
 
-decode_list_to_string([C1 | Cs]) ->
-    case b64d(C1) of
-        ws -> decode_list_to_string(Cs);
-        B1 -> decode_list_to_string(Cs, B1)
+decode_list_to_string(ModeOffset, [C1 | Cs]) ->
+    case b64d(C1, ModeOffset) of
+        ws -> decode_list_to_string(ModeOffset, Cs);
+        B1 -> decode_list_to_string(ModeOffset, Cs, B1)
     end;
-decode_list_to_string([]) ->
+decode_list_to_string(_ModeOffset, []) ->
     [].
 
-decode_list_to_string([C2 | Cs], B1) ->
-    case b64d(C2) of
-        ws -> decode_list_to_string(Cs, B1);
-        B2 -> decode_list_to_string(Cs, B1, B2)
+decode_list_to_string(ModeOffset, [C2 | Cs], B1) ->
+    case b64d(C2, ModeOffset) of
+        ws -> decode_list_to_string(ModeOffset, Cs, B1);
+        B2 -> decode_list_to_string(ModeOffset, Cs, B1, B2)
     end.
 
-decode_list_to_string([C3 | Cs], B1, B2) ->
-    case b64d(C3) of
-        ws -> decode_list_to_string(Cs, B1, B2);
-        B3 -> decode_list_to_string(Cs, B1, B2, B3)
+decode_list_to_string(ModeOffset, [C3 | Cs], B1, B2) ->
+    case b64d(C3, ModeOffset) of
+        ws -> decode_list_to_string(ModeOffset, Cs, B1, B2);
+        B3 -> decode_list_to_string(ModeOffset, Cs, B1, B2, B3)
     end.
 
-decode_list_to_string([C4 | Cs], B1, B2, B3) ->
-    case b64d(C4) of
+decode_list_to_string(ModeOffset, [C4 | Cs], B1, B2, B3) ->
+    case b64d(C4, ModeOffset) of
         ws ->
-            decode_list_to_string(Cs, B1, B2, B3);
+            decode_list_to_string(ModeOffset, Cs, B1, B2, B3);
         eq when B3 =:= eq ->
-            only_ws(Cs, binary_to_list(<<B1:6,(B2 bsr 4):2>>));
+            only_ws(ModeOffset, Cs, binary_to_list(<<B1:6,(B2 bsr 4):2>>));
         eq ->
-            only_ws(Cs, binary_to_list(<<B1:6,B2:6,(B3 bsr 2):4>>));
+            only_ws(ModeOffset, Cs, binary_to_list(<<B1:6,B2:6,(B3 bsr 2):4>>));
         B4 ->
             Bits4x6 = (B1 bsl 18) bor (B2 bsl 12) bor (B3 bsl 6) bor B4,
             Octet1 = Bits4x6 bsr 16,
             Octet2 = (Bits4x6 bsr 8) band 16#ff,
             Octet3 = Bits4x6 band 16#ff,
-            [Octet1, Octet2, Octet3 | decode_list_to_string(Cs)]
+            [Octet1, Octet2, Octet3 | decode_list_to_string(ModeOffset, Cs)]
     end.
 
-only_ws([], A) ->
+only_ws(_ModeOffset, [], A) ->
     A;
-only_ws([C | Cs], A) ->
-    case b64d(C) of
-        ws -> only_ws(Cs, A)
+only_ws(ModeOffset, [C | Cs], A) ->
+    case b64d(C, ModeOffset) of
+        ws -> only_ws(ModeOffset, Cs, A)
     end.
 
 %%%========================================================================
@@ -493,14 +521,19 @@ only_ws([C | Cs], A) ->
 %%%========================================================================
 
 %% accessors 
--compile({inline, [{b64d, 1}]}).
-%% One-based decode map.
-b64d(X) ->
-    element(X,
-            {bad,bad,bad,bad,bad,bad,bad,bad,ws,ws,bad,bad,ws,bad,bad, %1-15
+
+get_decoding_offset(standard) -> 1;
+get_decoding_offset(urlsafe) -> 257.
+
+-compile({inline, [{b64d, 2}]}).
+b64d(X, Off) ->
+    element(X + Off,
+            {
+	     %% standard base64 alphabet (RFC 4648 Section 4)
+	     bad,bad,bad,bad,bad,bad,bad,bad,bad,ws,ws,bad,bad,ws,bad,bad, %0-15
              bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad, %16-31
              ws,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,62,bad,bad,bad,63, %32-47
-             52,53,54,55,56,57,58,59,60,61,bad,bad,bad,eq,bad,bad, %48-63
+             52,53,54,55,56,57,58,59,60,61,bad,bad,bad,eq,bad,bad, %48-61
              bad,0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,
              15,16,17,18,19,20,21,22,23,24,25,bad,bad,bad,bad,bad,
              bad,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,
@@ -512,13 +545,44 @@ b64d(X) ->
              bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
              bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
              bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+
+	     %% alternative base64url alphabet (RFC 4648 Section 5)
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,ws,ws,bad,bad,ws,bad,bad, %0-15
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad, %16-31
+             ws,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,62,bad,bad, %32-47
+             52,53,54,55,56,57,58,59,60,61,bad,bad,bad,eq,bad,bad, %48-61
+             bad,0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,
+             15,16,17,18,19,20,21,22,23,24,25,bad,bad,bad,bad,63,
+             bad,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,
+             41,42,43,44,45,46,47,48,49,50,51,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
+             bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,
              bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad,bad}).
 
--compile({inline, [{b64e, 1}]}).
-b64e(X) ->
-    element(X+1,
-	    {$A, $B, $C, $D, $E, $F, $G, $H, $I, $J, $K, $L, $M, $N,
+get_encoding_offset(standard) -> 1;
+get_encoding_offset(urlsafe) -> 65.
+
+-compile({inline, [{b64e, 2}]}).
+b64e(X, Off) ->
+    element(X + Off,
+	    {
+	     %% standard base64 alphabet (RFC 4648 Section 4)
+	     $A, $B, $C, $D, $E, $F, $G, $H, $I, $J, $K, $L, $M, $N,
+	     $O, $P, $Q, $R, $S, $T, $U, $V, $W, $X, $Y, $Z,
+	     $a, $b, $c, $d, $e, $f, $g, $h, $i, $j, $k, $l, $m, $n,
+	     $o, $p, $q, $r, $s, $t, $u, $v, $w, $x, $y, $z,
+	     $0, $1, $2, $3, $4, $5, $6, $7, $8, $9, $+, $/,
+
+	     %% alternative base64url alphabet (RFC 4648 Section 5)
+	     $A, $B, $C, $D, $E, $F, $G, $H, $I, $J, $K, $L, $M, $N,
 	     $O, $P, $Q, $R, $S, $T, $U, $V, $W, $X, $Y, $Z,
 	     $a, $b, $c, $d, $e, $f, $g, $h, $i, $j, $k, $l, $m, $n,
 	     $o, $p, $q, $r, $s, $t, $u, $v, $w, $x, $y, $z,
-	     $0, $1, $2, $3, $4, $5, $6, $7, $8, $9, $+, $/}).
+	     $0, $1, $2, $3, $4, $5, $6, $7, $8, $9, $-, $_}).
+
diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl
index 1fc4c3fc0e..d1625108bd 100644
--- a/lib/stdlib/test/base64_SUITE.erl
+++ b/lib/stdlib/test/base64_SUITE.erl
@@ -26,9 +26,11 @@
 -export([all/0, suite/0, groups/0, group/1]).
 
 %% Test cases must be exported.
--export([base64_encode/1, base64_decode/1, base64_otp_5635/1,
-	 base64_otp_6279/1, big/1, illegal/1, mime_decode/1,
-	 mime_decode_to_string/1,
+-export([base64_encode/1, base64_encode_modes/1,
+	 base64_decode/1, base64_decode_modes/1,
+	 base64_otp_5635/1, base64_otp_6279/1, big/1, illegal/1,
+	 mime_decode/1, mime_decode_modes/1,
+	 mime_decode_to_string/1, mime_decode_to_string_modes/1,
 	 roundtrip_1/1, roundtrip_2/1, roundtrip_3/1, roundtrip_4/1]).
 
 %%-------------------------------------------------------------------------
@@ -40,8 +42,11 @@ suite() ->
      {timetrap,{minutes,4}}].
 
 all() ->
-    [base64_encode, base64_decode, base64_otp_5635,
-     base64_otp_6279, big, illegal, mime_decode, mime_decode_to_string,
+    [base64_encode, base64_encode_modes,
+     base64_decode, base64_decode_modes,
+     base64_otp_5635, base64_otp_6279, big, illegal,
+     mime_decode, mime_decode_modes,
+     mime_decode_to_string, mime_decode_to_string_modes,
      {group, roundtrip}].
 
 groups() ->
@@ -67,6 +72,20 @@ base64_encode(Config) when is_list(Config) ->
     "MDEyMzQ1Njc4OSFAIzBeJiooKTs6PD4sLiBbXXt9" =
 	base64:encode_to_string(<<"0123456789!@#0^&*();:<>,. []{}">>),
     ok.
+
+%%-------------------------------------------------------------------------
+%% Test base64:encode/2.
+base64_encode_modes(Config) when is_list(Config) ->
+    Data = <<23, 234, 63, 163, 239, 129, 253, 175, 171>>,
+
+    <<"F+o/o++B/a+r">> = base64:encode(Data, standard),
+    <<"F-o_o--B_a-r">> = base64:encode(Data, urlsafe),
+
+    "F+o/o++B/a+r" = base64:encode_to_string(Data, standard),
+    "F-o_o--B_a-r" = base64:encode_to_string(Data, urlsafe),
+
+    ok.
+
 %%-------------------------------------------------------------------------
 %% Test base64:decode/1.
 base64_decode(Config) when is_list(Config) ->
@@ -91,6 +110,24 @@ base64_decode(Config) when is_list(Config) ->
 	base64:decode_to_string(
 	  <<"MDEy MzQ1Njc4 \tOSFAIzBeJ \niooKTs6 PD4sLi \r\nBbXXt9">>),
     ok.
+
+%%-------------------------------------------------------------------------
+%% Test base64:decode/2.
+base64_decode_modes(Config) when is_list(Config) ->
+    DataBin = <<23, 234, 63, 163, 239, 129, 253, 175, 171>>,
+    DataStr = [23, 234, 63, 163, 239, 129, 253, 175, 171],
+
+    DataBin = base64:decode("F+o/o++B/a+r", standard),
+    DataBin = base64:decode("F-o_o--B_a-r", urlsafe),
+    {'EXIT', _} = catch base64:decode("F-o_o--B_a-r", standard),
+    {'EXIT', _} = catch base64:decode("F+o/o++B/a+r", urlsafe),
+
+    DataStr = base64:decode_to_string("F+o/o++B/a+r", standard),
+    DataStr = base64:decode_to_string("F-o_o--B_a-r", urlsafe),
+    {'EXIT', _} = catch base64:decode_to_string("F-o_o--B_a-r", standard),
+    {'EXIT', _} = catch base64:decode_to_string("F+o/o++B/a+r", urlsafe),
+
+    ok.
 %%-------------------------------------------------------------------------
 %% OTP-5635: Some data doesn't pass through base64:decode/1 correctly.
 base64_otp_5635(Config) when is_list(Config) ->
@@ -171,6 +208,31 @@ mime_decode(Config) when is_list(Config) ->
     <<"o">>   = MimeDecode(<<"bw=\000=">>),
     ok.
 
+%% Test base64:mime_decode/2.
+mime_decode_modes(Config) when is_list(Config) ->
+    MimeDecode = fun (In, Mode) ->
+                                Out = base64:mime_decode(In, Mode),
+                                Out = base64:mime_decode(binary_to_list(In), Mode)
+                 end,
+
+    %% The following all decode to the same data.
+    Data = <<23, 234, 63, 163, 239, 129, 253, 175, 171>>,
+    Data = MimeDecode(<<"F+o/o++B/a+r">>, standard),
+    Data = MimeDecode(<<"F-o_o--B_a-r">>, urlsafe),
+
+    %% The following decodes to different data depending on mode.
+    Base64 = <<"AB+C+D/E/FG-H-I_J_KL">>,
+    %% In standard mode, "-" and "_" are invalid and thus ignored.
+    %% The base64 string to be decoded is equivalent to "AB+C+D/E/FGHIJKL".
+    <<0, 31, 130, 248, 63, 196, 252, 81, 135, 32, 146, 139>> =
+        MimeDecode(Base64, standard),
+    %% In urlsafe mode, "+" and "/" are invalid and thus ignored.
+    %% The base64 string to be decoded is equivalent to "ABCDEFG-H-I_J_KL".
+    <<0, 16, 131, 16, 81, 190, 31, 226, 63, 39, 242, 139>> =
+        MimeDecode(Base64, urlsafe),
+
+    ok.
+
 %%-------------------------------------------------------------------------
 
 %% Repeat of mime_decode() tests
@@ -221,6 +283,32 @@ mime_decode_to_string(Config) when is_list(Config) ->
     "o"   = MimeDecodeToString(<<"bw=\000=">>),
     ok.
 
+
+%% Test base64:mime_decode_to_string/2.
+mime_decode_to_string_modes(Config) when is_list(Config) ->
+    MimeDecode = fun (In, Mode) ->
+                                Out = base64:mime_decode_to_string(In, Mode),
+                                Out = base64:mime_decode_to_string(binary_to_list(In), Mode)
+                 end,
+
+    %% The following all decode to the same data.
+    Data = [23, 234, 63, 163, 239, 129, 253, 175, 171],
+    Data = MimeDecode(<<"F+o/o++B/a+r">>, standard),
+    Data = MimeDecode(<<"F-o_o--B_a-r">>, urlsafe),
+
+    %% The following decodes to different data depending on mode.
+    Base64 = <<"AB+C+D/E/FG-H-I_J_KL">>,
+    %% In standard mode, "-" and "_" are invalid and thus ignored.
+    %% The base64 string to be decoded is equivalent to "AB+C+D/E/FGHIJKL".
+    [0, 31, 130, 248, 63, 196, 252, 81, 135, 32, 146, 139] =
+        MimeDecode(Base64, standard),
+    %% In urlsafe mode, "+" and "/" are invalid and thus ignored.
+    %% The base64 string to be decoded is equivalent to "ABCDEFG-H-I_J_KL".
+    [0, 16, 131, 16, 81, 190, 31, 226, 63, 39, 242, 139] =
+        MimeDecode(Base64, urlsafe),
+
+    ok.
+
 %%-------------------------------------------------------------------------
 
 roundtrip_1(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/base64_property_test_SUITE.erl b/lib/stdlib/test/base64_property_test_SUITE.erl
index 3802b68ce3..0b8d1f69e3 100644
--- a/lib/stdlib/test/base64_property_test_SUITE.erl
+++ b/lib/stdlib/test/base64_property_test_SUITE.erl
@@ -24,18 +24,18 @@
 
 all() ->
     [
-     encode_case,
-     encode_to_string_case,
-     decode_case,
-     decode_malformed_case,
-     decode_noisy_case,
-     decode_to_string_case,
-     decode_to_string_malformed_case,
-     decode_to_string_noisy_case,
-     mime_decode_case,
-     mime_decode_malformed_case,
-     mime_decode_to_string_case,
-     mime_decode_to_string_malformed_case
+     encode_1_case, encode_2_case,
+     encode_to_string_1_case, encode_to_string_2_case,
+     decode_1_case, decode_2_case,
+     decode_1_malformed_case, decode_2_malformed_case,
+     decode_1_noisy_case, decode_2_noisy_case,
+     decode_to_string_1_case, decode_to_string_2_case,
+     decode_to_string_1_malformed_case, decode_to_string_2_malformed_case,
+     decode_to_string_1_noisy_case, decode_to_string_2_noisy_case,
+     mime_decode_1_case, mime_decode_2_case,
+     mime_decode_1_malformed_case, mime_decode_2_malformed_case,
+     mime_decode_to_string_1_case, mime_decode_to_string_2_case,
+     mime_decode_to_string_1_malformed_case, mime_decode_to_string_2_malformed_case
     ].
 
 init_per_suite(Config) ->
@@ -44,41 +44,77 @@ init_per_suite(Config) ->
 end_per_suite(Config) ->
     Config.
 
-encode_case(Config) ->
-    do_proptest(prop_encode, Config).
+encode_1_case(Config) ->
+    do_proptest(prop_encode_1, Config).
 
-encode_to_string_case(Config) ->
-    do_proptest(prop_encode_to_string, Config).
+encode_2_case(Config) ->
+    do_proptest(prop_encode_2, Config).
 
-decode_case(Config) ->
-    do_proptest(prop_decode, Config).
+encode_to_string_1_case(Config) ->
+    do_proptest(prop_encode_to_string_1, Config).
 
-decode_malformed_case(Config) ->
-    do_proptest(prop_decode_malformed, Config).
+encode_to_string_2_case(Config) ->
+    do_proptest(prop_encode_to_string_2, Config).
 
-decode_noisy_case(Config) ->
-    do_proptest(prop_decode_noisy, Config).
+decode_1_case(Config) ->
+    do_proptest(prop_decode_1, Config).
 
-decode_to_string_case(Config) ->
-    do_proptest(prop_decode_to_string, Config).
+decode_2_case(Config) ->
+    do_proptest(prop_decode_2, Config).
 
-decode_to_string_malformed_case(Config) ->
-    do_proptest(prop_decode_to_string_malformed, Config).
+decode_1_malformed_case(Config) ->
+    do_proptest(prop_decode_1_malformed, Config).
 
-decode_to_string_noisy_case(Config) ->
-    do_proptest(prop_decode_to_string_noisy, Config).
+decode_2_malformed_case(Config) ->
+    do_proptest(prop_decode_2_malformed, Config).
 
-mime_decode_case(Config) ->
-    do_proptest(prop_mime_decode, Config).
+decode_1_noisy_case(Config) ->
+    do_proptest(prop_decode_1_noisy, Config).
 
-mime_decode_malformed_case(Config) ->
-    do_proptest(prop_mime_decode_malformed, Config).
+decode_2_noisy_case(Config) ->
+    do_proptest(prop_decode_2_noisy, Config).
 
-mime_decode_to_string_case(Config) ->
-    do_proptest(prop_mime_decode_to_string, Config).
+decode_to_string_1_case(Config) ->
+    do_proptest(prop_decode_to_string_1, Config).
 
-mime_decode_to_string_malformed_case(Config) ->
-    do_proptest(prop_mime_decode_to_string_malformed, Config).
+decode_to_string_2_case(Config) ->
+    do_proptest(prop_decode_to_string_2, Config).
+
+decode_to_string_1_malformed_case(Config) ->
+    do_proptest(prop_decode_to_string_1_malformed, Config).
+
+decode_to_string_2_malformed_case(Config) ->
+    do_proptest(prop_decode_to_string_2_malformed, Config).
+
+decode_to_string_1_noisy_case(Config) ->
+    do_proptest(prop_decode_to_string_1_noisy, Config).
+
+decode_to_string_2_noisy_case(Config) ->
+    do_proptest(prop_decode_to_string_2_noisy, Config).
+
+mime_decode_1_case(Config) ->
+    do_proptest(prop_mime_decode_1, Config).
+
+mime_decode_2_case(Config) ->
+    do_proptest(prop_mime_decode_2, Config).
+
+mime_decode_1_malformed_case(Config) ->
+    do_proptest(prop_mime_decode_1_malformed, Config).
+
+mime_decode_2_malformed_case(Config) ->
+    do_proptest(prop_mime_decode_2_malformed, Config).
+
+mime_decode_to_string_1_case(Config) ->
+    do_proptest(prop_mime_decode_to_string_1, Config).
+
+mime_decode_to_string_2_case(Config) ->
+    do_proptest(prop_mime_decode_to_string_2, Config).
+
+mime_decode_to_string_1_malformed_case(Config) ->
+    do_proptest(prop_mime_decode_to_string_1_malformed, Config).
+
+mime_decode_to_string_2_malformed_case(Config) ->
+    do_proptest(prop_mime_decode_to_string_2_malformed, Config).
 
 do_proptest(Prop, Config) ->
     ct_property_test:quickcheck(
diff --git a/lib/stdlib/test/property_test/base64_prop.erl b/lib/stdlib/test/property_test/base64_prop.erl
index 6ab7e4c68a..44b1811936 100644
--- a/lib/stdlib/test/property_test/base64_prop.erl
+++ b/lib/stdlib/test/property_test/base64_prop.erl
@@ -54,96 +54,200 @@
 %%% Properties %%%
 %%%%%%%%%%%%%%%%%%
 
-prop_encode() ->
+prop_encode_1() ->
     ?FORALL(
         Str,
         oneof([list(byte()), binary()]),
         begin
             Enc = base64:encode(Str),
             Dec = base64:decode(Enc),
-            is_b64_binary(Enc) andalso str_equals(Str, Dec)
+            is_b64_binary(standard, Enc) andalso str_equals(Str, Dec)
         end
     ).
 
-prop_encode_to_string() ->
+prop_encode_2() ->
+    ?FORALL(
+        {Str, Mode},
+        {oneof([list(byte()), binary()]), mode()},
+        begin
+            Enc = base64:encode(Str, Mode),
+            Dec = base64:decode(Enc, Mode),
+            is_b64_binary(Mode, Enc) andalso str_equals(Str, Dec)
+        end
+    ).
+
+prop_encode_to_string_1() ->
     ?FORALL(
         Str,
         oneof([list(byte()), binary()]),
         begin
             Enc = base64:encode_to_string(Str),
             Dec = base64:decode_to_string(Enc),
-            is_b64_string(Enc) andalso str_equals(Str, Dec)
+            is_b64_string(standard, Enc) andalso str_equals(Str, Dec)
+        end
+    ).
+
+prop_encode_to_string_2() ->
+    ?FORALL(
+        {Str, Mode},
+        {oneof([list(byte()), binary()]), mode()},
+        begin
+            Enc = base64:encode_to_string(Str, Mode),
+            Dec = base64:decode_to_string(Enc, Mode),
+            is_b64_string(Mode, Enc) andalso str_equals(Str, Dec)
         end
     ).
 
-prop_decode() ->
+prop_decode_1() ->
     ?FORALL(
         {NormalizedB64, WspedB64},
-        wsped_b64(),
+        wsped_b64(standard),
         begin
             Dec = base64:decode(WspedB64),
             Enc = base64:encode(Dec),
-            is_binary(Dec) andalso b64_equals(NormalizedB64, Enc)
+            is_binary(Dec) andalso b64_equals(standard, NormalizedB64, Enc)
+        end
+    ).
+
+prop_decode_2() ->
+    ?FORALL(
+        {{NormalizedB64, WspedB64}, Mode},
+        ?LET(
+            Mode,
+            mode(),
+            {wsped_b64(Mode), Mode}
+        ),
+        begin
+            Dec = base64:decode(WspedB64, Mode),
+            Enc = base64:encode(Dec, Mode),
+            is_binary(Dec) andalso b64_equals(Mode, NormalizedB64, Enc)
         end
     ).
 
-prop_decode_malformed() ->
-    common_decode_malformed(wsped_b64(), fun base64:decode/1).
+prop_decode_1_malformed() ->
+    common_decode_malformed(fun wsped_b64/1, standard, fun(Data, _) -> base64:decode(Data) end).
+
+prop_decode_2_malformed() ->
+    common_decode_malformed(fun wsped_b64/1, mode(), fun base64:decode/2).
 
-prop_decode_noisy() ->
-    common_decode_noisy(fun base64:decode/1).
+prop_decode_1_noisy() ->
+    common_decode_noisy(standard, fun(Data, _) -> base64:decode(Data) end).
 
-prop_decode_to_string() ->
+prop_decode_2_noisy() ->
+    common_decode_noisy(mode(), fun base64:decode/2).
+
+prop_decode_to_string_1() ->
     ?FORALL(
         {NormalizedB64, WspedB64},
-        wsped_b64(),
+        wsped_b64(standard),
         begin
             Dec = base64:decode_to_string(WspedB64),
             Enc = base64:encode(Dec),
-            is_bytelist(Dec) andalso b64_equals(NormalizedB64, Enc)
+            is_bytelist(Dec) andalso b64_equals(standard, NormalizedB64, Enc)
+        end
+    ).
+
+prop_decode_to_string_2() ->
+    ?FORALL(
+        {{NormalizedB64, WspedB64}, Mode},
+        ?LET(
+            Mode,
+            mode(),
+            {wsped_b64(Mode), Mode}
+        ),
+        begin
+            Dec = base64:decode_to_string(WspedB64, Mode),
+            Enc = base64:encode(Dec, Mode),
+            is_bytelist(Dec) andalso b64_equals(Mode, NormalizedB64, Enc)
         end
     ).
 
-prop_decode_to_string_malformed() ->
-    common_decode_malformed(wsped_b64(), fun base64:decode_to_string/1).
+prop_decode_to_string_1_malformed() ->
+    common_decode_malformed(fun wsped_b64/1, standard, fun(Data, _) -> base64:decode_to_string(Data) end).
+
+prop_decode_to_string_2_malformed() ->
+    common_decode_malformed(fun wsped_b64/1, mode(), fun base64:decode_to_string/2).
+
+prop_decode_to_string_1_noisy() ->
+    common_decode_noisy(standard, fun(Data, _) -> base64:decode_to_string(Data) end).
 
-prop_decode_to_string_noisy() ->
-    common_decode_noisy(fun base64:decode_to_string/1).
+prop_decode_to_string_2_noisy() ->
+    common_decode_noisy(mode(), fun base64:decode_to_string/2).
 
-prop_mime_decode() ->
+prop_mime_decode_1() ->
     ?FORALL(
         {NormalizedB64, NoisyB64},
-        noisy_b64(),
+        noisy_b64(standard),
         begin
             Dec = base64:mime_decode(NoisyB64),
             Enc = base64:encode(Dec),
-            is_binary(Dec) andalso b64_equals(NormalizedB64, Enc)
+            is_binary(Dec) andalso b64_equals(standard, NormalizedB64, Enc)
         end
     ).
 
-prop_mime_decode_malformed() ->
-    common_decode_malformed(noisy_b64(), fun base64:mime_decode/1).
+prop_mime_decode_2() ->
+    ?FORALL(
+        {{NormalizedB64, NoisyB64}, Mode},
+        ?LET(
+            Mode,
+            mode(),
+            {wsped_b64(Mode), Mode}
+        ),
+        begin
+            Dec = base64:mime_decode(NoisyB64, Mode),
+            Enc = base64:encode(Dec, Mode),
+            is_binary(Dec) andalso b64_equals(Mode, NormalizedB64, Enc)
+        end
+    ).
+
+prop_mime_decode_1_malformed() ->
+    common_decode_malformed(fun noisy_b64/1, standard, fun(Data, _) -> base64:mime_decode(Data) end).
 
-prop_mime_decode_to_string() ->
+prop_mime_decode_2_malformed() ->
+    common_decode_malformed(fun noisy_b64/1, mode(), fun base64:mime_decode/2).
+
+prop_mime_decode_to_string_1() ->
     ?FORALL(
         {NormalizedB64, NoisyB64},
-        noisy_b64(),
+        noisy_b64(standard),
         begin
             Dec = base64:mime_decode_to_string(NoisyB64),
             Enc = base64:encode(Dec),
-            is_bytelist(Dec) andalso b64_equals(NormalizedB64, Enc)
+            is_bytelist(Dec) andalso b64_equals(standard, NormalizedB64, Enc)
         end
     ).
 
-prop_mime_decode_to_string_malformed() ->
-    common_decode_malformed(noisy_b64(), fun base64:mime_decode_to_string/1).
+prop_mime_decode_to_string_2() ->
+    ?FORALL(
+        {{NormalizedB64, NoisyB64}, Mode},
+        ?LET(
+            Mode,
+            mode(),
+            {wsped_b64(Mode), Mode}
+        ),
+        begin
+            Dec = base64:mime_decode_to_string(NoisyB64, Mode),
+            Enc = base64:encode(Dec, Mode),
+            is_bytelist(Dec) andalso b64_equals(Mode, NormalizedB64, Enc)
+        end
+    ).
 
-common_decode_noisy(Fn) ->
+prop_mime_decode_to_string_1_malformed() ->
+    common_decode_malformed(fun noisy_b64/1, standard, fun(Data, _) -> base64:mime_decode_to_string(Data) end).
+
+prop_mime_decode_to_string_2_malformed() ->
+    common_decode_malformed(fun noisy_b64/1, mode(), fun base64:mime_decode_to_string/2).
+
+common_decode_noisy(ModeGen, Fn) ->
     ?FORALL(
-        {_, NoisyB64},
-        ?SUCHTHAT({NormalizedB64, NoisyB64}, noisy_b64(), NormalizedB64 =/= NoisyB64),
+        {{_, NoisyB64}, Mode},
+        ?LET(
+            Mode,
+            ModeGen,
+            {?SUCHTHAT({NormalizedB64, NoisyB64}, noisy_b64(Mode), NormalizedB64 =/= NoisyB64), Mode}
+        ),
         try
-            Fn(NoisyB64)
+            Fn(NoisyB64, Mode)
         of
             _ ->
                 false
@@ -153,25 +257,30 @@ common_decode_noisy(Fn) ->
         end
     ).
 
-common_decode_malformed(Gen, Fn) ->
+common_decode_malformed(DataGen, ModeGen, Fn) ->
     ?FORALL(
-        MalformedB64,
+        {MalformedB64, Mode},
         ?LET(
-            {{NormalizedB64, NoisyB64}, Malformings},
-            {
-                Gen,
-                oneof(
-                    [
-                        [b64_char()],
-                        [b64_char(), b64_char()],
-                        [b64_char(), b64_char(), b64_char()]
-                    ]
-                )
-            },
-            {NormalizedB64, insert_noise(NoisyB64, Malformings)}
+            Mode,
+            ModeGen,
+            ?LET(
+                {{NormalizedB64, NoisyB64}, Malformings, InsertFn},
+                {
+                    DataGen(Mode),
+                    oneof(
+                        [
+                            [b64_char(Mode)],
+                            [b64_char(Mode), b64_char(Mode)],
+                            [b64_char(Mode), b64_char(Mode), b64_char(Mode)]
+                        ]
+                    ),
+                    function1(boolean())
+                },
+                {{NormalizedB64, insert_noise(NoisyB64, Malformings, InsertFn)}, Mode}
+            )
         ),
         try
-            Fn(MalformedB64)
+            Fn(MalformedB64, Mode)
         of
             _ ->
                 false
@@ -185,16 +294,20 @@ common_decode_malformed(Gen, Fn) ->
 %%% Generators %%%
 %%%%%%%%%%%%%%%%%%
 
+%% Generate base64 encoding mode.
+mode() ->
+    oneof([standard, urlsafe]).
+
 %% Generate a single character from the base64 alphabet.
-b64_char() ->
-    oneof(b64_chars()).
+b64_char(Mode) ->
+    oneof(b64_chars(Mode)).
 
 %% Generate a string of characters from the base64 alphabet,
 %% including padding if needed.
-b64_string() ->
+b64_string(Mode) ->
     ?LET(
         {L, Filler},
-        {list(b64_char()), b64_char()},
+        {list(b64_char(Mode)), b64_char(Mode)},
         case length(L) rem 4 of
             0 -> L;
             1 -> L ++ [Filler, $=, $=];
@@ -205,43 +318,43 @@ b64_string() ->
 
 %% Generate a binary of characters from the base64 alphabet,
 %% including padding if needed.
-b64_binary() ->
+b64_binary(Mode) ->
     ?LET(
         L,
-        b64_string(),
+        b64_string(Mode),
         list_to_binary(L)
     ).
 
 %% Generate a string or binary of characters from the
 %% base64 alphabet, including padding if needed.
-b64() ->
-    oneof([b64_string(), b64_binary()]).
+b64(Mode) ->
+    oneof([b64_string(Mode), b64_binary(Mode)]).
 
 %% Generate a string or binary of characters from the
 %% base64 alphabet, including padding if needed, with
 %% whitespaces inserted at random indexes.
-wsped_b64() ->
+wsped_b64(Mode) ->
     ?LET(
-        {B64, Wsps},
-        {b64(), list(oneof([$\t, $\r, $\n, $\s]))},
-        {B64, insert_noise(B64, Wsps)}
+        {B64, Wsps, InsertFn},
+        {b64(Mode), list(oneof([$\t, $\r, $\n, $\s])), function1(boolean())},
+        {B64, insert_noise(B64, Wsps, InsertFn)}
     ).
 
 %% Generate a single character outside of the base64 alphabet.
 %% As whitespaces are allowed but ignored in base64, this generator
 %% will produce no whitespaces, either.
-non_b64_char() ->
-    oneof(lists:seq(16#00, 16#FF) -- b64_allowed_chars()).
+non_b64_char(Mode) ->
+    oneof(lists:seq(16#00, 16#FF) -- b64_allowed_chars(Mode)).
 
 %% Generate a string or binary of characters from the
 %% base64 alphabet, including padding if needed, with
 %% whitespaces and non-base64 ("invalid") characters
 %% inserted at random indexes.
-noisy_b64() ->
+noisy_b64(Mode) ->
     ?LET(
-        {{B64, WspedB64}, Noise},
-        {wsped_b64(), non_empty(list(non_b64_char()))},
-        {B64, insert_noise(WspedB64, Noise)}
+        {{B64, WspedB64}, Noise, InsertFn},
+        {wsped_b64(Mode), non_empty(list(non_b64_char(Mode))), function1(boolean())},
+        {B64, insert_noise(WspedB64, Noise, InsertFn)}
     ).
 
 %%%%%%%%%%%%%%%
@@ -252,81 +365,92 @@ noisy_b64() ->
 %% "=" is not included, as it is special in that it
 %% may only appear at the end of a base64 encoded string
 %% for padding.
-b64_chars() ->
+b64_chars_common() ->
     lists:seq($0, $9) ++
     lists:seq($a, $z) ++
-    lists:seq($A, $Z) ++
-    [$+, $/].
+    lists:seq($A, $Z).
+
+b64_chars(standard) ->
+    b64_chars_common() ++ [$+, $/];
+b64_chars(urlsafe) ->
+    b64_chars_common() ++ [$-, $_].
 
 %% In addition to the above, the whitespace characters
 %% HTAB, CR, LF and SP are allowed to appear in a base64
 %% encoded string and should be ignored.
-b64_allowed_chars() ->
-    [$\t, $\r, $\n, $\s | b64_chars()].
+b64_allowed_chars(Mode) ->
+    [$\t, $\r, $\n, $\s | b64_chars(Mode)].
 
 %% Insert the given list of noise characters at random
 %% places into the given base64 string.
-insert_noise(B64, []) ->
+insert_noise(B64, Noise, InsertFn) ->
+    insert_noise(B64, Noise, InsertFn, 0).
+
+insert_noise(B64, [], _, _) ->
     B64;
-insert_noise([], Noise) ->
+insert_noise([], Noise, _, _) ->
     Noise;
-insert_noise(<<>>, Noise) ->
+insert_noise(<<>>, Noise, _, _) ->
     list_to_binary(Noise);
-insert_noise([B|Bs] = B64, [N|Ns] = Noise) ->
-    case rand:uniform(2) of
-        1 ->
-            [B|insert_noise(Bs, Noise)];
-        2 ->
-            [N|insert_noise(B64, Ns)]
+insert_noise([B|Bs] = B64, [N|Ns] = Noise, InsertFn, Idx) ->
+    case InsertFn(Idx) of
+        true ->
+            [B|insert_noise(Bs, Noise, InsertFn, Idx + 1)];
+        false ->
+            [N|insert_noise(B64, Ns, InsertFn, Idx + 1)]
     end;
-insert_noise(<<B, Bs/binary>> = B64, [N|Ns] = Noise) ->
-    case rand:uniform(2) of
-        1 ->
-            <<B, (insert_noise(Bs, Noise))/binary>>;
-        2 ->
-            <<N, (insert_noise(B64, Ns))/binary>>
+insert_noise(<<B, Bs/binary>> = B64, [N|Ns] = Noise, InsertFn, Idx) ->
+    case InsertFn(Idx) of
+        true ->
+            <<B, (insert_noise(Bs, Noise, InsertFn, Idx + 1))/binary>>;
+        false ->
+            <<N, (insert_noise(B64, Ns, InsertFn, Idx + 1))/binary>>
     end.
 
 %% Check if the given character is in the base64 alphabet.
 %% This does not include the padding character "=".
-is_b64_char($+) ->
+is_b64_char(standard, $+) ->
+    true;
+is_b64_char(standard, $/) ->
+    true;
+is_b64_char(urlsafe, $-) ->
     true;
-is_b64_char($/) ->
+is_b64_char(urlsafe, $_) ->
     true;
-is_b64_char(C) when C >= $0, C =< $9 ->
+is_b64_char(_, C) when C >= $0, C =< $9 ->
     true;
-is_b64_char(C) when C >= $A, C =< $Z ->
+is_b64_char(_, C) when C >= $A, C =< $Z ->
     true;
-is_b64_char(C) when C >= $a, C =< $z ->
+is_b64_char(_, C) when C >= $a, C =< $z ->
     true;
-is_b64_char(_) ->
+is_b64_char(_, _) ->
     false.
 
 %% Check if the given argument is a base64 binary,
 %% ie that it consists of quadruplets of characters
 %% from the base64 alphabet, whereas the last quadruplet
 %% may be padded with one or two "="s
-is_b64_binary(B) ->
-    is_b64_binary(B, 0).
+is_b64_binary(Mode, B) ->
+    is_b64_binary(Mode, B, 0).
 
-is_b64_binary(<<>>, N) ->
+is_b64_binary(_, <<>>, N) ->
     N rem 4 =:= 0;
-is_b64_binary(<<$=>>, N) ->
+is_b64_binary(_, <<$=>>, N) ->
     N rem 4 =:= 3;
-is_b64_binary(<<$=, $=>>, N) ->
+is_b64_binary(_, <<$=, $=>>, N) ->
     N rem 4 =:= 2;
-is_b64_binary(<<C, More/binary>>, N) ->
-    case is_b64_char(C) of
+is_b64_binary(Mode, <<C, More/binary>>, N) ->
+    case is_b64_char(Mode, C) of
         true ->
-            is_b64_binary(More, N + 1);
+            is_b64_binary(Mode, More, N + 1);
         false ->
             false
     end.
 
 %% Check if the given argument is a base64 string
 %% (see is_b64_binary/1)
-is_b64_string(S) ->
-    is_b64_binary(list_to_binary(S)).
+is_b64_string(Mode, S) ->
+    is_b64_binary(Mode, list_to_binary(S)).
 
 %% Check if the argument is a list of bytes.
 is_bytelist(L) ->
@@ -349,23 +473,23 @@ str_equals(Str1, Str2) when is_binary(Str1), is_binary(Str2) ->
 %% Assumes that the given arguments are in a normalized form,
 %% ie that they consist only of characters from the base64
 %% alphabet and possible padding ("=").
-b64_equals(L, B) when is_list(L) ->
-    b64_equals(list_to_binary(L), B);
-b64_equals(B, L) when is_list(L) ->
-    b64_equals(B, list_to_binary(L));
-b64_equals(B1, B2) when is_binary(B1), is_binary(B2) ->
-    b64_equals1(B1, B2).
-
-b64_equals1(<<Eq:4/bytes>>, <<Eq:4/bytes>>) ->
-    is_b64_binary(Eq);
-b64_equals1(<<Eq:4/bytes, More1/binary>>, <<Eq:4/bytes, More2/binary>>) ->
-    case lists:all(fun is_b64_char/1, binary_to_list(Eq)) of
+b64_equals(Mode, L, B) when is_list(L) ->
+    b64_equals(Mode, list_to_binary(L), B);
+b64_equals(Mode, B, L) when is_list(L) ->
+    b64_equals(Mode, B, list_to_binary(L));
+b64_equals(Mode, B1, B2) when is_binary(B1), is_binary(B2) ->
+    b64_equals1(Mode, B1, B2).
+
+b64_equals1(Mode, <<Eq:4/bytes>>, <<Eq:4/bytes>>) ->
+    is_b64_binary(Mode, Eq);
+b64_equals1(Mode, <<Eq:4/bytes, More1/binary>>, <<Eq:4/bytes, More2/binary>>) ->
+    case lists:all(fun(C) -> is_b64_char(Mode, C) end, binary_to_list(Eq)) of
         true ->
-            b64_equals1(More1, More2);
+            b64_equals1(Mode, More1, More2);
         false ->
             false
     end;
-b64_equals1(<<Eq, B1, $=, $=>>, <<Eq, B2, $=, $=>>) ->
+b64_equals1(Mode, <<Eq, B1, $=, $=>>, <<Eq, B2, $=, $=>>) ->
     %% If the encoded string ends with "==", there exist multiple
     %% possibilities for the character preceding the "==" as only the
     %% 3rd and 4th bits of the encoded byte represented by that
@@ -374,7 +498,7 @@ b64_equals1(<<Eq, B1, $=, $=>>, <<Eq, B2, $=, $=>>) ->
     %% For example, all of the encoded strings "QQ==", "QR==", ..., "QZ=="
     %% decode to the string "A", since all the bytes represented by Q to Z
     %% are the same in the significant 3rd and 4th bit.
-    case is_b64_char(Eq) of
+    case is_b64_char(Mode, Eq) of
         true ->
             Normalize = fun
                 (C) when C >= $A, C =< $P -> $A;
@@ -383,20 +507,21 @@ b64_equals1(<<Eq, B1, $=, $=>>, <<Eq, B2, $=, $=>>) ->
                 (C) when C >= $g, C =< $v -> $g;
                 (C) when C >= $w, C =< $z -> $w;
                 (C) when C >= $0, C =< $9 -> $w;
-                ($+) -> $w;
-                ($/) -> $w
+                ($+) when Mode =:= standard -> $w;
+                ($-) when Mode =:= urlsafe -> $w;
+                ($/) when Mode =:= standard -> $w;
+                ($_) when Mode =:= urlsafe -> $w
             end,
             Normalize(B1) =:= Normalize(B2);
         false ->
             false
     end;
-b64_equals1(<<Eq:2/bytes, B1, $=>>, <<Eq:2/bytes, B2, $=>>) ->
+b64_equals1(Mode, <<Eq1, Eq2, B1, $=>>, <<Eq1, Eq2, B2, $=>>) ->
     %% Similar to the above, but with the encoded string ending with a
     %% single "=" the 3rd to 6th bits of the encoded byte are significant,
     %% such that, for example, all the encoded strings "QUE=" to "QUH="
     %% decode to the same string "AA".
-    <<Eq1, Eq2>> = Eq,
-    case is_b64_char(Eq1) andalso is_b64_char(Eq2) of
+    case is_b64_char(Mode, Eq1) andalso is_b64_char(Mode, Eq2) of
         true ->
             Normalize = fun
                 (C) when C >= $A, C =< $D -> $A;
@@ -416,14 +541,16 @@ b64_equals1(<<Eq:2/bytes, B1, $=>>, <<Eq:2/bytes, B2, $=>>) ->
                 (C) when C >= $0, C =< $3 -> $0;
                 (C) when C >= $4, C =< $7 -> $4;
                 (C) when C >= $8, C =< $9 -> $8;
-                ($+) -> $8;
-                ($/) -> $8
+                ($+) when Mode =:= standard -> $8;
+                ($-) when Mode =:= urlsafe -> $8;
+                ($/) when Mode =:= standard -> $8;
+                ($_) when Mode =:= urlsafe -> $8
             end,
             Normalize(B1) =:= Normalize(B2);
         false ->
             false
     end;
-b64_equals1(<<>>, <<>>) ->
+b64_equals1(_, <<>>, <<>>) ->
     true;
-b64_equals1(_, _) ->
+b64_equals1(_, _, _) ->
     false.
-- 
2.35.3

openSUSE Build Service is sponsored by