File 0704-dialyzer-Add-test-cases-with-indentation.patch of Package erlang

From 77cbe3b6ced0ca42cf3ec5c8ca0333d9418a0372 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Wed, 17 Apr 2019 13:20:56 +0200
Subject: [PATCH 4/5] dialyzer: Add test cases with indentation

A smallish selection of already existing tests, run with
the indentation option.
---
 .../test/behaviour_SUITE_data/dialyzer_options     |    2 +-
 .../test/callgraph_SUITE_data/dialyzer_options     |    2 +-
 .../test/indent2_SUITE_data/dialyzer_options       |    1 +
 lib/dialyzer/test/indent2_SUITE_data/results/arr   |   15 +
 .../test/indent2_SUITE_data/results/iodata         |   24 +
 .../test/indent2_SUITE_data/results/remote         |   25 +
 lib/dialyzer/test/indent2_SUITE_data/src/arr.erl   |   41 +
 .../test/indent2_SUITE_data/src/iodata.erl         |   41 +
 .../indent2_SUITE_data/src/remote/remotes1.erl     |   61 +
 .../src/remote/some_known_remote.erl               |    5 +
 .../test/indent_SUITE_data/dialyzer_options        |    1 +
 lib/dialyzer/test/indent_SUITE_data/results/abs    |   13 +
 .../test/indent_SUITE_data/results/app_call        |    9 +
 lib/dialyzer/test/indent_SUITE_data/results/arr    |    4 +
 .../indent_SUITE_data/results/blame_contract_range |    8 +
 .../test/indent_SUITE_data/results/bs_fail_constr  |    9 +
 .../indent_SUITE_data/results/callbacks_and_specs  |   23 +
 .../test/indent_SUITE_data/results/contract3       |    3 +
 .../results/contracts_with_subtypes                |  142 +
 .../test/indent_SUITE_data/results/dict_use        |   48 +
 .../test/indent_SUITE_data/results/fun_app         |    7 +
 .../test/indent_SUITE_data/results/fun_app_args    |    5 +
 .../test/indent_SUITE_data/results/guard_update    |    6 +
 .../test/indent_SUITE_data/results/guard_warnings  |  134 +
 .../test/indent_SUITE_data/results/map_galore      |  713 +++++
 lib/dialyzer/test/indent_SUITE_data/results/order  |   23 +
 .../test/indent_SUITE_data/results/queue_use       |   34 +
 lib/dialyzer/test/indent_SUITE_data/results/rec    |   15 +
 .../indent_SUITE_data/results/record_construct     |   11 +
 .../results/record_creation_diffs                  |    4 +
 .../test/indent_SUITE_data/results/record_match    |    4 +
 .../test/indent_SUITE_data/results/record_pat      |    4 +
 .../indent_SUITE_data/results/record_send_test     |    6 +
 .../test/indent_SUITE_data/results/record_test     |    6 +
 .../test/indent_SUITE_data/results/record_update   |    3 +
 .../indent_SUITE_data/results/sample_behaviour     |   23 +
 lib/dialyzer/test/indent_SUITE_data/results/simple |  289 ++
 .../indent_SUITE_data/results/suppress_request     |   11 +
 lib/dialyzer/test/indent_SUITE_data/results/trec   |   10 +
 .../results/whereis_control_flow1                  |    4 +
 lib/dialyzer/test/indent_SUITE_data/src/abs.erl    |   78 +
 .../test/indent_SUITE_data/src/app_call.erl        |   17 +
 .../indent_SUITE_data/src/blame_contract_range.erl |   16 +
 .../test/indent_SUITE_data/src/bs_fail_constr.erl  |   15 +
 .../src/callbacks_and_specs/my_behaviour.erl       |   11 +
 .../callbacks_and_specs/my_callbacks_correct.erl   |   59 +
 .../src/callbacks_and_specs/my_callbacks_wrong.erl |   61 +
 .../test/indent_SUITE_data/src/contract3.erl       |   40 +
 .../src/contracts_with_subtypes.erl                |  300 +++
 .../test/indent_SUITE_data/src/dict_use.erl        |   82 +
 .../test/indent_SUITE_data/src/fun_app.erl         |   41 +
 .../test/indent_SUITE_data/src/fun_app_args.erl    |   12 +
 .../test/indent_SUITE_data/src/guard_update.erl    |   18 +
 .../test/indent_SUITE_data/src/guard_warnings.erl  |  118 +
 .../test/indent_SUITE_data/src/map_galore.erl      | 2800 ++++++++++++++++++++
 lib/dialyzer/test/indent_SUITE_data/src/order.erl  |   56 +
 .../test/indent_SUITE_data/src/queue_use.erl       |   65 +
 .../test/indent_SUITE_data/src/rec/rec_adt.erl     |   22 +
 .../test/indent_SUITE_data/src/rec/rec_use.erl     |   30 +
 .../indent_SUITE_data/src/record_construct.erl     |   21 +
 .../src/record_creation_diffs.erl                  |   11 +
 .../test/indent_SUITE_data/src/record_match.erl    |   17 +
 .../test/indent_SUITE_data/src/record_pat.erl      |   15 +
 .../indent_SUITE_data/src/record_send_test.erl     |   32 +
 .../test/indent_SUITE_data/src/record_test.erl     |   22 +
 .../test/indent_SUITE_data/src/record_update.erl   |   10 +
 .../src/sample_behaviour/sample_behaviour.erl      |   13 +
 .../sample_behaviour/sample_callback_correct.erl   |   32 +
 .../sample_behaviour/sample_callback_correct_2.erl |   38 +
 .../src/sample_behaviour/sample_callback_wrong.erl |   26 +
 .../indent_SUITE_data/src/simple/exact_adt.erl     |   17 +
 .../indent_SUITE_data/src/simple/exact_api.erl     |   60 +
 .../test/indent_SUITE_data/src/simple/is_rec.erl   |   65 +
 .../test/indent_SUITE_data/src/simple/rec_adt.erl  |   28 +
 .../test/indent_SUITE_data/src/simple/rec_api.erl  |  123 +
 .../indent_SUITE_data/src/simple/simple1_adt.erl   |  138 +
 .../indent_SUITE_data/src/simple/simple1_api.erl   |  571 ++++
 .../indent_SUITE_data/src/simple/simple2_api.erl   |  125 +
 .../indent_SUITE_data/src/suppress_request.erl     |   50 +
 lib/dialyzer/test/indent_SUITE_data/src/trec.erl   |   39 +
 .../src/whereis_control_flow1.erl                  |   17 +
 lib/dialyzer/test/map_SUITE_data/dialyzer_options  |    2 +-
 .../test/opaque_SUITE_data/dialyzer_options        |    2 +-
 .../test/options1_SUITE_data/dialyzer_options      |    2 +-
 .../test/options2_SUITE_data/dialyzer_options      |    2 +-
 .../test/overspecs_SUITE_data/dialyzer_options     |    2 +-
 lib/dialyzer/test/r9c_SUITE_data/dialyzer_options  |    2 +-
 lib/dialyzer/test/race_SUITE_data/dialyzer_options |    2 +-
 .../test/small_SUITE_data/dialyzer_options         |    2 +-
 .../test/specdiffs_SUITE_data/dialyzer_options     |    2 +-
 .../test/underspecs_SUITE_data/dialyzer_options    |    2 +-
 .../unmatched_returns_SUITE_data/dialyzer_options  |    2 +-
 lib/dialyzer/test/user_SUITE_data/dialyzer_options |    2 +-
 93 files changed, 7110 insertions(+), 14 deletions(-)
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/dialyzer_options
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/results/arr
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/results/iodata
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/results/remote
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/src/arr.erl
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/src/iodata.erl
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/src/remote/remotes1.erl
 create mode 100644 lib/dialyzer/test/indent2_SUITE_data/src/remote/some_known_remote.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/dialyzer_options
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/abs
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/app_call
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/arr
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/blame_contract_range
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/bs_fail_constr
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/contract3
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/dict_use
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/fun_app
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/fun_app_args
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/guard_update
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/guard_warnings
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/map_galore
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/order
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/queue_use
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/rec
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/record_construct
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/record_creation_diffs
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/record_match
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/record_pat
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/record_send_test
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/record_test
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/record_update
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/simple
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/suppress_request
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/trec
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/results/whereis_control_flow1
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/abs.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/app_call.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/blame_contract_range.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/bs_fail_constr.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_behaviour.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_correct.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/contract3.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/contracts_with_subtypes.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/dict_use.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/fun_app.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/fun_app_args.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/guard_update.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/guard_warnings.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/order.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/queue_use.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/rec/rec_adt.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/rec/rec_use.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/record_construct.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/record_creation_diffs.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/record_match.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/record_pat.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/record_send_test.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/record_test.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/record_update.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_behaviour.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct_2.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_wrong.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/exact_adt.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/exact_api.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/rec_adt.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/rec_api.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_adt.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_api.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/simple/simple2_api.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/suppress_request.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/trec.erl
 create mode 100644 lib/dialyzer/test/indent_SUITE_data/src/whereis_control_flow1.erl

diff --git a/lib/dialyzer/test/behaviour_SUITE_data/dialyzer_options b/lib/dialyzer/test/behaviour_SUITE_data/dialyzer_options
index 365b4798c5..83d4a0ec35 100644
--- a/lib/dialyzer/test/behaviour_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/behaviour_SUITE_data/dialyzer_options
@@ -1,2 +1,2 @@
-{dialyzer_options, []}.
+{dialyzer_options, [{indent_opt, false}]}.
 {time_limit, 5}.
diff --git a/lib/dialyzer/test/callgraph_SUITE_data/dialyzer_options b/lib/dialyzer/test/callgraph_SUITE_data/dialyzer_options
index 50991c9bc5..8413436b67 100644
--- a/lib/dialyzer/test/callgraph_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/callgraph_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, []}.
+{dialyzer_options, [{indent_opt, false}]}.
diff --git a/lib/dialyzer/test/indent2_SUITE_data/dialyzer_options b/lib/dialyzer/test/indent2_SUITE_data/dialyzer_options
new file mode 100644
index 0000000000..ee07090337
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/dialyzer_options
@@ -0,0 +1 @@
+{dialyzer_options, [{warnings, [no_unused, no_return, specdiffs]}]}.
diff --git a/lib/dialyzer/test/indent2_SUITE_data/results/arr b/lib/dialyzer/test/indent2_SUITE_data/results/arr
new file mode 100644
index 0000000000..77e67f0cab
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/results/arr
@@ -0,0 +1,15 @@
+
+arr.erl:14: Type specification arr:test2
+          (array:array(T), non_neg_integer(), T) -> array:array(T) is a supertype of the success typing: arr:test2
+          (array:array(_), pos_integer(), _) -> array:array(_)
+arr.erl:24: Type specification arr:test4
+          (array:array(T), non_neg_integer(), _) -> array:array(T) is a supertype of the success typing: arr:test4
+          (array:array(_), pos_integer(), _) -> array:array(_)
+arr.erl:29: Type specification arr:test5
+          (array:array(T), non_neg_integer(), T) -> array:array(T) is a supertype of the success typing: arr:test5
+          (array:array(_), non_neg_integer(), integer()) ->
+             array:array(_)
+arr.erl:37: Type specification arr:test6
+          (array:array(integer()), non_neg_integer(), integer()) ->
+             array:array(any()) is not equal to the success typing: arr:test6
+          (array:array(_), non_neg_integer(), _) -> array:array(_)
diff --git a/lib/dialyzer/test/indent2_SUITE_data/results/iodata b/lib/dialyzer/test/indent2_SUITE_data/results/iodata
new file mode 100644
index 0000000000..d95551d330
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/results/iodata
@@ -0,0 +1,24 @@
+
+iodata.erl:7: The specification for iodata:encode/2 states that the function might also return 
+          binary() but the inferred return is 
+          nonempty_maybe_improper_list(<<_:8, _:_*8>> |
+                                       nonempty_maybe_improper_list(<<_:8,
+                                                                      _:_*8>> |
+                                                                    nonempty_maybe_improper_list(any(),
+                                                                                                 <<_:8,
+                                                                                                   _:_*8>> |
+                                                                                                 []) |
+                                                                    byte(),
+                                                                    <<_:8,
+                                                                      _:_*8>> |
+                                                                    []) |
+                                       integer(),
+                                       <<_:8, _:_*8>> | []) |
+          integer()
+iodata.erl:7: The success typing for iodata:encode/2 implies that the function might also return 
+          integer() but the specification return is 
+          binary() |
+          maybe_improper_list(binary() |
+                              maybe_improper_list(any(), binary() | []) |
+                              byte(),
+                              binary() | [])
diff --git a/lib/dialyzer/test/indent2_SUITE_data/results/remote b/lib/dialyzer/test/indent2_SUITE_data/results/remote
new file mode 100644
index 0000000000..6decec6c6a
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/results/remote
@@ -0,0 +1,25 @@
+
+remotes1.erl:17: The specification for remotes1:foo5/1 states that the function might also return 
+          'ko' but the inferred return is 
+          'ok'
+remotes1.erl:20: Type specification remotes1:foo6
+          ('ok' | 'ko') -> 'ok' is a supertype of the success typing: remotes1:foo6
+          ('ok') -> 'ok'
+remotes1.erl:25: The specification for remotes1:foo7/1 states that the function might also return 
+          'ko' but the inferred return is 
+          'ok'
+remotes1.erl:28: Type specification remotes1:foo8
+          (local_type_42()) -> 'ok' is a supertype of the success typing: remotes1:foo8
+          ('ok') -> 'ok'
+remotes1.erl:33: The specification for remotes1:foo9/1 states that the function might also return 
+          'ko' but the inferred return is 
+          'ok'
+remotes1.erl:36: Type specification remotes1:foo10
+          (local_and_known_remote_type_42()) -> 'ok' is a supertype of the success typing: remotes1:foo10
+          ('ok') -> 'ok'
+remotes1.erl:49: Type specification remotes1:foo13
+          ('ok') -> local_and_unknown_remote_type_42() is a supertype of the success typing: remotes1:foo13
+          ('ok') -> 'ok'
+remotes1.erl:52: Type specification remotes1:foo14
+          (local_and_unknown_remote_type_42()) -> 'ok' is a supertype of the success typing: remotes1:foo14
+          ('ok') -> 'ok'
diff --git a/lib/dialyzer/test/indent2_SUITE_data/src/arr.erl b/lib/dialyzer/test/indent2_SUITE_data/src/arr.erl
new file mode 100644
index 0000000000..3b265ccec2
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/src/arr.erl
@@ -0,0 +1,41 @@
+-module(arr).
+
+%% http://erlang.org/pipermail/erlang-questions/2014-August/080445.html
+
+-define(A, array).
+
+-export([test/3, test2/3, test3/3, test4/3, test5/3, test6/3]).
+
+-spec test(?A:array(T), non_neg_integer(), T) -> ?A:array(T).
+
+test(Array, N, Value) ->
+    ?A:set(N, Value, Array).
+
+-spec test2(?A:array(T), non_neg_integer(), T) -> ?A:array(T).
+
+test2(Array, N, Value) when N > 0 ->
+    ?A:set(N, Value, Array).
+
+-spec test3(?A:array(T), non_neg_integer(), _) -> ?A:array(T).
+
+test3(Array, N, Value) ->
+    ?A:set(N, Value, Array).
+
+-spec test4(?A:array(T), non_neg_integer(), _) -> ?A:array(T).
+
+test4(Array, N, Value) when N > 0 ->
+    ?A:set(N, Value, Array).
+
+-spec test5(?A:array(T), non_neg_integer(), T) -> ?A:array(T).
+
+test5(Array, N, Value) when is_integer(Value) ->
+    ?A:set(N, Value, Array).
+
+%% One would ideally want a warning also for test6(), but the current
+%% analysis of parametrized opaque types is not strong enough to
+%% discover this.
+-spec test6(?A:array(integer()), non_neg_integer(), integer()) ->
+                   ?A:array(any()).
+
+test6(Array, N, Value) ->
+     ?A:set(N, Value, Array).
diff --git a/lib/dialyzer/test/indent2_SUITE_data/src/iodata.erl b/lib/dialyzer/test/indent2_SUITE_data/src/iodata.erl
new file mode 100644
index 0000000000..caa44f6c91
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/src/iodata.erl
@@ -0,0 +1,41 @@
+-module(iodata).
+
+%% A small part of beam_asm.
+
+-export([encode/2]).
+
+-spec encode(non_neg_integer(), integer()) -> iodata(). % extra range binary()
+
+encode(Tag, N) when Tag >= 0, N < 0 ->
+    encode1(Tag, negative_to_bytes(N));
+encode(Tag, N) when Tag >= 0, N < 16 ->
+    (N bsl 4) bor Tag; % not in the specification
+encode(Tag, N) when Tag >= 0, N < 16#800  ->
+    [((N bsr 3) band 2#11100000) bor Tag bor 2#00001000, N band 16#ff];
+encode(Tag, N) when Tag >= 0 ->
+    encode1(Tag, to_bytes(N)).
+
+encode1(Tag, Bytes) ->
+    case iolist_size(Bytes) of
+	Num when 2 =< Num, Num =< 8 ->
+	    [((Num-2) bsl 5) bor 2#00011000 bor Tag| Bytes];
+	Num when 8 < Num ->
+	    [2#11111000 bor Tag, encode(0, Num-9)| Bytes]
+    end.
+
+to_bytes(N) ->
+    Bin = binary:encode_unsigned(N),
+    case Bin of
+	<<0:1,_/bits>> -> Bin;
+	<<1:1,_/bits>> -> [0,Bin]
+    end.
+
+negative_to_bytes(N) when N >= -16#8000 ->
+    <<N:16>>;
+negative_to_bytes(N) ->
+    Bytes = byte_size(binary:encode_unsigned(-N)),
+    Bin = <<N:Bytes/unit:8>>,
+    case Bin of
+	<<0:1,_/bits>> -> [16#ff,Bin];
+	<<1:1,_/bits>> -> Bin
+    end.
diff --git a/lib/dialyzer/test/indent2_SUITE_data/src/remote/remotes1.erl b/lib/dialyzer/test/indent2_SUITE_data/src/remote/remotes1.erl
new file mode 100644
index 0000000000..b722495095
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/src/remote/remotes1.erl
@@ -0,0 +1,61 @@
+-module(remotes1).
+
+-compile(export_all).
+
+-spec foo1(some_unknown_remote:type42()) -> ok.
+foo1(ok) -> ok.
+
+-spec foo2(ok) -> some_unknown_remote:type42().
+foo2(ok) -> ok.
+
+-spec foo3(some_known_remote:type42()) -> ok.
+foo3(ok) -> ok.
+
+-spec foo4(ok) -> some_known_remote:type42().
+foo4(ok) -> ok.
+
+-spec foo5(ok|ko) -> ok|ko.
+foo5(ok) -> ok.
+
+-spec foo6(ok|ko) -> ok.
+foo6(ok) -> ok.
+
+-type local_type_42() :: ok | ko.
+
+-spec foo7(ok) -> local_type_42().
+foo7(ok) -> ok.
+
+-spec foo8(local_type_42()) -> ok.
+foo8(ok) -> ok.
+
+-type local_and_known_remote_type_42() :: some_known_remote:type42() | ok | ko.
+
+-spec foo9(ok) -> local_and_known_remote_type_42().
+foo9(ok) -> ok.
+
+-spec foo10(local_and_known_remote_type_42()) -> ok.
+foo10(ok) -> ok.
+
+-type local_and_ok_known_remote_type_42() :: some_known_remote:type42() | ok.
+
+-spec foo11(ok) -> local_and_ok_known_remote_type_42().
+foo11(ok) -> ok.
+
+-spec foo12(local_and_ok_known_remote_type_42()) -> ok.
+foo12(ok) -> ok.
+
+-type local_and_unknown_remote_type_42() :: some_unknown_remote:type42() | ok | ko.
+
+-spec foo13(ok) -> local_and_unknown_remote_type_42().
+foo13(ok) -> ok.
+
+-spec foo14(local_and_unknown_remote_type_42()) -> ok.
+foo14(ok) -> ok.
+
+-type local_and_ok_unknown_remote_type_42() :: some_unknown_remote:type42() | ok.
+
+-spec foo15(ok) -> local_and_ok_unknown_remote_type_42().
+foo15(ok) -> ok.
+
+-spec foo16(local_and_ok_unknown_remote_type_42()) -> ok.
+foo16(ok) -> ok.
diff --git a/lib/dialyzer/test/indent2_SUITE_data/src/remote/some_known_remote.erl b/lib/dialyzer/test/indent2_SUITE_data/src/remote/some_known_remote.erl
new file mode 100644
index 0000000000..437f1e7826
--- /dev/null
+++ b/lib/dialyzer/test/indent2_SUITE_data/src/remote/some_known_remote.erl
@@ -0,0 +1,5 @@
+-module(some_known_remote).
+
+-export_type([type42/0]).
+
+-type type42() :: ok | ko.
diff --git a/lib/dialyzer/test/indent_SUITE_data/dialyzer_options b/lib/dialyzer/test/indent_SUITE_data/dialyzer_options
new file mode 100644
index 0000000000..7c088f9a65
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/dialyzer_options
@@ -0,0 +1 @@
+{dialyzer_options, [{warnings, [no_unused, no_return, race_conditions]}]}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/abs b/lib/dialyzer/test/indent_SUITE_data/results/abs
new file mode 100644
index 0000000000..ac663a4e80
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/abs
@@ -0,0 +1,13 @@
+
+abs.erl:16: The pattern 
+          'true' can never match the type 
+          'false'
+abs.erl:27: The pattern 
+          'true' can never match the type 
+          'false'
+abs.erl:37: The pattern 
+          'true' can never match the type 
+          'false'
+abs.erl:49: The pattern 
+          'true' can never match the type 
+          'false'
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/app_call b/lib/dialyzer/test/indent_SUITE_data/results/app_call
new file mode 100644
index 0000000000..729587b5c6
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/app_call
@@ -0,0 +1,9 @@
+
+app_call.erl:6: The call M:'foo'
+         () requires that M is of type 
+          atom() not 
+          42
+app_call.erl:9: The call 'mod':F
+         () requires that F is of type 
+          atom() not 
+          {'gazonk', []}
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/arr b/lib/dialyzer/test/indent_SUITE_data/results/arr
new file mode 100644
index 0000000000..9497d12eec
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/arr
@@ -0,0 +1,4 @@
+
+arr.erl:14: Type specification arr:test2(array:array(T),non_neg_integer(),T) -> array:array(T) is a supertype of the success typing: arr:test2(array:array(_),pos_integer(),_) -> array:array(_)
+arr.erl:24: Type specification arr:test4(array:array(T),non_neg_integer(),_) -> array:array(T) is a supertype of the success typing: arr:test4(array:array(_),pos_integer(),_) -> array:array(_)
+arr.erl:29: Type specification arr:test5(array:array(T),non_neg_integer(),T) -> array:array(T) is a supertype of the success typing: arr:test5(array:array(_),non_neg_integer(),integer()) -> array:array(_)
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/blame_contract_range b/lib/dialyzer/test/indent_SUITE_data/results/blame_contract_range
new file mode 100644
index 0000000000..287d23d91f
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/blame_contract_range
@@ -0,0 +1,8 @@
+
+blame_contract_range.erl:14: The contract blame_contract_range:bar
+          (atom()) -> 'a' cannot be right because the inferred return for bar
+         ('b') on line 12 is 
+          'b'
+blame_contract_range.erl:15: The pattern 
+          'a' can never match the type 
+          'b'
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/bs_fail_constr b/lib/dialyzer/test/indent_SUITE_data/results/bs_fail_constr
new file mode 100644
index 0000000000..86f1329bf3
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/bs_fail_constr
@@ -0,0 +1,9 @@
+
+bs_fail_constr.erl:12: Binary construction will fail since the size field S in segment 42:S has type 
+          neg_integer()
+bs_fail_constr.erl:15: Binary construction will fail since the value field V in segment V/utf32 has type 
+          float()
+bs_fail_constr.erl:6: Binary construction will fail since the value field V in segment V has type 
+          float()
+bs_fail_constr.erl:9: Binary construction will fail since the value field V in segment V/binary has type 
+          atom()
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs b/lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs
new file mode 100644
index 0000000000..dd9d3397d2
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs
@@ -0,0 +1,23 @@
+
+my_callbacks_wrong.erl:26: The return type 
+          #state{parent :: pid(),
+                 status :: 'closed' | 'init' | 'open',
+                 subscribe :: [{pid(), integer()}],
+                 counter :: integer()} in the specification of callback_init/1 is not a subtype of 
+          {'ok', _}, which is the expected return type for the callback of the my_behaviour behaviour
+my_callbacks_wrong.erl:28: The inferred return type of callback_init/1 
+         (#state{parent :: pid(),
+                 status :: 'init',
+                 subscribe :: [],
+                 counter :: 1}) has nothing in common with 
+          {'ok', _}, which is the expected return type for the callback of the my_behaviour behaviour
+my_callbacks_wrong.erl:30: The return type 
+          {'reply',
+           #state{parent :: pid(),
+                  status :: 'closed' | 'init' | 'open',
+                  subscribe :: [{pid(), integer()}],
+                  counter :: integer()}} in the specification of callback_cast/3 is not a subtype of 
+          {'noreply', _}, which is the expected return type for the callback of the my_behaviour behaviour
+my_callbacks_wrong.erl:39: The specified type for the 2nd argument of callback_call/3 (
+          atom()) is not a supertype of 
+          pid(), which is expected type for this argument in the callback of the my_behaviour behaviour
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/contract3 b/lib/dialyzer/test/indent_SUITE_data/results/contract3
new file mode 100644
index 0000000000..6e111f87d9
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/contract3
@@ -0,0 +1,3 @@
+
+contract3.erl:17: Overloaded contract for contract3:t1/1 has overlapping domains; such contracts are currently unsupported and are simply ignored
+contract3.erl:29: Overloaded contract for contract3:t3/3 has overlapping domains; such contracts are currently unsupported and are simply ignored
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes b/lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes
new file mode 100644
index 0000000000..737959a49d
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes
@@ -0,0 +1,142 @@
+
+contracts_with_subtypes.erl:106: The call contracts_with_subtypes:rec_arg
+         ({'a', 'b'}) breaks the contract 
+          (Arg) -> 'ok'
+             when
+                 Arg :: {'a', A} | {'b', B},
+                 A :: 'a' | {'b', B},
+                 B :: 'b' | {'a', A}
+contracts_with_subtypes.erl:107: The call contracts_with_subtypes:rec_arg
+         ({'b', 'a'}) breaks the contract 
+          (Arg) -> 'ok'
+             when
+                 Arg :: {'a', A} | {'b', B},
+                 A :: 'a' | {'b', B},
+                 B :: 'b' | {'a', A}
+contracts_with_subtypes.erl:109: The call contracts_with_subtypes:rec_arg
+         ({'b', {'a', 'b'}}) breaks the contract 
+          (Arg) -> 'ok'
+             when
+                 Arg :: {'a', A} | {'b', B},
+                 A :: 'a' | {'b', B},
+                 B :: 'b' | {'a', A}
+contracts_with_subtypes.erl:135: The call contracts_with_subtypes:rec2
+         ({'a', 'b'}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:136: The call contracts_with_subtypes:rec2
+         ({'b', 'a'}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:137: The call contracts_with_subtypes:rec2
+         ({'a', {'b', 'a'}}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:138: The call contracts_with_subtypes:rec2
+         ({'b', {'a', 'b'}}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:139: The call contracts_with_subtypes:rec2
+         ({'a', {'b', {'a', 'b'}}}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:140: The call contracts_with_subtypes:rec2
+         ({'b', {'a', {'b', 'a'}}}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:141: The call contracts_with_subtypes:rec2
+         ({'a', {'b', {'a', {'b', 'a'}}}}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:142: The call contracts_with_subtypes:rec2
+         ({'b', {'a', {'b', {'a', 'b'}}}}) breaks the contract 
+          (Arg) -> 'ok' when Arg :: ab()
+contracts_with_subtypes.erl:175: The pattern 
+          1 can never match the type 
+          string()
+contracts_with_subtypes.erl:178: The pattern 
+          'alpha' can never match the type 
+          {'ok', _} | {'ok', _, string()}
+contracts_with_subtypes.erl:180: The pattern 
+          42 can never match the type 
+          {'ok', _} | {'ok', _, string()}
+contracts_with_subtypes.erl:196: The pattern 
+          'alpha' can never match the type 
+          {'ok', _}
+contracts_with_subtypes.erl:198: The pattern 
+          42 can never match the type 
+          {'ok', _}
+contracts_with_subtypes.erl:216: The pattern 
+          'alpha' can never match the type 
+          {'ok', _}
+contracts_with_subtypes.erl:218: The pattern 
+          42 can never match the type 
+          {'ok', _}
+contracts_with_subtypes.erl:235: The pattern 
+          1 can never match the type 
+          string()
+contracts_with_subtypes.erl:238: The pattern 
+          {'ok', _} can never match the type 
+          {'ok', _, string()}
+contracts_with_subtypes.erl:239: The pattern 
+          'alpha' can never match the type 
+          {'ok', _, string()}
+contracts_with_subtypes.erl:23: Invalid type specification for function contracts_with_subtypes:extract2/0. The success typing is 
+          () -> 'something'
+contracts_with_subtypes.erl:240: The pattern 
+          {'ok', 42} can never match the type 
+          {'ok', _, string()}
+contracts_with_subtypes.erl:241: The pattern 
+          42 can never match the type 
+          {'ok', _, string()}
+contracts_with_subtypes.erl:268: The call contracts_with_subtypes:flat_ets_new
+         (12,
+          []) breaks the contract 
+          (Name, Options) -> atom()
+             when
+                 Name :: atom(),
+                 Options :: [Option],
+                 Option ::
+                     'set' | 'ordered_set' | 'bag' | 'duplicate_bag' |
+                     'public' | 'protected' | 'private' |
+                     'named_table' |
+                     {'keypos', integer()} |
+                     {'heir', pid(), term()} |
+                     {'heir', 'none'} |
+                     {'write_concurrency', boolean()} |
+                     {'read_concurrency', boolean()} |
+                     'compressed'
+contracts_with_subtypes.erl:295: The call contracts_with_subtypes:factored_ets_new
+         (12,
+          []) breaks the contract 
+          (Name, Options) -> atom()
+             when
+                 Name :: atom(),
+                 Options :: [Option],
+                 Option ::
+                     Type | Access | 'named_table' |
+                     {'keypos', Pos} |
+                     {'heir', Pid :: pid(), HeirData} |
+                     {'heir', 'none'} |
+                     Tweaks,
+                 Type :: type(),
+                 Access :: access(),
+                 Tweaks ::
+                     {'write_concurrency', boolean()} |
+                     {'read_concurrency', boolean()} |
+                     'compressed',
+                 Pos :: pos_integer(),
+                 HeirData :: term()
+contracts_with_subtypes.erl:77: The call contracts_with_subtypes:foo1
+         (5) breaks the contract 
+          (Arg1) -> Res when Arg1 :: atom(), Res :: atom()
+contracts_with_subtypes.erl:78: The call contracts_with_subtypes:foo2
+         (5) breaks the contract 
+          (Arg1) -> Res when Arg1 :: Arg2, Arg2 :: atom(), Res :: atom()
+contracts_with_subtypes.erl:79: The call contracts_with_subtypes:foo3
+         (5) breaks the contract 
+          (Arg1) -> Res when Arg2 :: atom(), Arg1 :: Arg2, Res :: atom()
+contracts_with_subtypes.erl:7: Invalid type specification for function contracts_with_subtypes:extract/0. The success typing is 
+          () -> 'something'
+contracts_with_subtypes.erl:80: The call contracts_with_subtypes:foo4
+         (5) breaks the contract 
+          (Type) -> Type when Type :: atom()
+contracts_with_subtypes.erl:81: The call contracts_with_subtypes:foo5
+         (5) breaks the contract 
+          (Type :: atom()) -> Type :: atom()
+contracts_with_subtypes.erl:82: The call contracts_with_subtypes:foo6
+         (5) breaks the contract 
+          (Type) -> Type when Type :: atom()
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/dict_use b/lib/dialyzer/test/indent_SUITE_data/results/dict_use
new file mode 100644
index 0000000000..c6863d057e
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/dict_use
@@ -0,0 +1,48 @@
+
+dict_use.erl:41: The attempt to match a term of type 
+          dict:dict(_, _) against the pattern 
+          'gazonk' breaks the opacity of the term
+dict_use.erl:45: The attempt to match a term of type 
+          dict:dict(_, _) against the pattern 
+          [] breaks the opacity of the term
+dict_use.erl:46: The attempt to match a term of type 
+          dict:dict(_, _) against the pattern 
+          42 breaks the opacity of the term
+dict_use.erl:51: The attempt to match a term of type 
+          dict:dict(_, _) against the pattern 
+          [] breaks the opacity of the term
+dict_use.erl:52: The attempt to match a term of type 
+          dict:dict(_, _) against the pattern 
+          42 breaks the opacity of the term
+dict_use.erl:58: Attempt to test for equality between a term of type 
+          maybe_improper_list() and a term of opaque type 
+          dict:dict(_, _)
+dict_use.erl:60: Attempt to test for inequality between a term of type 
+          atom() and a term of opaque type 
+          dict:dict(_, _)
+dict_use.erl:64: Guard test length
+         (D :: dict:dict(_, _)) breaks the opacity of its argument
+dict_use.erl:65: Guard test is_atom
+         (D :: dict:dict(_, _)) breaks the opacity of its argument
+dict_use.erl:66: Guard test is_list
+         (D :: dict:dict(_, _)) breaks the opacity of its argument
+dict_use.erl:70: The type test is_list
+         (dict:dict(_, _)) breaks the opacity of the term 
+          dict:dict(_, _)
+dict_use.erl:73: The call dict:fetch
+         ('foo',
+          [1, 2, 3]) does not have an opaque term of type 
+          dict:dict(_, _) as 2nd argument
+dict_use.erl:76: The call dict:merge
+         (Fun :: any(),
+          42,
+          [1, 2]) does not have opaque terms as 2nd and 3rd arguments
+dict_use.erl:79: The call dict:store
+         (42,
+          'elli',
+          {'dict', 0, 16, 16, 8, 80, 48,
+           {[], [], [], [], [], [], [], [], [], [], [], [], [], [], [],
+            []},
+           {{[], [], [], [], [], [], [], [], [], [], [], [], [], [], [],
+             []}}}) does not have an opaque term of type 
+          dict:dict(_, _) as 3rd argument
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/fun_app b/lib/dialyzer/test/indent_SUITE_data/results/fun_app
new file mode 100644
index 0000000000..d4a3caf749
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/fun_app
@@ -0,0 +1,7 @@
+
+fun_app.erl:37: Fun application will fail since F :: 
+          fun((_, _, _) -> 'ok' | 'true') is not a function of arity 1
+fun_app.erl:38: Fun application will fail since F :: 
+          fun((_, _, _) -> 'ok' | 'true') is not a function of arity 2
+fun_app.erl:40: Fun application will fail since F :: 
+          fun((_, _, _) -> 'ok' | 'true') is not a function of arity 4
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/fun_app_args b/lib/dialyzer/test/indent_SUITE_data/results/fun_app_args
new file mode 100644
index 0000000000..ac1bbb62b8
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/fun_app_args
@@ -0,0 +1,5 @@
+
+fun_app_args.erl:12: Fun application with arguments 
+         ('b',
+          []) will fail since the function has type 
+          'c' | fun(('a', []) -> any()), which differs in the 1st argument
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/guard_update b/lib/dialyzer/test/indent_SUITE_data/results/guard_update
new file mode 100644
index 0000000000..bd0e8cd5dd
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/guard_update
@@ -0,0 +1,6 @@
+
+guard_update.erl:6: The call guard_update:f
+         (#{'a' => 2}) will never return since it differs in the 1st argument from the success typing arguments: 
+         (#{'b' := _, _ => _})
+guard_update.erl:8: Clause guard cannot succeed. The variable M was matched against the type 
+          #{'a' := 2}
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/guard_warnings b/lib/dialyzer/test/indent_SUITE_data/results/guard_warnings
new file mode 100644
index 0000000000..a6cb54ff9c
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/guard_warnings
@@ -0,0 +1,134 @@
+
+guard_warnings.erl:100: Guard test not
+         ('true') can never succeed
+guard_warnings.erl:102: Guard test 
+          X :: 'true' =:= 
+          'false' can never succeed
+guard_warnings.erl:104: Guard test 
+          X :: 'true' == 
+          'false' can never succeed
+guard_warnings.erl:106: Guard test 
+          X :: 'true' =/= 
+          'true' can never succeed
+guard_warnings.erl:12: Guard test 
+          X :: 'true' =:= 
+          'false' can never succeed
+guard_warnings.erl:14: Guard test 
+          X :: 'false' =:= 
+          'true' can never succeed
+guard_warnings.erl:16: Guard test not
+         (X :: 'true') can never succeed
+guard_warnings.erl:18: Guard test and
+         ('true',
+          X :: none()) can never succeed
+guard_warnings.erl:20: Guard test not
+         (X :: 'true') can never succeed
+guard_warnings.erl:22: Guard test and
+         ('true',
+          X :: none()) can never succeed
+guard_warnings.erl:28: Guard test not(not
+         (X :: 'false')) can never succeed
+guard_warnings.erl:30: Guard test not(or
+         ('false',
+          X :: none())) can never succeed
+guard_warnings.erl:32: Guard test not(not
+         (X :: 'false')) can never succeed
+guard_warnings.erl:34: Guard test not(or
+         ('false',
+          X :: none())) can never succeed
+guard_warnings.erl:36: Guard test and
+         ('true',
+          'false') can never succeed
+guard_warnings.erl:38: Guard test and
+         ('false',
+          any()) can never succeed
+guard_warnings.erl:40: Guard test and
+         (X :: 'true',
+          'false') can never succeed
+guard_warnings.erl:42: Guard test and
+         ('false',
+          X :: any()) can never succeed
+guard_warnings.erl:44: Guard test and
+         (X :: 'true',
+          'false') can never succeed
+guard_warnings.erl:46: Guard test and
+         ('false',
+          X :: any()) can never succeed
+guard_warnings.erl:48: Guard test not(or
+         ('true',
+          any())) can never succeed
+guard_warnings.erl:50: Guard test not(or
+         ('false',
+          'true')) can never succeed
+guard_warnings.erl:52: Guard test not(or
+         ('true',
+          X :: any())) can never succeed
+guard_warnings.erl:54: Guard test not(or
+         (X :: 'false',
+          'true')) can never succeed
+guard_warnings.erl:56: Guard test not(or
+         ('true',
+          X :: any())) can never succeed
+guard_warnings.erl:58: Guard test not(or
+         (X :: 'false',
+          'true')) can never succeed
+guard_warnings.erl:60: Guard test and
+         ('false',
+          any()) can never succeed
+guard_warnings.erl:62: Guard test and
+         ('true',
+          'false') can never succeed
+guard_warnings.erl:64: Guard test and
+         ('false',
+          X :: any()) can never succeed
+guard_warnings.erl:66: Guard test and
+         (X :: 'true',
+          'false') can never succeed
+guard_warnings.erl:68: Guard test and
+         ('false',
+          X :: any()) can never succeed
+guard_warnings.erl:70: Guard test and
+         (X :: 'true',
+          'false') can never succeed
+guard_warnings.erl:72: Guard test and
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:74: Guard test and
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:76: Guard test not(and
+         ('true',
+          'true')) can never succeed
+guard_warnings.erl:78: Guard test and
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:80: Guard test not(and
+         ('true',
+          'true')) can never succeed
+guard_warnings.erl:82: Guard test or
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:84: Guard test or
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:86: Guard test or
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:88: Guard test or
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:90: Guard test or
+         ('false',
+          'false') can never succeed
+guard_warnings.erl:92: Guard test 
+          'true' =:= 
+          'false' can never succeed
+guard_warnings.erl:94: Guard test 
+          'true' == 
+          'false' can never succeed
+guard_warnings.erl:96: Guard test 
+          'true' =:= 
+          'false' can never succeed
+guard_warnings.erl:98: Guard test not(
+          'true' == 
+          'true') can never succeed
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/map_galore b/lib/dialyzer/test/indent_SUITE_data/results/map_galore
new file mode 100644
index 0000000000..1b63e28ace
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/map_galore
@@ -0,0 +1,713 @@
+
+map_galore.erl:1000: A key of type 
+          42 cannot exist in a map of type 
+          #{1 := 'a',
+            2 := 'b',
+            4 := 'd',
+            5 := 'e',
+            float() => 'c' | 'v'}
+map_galore.erl:1080: A key of type 
+          'nonexisting' cannot exist in a map of type 
+          #{10 := 'a0',
+            11 := 'a1',
+            12 := 'a2',
+            13 := 'a3',
+            14 := 'a4',
+            15 := 'a5',
+            16 := 'a6',
+            17 := 'a7',
+            18 := 'a8',
+            19 := 'a9',
+            20 := 'b0',
+            21 := 'b1',
+            22 := 'b2',
+            23 := 'b3',
+            24 := 'b4',
+            25 := 'b5',
+            26 := 'b6',
+            27 := 'b7',
+            28 := 'b8',
+            29 := 'b9',
+            30 := [48 | 99, ...],
+            31 := [49 | 99, ...],
+            32 := [50 | 99, ...],
+            33 := [51 | 99, ...],
+            34 := [52 | 99, ...],
+            35 := [53 | 99, ...],
+            36 := [54 | 99, ...],
+            37 := [55 | 99, ...],
+            38 := [56 | 99, ...],
+            39 := [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...],
+              ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [54 | 99, ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [48 | 99, ...],
+              31 => [49 | 99, ...],
+              32 => [50 | 99, ...],
+              33 => [51 | 99, ...],
+              34 => [52 | 99, ...],
+              35 => [53 | 99, ...],
+              36 => [54 | 99, ...],
+              37 => [55 | 99, ...],
+              38 => [56 | 99, ...],
+              39 => [57 | 99, ...],
+              <<_:16>> |
+              [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+              {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...],
+                ...]} =>
+                  [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 |
+                   100 | 101,
+                   ...]} =>
+                atom() | [1..255, ...]}
+map_galore.erl:1082: A key of type 
+          42 cannot exist in a map of type 
+          #{10 := 'a0',
+            11 := 'a1',
+            12 := 'a2',
+            13 := 'a3',
+            14 := 'a4',
+            15 := 'a5',
+            16 := 'a6',
+            17 := 'a7',
+            18 := 'a8',
+            19 := 'a9',
+            20 := 'b0',
+            21 := 'b1',
+            22 := 'b2',
+            23 := 'b3',
+            24 := 'b4',
+            25 := 'b5',
+            26 := 'b6',
+            27 := 'b7',
+            28 := 'b8',
+            29 := 'b9',
+            30 := [48 | 99, ...],
+            31 := [49 | 99, ...],
+            32 := [50 | 99, ...],
+            33 := [51 | 99, ...],
+            34 := [52 | 99, ...],
+            35 := [53 | 99, ...],
+            36 := [54 | 99, ...],
+            37 := [55 | 99, ...],
+            38 := [56 | 99, ...],
+            39 := [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...],
+              ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [54 | 99, ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [48 | 99, ...],
+              31 => [49 | 99, ...],
+              32 => [50 | 99, ...],
+              33 => [51 | 99, ...],
+              34 => [52 | 99, ...],
+              35 => [53 | 99, ...],
+              36 => [54 | 99, ...],
+              37 => [55 | 99, ...],
+              38 => [56 | 99, ...],
+              39 => [57 | 99, ...],
+              <<_:16>> |
+              [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+              {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...],
+                ...]} =>
+                  [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 |
+                   100 | 101,
+                   ...]} =>
+                atom() | [1..255, ...]}
+map_galore.erl:1140: The call map_galore:map_guard_sequence_1
+         (#{seq => 6, val => "e"}) will never return since it differs in the 1st argument from the success typing arguments: 
+         (#{'seq' := 1 | 2 | 3 | 4 | 5,
+            'val' := [97 | 98 | 99 | 100 | 101, ...],
+            10 => 'a0',
+            11 => 'a1',
+            12 => 'a2',
+            13 => 'a3',
+            14 => 'a4',
+            15 => 'a5',
+            16 => 'a6',
+            17 => 'a7',
+            18 => 'a8',
+            19 => 'a9',
+            20 => 'b0',
+            21 => 'b1',
+            22 => 'b2',
+            23 => 'b3',
+            24 => 'b4',
+            25 => 'b5',
+            26 => 'b6',
+            27 => 'b7',
+            28 => 'b8',
+            29 => 'b9',
+            30 => [48 | 99, ...],
+            31 => [49 | 99, ...],
+            32 => [50 | 99, ...],
+            33 => [51 | 99, ...],
+            34 => [52 | 99, ...],
+            35 => [53 | 99, ...],
+            36 => [54 | 99, ...],
+            37 => [55 | 99, ...],
+            38 => [56 | 99, ...],
+            39 => [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[any(), ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [any(), ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [any(), ...],
+              31 => [any(), ...],
+              32 => [any(), ...],
+              33 => [any(), ...],
+              34 => [any(), ...],
+              35 => [any(), ...],
+              36 => [any(), ...],
+              37 => [any(), ...],
+              38 => [any(), ...],
+              39 => [any(), ...],
+              <<_:16>> | [any(), ...] | {_} => [any(), ...]} =>
+                atom() | [1..255, ...]})
+map_galore.erl:1141: The call map_galore:map_guard_sequence_2
+         (#{'b' => 5}) will never return since it differs in the 1st argument from the success typing arguments: 
+         (#{'a' := 'gg' | 'kk' | 'sc' | 3 | 4,
+            'b' => 'other' | 3 | 4 | 5,
+            'c' => 'sc2',
+            10 => 'a0',
+            11 => 'a1',
+            12 => 'a2',
+            13 => 'a3',
+            14 => 'a4',
+            15 => 'a5',
+            16 => 'a6',
+            17 => 'a7',
+            18 => 'a8',
+            19 => 'a9',
+            20 => 'b0',
+            21 => 'b1',
+            22 => 'b2',
+            23 => 'b3',
+            24 => 'b4',
+            25 => 'b5',
+            26 => 'b6',
+            27 => 'b7',
+            28 => 'b8',
+            29 => 'b9',
+            30 => [48 | 99, ...],
+            31 => [49 | 99, ...],
+            32 => [50 | 99, ...],
+            33 => [51 | 99, ...],
+            34 => [52 | 99, ...],
+            35 => [53 | 99, ...],
+            36 => [54 | 99, ...],
+            37 => [55 | 99, ...],
+            38 => [56 | 99, ...],
+            39 => [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[any(), ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [any(), ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [any(), ...],
+              31 => [any(), ...],
+              32 => [any(), ...],
+              33 => [any(), ...],
+              34 => [any(), ...],
+              35 => [any(), ...],
+              36 => [any(), ...],
+              37 => [any(), ...],
+              38 => [any(), ...],
+              39 => [any(), ...],
+              <<_:16>> | [any(), ...] | {_} => [any(), ...]} =>
+                atom() | [1..255, ...]})
+map_galore.erl:1209: The call map_galore:map_guard_sequence_1
+         (#{'seq' := 6,
+            'val' := [101, ...],
+            10 := 'a0',
+            11 := 'a1',
+            12 := 'a2',
+            13 := 'a3',
+            14 := 'a4',
+            15 := 'a5',
+            16 := 'a6',
+            17 := 'a7',
+            18 := 'a8',
+            19 := 'a9',
+            20 := 'b0',
+            21 := 'b1',
+            22 := 'b2',
+            23 := 'b3',
+            24 := 'b4',
+            25 := 'b5',
+            26 := 'b6',
+            27 := 'b7',
+            28 := 'b8',
+            29 := 'b9',
+            30 := [48 | 99, ...],
+            31 := [49 | 99, ...],
+            32 := [50 | 99, ...],
+            33 := [51 | 99, ...],
+            34 := [52 | 99, ...],
+            35 := [53 | 99, ...],
+            36 := [54 | 99, ...],
+            37 := [55 | 99, ...],
+            38 := [56 | 99, ...],
+            39 := [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] | 3,
+              ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [54 | 99, ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [48 | 99, ...],
+              31 => [49 | 99, ...],
+              32 => [50 | 99, ...],
+              33 => [51 | 99, ...],
+              34 => [52 | 99, ...],
+              35 => [53 | 99, ...],
+              36 => [54 | 99, ...],
+              37 => [55 | 99, ...],
+              38 => [56 | 99, ...],
+              39 => [57 | 99, ...],
+              <<_:16>> |
+              [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+              {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...],
+                ...]} =>
+                  [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 |
+                   100 | 101,
+                   ...]} =>
+                atom() | [1..255, ...]}) will never return since it differs in the 1st argument from the success typing arguments: 
+         (#{'seq' := 1 | 2 | 3 | 4 | 5,
+            'val' := [97 | 98 | 99 | 100 | 101, ...],
+            10 => 'a0',
+            11 => 'a1',
+            12 => 'a2',
+            13 => 'a3',
+            14 => 'a4',
+            15 => 'a5',
+            16 => 'a6',
+            17 => 'a7',
+            18 => 'a8',
+            19 => 'a9',
+            20 => 'b0',
+            21 => 'b1',
+            22 => 'b2',
+            23 => 'b3',
+            24 => 'b4',
+            25 => 'b5',
+            26 => 'b6',
+            27 => 'b7',
+            28 => 'b8',
+            29 => 'b9',
+            30 => [48 | 99, ...],
+            31 => [49 | 99, ...],
+            32 => [50 | 99, ...],
+            33 => [51 | 99, ...],
+            34 => [52 | 99, ...],
+            35 => [53 | 99, ...],
+            36 => [54 | 99, ...],
+            37 => [55 | 99, ...],
+            38 => [56 | 99, ...],
+            39 => [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[any(), ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [any(), ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [any(), ...],
+              31 => [any(), ...],
+              32 => [any(), ...],
+              33 => [any(), ...],
+              34 => [any(), ...],
+              35 => [any(), ...],
+              36 => [any(), ...],
+              37 => [any(), ...],
+              38 => [any(), ...],
+              39 => [any(), ...],
+              <<_:16>> | [any(), ...] | {_} => [any(), ...]} =>
+                atom() | [1..255, ...]})
+map_galore.erl:1210: The call map_galore:map_guard_sequence_2
+         (#{'b' := 5,
+            10 := 'a0',
+            11 := 'a1',
+            12 := 'a2',
+            13 := 'a3',
+            14 := 'a4',
+            15 := 'a5',
+            16 := 'a6',
+            17 := 'a7',
+            18 := 'a8',
+            19 := 'a9',
+            20 := 'b0',
+            21 := 'b1',
+            22 := 'b2',
+            23 := 'b3',
+            24 := 'b4',
+            25 := 'b5',
+            26 := 'b6',
+            27 := 'b7',
+            28 := 'b8',
+            29 := 'b9',
+            30 := [48 | 99, ...],
+            31 := [49 | 99, ...],
+            32 := [50 | 99, ...],
+            33 := [51 | 99, ...],
+            34 := [52 | 99, ...],
+            35 := [53 | 99, ...],
+            36 := [54 | 99, ...],
+            37 := [55 | 99, ...],
+            38 := [56 | 99, ...],
+            39 := [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] | 3,
+              ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [54 | 99, ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [48 | 99, ...],
+              31 => [49 | 99, ...],
+              32 => [50 | 99, ...],
+              33 => [51 | 99, ...],
+              34 => [52 | 99, ...],
+              35 => [53 | 99, ...],
+              36 => [54 | 99, ...],
+              37 => [55 | 99, ...],
+              38 => [56 | 99, ...],
+              39 => [57 | 99, ...],
+              <<_:16>> |
+              [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+              {[[48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...],
+                ...]} =>
+                  [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 |
+                   100 | 101,
+                   ...]} =>
+                atom() | [1..255, ...]}) will never return since it differs in the 1st argument from the success typing arguments: 
+         (#{'a' := 'gg' | 'kk' | 'sc' | 3 | 4,
+            'b' => 'other' | 3 | 4 | 5,
+            'c' => 'sc2',
+            10 => 'a0',
+            11 => 'a1',
+            12 => 'a2',
+            13 => 'a3',
+            14 => 'a4',
+            15 => 'a5',
+            16 => 'a6',
+            17 => 'a7',
+            18 => 'a8',
+            19 => 'a9',
+            20 => 'b0',
+            21 => 'b1',
+            22 => 'b2',
+            23 => 'b3',
+            24 => 'b4',
+            25 => 'b5',
+            26 => 'b6',
+            27 => 'b7',
+            28 => 'b8',
+            29 => 'b9',
+            30 => [48 | 99, ...],
+            31 => [49 | 99, ...],
+            32 => [50 | 99, ...],
+            33 => [51 | 99, ...],
+            34 => [52 | 99, ...],
+            35 => [53 | 99, ...],
+            36 => [54 | 99, ...],
+            37 => [55 | 99, ...],
+            38 => [56 | 99, ...],
+            39 => [57 | 99, ...],
+            <<_:16>> |
+            [48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57, ...] |
+            float() |
+            {[any(), ...]} |
+            #{'k16' => 'a6',
+              'k26' => 'b6',
+              'k36' => [any(), ...],
+              'map' => 'key',
+              'one' => 'small',
+              'second' => 'small',
+              'third' => 'small',
+              10 => 'a0',
+              11 => 'a1',
+              12 => 'a2',
+              13 => 'a3',
+              14 => 'a4',
+              15 => 'a5',
+              16 => 'a6',
+              17 => 'a7',
+              18 => 'a8',
+              19 => 'a9',
+              20 => 'b0',
+              21 => 'b1',
+              22 => 'b2',
+              23 => 'b3',
+              24 => 'b4',
+              25 => 'b5',
+              26 => 'b6',
+              27 => 'b7',
+              28 => 'b8',
+              29 => 'b9',
+              30 => [any(), ...],
+              31 => [any(), ...],
+              32 => [any(), ...],
+              33 => [any(), ...],
+              34 => [any(), ...],
+              35 => [any(), ...],
+              36 => [any(), ...],
+              37 => [any(), ...],
+              38 => [any(), ...],
+              39 => [any(), ...],
+              <<_:16>> | [any(), ...] | {_} => [any(), ...]} =>
+                atom() | [1..255, ...]})
+map_galore.erl:1418: Fun application with arguments 
+         (#{'s' => 'none', 'v' => 'none'}) will never return since it differs in the 1st argument from the success typing arguments: 
+         (#{'s' := 'l' | 't' | 'v',
+            'v' :=
+                'none' |
+                <<_:16>> |
+                [<<_:16>>, ...] |
+                {<<_:16>>, <<_:16>>}})
+map_galore.erl:1491: The test 
+          #{} =:= 
+          #{'a' := 1} can never evaluate to 'true'
+map_galore.erl:1492: The test 
+          #{'a' := 1} =:= 
+          #{} can never evaluate to 'true'
+map_galore.erl:1495: The test 
+          #{'a' := 1} =:= 
+          #{'a' := 2} can never evaluate to 'true'
+map_galore.erl:1496: The test 
+          #{'a' := 2} =:= 
+          #{'a' := 1} can never evaluate to 'true'
+map_galore.erl:1497: The test 
+          #{'a' := 2, 'b' := 1} =:= 
+          #{'a' := 1, 'b' := 3} can never evaluate to 'true'
+map_galore.erl:1498: The test 
+          #{'a' := 1, 'b' := 1} =:= 
+          #{'a' := 1, 'b' := 3} can never evaluate to 'true'
+map_galore.erl:1762: The call maps:get
+         ({1, 1},
+          #{{1, float()} => [101 | 108 | 112 | 116 | 117, ...]}) will never return since the success typing arguments are 
+         (any(),
+          map())
+map_galore.erl:1763: The call maps:get
+         ('a',
+          #{}) will never return since the success typing arguments are 
+         (any(),
+          map())
+map_galore.erl:1765: The call maps:get
+         ('a',
+          #{'b' => 1, 'c' => 2}) will never return since the success typing arguments are 
+         (any(),
+          map())
+map_galore.erl:186: The pattern 
+          #{'x' := 2} can never match the type 
+          #{'x' := 3}
+map_galore.erl:187: The pattern 
+          #{'x' := 3} can never match the type 
+          {'a', 'b', 'c'}
+map_galore.erl:188: The pattern 
+          #{'x' := 3} can never match the type 
+          #{'y' := 3}
+map_galore.erl:189: The pattern 
+          #{'x' := 3} can never match the type 
+          #{'x' := [101 | 104 | 114 | 116, ...]}
+map_galore.erl:2280: Cons will produce an improper list since its 2nd argument is 
+          {'b', 'a'}
+map_galore.erl:2280: The call maps:from_list
+         ([{'a', 'b'} | {'b', 'a'}]) will never return since it differs in the 1st argument from the success typing arguments: 
+         ([{_, _}])
+map_galore.erl:2281: The call maps:from_list
+         ('a') will never return since it differs in the 1st argument from the success typing arguments: 
+         ([{_, _}])
+map_galore.erl:2282: The call maps:from_list
+         (42) will never return since it differs in the 1st argument from the success typing arguments: 
+         ([{_, _}])
+map_galore.erl:997: A key of type 
+          'nonexisting' cannot exist in a map of type 
+          #{}
+map_galore.erl:998: A key of type 
+          'nonexisting' cannot exist in a map of type 
+          #{1 := 'a', 2 := 'b', 4 := 'd', 5 := 'e', float() => 'c'}
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/order b/lib/dialyzer/test/indent_SUITE_data/results/order
new file mode 100644
index 0000000000..5b0030d7b1
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/order
@@ -0,0 +1,23 @@
+
+order.erl:14: Guard test is_integer
+         (Int :: 'b') can never succeed
+order.erl:16: The variable _Else can never match since previous clauses completely covered the type 
+          'b'
+order.erl:21: Guard test is_integer
+         (Int :: 'b') can never succeed
+order.erl:23: The variable _Else can never match since previous clauses completely covered the type 
+          'b'
+order.erl:30: The variable _Else can never match since previous clauses completely covered the type 
+          'b' | 1
+order.erl:36: The variable Atom can never match since previous clauses completely covered the type 
+          1
+order.erl:37: The variable _Else can never match since previous clauses completely covered the type 
+          1
+order.erl:42: Guard test is_integer
+         (Int :: 'b') can never succeed
+order.erl:44: The variable _Else can never match since previous clauses completely covered the type 
+          'b'
+order.erl:7: Guard test is_integer
+         (Int :: 'b') can never succeed
+order.erl:9: The variable _Else can never match since previous clauses completely covered the type 
+          'b'
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/queue_use b/lib/dialyzer/test/indent_SUITE_data/results/queue_use
new file mode 100644
index 0000000000..b6604e5320
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/queue_use
@@ -0,0 +1,34 @@
+
+queue_use.erl:18: The call queue:is_empty
+         ({[], []}) does not have an opaque term of type 
+          queue:queue(_) as 1st argument
+queue_use.erl:22: The call queue:in
+         (42,
+          Q0 :: {[], []}) does not have an opaque term of type 
+          queue:queue(_) as 2nd argument
+queue_use.erl:27: The attempt to match a term of type 
+          queue:queue(_) against the pattern 
+          {"*", Q2} breaks the opacity of the term
+queue_use.erl:33: Attempt to test for equality between a term of type 
+          {[42, ...], []} and a term of opaque type 
+          queue:queue(_)
+queue_use.erl:36: The attempt to match a term of type 
+          queue:queue(_) against the pattern 
+          {F, _R} breaks the opacity of the term
+queue_use.erl:40: The call queue:out
+         ({"*", []}) does not have an opaque term of type 
+          queue:queue(_) as 1st argument
+queue_use.erl:51: The call queue_use:is_in_queue
+         (E :: 42,
+          DB :: #db{p :: [], q :: queue:queue(_)}) contains an opaque term as 2nd argument when terms of different types are expected in these positions
+queue_use.erl:56: The attempt to match a term of type 
+          #db{p :: [], q :: queue:queue(_)} against the pattern 
+          {'db', _, {L1, L2}} breaks the opacity of 
+          queue:queue(_)
+queue_use.erl:62: The call queue_use:tuple_queue
+         ({42, 'gazonk'}) does not have a term of type 
+          {_, queue:queue(_)} (with opaque subterms) as 1st argument
+queue_use.erl:65: The call queue:in
+         (F :: 42,
+          Q :: 'gazonk') does not have an opaque term of type 
+          queue:queue(_) as 2nd argument
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/rec b/lib/dialyzer/test/indent_SUITE_data/results/rec
new file mode 100644
index 0000000000..5938b18be0
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/rec
@@ -0,0 +1,15 @@
+
+rec_use.erl:17: The attempt to match a term of type 
+          rec_adt:rec() against the pattern 
+          {'rec', _, 42} breaks the opacity of the term
+rec_use.erl:18: Guard test tuple_size
+         (R :: rec_adt:rec()) breaks the opacity of its argument
+rec_use.erl:23: The call rec_adt:get_a
+         (R :: tuple()) does not have an opaque term of type 
+          rec_adt:rec() as 1st argument
+rec_use.erl:27: Attempt to test for equality between a term of type 
+          {'rec', 'gazonk', 42} and a term of opaque type 
+          rec_adt:rec()
+rec_use.erl:30: The call erlang:tuple_size
+         (rec_adt:rec()) contains an opaque term as 1st argument when a structured term of type 
+          tuple() is expected
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_construct b/lib/dialyzer/test/indent_SUITE_data/results/record_construct
new file mode 100644
index 0000000000..a1268de690
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/record_construct
@@ -0,0 +1,11 @@
+
+record_construct.erl:16: Record construction 
+          #r_opa{b :: gb_sets:set(_), c :: 42, e :: 'false'} violates the declared type of field c ::
+          boolean()
+record_construct.erl:21: Record construction 
+          #r_rem{a :: 'gazonk'} violates the declared type of field a ::
+          string()
+record_construct.erl:7: Record construction 
+          #r_loc{a :: 'gazonk', b :: 42} violates the declared type of field a ::
+          integer() and b ::
+          atom()
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_creation_diffs b/lib/dialyzer/test/indent_SUITE_data/results/record_creation_diffs
new file mode 100644
index 0000000000..9b5f9489db
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/record_creation_diffs
@@ -0,0 +1,4 @@
+
+record_creation_diffs.erl:11: Record construction 
+          #bar{some_list :: {'this', 'is', 'a', 'tuple'}} violates the declared type of field some_list ::
+          [any()]
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_match b/lib/dialyzer/test/indent_SUITE_data/results/record_match
new file mode 100644
index 0000000000..4738a4b0c9
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/record_match
@@ -0,0 +1,4 @@
+
+record_match.erl:17: Matching of pattern 
+          {'b_literal', 'undefined'} tagged with a record name violates the declared type of 
+          #b_local{} | #b_remote{}
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_pat b/lib/dialyzer/test/indent_SUITE_data/results/record_pat
new file mode 100644
index 0000000000..cf9247d5a8
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/record_pat
@@ -0,0 +1,4 @@
+
+record_pat.erl:14: Matching of pattern 
+          {'foo', 'baz'} tagged with a record name violates the declared type of 
+          #foo{bar :: integer()}
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_send_test b/lib/dialyzer/test/indent_SUITE_data/results/record_send_test
new file mode 100644
index 0000000000..51d8e1a852
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/record_send_test
@@ -0,0 +1,6 @@
+
+record_send_test.erl:30: The call erlang:'!'
+         (Rec1 :: #rec1{a :: 'a', b :: 'b', c :: 'c'},
+          'hello_again') will never return since it differs in the 1st argument from the success typing arguments: 
+         (atom() | pid() | port() | {atom(), atom()},
+          any())
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_test b/lib/dialyzer/test/indent_SUITE_data/results/record_test
new file mode 100644
index 0000000000..1574459578
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/record_test
@@ -0,0 +1,6 @@
+
+record_test.erl:19: Matching of pattern 
+          {'foo', _} tagged with a record name violates the declared type of 
+          'foo'
+record_test.erl:21: The variable _ can never match since previous clauses completely covered the type 
+          'foo'
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_update b/lib/dialyzer/test/indent_SUITE_data/results/record_update
new file mode 100644
index 0000000000..6e4124552e
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/record_update
@@ -0,0 +1,3 @@
+
+record_update.erl:7: Invalid type specification for function record_update:quux/2. The success typing is 
+          (#foo{bar :: atom()}, atom()) -> #foo{bar :: atom()}
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour b/lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour
new file mode 100644
index 0000000000..f0e41d024a
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour
@@ -0,0 +1,23 @@
+
+sample_callback_wrong.erl:16: The inferred return type of sample_callback_2/0 
+         (42) has nothing in common with 
+          atom(), which is the expected return type for the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:17: The inferred return type of sample_callback_3/0 
+         ('fair') has nothing in common with 
+          'fail' | {'ok', 1..255}, which is the expected return type for the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:18: The inferred return type of sample_callback_4/1 
+         ('fail') has nothing in common with 
+          'ok', which is the expected return type for the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:20: The inferred return type of sample_callback_5/1 
+         (string()) has nothing in common with 
+          'fail' | 'ok', which is the expected return type for the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:20: The inferred type for the 1st argument of sample_callback_5/1 (
+          atom()) is not a supertype of 
+          1..255, which is expected type for this argument in the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:22: The inferred return type of sample_callback_6/3 
+         ({'okk', number()}) has nothing in common with 
+          'fail' | {'ok', 1..255}, which is the expected return type for the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:22: The inferred type for the 3rd argument of sample_callback_6/3 (
+          atom()) is not a supertype of 
+          string(), which is expected type for this argument in the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:4: Undefined callback function sample_callback_1/0 (behaviour sample_behaviour)
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/simple b/lib/dialyzer/test/indent_SUITE_data/results/simple
new file mode 100644
index 0000000000..bafe334405
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/simple
@@ -0,0 +1,289 @@
+
+exact_api.erl:17: The call exact_api:set_type
+         (A ::
+              #digraph{vtab :: 'notable',
+                       etab :: 'notable',
+                       ntab :: 'notable',
+                       cyclic :: 'true'}) does not have an opaque term of type 
+          digraph:graph() as 1st argument
+exact_api.erl:23: The call digraph:delete
+         (G ::
+              #digraph{vtab :: 'notable',
+                       etab :: 'notable',
+                       ntab :: 'notable',
+                       cyclic :: 'true'}) does not have an opaque term of type 
+          digraph:graph() as 1st argument
+exact_api.erl:55: The attempt to match a term of type 
+          exact_adt:exact_adt() against the pattern 
+          {'exact_adt'} breaks the opacity of the term
+exact_api.erl:59: The call exact_adt:exact_adt_set_type2
+         (A :: #exact_adt{}) does not have an opaque term of type 
+          exact_adt:exact_adt() as 1st argument
+is_rec.erl:10: The call erlang:is_record
+         (simple1_adt:d1(),
+          'r',
+          2) contains an opaque term as 1st argument when terms of different types are expected in these positions
+is_rec.erl:15: The call erlang:is_record
+         (A :: simple1_adt:d1(),
+          'r',
+          I :: 1 | 2 | 3) contains an opaque term as 1st argument when terms of different types are expected in these positions
+is_rec.erl:19: Guard test is_record
+         (A :: simple1_adt:d1(),
+          'r',
+          2) breaks the opacity of its argument
+is_rec.erl:23: Guard test is_record
+         ({simple1_adt:d1(), 1},
+          'r',
+          2) breaks the opacity of its argument
+is_rec.erl:41: The call erlang:is_record
+         (A :: simple1_adt:d1(),
+          R :: 'a') contains an opaque term as 1st argument when terms of different types are expected in these positions
+is_rec.erl:45: The call erlang:is_record
+         (A :: simple1_adt:d1(),
+          A :: simple1_adt:d1(),
+          1) contains an opaque term as 2nd argument when terms of different types are expected in these positions
+is_rec.erl:49: The call erlang:is_record
+         (A :: simple1_adt:d1(),
+          any(),
+          1) contains an opaque term as 1st argument when terms of different types are expected in these positions
+is_rec.erl:53: The call erlang:is_record
+         (A :: simple1_adt:d1(),
+          A :: simple1_adt:d1(),
+          any()) contains an opaque term as 2nd argument when terms of different types are expected in these positions
+is_rec.erl:57: Guard test is_record
+         (A :: simple1_adt:d1(),
+          'r',
+          2) breaks the opacity of its argument
+is_rec.erl:61: The record 
+          #r{f1 :: simple1_adt:d1()} violates the declared type for #r{}
+is_rec.erl:65: The call erlang:is_record
+         ({simple1_adt:d1(), 1},
+          'r',
+          2) contains an opaque term as 1st argument when terms of different types are expected in these positions
+rec_api.erl:104: Matching of pattern 
+          {'r2', 10} tagged with a record name violates the declared type of 
+          #r2{f1 :: 10}
+rec_api.erl:113: The attempt to match a term of type 
+          #r3{f1 :: queue:queue(_)} against the pattern 
+          {'r3', 'a'} breaks the opacity of 
+          queue:queue(_)
+rec_api.erl:118: Record construction 
+          #r3{f1 :: 10} violates the declared type of field f1 ::
+          queue:queue(_)
+rec_api.erl:123: The attempt to match a term of type 
+          #r3{f1 :: 10} against the pattern 
+          {'r3', 10} breaks the opacity of 
+          queue:queue(_)
+rec_api.erl:24: Record construction 
+          #r1{f1 :: 10} violates the declared type of field f1 ::
+          rec_api:a()
+rec_api.erl:29: Matching of pattern 
+          {'r1', 10} tagged with a record name violates the declared type of 
+          #r1{f1 :: 10}
+rec_api.erl:33: The attempt to match a term of type 
+          rec_adt:r1() against the pattern 
+          {'r1', 'a'} breaks the opacity of the term
+rec_api.erl:35: Invalid type specification for function rec_api:adt_t1/1. The success typing is 
+          (#r1{f1 :: 'a'}) -> #r1{f1 :: 'a'}
+rec_api.erl:40: The specification for rec_api:adt_r1/0 has an opaque subtype 
+          rec_adt:r1() which is violated by the success typing 
+          () -> #r1{f1 :: 'a'}
+rec_api.erl:85: The attempt to match a term of type 
+          rec_adt:f() against the record field 'f' declared to be of type 
+          rec_api:f() breaks the opacity of the term
+rec_api.erl:99: Record construction 
+          #r2{f1 :: 10} violates the declared type of field f1 ::
+          rec_api:a()
+simple1_api.erl:113: The test 
+          simple1_api:d1() =:= 
+          simple1_api:d2() can never evaluate to 'true'
+simple1_api.erl:118: Guard test 
+          simple1_api:d2() =:= 
+          A :: simple1_api:d1() can never succeed
+simple1_api.erl:142: Attempt to test for equality between a term of type 
+          simple1_adt:o2() and a term of opaque type 
+          simple1_adt:o1()
+simple1_api.erl:148: Guard test 
+          simple1_adt:o2() =:= 
+          A :: simple1_adt:o1() contains opaque terms as 1st and 2nd arguments
+simple1_api.erl:154: Attempt to test for inequality between a term of type 
+          simple1_adt:o2() and a term of opaque type 
+          simple1_adt:o1()
+simple1_api.erl:160: Attempt to test for inequality between a term of type 
+          simple1_adt:o2() and a term of opaque type 
+          simple1_adt:o1()
+simple1_api.erl:165: Attempt to test for equality between a term of type 
+          simple1_adt:c2() and a term of opaque type 
+          simple1_adt:c1()
+simple1_api.erl:181: Guard test 
+          A :: simple1_adt:d1() =< 
+          B :: simple1_adt:d2() contains opaque terms as 1st and 2nd arguments
+simple1_api.erl:185: Guard test 
+          'a' =< 
+          B :: simple1_adt:d2() contains an opaque term as 2nd argument
+simple1_api.erl:189: Guard test 
+          A :: simple1_adt:d1() =< 
+          'd' contains an opaque term as 1st argument
+simple1_api.erl:197: The type test is_integer
+         (A :: simple1_adt:d1()) breaks the opacity of the term A::
+          simple1_adt:d1()
+simple1_api.erl:221: Guard test 
+          A :: simple1_api:i1() > 
+          3 can never succeed
+simple1_api.erl:225: Guard test 
+          A :: simple1_adt:i1() > 
+          3 contains an opaque term as 1st argument
+simple1_api.erl:233: Guard test 
+          A :: simple1_adt:i1() < 
+          3 contains an opaque term as 1st argument
+simple1_api.erl:239: Guard test 
+          A :: 1 > 
+          3 can never succeed
+simple1_api.erl:243: Guard test 
+          A :: 1 > 
+          3 can never succeed
+simple1_api.erl:257: Guard test is_function
+         (T :: simple1_api:o1()) can never succeed
+simple1_api.erl:265: Guard test is_function
+         (T :: simple1_adt:o1()) breaks the opacity of its argument
+simple1_api.erl:269: The type test is_function
+         (T :: simple1_adt:o1()) breaks the opacity of the term T::
+          simple1_adt:o1()
+simple1_api.erl:274: Guard test is_function
+         (T :: simple1_api:o1(),
+          A :: simple1_api:i1()) can never succeed
+simple1_api.erl:284: Guard test is_function
+         (T :: simple1_adt:o1(),
+          A :: simple1_adt:i1()) breaks the opacity of its argument
+simple1_api.erl:289: The type test is_function
+         (T :: simple1_adt:o1(),
+          A :: simple1_adt:i1()) breaks the opacity of the term T::
+          simple1_adt:o1()
+simple1_api.erl:294: The call erlang:is_function
+         (T :: simple1_api:o1(),
+          A :: simple1_adt:i1()) contains an opaque term as 2nd argument when terms of different types are expected in these positions
+simple1_api.erl:300: The type test is_function
+         (T :: simple1_adt:o1(),
+          A :: simple1_api:i1()) breaks the opacity of the term T::
+          simple1_adt:o1()
+simple1_api.erl:306: Guard test 
+          B :: simple1_api:b2() =:= 
+          'true' can never succeed
+simple1_api.erl:315: Guard test 
+          A :: simple1_api:b1() =:= 
+          'false' can never succeed
+simple1_api.erl:319: Guard test not(and
+         ('true',
+          'true')) can never succeed
+simple1_api.erl:337: Clause guard cannot succeed.
+simple1_api.erl:342: Guard test 
+          B :: simple1_adt:b2() =:= 
+          'true' contains an opaque term as 1st argument
+simple1_api.erl:347: Guard test 
+          A :: simple1_adt:b1() =:= 
+          'true' contains an opaque term as 1st argument
+simple1_api.erl:355: Invalid type specification for function simple1_api:bool_adt_t6/1. The success typing is 
+          ('true') -> 1
+simple1_api.erl:365: Clause guard cannot succeed.
+simple1_api.erl:368: Invalid type specification for function simple1_api:bool_adt_t8/2. The success typing is 
+          (boolean(), boolean()) -> 1
+simple1_api.erl:378: Clause guard cannot succeed.
+simple1_api.erl:381: Invalid type specification for function simple1_api:bool_adt_t9/2. The success typing is 
+          ('false', 'false') -> 1
+simple1_api.erl:407: The size 
+          simple1_adt:i1() breaks the opacity of A
+simple1_api.erl:418: The attempt to match a term of type 
+          non_neg_integer() against the variable A breaks the opacity of 
+          simple1_adt:i1()
+simple1_api.erl:425: The attempt to match a term of type 
+          non_neg_integer() against the variable B breaks the opacity of 
+          simple1_adt:i1()
+simple1_api.erl:432: The pattern 
+          <<_:B>> can never match the type 
+          any()
+simple1_api.erl:448: The attempt to match a term of type 
+          non_neg_integer() against the variable Sz breaks the opacity of 
+          simple1_adt:i1()
+simple1_api.erl:460: The attempt to match a term of type 
+          simple1_adt:bit1() against the pattern 
+          <<_/binary>> breaks the opacity of the term
+simple1_api.erl:478: The call 'foo':A
+         (A :: simple1_adt:a()) breaks the opacity of the term A :: 
+          simple1_adt:a()
+simple1_api.erl:486: The call A:'foo'
+         (A :: simple1_adt:a()) breaks the opacity of the term A :: 
+          simple1_adt:a()
+simple1_api.erl:499: The call 'foo':A
+         (A :: simple1_api:i()) requires that A is of type 
+          atom() not 
+          simple1_api:i()
+simple1_api.erl:503: The call 'foo':A
+         (A :: simple1_adt:i()) requires that A is of type 
+          atom() not 
+          simple1_adt:i()
+simple1_api.erl:507: The call A:'foo'
+         (A :: simple1_api:i()) requires that A is of type 
+          atom() not 
+          simple1_api:i()
+simple1_api.erl:511: The call A:'foo'
+         (A :: simple1_adt:i()) requires that A is of type 
+          atom() not 
+          simple1_adt:i()
+simple1_api.erl:519: Guard test 
+          A :: simple1_adt:d2() == 
+          B :: simple1_adt:d1() contains opaque terms as 1st and 2nd arguments
+simple1_api.erl:534: Guard test 
+          A :: simple1_adt:d1() >= 
+          3 contains an opaque term as 1st argument
+simple1_api.erl:536: Guard test 
+          A :: simple1_adt:d1() == 
+          3 contains an opaque term as 1st argument
+simple1_api.erl:538: Guard test 
+          A :: simple1_adt:d1() =:= 
+          3 contains an opaque term as 1st argument
+simple1_api.erl:548: The call erlang:'<'
+         (A :: simple1_adt:d1(),
+          3) contains an opaque term as 1st argument when terms of different types are expected in these positions
+simple1_api.erl:558: The call erlang:'=<'
+         (A :: simple1_adt:d1(),
+          B :: simple1_adt:d2()) contains opaque terms as 1st and 2nd arguments when terms of different types are expected in these positions
+simple1_api.erl:565: Guard test 
+          {digraph:graph(), 3} > 
+          {digraph:graph(), atom() | ets:tid()} contains an opaque term as 2nd argument
+simple1_api.erl:91: The specification for simple1_api:tup/0 has an opaque subtype 
+          simple1_adt:tuple1() which is violated by the success typing 
+          () -> {'a', 'b'}
+simple2_api.erl:100: The call lists:flatten
+         (A :: simple1_adt:tuple1()) contains an opaque term as 1st argument when a structured term of type 
+          [any()] is expected
+simple2_api.erl:116: The call lists:flatten
+         ({simple1_adt:tuple1()}) will never return since it differs in the 1st argument from the success typing arguments: 
+         ([any()])
+simple2_api.erl:121: Guard test 
+          {simple1_adt:d1(), 3} > 
+          {simple1_adt:d1(), simple1_adt:tuple1()} contains an opaque term as 2nd argument
+simple2_api.erl:125: The call erlang:tuple_to_list
+         (B :: simple1_adt:tuple1()) contains an opaque term as 1st argument when a structured term of type 
+          tuple() is expected
+simple2_api.erl:31: The call erlang:'!'
+         (A :: simple1_adt:d1(),
+          'foo') contains an opaque term as 1st argument when terms of different types are expected in these positions
+simple2_api.erl:35: The call erlang:send
+         (A :: simple1_adt:d1(),
+          'foo') contains an opaque term as 1st argument when terms of different types are expected in these positions
+simple2_api.erl:51: The call erlang:'<'
+         (A :: simple1_adt:d1(),
+          3) contains an opaque term as 1st argument when terms of different types are expected in these positions
+simple2_api.erl:59: The call lists:keysearch
+         (1,
+          A :: simple1_adt:d1(),
+          []) contains an opaque term as 2nd argument when terms of different types are expected in these positions
+simple2_api.erl:67: The call lists:keysearch
+         ('key',
+          1,
+          A :: simple1_adt:tuple1()) contains an opaque term as 3rd argument when terms of different types are expected in these positions
+simple2_api.erl:96: The call lists:keyreplace
+         ('a',
+          1,
+          [{1, 2}],
+          A :: simple1_adt:tuple1()) contains an opaque term as 4th argument when terms of different types are expected in these positions
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/suppress_request b/lib/dialyzer/test/indent_SUITE_data/results/suppress_request
new file mode 100644
index 0000000000..c08f1798c1
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/suppress_request
@@ -0,0 +1,11 @@
+
+suppress_request.erl:21: Expression produces a value of type 
+          {'a', 'b'}, but this value is unmatched
+suppress_request.erl:25: Expression produces a value of type 
+          {'a', 'b'}, but this value is unmatched
+suppress_request.erl:39: Guard test 
+          2 =:= 
+          A :: fun((none()) -> no_return()) can never succeed
+suppress_request.erl:7: Type specification suppress_request:test1
+          ('a' | 'b') -> 'ok' is a subtype of the success typing: suppress_request:test1
+          ('a' | 'b' | 'c') -> 'ok'
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/trec b/lib/dialyzer/test/indent_SUITE_data/results/trec
new file mode 100644
index 0000000000..f19f728750
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/trec
@@ -0,0 +1,10 @@
+
+trec.erl:29: The call trec:mk_foo_loc
+         (42,
+          any()) will never return since it differs in the 1st argument from the success typing arguments: 
+         ('undefined',
+          atom())
+trec.erl:32: Record construction violates the declared type for #foo{} since variable A cannot be of type 
+          atom()
+trec.erl:39: Record construction violates the declared type for #foo{} since variable A cannot be of type 
+          atom()
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/whereis_control_flow1 b/lib/dialyzer/test/indent_SUITE_data/results/whereis_control_flow1
new file mode 100644
index 0000000000..0e733fced6
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/results/whereis_control_flow1
@@ -0,0 +1,4 @@
+
+whereis_control_flow1.erl:13: The call erlang:register
+         (AnAtom :: atom(),
+          Pid :: pid()) might fail due to a possible race condition caused by its combination with the erlang:whereis(AnAtom::any()) call in whereis_control_flow1.erl on line 8
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/abs.erl b/lib/dialyzer/test/indent_SUITE_data/src/abs.erl
new file mode 100644
index 0000000000..0e38c3dbb7
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/abs.erl
@@ -0,0 +1,78 @@
+-module(abs).
+
+%% OTP-12948. erlang:abs/1 bug fix.
+
+-export([t/0]).
+
+t() ->
+    Fs = [fun i1/0, fun i2/0, fun i3/0, fun i4/0, fun f1/0, fun erl_551/0],
+    _ = [catch F() || F <- Fs],
+    ok.
+
+i1() ->
+    A = int(),
+    I1 = i1(A),
+    true = I1 < 2,
+    true = I1 < 1. % can never match
+
+-spec i1(neg_integer()) -> non_neg_integer().
+
+i1(A) when is_integer(A), A < 0 ->
+    abs(A).
+
+i2() ->
+    A = int(),
+    I2 = i2(A),
+    true = I2 < 1,
+    true = I2 < 0. % can never match
+
+-spec i2(non_neg_integer()) -> non_neg_integer().
+
+i2(A) when is_integer(A), A >= 0 ->
+    abs(A).
+
+i3() ->
+    A = int(),
+    I3 = i3(A),
+    true = I3 < -1,
+    true = I3 < 0. % can never match
+
+-spec i3(integer()) -> non_neg_integer().
+
+i3(A) when is_integer(A) ->
+    abs(A).
+
+i4() ->
+    A = int(),
+    I4 = i4(A),
+    true = I4 =:= 0 orelse I4 =:= 1,
+    true = I4 < 0 orelse I4 > 1. % can never match
+
+-spec i4(integer()) -> number().
+
+i4(A) when A =:= -1; A =:= 0; A =:= 1 ->
+    abs(A).
+
+f1() ->
+    F1 = f1(float()),
+    math:sqrt(F1).
+
+f1(A) ->
+    abs(A).
+
+erl_551() ->
+    accept(9),
+    accept(-3).
+
+accept(Number) when abs(Number) >= 8 -> first;
+accept(_Number) -> second.
+
+-spec int() -> integer().
+
+int() ->
+    foo:bar().
+
+-spec float() -> float().
+
+float() ->
+    math:sqrt(1.0).
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/app_call.erl b/lib/dialyzer/test/indent_SUITE_data/src/app_call.erl
new file mode 100644
index 0000000000..54d178d29a
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/app_call.erl
@@ -0,0 +1,17 @@
+-module(app_call).
+-export([test/1]).
+
+test(m) ->
+  M = get_mod(),
+  M:foo();
+test(f) ->
+  F = get_fun(),
+  mod:F();
+test(_) ->
+  ok.
+
+get_mod() ->
+  42.
+
+get_fun() ->
+  {gazonk, []}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/blame_contract_range.erl b/lib/dialyzer/test/indent_SUITE_data/src/blame_contract_range.erl
new file mode 100644
index 0000000000..efd3332b44
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/blame_contract_range.erl
@@ -0,0 +1,16 @@
+%%-----------------------------------------------------------------------
+%% A test where the contract is wrongly specified by the programmer;
+%% however, this is found only by refinement.
+%% Dialyzer in R14B01 and prior gave a confusing (if not bogus) warning
+%% for this case.  Corrected in R14B02.
+%%-----------------------------------------------------------------------
+-module(blame_contract_range).
+
+-export([foo/0]).
+
+foo() ->
+  bar(b).
+
+-spec bar(atom()) -> a.
+bar(a) -> a;
+bar(b) -> b.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/bs_fail_constr.erl b/lib/dialyzer/test/indent_SUITE_data/src/bs_fail_constr.erl
new file mode 100644
index 0000000000..8c1f8c009a
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/bs_fail_constr.erl
@@ -0,0 +1,15 @@
+-module(bs_fail_constr).
+
+-export([w1/1, w2/1, w3/1, w4/1]).
+
+w1(V) when is_float(V) ->
+  <<V/integer>>.
+
+w2(V) when is_atom(V) ->
+  <<V/binary>>.
+
+w3(S) when is_integer(S), S < 0 ->
+  <<42:S/integer>>.
+
+w4(V) when is_float(V) ->
+  <<V/utf32>>.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_behaviour.erl b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_behaviour.erl
new file mode 100644
index 0000000000..c4e5203448
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_behaviour.erl
@@ -0,0 +1,11 @@
+-module(my_behaviour).
+
+-callback callback_init(Parent :: pid()) -> {'ok', State::term()}.
+
+-callback callback_cast(State::term(), From::pid(), Msg::term()) ->
+    {'noreply', NewState::term()}.
+
+-callback callback_call(State::term(), From::pid(), Msg::term()) ->
+    {'reply', NewState::term(), Reply::term()}.
+
+-callback callback_exit(State::term()) -> 'ok'.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_correct.erl b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_correct.erl
new file mode 100644
index 0000000000..041b4ac56c
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_correct.erl
@@ -0,0 +1,59 @@
+-module(my_callbacks_correct).
+
+-export([
+	 callback_init/1
+	 , callback_call/3
+	 , callback_cast/3
+	 , callback_exit/1
+	]).
+
+-record(state, {
+	  parent           :: pid(),
+	  status    = init :: 'init' | 'open' | 'closed',
+	  subscribe = []   :: list({pid(), integer()}),
+	  counter   = 1    :: integer()
+	 }).
+
+-type state()        :: #state{}.
+
+-type cast_message() :: 'open' | 'closed'.
+
+-type call_message() :: 'subscribe' | 'unsubscribe'.
+-type call_reply()   :: 'accepted' | 'rejected'.
+
+-spec callback_init(Parent::pid()) -> {'ok', state()}.
+
+callback_init(Parent) ->
+    {ok, #state{parent = Parent}}.
+
+-spec callback_cast(state(), pid(), cast_message()) -> {'noreply', state()}.
+
+callback_cast(#state{parent = Pid} = State, Pid, Message)
+  when Message =:= 'open'; Message =:= 'close' ->
+    {noreply, State#state{status = Message}};
+callback_cast(State, _Pid, _Message) ->
+    {noreply, State}.
+
+-spec callback_call(state(), pid(), call_message()) ->
+			   {'reply', state(), call_reply()}.
+
+callback_call(#state{status = open, subscribe = Subscribers} = State,
+	      Pid, Message)
+  when Message =:= 'subscribe';
+       Message =:= 'unsubscribe' ->
+    NewState =
+	case Message of
+	    subscribe ->
+		N = State#state.counter,
+		State#state{subscribe = [{Pid, N}|Subscribers], counter = N+1};
+	    unsubscribe ->
+		State#state{subscribe = lists:keydelete(Pid, 1, Subscribers)}
+	end,
+    {reply, NewState, accepted};
+callback_call(State, _Pid, _Message) ->
+    {reply, State, rejected}.
+
+-spec callback_exit(state()) -> 'ok'.
+
+callback_exit(_State) ->
+    ok.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
new file mode 100644
index 0000000000..0459622dc1
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
@@ -0,0 +1,61 @@
+-module(my_callbacks_wrong).
+
+-export([
+	 callback_init/1
+	 , callback_call/3
+	 , callback_cast/3
+	 , callback_exit/1
+	]).
+
+-behaviour(my_behaviour).
+
+-record(state, {
+	  parent           :: pid(),
+	  status    = init :: 'init' | 'open' | 'closed',
+	  subscribe = []   :: list({pid(), integer()}),
+	  counter   = 1    :: integer()
+	 }).
+
+-type state()        :: #state{}.
+
+-type cast_message() :: 'open' | 'closed'.
+
+-type call_message() :: 'subscribe' | 'unsubscribe'.
+-type call_reply()   :: 'accepted' | 'rejected'.
+
+-spec callback_init(Parent::pid()) -> state().    %% Wrong return spec
+
+callback_init(Parent) -> #state{parent = Parent}. %% Wrong return
+
+-spec callback_cast(state(), pid() | atom(), cast_message()) ->
+			   {'noreply' | 'reply', state()}. %% More generic spec
+
+callback_cast(#state{parent = Pid} = State, Pid, Message)
+  when Message =:= 'open'; Message =:= 'close' ->
+    {noreply, State#state{status = Message}};
+callback_cast(State, _Pid, _Message) ->
+    {noreply, State}.
+
+-spec callback_call(state(), atom(), call_message()) ->      %% Wrong arg spec
+			   {'reply', state(), call_reply()}.
+
+callback_call(#state{status = open, subscribe = Subscribers} = State,
+	      Pid, Message)
+  when Message =:= 'subscribe';
+       Message =:= 'unsubscribe' ->
+    NewState =
+	case Message of
+	    subscribe ->
+		N = State#state.counter,
+		State#state{subscribe = [{Pid, N}|Subscribers], counter = N+1};
+	    unsubscribe ->
+		State#state{subscribe = lists:keydelete(Pid, 1, Subscribers)}
+	end,
+    {reply, NewState, accepted};
+callback_call(State, _Pid, _Message) ->
+    {reply, State, rejected}.
+
+-spec callback_exit(state()) -> ok.
+
+callback_exit(_State) ->
+    ok.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/contract3.erl b/lib/dialyzer/test/indent_SUITE_data/src/contract3.erl
new file mode 100644
index 0000000000..a6ce91882e
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/contract3.erl
@@ -0,0 +1,40 @@
+%%%-------------------------------------------------------------------
+%%% File    : contract3.erl
+%%% Author  : Tobias Lindahl <tobiasl@csd.uu.se>
+%%% Description : Check overloaded domains
+%%%
+%%% Created :  2 Nov 2007 by Tobias Lindahl <tobiasl@csd.uu.se>
+%%%-------------------------------------------------------------------
+-module(contract3).
+
+-export([t/3]).
+
+t(X, Y, Z) ->
+  t1(X),
+  t2(X, Y),
+  t3(X, Y, Z).
+
+-spec t1(atom()|integer()) -> integer();
+        (atom()|list()) -> atom().
+
+t1(X) ->
+  f(X).
+
+-spec t2(atom(), integer()) -> integer();
+        (atom(), list()) -> atom().
+
+t2(X, Y) ->
+  g(X, Y).
+
+-spec t3(atom(), integer(), list()) -> integer();
+        (X, integer(), list()) -> X.
+
+t3(X, Y, Z) ->
+  X.
+
+%% dummy functions below
+
+f(X) -> X.
+
+g(X, Y) when is_atom(X), is_integer(Y) -> Y;
+g(X, Y) when is_atom(X), is_list(Y) -> X.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/contracts_with_subtypes.erl b/lib/dialyzer/test/indent_SUITE_data/src/contracts_with_subtypes.erl
new file mode 100644
index 0000000000..dbabd904c2
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/contracts_with_subtypes.erl
@@ -0,0 +1,300 @@
+-module(contracts_with_subtypes).
+
+-compile(export_all).
+
+%===============================================================================
+
+-spec extract() -> 'ok'.
+
+extract() ->
+   case dz_extract() of
+       {ok, Val} -> Val;
+       error -> exit(boom)
+   end.
+
+-spec dz_extract() -> RetValue when
+     FileList :: something,
+     RetValue :: {ok, FileList} | error.
+
+dz_extract() -> get(foo).
+
+%-------------------------------------------------------------------------------
+
+-spec extract2() -> 'ok'.
+
+extract2() ->
+   case dz_extract2() of
+       {ok, Val} -> Val;
+       error -> exit(boom)
+   end.
+
+-spec dz_extract2() -> RetValue when
+     RetValue :: {ok, FileList} | error,
+     FileList :: something.
+
+dz_extract2() -> get(foo).
+
+%===============================================================================
+
+-spec foo1(Arg1) -> Res when
+      Arg1 :: atom(),
+      Res  :: atom().
+
+foo1(X) -> X.
+
+-spec foo2(Arg1) -> Res when
+      Arg1 :: Arg2,
+      Arg2 :: atom(),
+      Res  :: atom().
+
+foo2(X) -> X.
+
+-spec foo3(Arg1) -> Res when
+      Arg2 :: atom(),
+      Arg1 :: Arg2,
+      Res  :: atom().
+
+foo3(X) -> X.
+
+-spec foo4(Type) -> Type when is_subtype(Type, atom()).
+
+foo4(X) -> X.
+
+-spec foo5(Type :: atom()) -> Type :: atom().
+
+foo5(X) -> X.
+
+-spec foo6(Type) -> Type when Type :: atom().
+
+foo6(X) -> X.
+
+-spec foo7(Type) -> Type.
+
+foo7(X) -> X.
+
+%-------------------------------------------------------------------------------
+
+bar(1) -> foo1(5);
+bar(2) -> foo2(5);
+bar(3) -> foo3(5);
+bar(4) -> foo4(5);
+bar(5) -> foo5(5);
+bar(6) -> foo6(5);
+bar(7) -> foo7(5).
+
+wrong_foo6() ->
+    b = foo6(a).
+
+%===============================================================================
+
+-spec rec_arg(Arg) -> ok when
+      Arg :: {a, A} | {b, B},
+      A   :: a | {b, B},
+      B   :: b | {a, A}.
+
+rec_arg(X) -> get(X).
+
+c(aa) -> rec_arg({a, a});
+c(bb) -> rec_arg({b, b});
+c(abb) -> rec_arg({a, {b, b}});
+c(baa) -> rec_arg({b, {a, a}});
+c(abaa) -> rec_arg({a, {b, {a, a}}});
+c(babb) -> rec_arg({b, {a, {b, b}}});
+c(ababb) -> rec_arg({a, {b, {a, {b, b}}}});
+c(babaa) -> rec_arg({b, {a, {b, {a, a}}}}).
+
+w(ab) -> rec_arg({a, b}); % breaks the contract
+w(ba) -> rec_arg({b, a}); % breaks the contract
+w(aba) -> rec_arg({a, {b, a}}); % no longer breaks the contract
+w(bab) -> rec_arg({b, {a, b}}); % breaks the contract
+w(abab) -> rec_arg({a, {b, {a, b}}}); % no longer breaks the contract
+w(baba) -> rec_arg({b, {a, {b, a}}}); % no longer breaks the contract
+w(ababa) -> rec_arg({a, {b, {a, {b, a}}}});
+w(babab) -> rec_arg({b, {a, {b, {a, b}}}}).
+
+%% For comparison: the same thing with types
+
+-type ab() :: {a, a()} | {b, b()}.
+-type a() :: a | {b, b()}.
+-type b() :: b | {a, a()}.
+
+-spec rec2(Arg) -> ok when
+      Arg :: ab().
+
+rec2(X) -> get(X).
+
+d(aa) -> rec2({a, a});
+d(bb) -> rec2({b, b});
+d(abb) -> rec2({a, {b, b}});
+d(baa) -> rec2({b, {a, a}});
+d(abaa) -> rec2({a, {b, {a, a}}});
+d(babb) -> rec2({b, {a, {b, b}}});
+d(ababb) -> rec2({a, {b, {a, {b, b}}}});
+d(babaa) -> rec2({b, {a, {b, {a, a}}}}).
+
+q(ab) -> rec2({a, b}); % breaks the contract
+q(ba) -> rec2({b, a}); % breaks the contract
+q(aba) -> rec2({a, {b, a}}); % breaks the contract
+q(bab) -> rec2({b, {a, b}}); % breaks the contract
+q(abab) -> rec2({a, {b, {a, b}}}); % breaks the contract
+q(baba) -> rec2({b, {a, {b, a}}}); % breaks the contract
+q(ababa) -> rec2({a, {b, {a, {b, a}}}}); % breaks the contract
+q(babab) -> rec2({b, {a, {b, {a, b}}}}); % breaks the contract
+q(ababab) -> rec2({a, {b, {a, {b, {a, b}}}}});
+q(bababa) -> rec2({b, {a, {b, {a, {b, a}}}}});
+q(abababa) -> rec2({a, {b, {a, {b, {a, {b, a}}}}}});
+q(bababab) -> rec2({b, {a, {b, {a, {b, {a, b}}}}}}).
+
+%===============================================================================
+
+-type dublo(X) :: {X, X}.
+
+-type weird(X,Y) :: {X, Y, X, X}.
+
+-spec forfun(dublo(Var)) -> ok when Var :: atom().
+
+forfun(_) -> ok.
+
+-spec forfun2(weird(Var, Var)) -> ok when Var :: atom().
+
+forfun2(_) -> ok.
+
+%===============================================================================
+
+-spec shallow(X) -> {ok, X} | {ok, X, file:filename()} | err1 | err2.
+
+shallow(X) -> get(X).
+
+st(X) when is_atom(X) ->
+    case shallow(X) of
+	err1 -> ok;
+	err2 -> ok;
+	{ok, X} -> ok;
+	{ok, X, Res} ->
+	    case Res of
+		1      -> bad;
+		_Other -> ok
+	    end;
+	alpha -> bad;
+	{ok, 42} -> ok;
+	42 -> bad
+    end.
+
+%-------------------------------------------------------------------------------
+
+-spec deep(X) -> Ret when
+      Ret :: {ok, X} | Err,
+      Err :: err1 | err2.
+
+deep(X) -> get(X).
+
+dt(X) when is_atom(X) ->
+    case deep(X) of
+	err1 -> ok;
+	err2 -> ok;
+	{ok, X} -> ok;
+	alpha -> bad;
+	{ok, 42} -> ok;
+	42 -> bad
+    end.
+
+%-------------------------------------------------------------------------------
+
+-type local_errors() :: err1 | err2.
+
+-spec deep2(X) -> Ret when
+      Ret :: {ok, X} | Err,
+      Err :: local_errors().
+
+deep2(X) -> get(X).
+
+dt2(X) when is_atom(X) ->
+    case deep2(X) of
+	err1 -> ok;
+	err2 -> ok;
+	{ok, X} -> ok;
+	alpha -> bad;
+	{ok, 42} -> ok;
+	42 -> bad
+    end.
+
+%-------------------------------------------------------------------------------
+
+-spec deep3(X) -> Ret when
+      Ret :: {ok, X, file:filename()} | Err,
+      Err :: local_errors().
+
+deep3(X) -> get(X).
+
+dt3(X) when is_atom(X) ->
+    case deep3(X) of
+	err1 -> ok;
+	err2 -> ok;
+	{ok, X, Res} ->
+	    case Res of
+		1      -> bad;
+		_Other -> ok
+	    end;
+	{ok, X} -> bad;
+	alpha -> bad;
+	{ok, 42} -> bad;
+	42 -> bad
+    end.
+
+%===============================================================================
+
+-spec flat_ets_new(Name, Options) -> atom() when
+      Name :: atom(),
+      Options :: [Option],
+      Option :: set
+              | ordered_set
+              | bag
+              | duplicate_bag
+              | public
+              | protected
+              | private
+              | named_table
+              | {keypos, integer()}
+              | {heir, pid(), term()}
+              | {heir, none}
+              | {write_concurrency, boolean()}
+              | {read_concurrency, boolean()}
+              | compressed.
+
+flat_ets_new(Name, Options) ->
+    get({Name, Options}).
+
+flat_ets_new_t() ->
+    flat_ets_new(12,[]),
+    flat_ets_new({a,b},[]),
+    flat_ets_new(name,[foo]),
+    flat_ets_new(name,{bag}),
+    flat_ets_new(name,bag),
+    ok.
+
+-type access()     :: public | protected | private.
+-type type()       :: set | ordered_set | bag | duplicate_bag.
+
+-spec factored_ets_new(Name, Options) -> atom() when
+      Name :: atom(),
+      Options :: [Option],
+      Option :: Type | Access | named_table | {keypos,Pos}
+              | {heir, Pid :: pid(), HeirData} | {heir, none} | Tweaks,
+      Type :: type(),
+      Access :: access(),
+      Tweaks :: {write_concurrency, boolean()}
+              | {read_concurrency, boolean()}
+              | compressed,
+      Pos :: pos_integer(),
+      HeirData :: term().
+
+factored_ets_new(Name, Options) ->
+    get({Name, Options}).
+
+factored_ets_new_t() ->
+    factored_ets_new(12,[]),
+    factored_ets_new({a,b},[]),
+    factored_ets_new(name,[foo]),
+    factored_ets_new(name,{bag}),
+    factored_ets_new(name,bag),
+    ok.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/dict_use.erl b/lib/dialyzer/test/indent_SUITE_data/src/dict_use.erl
new file mode 100644
index 0000000000..2527f166f2
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/dict_use.erl
@@ -0,0 +1,82 @@
+-module(dict_use).
+
+-export([ok1/0, ok2/0, ok3/0, ok4/0, ok5/0, ok6/0]).
+-export([middle/0]).
+-export([w1/0, w2/0, w3/0, w4/1, w5/0, w6/0, w7/0, w8/1, w9/0]).
+
+-define(DICT, dict).
+
+%%---------------------------------------------------------------------
+%% Cases that are OK
+%%---------------------------------------------------------------------
+
+ok1() ->
+  dict:new().
+
+ok2() ->
+  case dict:new() of X -> X end.
+
+ok3() ->
+  Dict1 = dict:new(),
+  Dict2 = dict:new(),
+  Dict1 =:= Dict2.
+
+ok4() ->
+  dict:fetch(foo, dict:new()).
+
+ok5() ->  % this is OK since some_mod:new/0 might be returning a dict:dict()
+  dict:fetch(foo, some_mod:new()).
+
+ok6() ->
+  dict:store(42, elli, dict:new()).
+
+middle() ->
+  {w1(), w2()}.
+
+%%---------------------------------------------------------------------
+%% Cases that are problematic w.r.t. opacity of types
+%%---------------------------------------------------------------------
+
+w1() ->
+  gazonk = dict:new().
+
+w2() ->
+  case dict:new() of
+    [] -> nil;
+    42 -> weird
+  end.
+
+w3() ->
+  try dict:new() of
+    [] -> nil;
+    42 -> weird
+  catch
+    _:_ -> exception
+  end.
+
+w4(Dict) when is_list(Dict) ->
+  Dict =:= dict:new();
+w4(Dict) when is_atom(Dict) ->
+  Dict =/= dict:new().
+
+w5() ->
+  case dict:new() of
+    D when length(D) =/= 42 -> weird;
+    D when is_atom(D) -> weirder;
+    D when is_list(D) -> gazonk
+  end.
+
+w6() ->
+  is_list(dict:new()).
+
+w7() ->
+  dict:fetch(foo, [1,2,3]).
+
+w8(Fun) ->
+  dict:merge(Fun, 42, [1,2]).
+
+w9() ->
+  dict:store(42, elli,
+	     {dict,0,16,16,8,80,48,
+	           {[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]},
+	           {{[],[],[],[],[],[],[],[],[],[],[],[],[],[],[],[]}}}).
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/fun_app.erl b/lib/dialyzer/test/indent_SUITE_data/src/fun_app.erl
new file mode 100644
index 0000000000..20b6138d26
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/fun_app.erl
@@ -0,0 +1,41 @@
+%% This is taken from the code of distel.
+
+-module(fun_app).
+-export([html_index/2]). % , lines/3, curry/2]).
+
+html_index(file,Dir) ->
+  fold_file(curry(fun lines/3,Dir),[],filename:join([Dir,"doc","man_index.html"])).
+
+fold_file(Fun,Acc0,File) ->
+  {ok, FD} = file:open(File, [read]),
+  Acc = fold_file_lines(FD,Fun,Acc0),
+  file:close(FD),
+  Acc.
+
+fold_file_lines(FD,Fun,Acc) ->
+  case io:get_line(FD, "") of
+    eof -> Acc;
+    Line -> fold_file_lines(FD,Fun,Fun(trim_nl(Line),Acc))
+  end.
+
+trim_nl(Str) -> lists:reverse(tl(lists:reverse(Str))).
+
+lines(Line,_,Dir) ->
+  case string:tokens(Line, "<> \"") of
+    ["TD", "A", "HREF=", "../"++Href, M|_] ->
+      case filename:basename(Href, ".html") of
+	"index" -> ok;
+	M -> e_set({file,M}, filename:join([Dir,Href]))
+      end;
+    _ -> ok
+  end.
+
+e_set(Key,Val) -> ets:insert(?MODULE, {Key,Val}).
+
+curry(F, Arg) ->
+  case erlang:fun_info(F,arity) of
+    {_,1} -> fun() -> F(Arg) end;
+    {_,2} -> fun(A) -> F(A,Arg) end;
+    {_,3} -> fun(A,B) -> F(A,B,Arg) end;
+    {_,4} -> fun(A,B,C) -> F(A,B,C,Arg) end
+  end.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/fun_app_args.erl b/lib/dialyzer/test/indent_SUITE_data/src/fun_app_args.erl
new file mode 100644
index 0000000000..b4409bc550
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/fun_app_args.erl
@@ -0,0 +1,12 @@
+-module(fun_app_args).
+
+-export([t/1]).
+
+-type ft() :: fun((a, []) -> any()).
+
+-record(r, {
+    h = c :: c | ft()
+}).
+
+t(#r{h = H}) ->
+    fun(_) -> (H)(b, []) end.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/guard_update.erl b/lib/dialyzer/test/indent_SUITE_data/src/guard_update.erl
new file mode 100644
index 0000000000..19d0089401
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/guard_update.erl
@@ -0,0 +1,18 @@
+-module(guard_update).
+
+-export([t/0, t2/0]).
+
+t() ->
+    f(#{a=>2}). %% Illegal
+
+f(M)
+  when M#{b := 7} =/= q
+       -> ok.
+
+t2() ->
+    f2(#{a=>2}). %% Legal!
+
+f2(M)
+  when M#{b := 7} =/= q;
+       M =/= p
+       -> ok.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/guard_warnings.erl b/lib/dialyzer/test/indent_SUITE_data/src/guard_warnings.erl
new file mode 100644
index 0000000000..6ab13eef9a
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/guard_warnings.erl
@@ -0,0 +1,118 @@
+%%
+%% A couple of tests for booleans in guards.
+%% Tests with suffix w have incomplete results due to weak dataflow.
+%% Tests with suffix ww have incomplete results due to weak dialyzer.
+%% Tests with suffix x should not give warnings.
+%%
+
+-module(and_bug).
+
+-compile(export_all).
+
+test1(X) when X and not X -> never.
+
+test2(X) when not X and X -> never.
+
+test3(X) when (X and not X) =:= true -> never.
+
+test4(X) when (not X and X) =:= true -> never.
+
+test5(X) when (X and not X) == true -> never.
+
+test6(X) when (not X and X) == true -> never.
+
+test7_w(X) when not (X or not X) -> never.
+
+test8_w(X) when not (not X or X) -> never.
+
+test9(X) when (X or not X) =:= false -> never.
+
+test10(X) when (not X or X) =:= false -> never.
+
+test11(X) when (X or not X) == false -> never.
+
+test12(X) when (not X or X) == false -> never.
+
+test13(X) when X and false -> never.
+
+test14(X) when false and X -> never.
+
+test15(X) when (X and false) =:= true -> never.
+
+test16(X) when (false and X) =:= true -> never.
+
+test17(X) when (X and false) == true -> never.
+
+test18(X) when (false and X) == true -> never.
+
+test19(X) when not (true or X) -> never.
+
+test20(X) when not (X or true) -> never.
+
+test21(X) when (true or X) =:= false -> never.
+
+test22(X) when (X or true) =:= false -> never.
+
+test23(X) when (true or X) == false -> never.
+
+test24(X) when (X or true) == false -> never.
+
+test25(X) when (false and X) -> never.
+
+test26(X) when (X and false) -> never.
+
+test27(X) when (false and X) =:= true -> never.
+
+test28(X) when (X and false) =:= true -> never.
+
+test29(X) when (false and X) == true -> never.
+
+test30(X) when (X and false) == true -> never.
+
+test31() when false and false -> never.
+
+test32() when (false and false) =:= true -> never.
+
+test33() when not (true and true) =:= true -> never.
+
+test34() when (false and false) == true -> never.
+
+test35() when not (true and true) == true -> never.
+
+test36() when false or false -> never.
+
+test37() when (false or false) =:= true -> never.
+
+test38() when not (false or false) =:= false -> never.
+
+test39() when (false or false) == true -> never.
+
+test40() when not (false or false) == false -> never.
+
+test41() when true =:= false -> never.
+
+test42() when true == false -> never.
+
+test43() when not (true =:= true) -> never.
+
+test44() when not (true == true) -> never.
+
+test45() when not (not (not (not (not (not (not true)))))) -> never.
+
+test46(X) when (X =:= true) and (X =:= false) -> never.
+
+test47(X) when (X == true) and (X == false) -> never.
+
+test48(X) when is_boolean(X) and (X =:= true) and (X =/= true) -> never.
+
+test49_x(X) when not (X or X) -> maybe.
+
+test50_x(X) when not (X and X) -> maybe.
+
+test51_x(X) when not (not X) -> maybe.
+
+test52_w(X) when is_boolean(X) and (X =/= true) and (X =:= true) -> never.
+
+test53_ww(X) when is_boolean(X) and (X =/= true) and (X =/= false) -> never.
+
+test54_w(X) when is_boolean(X) and not ((X =:= true) or (X =:= false)) -> never.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl b/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
new file mode 100644
index 0000000000..99eb73a5f6
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
@@ -0,0 +1,2800 @@
+%% %CopyrightBegin%
+%% 
+%% Copyright Ericsson AB 2013. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%% 
+%% %CopyrightEnd%
+%%
+-module(map_galore).
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
+	init_per_group/2,end_per_group/2
+    ]).
+
+-export([
+	t_build_and_match_literals/1, t_build_and_match_literals_large/1,
+	t_update_literals/1, t_update_literals_large/1,
+        t_match_and_update_literals/1, t_match_and_update_literals_large/1,
+	t_update_map_expressions/1,
+	t_update_assoc/1, t_update_assoc_large/1,
+        t_update_exact/1, t_update_exact_large/1,
+	t_guard_bifs/1,
+        t_guard_sequence/1, t_guard_sequence_large/1,
+        t_guard_update/1, t_guard_update_large/1,
+	t_guard_receive/1, t_guard_receive_large/1,
+        t_guard_fun/1,
+        t_update_deep/1,
+	t_list_comprehension/1,
+	t_map_sort_literals/1,
+	t_map_equal/1,
+	t_map_compare/1,
+	t_map_size/1,
+	t_is_map/1,
+
+	%% Specific Map BIFs
+	t_bif_map_get/1,
+	t_bif_map_find/1,
+	t_bif_map_is_key/1,
+	t_bif_map_keys/1,
+	t_bif_map_merge/1,
+	t_bif_map_new/1,
+	t_bif_map_put/1,
+	t_bif_map_remove/1,
+	t_bif_map_update/1,
+	t_bif_map_values/1,
+	t_bif_map_to_list/1,
+	t_bif_map_from_list/1,
+
+	%% erlang
+	t_erlang_hash/1,
+	t_map_encode_decode/1,
+
+	%% non specific BIF related
+	t_bif_build_and_check/1,
+	t_bif_merge_and_check/1,
+
+	%% maps module not bifs
+	t_maps_fold/1,
+	t_maps_map/1,
+	t_maps_size/1,
+	t_maps_without/1,
+
+	%% misc
+	t_erts_internal_order/1,
+        t_erts_internal_hash/1,
+	t_pdict/1,
+	t_ets/1,
+	t_dets/1,
+	t_tracing/1,
+
+	%% instruction-level tests
+	t_has_map_fields/1,
+	y_regs/1
+    ]).
+
+-include_lib("stdlib/include/ms_transform.hrl").
+
+-define(CHECK(Cond,Term),
+	case (catch (Cond)) of
+	    true -> true;
+	    _ -> io:format("###### CHECK FAILED ######~nINPUT:  ~p~n", [Term]),
+		 exit(Term)
+	end).
+
+suite() -> [].
+
+all() -> [
+	t_build_and_match_literals, t_build_and_match_literals_large,
+	t_update_literals, t_update_literals_large,
+        t_match_and_update_literals, t_match_and_update_literals_large,
+	t_update_map_expressions,
+	t_update_assoc, t_update_assoc_large,
+        t_update_exact, t_update_exact_large,
+	t_guard_bifs,
+        t_guard_sequence, t_guard_sequence_large,
+        t_guard_update, t_guard_update_large,
+	t_guard_receive, t_guard_receive_large,
+        t_guard_fun, t_list_comprehension,
+        t_update_deep,
+	t_map_equal, t_map_compare,
+	t_map_sort_literals,
+
+	%% Specific Map BIFs
+	t_bif_map_get,t_bif_map_find,t_bif_map_is_key,
+	t_bif_map_keys, t_bif_map_merge, t_bif_map_new,
+	t_bif_map_put,
+	t_bif_map_remove, t_bif_map_update,
+	t_bif_map_values,
+	t_bif_map_to_list, t_bif_map_from_list,
+
+	%% erlang
+	t_erlang_hash, t_map_encode_decode,
+	t_map_size, t_is_map,
+
+	%% non specific BIF related
+	t_bif_build_and_check,
+	t_bif_merge_and_check,
+
+	%% maps module
+	t_maps_fold, t_maps_map,
+	t_maps_size, t_maps_without,
+
+
+        %% Other functions
+	t_erts_internal_order,
+        t_erts_internal_hash,
+	t_pdict,
+	t_ets,
+	t_tracing,
+
+	%% instruction-level tests
+	t_has_map_fields,
+	y_regs
+    ].
+
+groups() -> [].
+
+init_per_suite(Config) -> Config.
+end_per_suite(_Config) -> ok.
+
+init_per_group(_GroupName, Config) -> Config.
+end_per_group(_GroupName, Config) -> Config.
+
+%% tests
+
+t_build_and_match_literals(Config) when is_list(Config) ->
+    #{} = #{},
+    #{1:=a} = #{1=>a},
+    #{1:=a,2:=b} = #{1=>a,2=>b},
+    #{1:=a,2:=b,3:="c"} = #{1=>a,2=>b,3=>"c"},
+    #{1:=a,2:=b,3:="c","4":="d"} = #{1=>a,2=>b,3=>"c","4"=>"d"},
+    #{1:=a,2:=b,3:="c","4":="d",<<"5">>:=<<"e">>} =
+	#{1=>a,2=>b,3=>"c","4"=>"d",<<"5">>=><<"e">>},
+    #{1:=a,2:=b,3:="c","4":="d",<<"5">>:=<<"e">>,{"6",7}:="f"} =
+	#{1=>a,2=>b,3=>"c","4"=>"d",<<"5">>=><<"e">>,{"6",7}=>"f"},
+    #{1:=a,2:=b,3:="c","4":="d",<<"5">>:=<<"e">>,{"6",7}:="f",8:=g} =
+	#{1=>a,2=>b,3=>"c","4"=>"d",<<"5">>=><<"e">>,{"6",7}=>"f",8=>g},
+
+    #{[]:=a,42.0:=b,x:={x,y},[a,b]:=list} =
+         #{[]=>a,42.0=>b,x=>{x,y},[a,b]=>list},
+
+    #{<<"hi all">> := 1} = #{<<"hi",32,"all">> => 1},
+
+    #{a:=X,a:=X=3,b:=4} = #{a=>3,b=>4}, % weird but ok =)
+
+    #{ a:=#{ b:=#{c := third, b:=second}}, b:=first} =
+	#{ b=>first, a=>#{ b=>#{c => third, b=> second}}},
+
+    M = #{ map_1=>#{ map_2=>#{value_3 => third}, value_2=> second}, value_1=>first},
+    M = #{ map_1:=#{ map_2:=#{value_3 := third}, value_2:= second}, value_1:=first} =
+	 #{ map_1=>#{ map_2=>#{value_3 => third}, value_2=> second}, value_1=>first},
+
+    %% error case
+    %V = 32,
+    %{'EXIT',{{badmatch,_},_}} = (catch (#{<<"hi all">> => 1} = #{<<"hi",V,"all">> => 1})),
+    {'EXIT',{{badmatch,_},_}} = (catch (#{x:=3,x:=2} = #{x=>3})),
+    {'EXIT',{{badmatch,_},_}} = (catch (#{x:=2} = #{x=>3})),
+    {'EXIT',{{badmatch,_},_}} = (catch (#{x:=3} = {a,b,c})),
+    {'EXIT',{{badmatch,_},_}} = (catch (#{x:=3} = #{y=>3})),
+    {'EXIT',{{badmatch,_},_}} = (catch (#{x:=3} = #{x=>"three"})),
+    ok.
+
+t_build_and_match_literals_large(Config) when is_list(Config) ->
+    % normal non-repeating
+    M0 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" },
+
+    #{10:=a0,20:=b0,30:="c0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M0,
+    #{11:=a1,21:=b1,31:="c1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M0,
+    #{12:=a2,22:=b2,32:="c2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M0,
+    #{13:=a3,23:=b3,33:="c3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M0,
+    #{14:=a4,24:=b4,34:="c4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M0,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M0,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M0,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M0,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M0,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M0,
+
+    60 = map_size(M0),
+    60 = maps:size(M0),
+
+    % with repeating
+    M1 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               10=>na0,20=>nb0,30=>"nc0","40"=>"nd0",<<"50">>=>"ne0",{["00"]}=>"n10",
+               11=>na1,21=>nb1,31=>"nc1","41"=>"nd1",<<"51">>=>"ne1",{["01"]}=>"n11",
+               12=>na2,22=>nb2,32=>"nc2","42"=>"nd2",<<"52">>=>"ne2",{["02"]}=>"n12",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+
+               13=>na3,23=>nb3,33=>"nc3","43"=>"nd3",<<"53">>=>"ne3",{["03"]}=>"n13",
+               14=>na4,24=>nb4,34=>"nc4","44"=>"nd4",<<"54">>=>"ne4",{["04"]}=>"n14",
+
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" },
+
+    #{10:=na0,20:=nb0,30:="nc0","40":="nd0",<<"50">>:="ne0",{["00"]}:="n10"} = M1,
+    #{11:=na1,21:=nb1,31:="nc1","41":="nd1",<<"51">>:="ne1",{["01"]}:="n11"} = M1,
+    #{12:=na2,22:=nb2,32:="nc2","42":="nd2",<<"52">>:="ne2",{["02"]}:="n12"} = M1,
+    #{13:=na3,23:=nb3,33:="nc3","43":="nd3",<<"53">>:="ne3",{["03"]}:="n13"} = M1,
+    #{14:=na4,24:=nb4,34:="nc4","44":="nd4",<<"54">>:="ne4",{["04"]}:="n14"} = M1,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M1,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M1,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M1,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M1,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M1,
+
+    60 = map_size(M1),
+    60 = maps:size(M1),
+
+    % with floats
+
+    M2 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+               10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+               11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+               12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+               13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+               14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+               15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+               16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+               17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+               18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+               19.0=>fa9,29.0=>fb9,39.0=>"fc9"},
+
+    #{10:=a0,20:=b0,30:="c0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M2,
+    #{11:=a1,21:=b1,31:="c1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M2,
+    #{12:=a2,22:=b2,32:="c2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M2,
+    #{13:=a3,23:=b3,33:="c3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M2,
+    #{14:=a4,24:=b4,34:="c4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M2,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M2,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M2,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M2,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M2,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M2,
+
+    #{10.0:=fa0,20.0:=fb0,30.0:="fc0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M2,
+    #{11.0:=fa1,21.0:=fb1,31.0:="fc1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M2,
+    #{12.0:=fa2,22.0:=fb2,32.0:="fc2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M2,
+    #{13.0:=fa3,23.0:=fb3,33.0:="fc3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M2,
+    #{14.0:=fa4,24.0:=fb4,34.0:="fc4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M2,
+
+    #{15.0:=fa5,25.0:=fb5,35.0:="fc5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M2,
+    #{16.0:=fa6,26.0:=fb6,36.0:="fc6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M2,
+    #{17.0:=fa7,27.0:=fb7,37.0:="fc7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M2,
+    #{18.0:=fa8,28.0:=fb8,38.0:="fc8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M2,
+    #{19.0:=fa9,29.0:=fb9,39.0:="fc9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M2,
+
+    90 = map_size(M2),
+    90 = maps:size(M2),
+
+    % with bignums
+    M3 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+               10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+               11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+               12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+               13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+               14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+               15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+               16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+               17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+               18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+               19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+               36893488147419103232=>big1,  73786976294838206464=>big2,
+               147573952589676412928=>big3, 18446744073709551616=>big4,
+               4294967296=>big5,            8589934592=>big6,
+               4294967295=>big7,            67108863=>big8
+             },
+
+    #{10:=a0,20:=b0,30:="c0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M3,
+    #{11:=a1,21:=b1,31:="c1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M3,
+    #{12:=a2,22:=b2,32:="c2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M3,
+    #{13:=a3,23:=b3,33:="c3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M3,
+    #{14:=a4,24:=b4,34:="c4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M3,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M3,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M3,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M3,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M3,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M3,
+
+    #{10.0:=fa0,20.0:=fb0,30.0:="fc0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M3,
+    #{11.0:=fa1,21.0:=fb1,31.0:="fc1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M3,
+    #{12.0:=fa2,22.0:=fb2,32.0:="fc2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M3,
+    #{13.0:=fa3,23.0:=fb3,33.0:="fc3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M3,
+    #{14.0:=fa4,24.0:=fb4,34.0:="fc4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M3,
+
+    #{15.0:=fa5,25.0:=fb5,35.0:="fc5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M3,
+    #{16.0:=fa6,26.0:=fb6,36.0:="fc6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M3,
+    #{17.0:=fa7,27.0:=fb7,37.0:="fc7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M3,
+    #{18.0:=fa8,28.0:=fb8,38.0:="fc8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M3,
+    #{19.0:=fa9,29.0:=fb9,39.0:="fc9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M3,
+
+    #{36893488147419103232:=big1,67108863:=big8,"45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M3,
+    #{147573952589676412928:=big3,8589934592:=big6,"46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M3,
+    #{4294967296:=big5,18446744073709551616:=big4,"47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M3,
+    #{4294967295:=big7,73786976294838206464:=big2,"48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M3,
+
+    98 = map_size(M3),
+    98 = maps:size(M3),
+
+    %% with maps
+
+    M4 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+               10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+               11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+               12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+               13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+               14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+               15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+               16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+               17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+               18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+               19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+               #{ one => small, map => key } => "small map key 1",
+               #{ second => small, map => key } => "small map key 2",
+               #{ third => small, map => key } => "small map key 3",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+    #{10:=a0,20:=b0,30:="c0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M4,
+    #{11:=a1,21:=b1,31:="c1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M4,
+    #{12:=a2,22:=b2,32:="c2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M4,
+    #{13:=a3,23:=b3,33:="c3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M4,
+    #{14:=a4,24:=b4,34:="c4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M4,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M4,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M4,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M4,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M4,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M4,
+
+    #{ #{ one => small, map => key }    := "small map key 1",
+       #{ second => small, map => key } := "small map key 2",
+       #{ third => small, map => key }  := "small map key 3" } = M4,
+
+    #{ #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+          11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+          12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+          13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+          14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+          15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+          16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+          17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+          18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+          19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } := "large map key 1",
+
+       #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+          11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+          12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+          13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+          14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+          15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+          k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+          17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+          18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+          19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } := "large map key 2" } = M4,
+
+
+    #{ 15:=V1,25:=b5,35:=V2,"45":="d5",<<"55">>:=V3,{["05"]}:="15",
+       #{ one => small, map => key }    := "small map key 1",
+       #{ second => small, map => key } := V4,
+       #{ third => small, map => key }  := "small map key 3",
+       #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+          11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+          12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+          13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+          14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+          15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+          16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+          17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+          18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+          19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } := V5 } = M4,
+
+    a5   = V1,
+    "c5" = V2,
+    "e5" = V3,
+    "small map key 2" = V4,
+    "large map key 1" = V5,
+
+    95 = map_size(M4),
+    95 = maps:size(M4),
+
+    % call for value
+
+    M5 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+               10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+               11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+               12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+               13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+               14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+               15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+               16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+               17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+               18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+               19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+               #{ one => small, map => key } => "small map key 1",
+               #{ second => small, map => key } => "small map key 2",
+               #{ third => small, map => key } => "small map key 3",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+    #{10:=a0,20:=b0,30:="c0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M5,
+    #{11:=a1,21:=b1,31:="c1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M5,
+    #{12:=a2,22:=b2,32:="c2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M5,
+    #{13:=a3,23:=b3,33:="c3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M5,
+    #{14:=a4,24:=b4,34:="c4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M5,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M5,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M5,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M5,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M5,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M5,
+
+    #{ #{ one => small, map => key }    := "small map key 1",
+       #{ second => small, map => key } := "small map key 2",
+       #{ third => small, map => key }  := "small map key 3" } = M5,
+
+    #{ #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+          11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+          12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+          13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+          14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+          15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+          16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+          17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+          18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+          19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } := "large map key 1",
+
+       #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+          11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+          12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+          13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+          14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+          15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+          k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+          17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+          18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+          19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } := "large map key 2" } = M5,
+
+    95 = map_size(M5),
+    95 = maps:size(M5),
+
+    %% remember
+
+    #{10:=a0,20:=b0,30:="c0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M0,
+    #{11:=a1,21:=b1,31:="c1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M0,
+    #{12:=a2,22:=b2,32:="c2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M0,
+    #{13:=a3,23:=b3,33:="c3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M0,
+    #{14:=a4,24:=b4,34:="c4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M0,
+
+    #{10:=na0,20:=nb0,30:="nc0","40":="nd0",<<"50">>:="ne0",{["00"]}:="n10"} = M1,
+    #{11:=na1,21:=nb1,31:="nc1","41":="nd1",<<"51">>:="ne1",{["01"]}:="n11"} = M1,
+    #{12:=na2,22:=nb2,32:="nc2","42":="nd2",<<"52">>:="ne2",{["02"]}:="n12"} = M1,
+    #{13:=na3,23:=nb3,33:="nc3","43":="nd3",<<"53">>:="ne3",{["03"]}:="n13"} = M1,
+    #{14:=na4,24:=nb4,34:="nc4","44":="nd4",<<"54">>:="ne4",{["04"]}:="n14"} = M1,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M1,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M1,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M1,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M1,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M1,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M2,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M2,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M2,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M2,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M2,
+
+    #{10.0:=fa0,20.0:=fb0,30.0:="fc0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M2,
+    #{11.0:=fa1,21.0:=fb1,31.0:="fc1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M2,
+    #{12.0:=fa2,22.0:=fb2,32.0:="fc2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M2,
+    #{13.0:=fa3,23.0:=fb3,33.0:="fc3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M2,
+    #{14.0:=fa4,24.0:=fb4,34.0:="fc4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M2,
+
+    #{15:=a5,25:=b5,35:="c5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M3,
+    #{16:=a6,26:=b6,36:="c6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M3,
+    #{17:=a7,27:=b7,37:="c7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M3,
+    #{18:=a8,28:=b8,38:="c8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M3,
+    #{19:=a9,29:=b9,39:="c9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M3,
+
+    #{10.0:=fa0,20.0:=fb0,30.0:="fc0","40":="d0",<<"50">>:="e0",{["00"]}:="10"} = M3,
+    #{11.0:=fa1,21.0:=fb1,31.0:="fc1","41":="d1",<<"51">>:="e1",{["01"]}:="11"} = M3,
+    #{12.0:=fa2,22.0:=fb2,32.0:="fc2","42":="d2",<<"52">>:="e2",{["02"]}:="12"} = M3,
+    #{13.0:=fa3,23.0:=fb3,33.0:="fc3","43":="d3",<<"53">>:="e3",{["03"]}:="13"} = M3,
+    #{14.0:=fa4,24.0:=fb4,34.0:="fc4","44":="d4",<<"54">>:="e4",{["04"]}:="14"} = M3,
+
+    #{15.0:=fa5,25.0:=fb5,35.0:="fc5","45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M3,
+    #{16.0:=fa6,26.0:=fb6,36.0:="fc6","46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M3,
+    #{17.0:=fa7,27.0:=fb7,37.0:="fc7","47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M3,
+    #{18.0:=fa8,28.0:=fb8,38.0:="fc8","48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M3,
+    #{19.0:=fa9,29.0:=fb9,39.0:="fc9","49":="d9",<<"59">>:="e9",{["09"]}:="19"} = M3,
+
+    #{36893488147419103232:=big1,67108863:=big8,"45":="d5",<<"55">>:="e5",{["05"]}:="15"} = M3,
+    #{147573952589676412928:=big3,8589934592:=big6,"46":="d6",<<"56">>:="e6",{["06"]}:="16"} = M3,
+    #{4294967296:=big5,18446744073709551616:=big4,"47":="d7",<<"57">>:="e7",{["07"]}:="17"} = M3,
+    #{4294967295:=big7,73786976294838206464:=big2,"48":="d8",<<"58">>:="e8",{["08"]}:="18"} = M3,
+
+    ok.
+
+
+t_map_size(Config) when is_list(Config) ->
+    0 = map_size(#{}),
+    1 = map_size(#{a=>1}),
+    1 = map_size(#{a=>"wat"}),
+    2 = map_size(#{a=>1, b=>2}),
+    3 = map_size(#{a=>1, b=>2, b=>"3","33"=><<"n">>}),
+
+    true = map_is_size(#{a=>1}, 1),
+    true = map_is_size(#{a=>1, a=>2}, 1),
+    M = #{ "a" => 1, "b" => 2},
+    true  = map_is_size(M, 2),
+    false = map_is_size(M, 3),
+    true  = map_is_size(M#{ "a" => 2}, 2),
+    false = map_is_size(M#{ "c" => 2}, 2),
+
+    Ks = [build_key(fun(K) -> <<1,K:32,1>> end,I)||I<-lists:seq(1,100)],
+    ok = build_and_check_size(Ks,0,#{}),
+
+    %% try deep collisions
+    %% statistically we get another subtree at 50k -> 100k elements
+    %% Try to be nice and don't use too much memory in the testcase,
+
+    N  = 500000,
+    Is = lists:seq(1,N),
+    N  = map_size(maps:from_list([{I,I}||I<-Is])),
+    N  = map_size(maps:from_list([{<<I:32>>,I}||I<-Is])),
+    N  = map_size(maps:from_list([{integer_to_list(I),I}||I<-Is])),
+    N  = map_size(maps:from_list([{float(I),I}||I<-Is])),
+
+    %% Error cases.
+    do_badmap(fun(T) ->
+                    {'EXIT',{{badmap,T},_}} =
+                      (catch map_size(T))
+              end),
+    ok.
+
+build_and_check_size([K|Ks],N,M0) ->
+    N = map_size(M0),
+    M1 = M0#{ K => K },
+    build_and_check_size(Ks,N + 1,M1);
+build_and_check_size([],N,M) ->
+    N = map_size(M),
+    ok.
+
+map_is_size(M,N) when map_size(M) =:= N -> true;
+map_is_size(_,_) -> false.
+
+t_is_map(Config) when is_list(Config) ->
+    true = is_map(#{}),
+    true = is_map(#{a=>1}),
+    false = is_map({a,b}),
+    false = is_map(x),
+    if is_map(#{}) -> ok end,
+    if is_map(#{b=>1}) -> ok end,
+    if not is_map([1,2,3]) -> ok end,
+    if not is_map(x) -> ok end,
+    ok.
+
+% test map updates without matching
+t_update_literals_large(Config) when is_list(Config) ->
+    Map = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+                10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+                11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+                12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+                13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+                14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+                15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+                16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+                17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+                18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+                19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+                #{ one => small, map => key } => "small map key 1",
+                #{ second => small, map => key } => "small map key 2",
+                #{ third => small, map => key } => "small map key 3",
+
+                #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                   11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                   12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                   13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                   14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                   15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                   16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                   17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                   18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                   19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+                #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                   11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                   12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                   13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                   14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                   15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                   k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                   17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                   18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                   19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+    #{x:="d",q:="4"} = loop_update_literals_x_q(Map, [
+		{"a","1"},{"b","2"},{"c","3"},{"d","4"}
+	]),
+    ok.
+
+t_update_literals(Config) when is_list(Config) ->
+    Map = #{x=>1,y=>2,z=>3,q=>4},
+    #{x:="d",q:="4"} = loop_update_literals_x_q(Map, [
+		{"a","1"},{"b","2"},{"c","3"},{"d","4"}
+	]),
+    ok.
+
+
+loop_update_literals_x_q(Map, []) -> Map;
+loop_update_literals_x_q(Map, [{X,Q}|Vs]) ->
+    loop_update_literals_x_q(Map#{q=>Q,x=>X},Vs).
+
+% test map updates with matching
+t_match_and_update_literals(Config) when is_list(Config) ->
+    Map = #{ x=>0,y=>"untouched",z=>"also untouched",q=>1,
+             #{ "one" => small, map => key } => "small map key 1" },
+    #{x:=16,q:=21,y:="untouched",z:="also untouched"} = loop_match_and_update_literals_x_q(Map, [
+	    {1,2},{3,4},{5,6},{7,8}
+	]),
+    M0 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+	    4 => number, 18446744073709551629 => wat},
+    M1 = #{},
+    M2 = M1#{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+	4 => number, 18446744073709551629 => wat},
+    M0 = M2,
+
+    #{ 4 := another_number, int := 3 } = M2#{ 4 => another_number },
+    ok.
+
+t_match_and_update_literals_large(Config) when is_list(Config) ->
+    Map = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+                10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+                11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+                12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+                13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+                14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+                15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+                16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+                17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+                18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+                19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+                x=>0,y=>"untouched",z=>"also untouched",q=>1,
+
+                #{ "one" => small, map => key } => "small map key 1",
+                #{ second => small, map => key } => "small map key 2",
+                #{ third => small, map => key } => "small map key 3",
+
+                #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                   11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                   12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                   13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                   14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                   15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                   16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                   17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                   18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                   19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+                #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                   11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                   12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                   13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                   14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                   15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                   k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                   17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                   18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                   19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+    #{x:=16,q:=21,y:="untouched",z:="also untouched"} = loop_match_and_update_literals_x_q(Map, [
+	    {1,2},{3,4},{5,6},{7,8}
+	]),
+    M0 = Map#{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+                  4 => number, 18446744073709551629 => wat},
+    M1 = Map#{},
+    M2 = M1#{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+              4 => number, 18446744073709551629 => wat},
+    M0 = M2,
+
+    #{ 4 := another_number, int := 3 } = M2#{ 4 => another_number },
+    ok.
+
+
+loop_match_and_update_literals_x_q(Map, []) -> Map;
+loop_match_and_update_literals_x_q(#{ q:=Q0, x:=X0,
+                                     #{ "one" => small, map => key } := "small map key 1" } = Map, [{X,Q}|Vs]) ->
+    loop_match_and_update_literals_x_q(Map#{q=>Q0+Q,x=>X0+X},Vs).
+
+
+t_update_map_expressions(Config) when is_list(Config) ->
+    M = maps:new(),
+    #{ a := 1 } = M#{a => 1},
+
+    #{ b := 2 } = (maps:new())#{ b => 2 },
+
+    #{ a :=42, b:=42, c:=42 } = (maps:from_list([{a,1},{b,2},{c,3}]))#{ a := 42, b := 42, c := 42 },
+    #{ "a" :=1, "b":=42, "c":=42 } = (maps:from_list([{"a",1},{"b",2}]))#{ "b" := 42, "c" => 42 },
+    Ks = lists:seq($a,$z),
+    #{ "aa" := {$a,$a}, "ac":=41, "dc":=42 } =
+        (maps:from_list([{[K1,K2],{K1,K2}}|| K1 <- Ks, K2 <- Ks]))#{ "ac" := 41, "dc" => 42 },
+
+    %% Error cases.
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},_}} =
+			  (catch (T)#{a:=42,b=>2})
+	      end),
+    ok.
+
+t_update_assoc(Config) when is_list(Config) ->
+    M0 = #{1=>a,2=>b,3.0=>c,4=>d,5=>e},
+
+    M1 = M0#{1=>42,2=>100,4=>[a,b,c]},
+    #{1:=42,2:=100,3.0:=c,4:=[a,b,c],5:=e} = M1,
+    #{1:=42,2:=b,4:=d,5:=e,2.0:=100,3.0:=c,4.0:=[a,b,c]} = M0#{1.0=>float,1:=42,2.0=>wrong,2.0=>100,4.0=>[a,b,c]},
+
+    M2 = M0#{3.0=>new},
+    #{1:=a,2:=b,3.0:=new,4:=d,5:=e} = M2,
+    M2 = M0#{3.0:=wrong,3.0=>new},
+
+    %% Errors cases.
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},_}} =
+			  (catch T#{nonexisting=>val})
+	      end),
+    ok.
+
+
+t_update_assoc_large(Config) when is_list(Config) ->
+    M0 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+               10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+               11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+               12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+               13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+               14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+               15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+               16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+               17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+               18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+               19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+               #{ one => small, map => key } => "small map key 1",
+               #{ second => small, map => key } => "small map key 2",
+               #{ third => small, map => key } => "small map key 3",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+
+    M1 = M0#{1=>42,2=>100,4=>[a,b,c]},
+    #{1:=42,2:=100,10.0:=fa0,4:=[a,b,c],25:=b5} = M1,
+    #{ 10:=43, 24:=b4, 15:=a5, 35:="c5", 2.0:=100, 13.0:=fa3, 4.0:=[a,b,c]} =
+        M0#{1.0=>float,10:=43,2.0=>wrong,2.0=>100,4.0=>[a,b,c]},
+
+    M2 = M0#{13.0=>new},
+    #{10:=a0,20:=b0,13.0:=new,"40":="d0",<<"50">>:="e0"} = M2,
+    M2 = M0#{13.0:=wrong,13.0=>new},
+
+    ok.
+
+t_update_exact(Config) when is_list(Config) ->
+    M0 = #{1=>a,2=>b,3.0=>c,4=>d,5=>e},
+
+    M1 = M0#{1:=42,2:=100,4:=[a,b,c]},
+    #{1:=42,2:=100,3.0:=c,4:=[a,b,c],5:=e} = M1,
+    M1 = M0#{1:=wrong,1=>42,2=>wrong,2:=100,4:=[a,b,c]},
+
+    M2 = M0#{3.0:=new},
+    #{1:=a,2:=b,3.0:=new,4:=d,5:=e} = M2,
+    M2 = M0#{3.0=>wrong,3.0:=new},
+    true = M2 =/= M0#{3=>right,3.0:=new},
+    #{ 3 := right, 3.0 := new } = M0#{3=>right,3.0:=new},
+
+    M3 = #{ 1 => val},
+    #{1 := update2,1.0 := new_val4} = M3#{
+	1.0 => new_val1, 1 := update, 1=> update3,
+	1 := update2, 1.0 := new_val2, 1.0 => new_val3,
+	1.0 => new_val4 },
+
+    %% Errors cases.
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},_}} =
+			  (catch T#{nonexisting=>val})
+	      end),
+    Empty = #{},
+    {'EXIT',{{badkey,nonexisting},_}} = (catch Empty#{nonexisting:=val}),
+    {'EXIT',{{badkey,nonexisting},_}} = (catch M0#{nonexisting:=val}),
+    {'EXIT',{{badkey,1.0},_}} = (catch M0#{1.0:=v,1.0=>v2}),
+    {'EXIT',{{badkey,42},_}} = (catch M0#{42.0:=v,42:=v2}),
+    {'EXIT',{{badkey,42.0},_}} = (catch M0#{42=>v1,42.0:=v2,42:=v3}),
+
+    ok.
+
+t_update_exact_large(Config) when is_list(Config) ->
+    M0 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19",
+
+               10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+               11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+               12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+               13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+               14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+               15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+               16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+               17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+               18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+               19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+               #{ one => small, map => key } => "small map key 1",
+               #{ second => small, map => key } => "small map key 2",
+               #{ third => small, map => key } => "small map key 3",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+
+    M1 = M0#{10:=42,<<"55">>:=100,10.0:=[a,b,c]},
+    #{ 10:=42,<<"55">>:=100,{["05"]}:="15",10.0:=[a,b,c],
+       #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+          11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+          12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+          13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+          14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+          15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+          16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+          17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+          18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+          19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } := "large map key 1" } = M1,
+
+    M1 = M0#{10:=wrong,10=>42,<<"55">>=>wrong,<<"55">>:=100,10.0:=[a,b,c]},
+
+    M2 = M0#{13.0:=new},
+    #{10:=a0,20:=b0,13.0:=new} = M2,
+    M2 = M0#{13.0=>wrong,13.0:=new},
+
+    %% Errors cases.
+    {'EXIT',{{badkey,nonexisting},_}} = (catch M0#{nonexisting:=val}),
+    {'EXIT',{{badkey,1.0},_}} = (catch M0#{1.0:=v,1.0=>v2}),
+    {'EXIT',{{badkey,42},_}} = (catch M0#{42.0:=v,42:=v2}),
+    {'EXIT',{{badkey,42.0},_}} = (catch M0#{42=>v1,42.0:=v2,42:=v3}),
+
+    ok.
+
+t_update_deep(Config) when is_list(Config) ->
+    N = 250000,
+    M0 = maps:from_list([{integer_to_list(I),a}||I<-lists:seq(1,N)]),
+    #{ "1" := a, "10" := a, "100" := a, "1000" := a, "10000" := a } = M0,
+
+    M1 = M0#{ "1" := b, "10" := b, "100" := b, "1000" := b, "10000" := b },
+    #{ "1" := a, "10" := a, "100" := a, "1000" := a, "10000" := a } = M0,
+    #{ "1" := b, "10" := b, "100" := b, "1000" := b, "10000" := b } = M1,
+
+    M2 = M0#{ "1" => c, "10" => c, "100" => c, "1000" => c, "10000" => c },
+    #{ "1" := a, "10" := a, "100" := a, "1000" := a, "10000" := a } = M0,
+    #{ "1" := b, "10" := b, "100" := b, "1000" := b, "10000" := b } = M1,
+    #{ "1" := c, "10" := c, "100" := c, "1000" := c, "10000" := c } = M2,
+
+    M3 = M2#{ "n1" => d, "n10" => d, "n100" => d, "n1000" => d, "n10000" => d },
+    #{  "1" := a,  "10" := a,  "100" := a,  "1000" := a,  "10000" := a } = M0,
+    #{  "1" := b,  "10" := b,  "100" := b,  "1000" := b,  "10000" := b } = M1,
+    #{  "1" := c,  "10" := c,  "100" := c,  "1000" := c,  "10000" := c } = M2,
+    #{  "1" := c,  "10" := c,  "100" := c,  "1000" := c,  "10000" := c } = M3,
+    #{ "n1" := d, "n10" := d, "n100" := d, "n1000" := d, "n10000" := d } = M3,
+    ok.
+
+t_guard_bifs(Config) when is_list(Config) ->
+    true   = map_guard_head(#{a=>1}),
+    false  = map_guard_head([]),
+    true   = map_guard_body(#{a=>1}),
+    false  = map_guard_body({}),
+    true   = map_guard_pattern(#{a=>1, <<"hi">> => "hi" }),
+    false  = map_guard_pattern("list"),
+    ok.
+
+map_guard_head(M) when is_map(M) -> true;
+map_guard_head(_) -> false.
+
+map_guard_body(M) -> is_map(M).
+
+map_guard_pattern(#{}) -> true;
+map_guard_pattern(_)   -> false.
+
+t_guard_sequence(Config) when is_list(Config) ->
+	{1, "a"} = map_guard_sequence_1(#{seq=>1,val=>"a"}),
+	{2, "b"} = map_guard_sequence_1(#{seq=>2,val=>"b"}),
+	{3, "c"} = map_guard_sequence_1(#{seq=>3,val=>"c"}),
+	{4, "d"} = map_guard_sequence_1(#{seq=>4,val=>"d"}),
+	{5, "e"} = map_guard_sequence_1(#{seq=>5,val=>"e"}),
+
+	{1,M1}       = map_guard_sequence_2(M1 = #{a=>3}),
+	{2,M2}       = map_guard_sequence_2(M2 = #{a=>4, b=>4}),
+	{3,gg,M3}    = map_guard_sequence_2(M3 = #{a=>gg, b=>4}),
+	{4,sc,sc,M4} = map_guard_sequence_2(M4 = #{a=>sc, b=>3, c=>sc2}),
+	{5,kk,kk,M5} = map_guard_sequence_2(M5 = #{a=>kk, b=>other, c=>sc2}),
+
+	%% error case
+	{'EXIT',{function_clause,_}} = (catch map_guard_sequence_1(#{seq=>6,val=>"e"})),
+	{'EXIT',{function_clause,_}} = (catch map_guard_sequence_2(#{b=>5})),
+	ok.
+
+t_guard_sequence_large(Config) when is_list(Config) ->
+    M0 = #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00",03]}=>"10",
+               11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01",03]}=>"11",
+               12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02",03]}=>"12",
+               13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03",03]}=>"13",
+               14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04",03]}=>"14",
+
+               15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05",03]}=>"15",
+               16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06",03]}=>"16",
+               17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07",03]}=>"17",
+               18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08",03]}=>"18",
+               19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09",03]}=>"19",
+
+               10.0=>fa0,20.0=>fb0,30.0=>"fc0",
+               11.0=>fa1,21.0=>fb1,31.0=>"fc1",
+               12.0=>fa2,22.0=>fb2,32.0=>"fc2",
+               13.0=>fa3,23.0=>fb3,33.0=>"fc3",
+               14.0=>fa4,24.0=>fb4,34.0=>"fc4",
+
+               15.0=>fa5,25.0=>fb5,35.0=>"fc5",
+               16.0=>fa6,26.0=>fb6,36.0=>"fc6",
+               17.0=>fa7,27.0=>fb7,37.0=>"fc7",
+               18.0=>fa8,28.0=>fb8,38.0=>"fc8",
+               19.0=>fa9,29.0=>fb9,39.0=>"fc9",
+
+               #{ one => small, map => key } => "small map key 1",
+               #{ second => small, map => key } => "small map key 2",
+               #{ third => small, map => key } => "small map key 3",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+	{1, "a"} = map_guard_sequence_1(M0#{seq=>1,val=>"a"}),
+	{2, "b"} = map_guard_sequence_1(M0#{seq=>2,val=>"b"}),
+	{3, "c"} = map_guard_sequence_1(M0#{seq=>3,val=>"c"}),
+	{4, "d"} = map_guard_sequence_1(M0#{seq=>4,val=>"d"}),
+	{5, "e"} = map_guard_sequence_1(M0#{seq=>5,val=>"e"}),
+
+	{1,M1}       = map_guard_sequence_2(M1 = M0#{a=>3}),
+	{2,M2}       = map_guard_sequence_2(M2 = M0#{a=>4, b=>4}),
+	{3,gg,M3}    = map_guard_sequence_2(M3 = M0#{a=>gg, b=>4}),
+	{4,sc,sc,M4} = map_guard_sequence_2(M4 = M0#{a=>sc, b=>3, c=>sc2}),
+	{5,kk,kk,M5} = map_guard_sequence_2(M5 = M0#{a=>kk, b=>other, c=>sc2}),
+
+	{'EXIT',{function_clause,_}} = (catch map_guard_sequence_1(M0#{seq=>6,val=>"e"})),
+	{'EXIT',{function_clause,_}} = (catch map_guard_sequence_2(M0#{b=>5})),
+        ok.
+
+
+map_guard_sequence_1(#{seq:=1=Seq, val:=Val}) -> {Seq,Val};
+map_guard_sequence_1(#{seq:=2=Seq, val:=Val}) -> {Seq,Val};
+map_guard_sequence_1(#{seq:=3=Seq, val:=Val}) -> {Seq,Val};
+map_guard_sequence_1(#{seq:=4=Seq, val:=Val}) -> {Seq,Val};
+map_guard_sequence_1(#{seq:=5=Seq, val:=Val}) -> {Seq,Val}.
+
+map_guard_sequence_2(#{ a:=3 }=M) -> {1, M};
+map_guard_sequence_2(#{ a:=4 }=M) -> {2, M};
+map_guard_sequence_2(#{ a:=X, a:=X, b:=4 }=M) -> {3,X,M};
+map_guard_sequence_2(#{ a:=X, a:=Y, b:=3 }=M) when X =:= Y -> {4,X,Y,M};
+map_guard_sequence_2(#{ a:=X, a:=Y }=M) when X =:= Y -> {5,X,Y,M}.
+
+
+t_guard_update(Config) when is_list(Config) ->
+    error  = map_guard_update(#{},#{}),
+    first  = map_guard_update(#{}, #{x=>first}),
+    second = map_guard_update(#{y=>old}, #{x=>second,y=>old}),
+    ok.
+
+t_guard_update_large(Config) when is_list(Config) ->
+    M0 = #{ 70=>a0,80=>b0,90=>"c0","40"=>"d0",<<"50">>=>"e0",{["00",03]}=>"10",
+               71=>a1,81=>b1,91=>"c1","41"=>"d1",<<"51">>=>"e1",{["01",03]}=>"11",
+               72=>a2,82=>b2,92=>"c2","42"=>"d2",<<"52">>=>"e2",{["02",03]}=>"12",
+               73=>a3,83=>b3,93=>"c3","43"=>"d3",<<"53">>=>"e3",{["03",03]}=>"13",
+               74=>a4,84=>b4,94=>"c4","44"=>"d4",<<"54">>=>"e4",{["04",03]}=>"14",
+
+               75=>a5,85=>b5,95=>"c5","45"=>"d5",<<"55">>=>"e5",{["05",03]}=>"15",
+               76=>a6,86=>b6,96=>"c6","46"=>"d6",<<"56">>=>"e6",{["06",03]}=>"16",
+               77=>a7,87=>b7,97=>"c7","47"=>"d7",<<"57">>=>"e7",{["07",03]}=>"17",
+               78=>a8,88=>b8,98=>"c8","48"=>"d8",<<"58">>=>"e8",{["08",03]}=>"18",
+               79=>a9,89=>b9,99=>"c9","49"=>"d9",<<"59">>=>"e9",{["09",03]}=>"19",
+
+               70.0=>fa0,80.0=>fb0,90.0=>"fc0",
+               71.0=>fa1,81.0=>fb1,91.0=>"fc1",
+               72.0=>fa2,82.0=>fb2,92.0=>"fc2",
+               73.0=>fa3,83.0=>fb3,93.0=>"fc3",
+               74.0=>fa4,84.0=>fb4,94.0=>"fc4",
+
+               75.0=>fa5,85.0=>fb5,95.0=>"fc5",
+               76.0=>fa6,86.0=>fb6,96.0=>"fc6",
+               77.0=>fa7,87.0=>fb7,97.0=>"fc7",
+               78.0=>fa8,88.0=>fb8,98.0=>"fc8",
+               79.0=>fa9,89.0=>fb9,99.0=>"fc9",
+
+               #{ one => small, map => key } => "small map key 1",
+               #{ second => small, map => key } => "small map key 2",
+               #{ third => small, map => key } => "small map key 3",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  16=>a6,26=>b6,36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 1",
+
+               #{ 10=>a0,20=>b0,30=>"c0","40"=>"d0",<<"50">>=>"e0",{["00"]}=>"10",
+                  11=>a1,21=>b1,31=>"c1","41"=>"d1",<<"51">>=>"e1",{["01"]}=>"11",
+                  12=>a2,22=>b2,32=>"c2","42"=>"d2",<<"52">>=>"e2",{["02"]}=>"12",
+                  13=>a3,23=>b3,33=>"c3","43"=>"d3",<<"53">>=>"e3",{["03"]}=>"13",
+                  14=>a4,24=>b4,34=>"c4","44"=>"d4",<<"54">>=>"e4",{["04"]}=>"14",
+
+                  15=>a5,25=>b5,35=>"c5","45"=>"d5",<<"55">>=>"e5",{["05"]}=>"15",
+                  k16=>a6,k26=>b6,k36=>"c6","46"=>"d6",<<"56">>=>"e6",{["06"]}=>"16",
+                  17=>a7,27=>b7,37=>"c7","47"=>"d7",<<"57">>=>"e7",{["07"]}=>"17",
+                  18=>a8,28=>b8,38=>"c8","48"=>"d8",<<"58">>=>"e8",{["08"]}=>"18",
+                  19=>a9,29=>b9,39=>"c9","49"=>"d9",<<"59">>=>"e9",{["09"]}=>"19" } => "large map key 2" },
+
+
+    error  = map_guard_update(M0#{},M0#{}),
+    first  = map_guard_update(M0#{},M0#{x=>first}),
+    second = map_guard_update(M0#{y=>old}, M0#{x=>second,y=>old}),
+    ok.
+
+
+map_guard_update(M1, M2) when M1#{x=>first}  =:= M2 -> first;
+map_guard_update(M1, M2) when M1#{x=>second} =:= M2 -> second;
+map_guard_update(_, _) -> error.
+
+t_guard_receive(Config) when is_list(Config) ->
+    M0  = #{ id => 0 },
+    Pid = spawn_link(fun() -> guard_receive_loop() end),
+    Big = 36893488147419103229,
+    B1  = <<"some text">>,
+    B2  = <<"was appended">>,
+    B3  = <<B1/binary, B2/binary>>,
+
+    #{id:=1, res:=Big} = M1 = call(Pid, M0#{op=>sub,in=>{1 bsl 65, 3}}),
+    #{id:=2, res:=26}  = M2 = call(Pid, M1#{op=>idiv,in=>{53,2}}),
+    #{id:=3, res:=832} = M3 = call(Pid, M2#{op=>imul,in=>{26,32}}),
+    #{id:=4, res:=4}   = M4 = call(Pid, M3#{op=>add,in=>{1,3}}),
+    #{id:=5, res:=Big} = M5 = call(Pid, M4#{op=>sub,in=>{1 bsl 65, 3}}),
+    #{id:=6, res:=B3}  = M6 = call(Pid, M5#{op=>"append",in=>{B1,B2}}),
+    #{id:=7, res:=4}   = _  = call(Pid, M6#{op=>add,in=>{1,3}}),
+
+
+    %% update old maps and check id update
+    #{id:=2, res:=B3} = call(Pid, M1#{op=>"append",in=>{B1,B2}}),
+    #{id:=5, res:=99} = call(Pid, M4#{op=>add,in=>{33, 66}}),
+
+    %% cleanup
+    done = call(Pid, done),
+    ok.
+
+-define(t_guard_receive_large_procs, 1500).
+
+t_guard_receive_large(Config) when is_list(Config) ->
+    M = lists:foldl(fun(_,#{procs := Ps } = M) ->
+                            M#{ procs := Ps#{ spawn_link(fun() -> grecv_loop() end) => 0 }}
+                    end, #{procs => #{}, done => 0}, lists:seq(1,?t_guard_receive_large_procs)),
+    lists:foreach(fun(Pid) ->
+                          Pid ! {self(), hello}
+                  end, maps:keys(maps:get(procs,M))),
+    ok = guard_receive_large_loop(M),
+    ok.
+
+guard_receive_large_loop(#{done := ?t_guard_receive_large_procs}) ->
+    ok;
+guard_receive_large_loop(M) ->
+    receive
+        #{pid := Pid, msg := hello} ->
+            case M of
+                #{done := Count, procs := #{Pid := 150}} ->
+                    Pid ! {self(), done},
+                    guard_receive_large_loop(M#{done := Count + 1});
+                #{procs := #{Pid := Count} = Ps} ->
+                    Pid ! {self(), hello},
+                    guard_receive_large_loop(M#{procs := Ps#{Pid := Count + 1}})
+            end
+    end.
+
+grecv_loop() ->
+    receive
+        {_, done} ->
+            ok;
+        {Pid, hello} ->
+            Pid ! #{pid=>self(), msg=>hello},
+            grecv_loop()
+    end.
+
+call(Pid, M) ->
+    Pid ! {self(), M}, receive {Pid, Res} -> Res end.
+
+guard_receive_loop() ->
+    receive
+	{Pid, #{ id:=Id, op:="append", in:={X,Y}}=M} when is_binary(X), is_binary(Y) ->
+	    Pid ! {self(), M#{ id=>Id+1, res=><<X/binary,Y/binary>>}},
+	    guard_receive_loop();
+	{Pid, #{ id:=Id, op:=add, in:={X,Y}}} ->
+	    Pid ! {self(), #{ id=>Id+1, res=>X+Y}},
+	    guard_receive_loop();
+	{Pid, #{ id:=Id, op:=sub,  in:={X,Y}}=M} ->
+	    Pid ! {self(), M#{ id=>Id+1, res=>X-Y}},
+	    guard_receive_loop();
+	{Pid, #{ id:=Id, op:=idiv, in:={X,Y}}=M} ->
+	    Pid ! {self(), M#{ id=>Id+1, res=>X div Y}},
+	    guard_receive_loop();
+	{Pid, #{ id:=Id, op:=imul, in:={X,Y}}=M} ->
+	    Pid ! {self(), M#{ id=>Id+1, res=>X * Y}},
+	    guard_receive_loop();
+	{Pid, done} ->
+	    Pid ! {self(), done};
+	{Pid, Other} ->
+	    Pid ! {error, Other},
+	    guard_receive_loop()
+    end.
+
+
+t_list_comprehension(Config) when is_list(Config) ->
+    [#{k:=1},#{k:=2},#{k:=3}] = [#{k=>I} || I <- [1,2,3]],
+
+    Ks = lists:seq($a,$z),
+    Ms = [#{[K1,K2]=>{K1,K2}} || K1 <- Ks, K2 <- Ks],
+    [#{"aa" := {$a,$a}},#{"ab":={$a,$b}}|_] = Ms,
+    [#{"zz" := {$z,$z}},#{"zy":={$z,$y}}|_] = lists:reverse(Ms),
+    ok.
+
+t_guard_fun(Config) when is_list(Config) ->
+    F1 = fun
+	    (#{s:=v,v:=V})     -> {v,V};
+	    (#{s:=t,v:={V,V}}) -> {t,V};
+	    (#{s:=l,v:=[V,V]}) -> {l,V}
+    end,
+    
+    F2 = fun
+	    (#{s:=T,v:={V,V}}) -> {T,V};
+	    (#{s:=T,v:=[V,V]}) -> {T,V};
+	    (#{s:=T,v:=V})     -> {T,V}
+    end,
+    V = <<"hi">>,
+
+    {v,V} = F1(#{s=>v,v=>V}),
+    {t,V} = F1(#{s=>t,v=>{V,V}}),
+    {l,V} = F1(#{s=>l,v=>[V,V]}),
+
+    {v,V} = F2(#{s=>v,v=>V}),
+    {t,V} = F2(#{s=>t,v=>{V,V}}),
+    {l,V} = F2(#{s=>l,v=>[V,V]}),
+
+    %% error case
+    {'EXIT', {function_clause,[{?MODULE,_,[#{s:=none,v:=none}],_}|_]}} = (catch F1(#{s=>none,v=>none})),
+    ok.
+
+
+t_map_sort_literals(Config) when is_list(Config) ->
+    % test relation
+
+    %% size order
+    true  = #{ a => 1, b => 2} < #{ a => 1, b => 1, c => 1},
+    true  = #{ b => 1, a => 1} < #{ c => 1, a => 1, b => 1},
+    false = #{ c => 1, b => 1, a => 1} < #{ c => 1, a => 1},
+
+    %% key order
+    true  = #{ a => 1 } < #{ b => 1},
+    false = #{ b => 1 } < #{ a => 1},
+    true  = #{ a => 1, b => 1, c => 1 } < #{ b => 1, c => 1, d => 1},
+    true  = #{ b => 1, c => 1, d => 1 } > #{ a => 1, b => 1, c => 1},
+    true  = #{ c => 1, b => 1, a => 1 } < #{ b => 1, c => 1, d => 1},
+    true  = #{ "a" => 1 } < #{ <<"a">> => 1},
+    false = #{ <<"a">> => 1 } < #{ "a" => 1},
+    true  = #{ 1 => 1 } < #{ 1.0 => 1},
+    false = #{ 1.0 => 1 } < #{ 1 => 1},
+
+    %% value order
+    true  = #{ a => 1 } < #{ a => 2},
+    false = #{ a => 2 } < #{ a => 1},
+    false = #{ a => 2, b => 1 } < #{ a => 1, b => 3},
+    true  = #{ a => 1, b => 1 } < #{ a => 1, b => 3},
+    false = #{ a => 1 } < #{ a => 1.0},
+    false = #{ a => 1.0 } < #{ a => 1},
+
+    true  = #{ "a" => "hi", b => 134 } == #{ b => 134,"a" => "hi"},
+
+    %% large maps
+
+    M = maps:from_list([{I,I}||I <- lists:seq(1,500)]),
+
+    %% size order
+    true  = M#{ a => 1, b => 2} < M#{ a => 1, b => 1, c => 1},
+    true  = M#{ b => 1, a => 1} < M#{ c => 1, a => 1, b => 1},
+    false = M#{ c => 1, b => 1, a => 1} < M#{ c => 1, a => 1},
+
+    %% key order
+    true  = M#{ a => 1 } < M#{ b => 1},
+    false = M#{ b => 1 } < M#{ a => 1},
+    true  = M#{ a => 1, b => 1, c => 1 } < M#{ b => 1, c => 1, d => 1},
+    true  = M#{ b => 1, c => 1, d => 1 } > M#{ a => 1, b => 1, c => 1},
+    true  = M#{ c => 1, b => 1, a => 1 } < M#{ b => 1, c => 1, d => 1},
+    true  = M#{ "a" => 1 } < M#{ <<"a">> => 1},
+    false = M#{ <<"a">> => 1 } < #{ "a" => 1},
+    true  = M#{ 1 => 1 } < maps:remove(1,M#{ 1.0 => 1}),
+    false = M#{ 1.0 => 1 } < M#{ 1 => 1},
+
+    %% value order
+    true  = M#{ a => 1 } < M#{ a => 2},
+    false = M#{ a => 2 } < M#{ a => 1},
+    false = M#{ a => 2, b => 1 } < M#{ a => 1, b => 3},
+    true  = M#{ a => 1, b => 1 } < M#{ a => 1, b => 3},
+    false = M#{ a => 1 } < M#{ a => 1.0},
+    false = M#{ a => 1.0 } < M#{ a => 1},
+
+    true  = M#{ "a" => "hi", b => 134 } == M#{ b => 134,"a" => "hi"},
+
+    %% lists:sort
+
+    SortVs = [#{"a"=>1},#{a=>2},#{1=>3},#{<<"a">>=>4}],
+    [#{1:=ok},#{a:=ok},#{"a":=ok},#{<<"a">>:=ok}] = lists:sort([#{"a"=>ok},#{a=>ok},#{1=>ok},#{<<"a">>=>ok}]),
+    [#{1:=3},#{a:=2},#{"a":=1},#{<<"a">>:=4}] = lists:sort(SortVs),
+    [#{1:=3},#{a:=2},#{"a":=1},#{<<"a">>:=4}] = lists:sort(lists:reverse(SortVs)),
+    ok.
+
+t_map_equal(Config) when is_list(Config) ->
+    true  = #{} =:= #{},
+    false = #{} =:= #{a=>1},
+    false = #{a=>1} =:= #{},
+    true  = #{ "a" => "hi", b => 134 } =:= #{ b => 134,"a" => "hi"},
+
+    false = #{ a => 1 } =:= #{ a => 2},
+    false = #{ a => 2 } =:= #{ a => 1},
+    false = #{ a => 2, b => 1 } =:= #{ a => 1, b => 3},
+    false = #{ a => 1, b => 1 } =:= #{ a => 1, b => 3},
+
+    true = #{ a => 1 } =:= #{ a => 1},
+    true = #{ "a" => 2 } =:= #{ "a" => 2},
+    true = #{ "a" => 2, b => 3 } =:= #{ "a" => 2, b => 3},
+    true = #{ a => 1, b => 3, c => <<"wat">> } =:= #{ a => 1, b => 3, c=><<"wat">>},
+    ok.
+
+
+t_map_compare(Config) when is_list(Config) ->
+    Seed = {erlang:monotonic_time(),
+	    erlang:time_offset(),
+	    erlang:unique_integer()},
+    io:format("seed = ~p\n", [Seed]),
+    random:seed(Seed),
+    repeat(100, fun(_) -> float_int_compare() end, []),
+    repeat(100, fun(_) -> recursive_compare() end, []),
+    ok.
+
+float_int_compare() ->
+    Terms = numeric_keys(3),
+    %%io:format("Keys to use: ~p\n", [Terms]),
+    Pairs = lists:map(fun(K) -> list_to_tuple([{K,V} || V <- Terms]) end, Terms),
+    lists:foreach(fun(Size) ->
+			  MapGen = fun() -> map_gen(list_to_tuple(Pairs), Size) end,
+			  repeat(100, fun do_compare/1, [MapGen, MapGen])
+		  end,
+		  lists:seq(1,length(Terms))),
+    ok.
+
+numeric_keys(N) ->
+    lists:foldl(fun(_,Acc) ->
+			Int = random:uniform(N*4) - N*2,
+			Float = float(Int),
+			[Int, Float, Float * 0.99, Float * 1.01 | Acc]
+		end,
+		[],
+		lists:seq(1,N)).
+
+
+repeat(0, _, _) ->
+    ok;
+repeat(N, Fun, Arg) ->
+    Fun(Arg),
+    repeat(N-1, Fun, Arg).
+
+copy_term(T) ->
+    Papa = self(),
+    P = spawn_link(fun() -> receive Msg -> Papa ! Msg end end),
+    P ! T,
+    receive R -> R end.
+
+do_compare([Gen1, Gen2]) ->
+    M1 = Gen1(),
+    M2 = Gen2(),
+    %%io:format("Maps to compare: ~p AND ~p\n", [M1, M2]),
+    C = (M1 < M2),
+    Erlang = maps_lessthan(M1, M2),
+    C = Erlang,
+    ?CHECK(M1==M1, M1),
+
+    %% Change one key from int to float (or vice versa) and check compare
+    ML1 = maps:to_list(M1),
+    {K1,V1} = lists:nth(random:uniform(length(ML1)), ML1),
+    case K1 of
+	I when is_integer(I) ->
+	    case maps:find(float(I),M1) of
+		error ->
+		    M1f = maps:remove(I, maps:put(float(I), V1, M1)),
+		    ?CHECK(M1f > M1, [M1f, M1]);
+		_ -> ok
+	    end;
+
+	F when is_float(F), round(F) == F ->
+	    case maps:find(round(F),M1) of
+		error ->
+		    M1i = maps:remove(F, maps:put(round(F), V1, M1)),
+		    ?CHECK(M1i < M1, [M1i, M1]);
+		_ -> ok
+	    end;
+
+	_ -> ok   % skip floats with decimals
+    end,
+
+    ?CHECK(M2 == M2, [M2]).
+
+
+maps_lessthan(M1, M2) ->
+  case {maps:size(M1),maps:size(M2)} of
+      {_S,_S} ->
+	  {K1,V1} = lists:unzip(term_sort(maps:to_list(M1))),
+	  {K2,V2} = lists:unzip(term_sort(maps:to_list(M2))),
+
+	  case erts_internal:cmp_term(K1,K2) of
+	      -1 -> true;
+	      0 -> (V1 < V2);
+	      1 -> false
+	  end;
+
+      {S1, S2} ->
+	  S1 < S2
+  end.
+
+term_sort(L) ->
+    lists:sort(fun(A,B) -> erts_internal:cmp_term(A,B) =< 0 end,
+	       L).
+
+
+cmp(T1, T2, Exact) when is_tuple(T1) and is_tuple(T2) ->
+    case {size(T1),size(T2)} of
+	{_S,_S} -> cmp(tuple_to_list(T1), tuple_to_list(T2), Exact);
+	{S1,S2} when S1 < S2 -> -1;
+	{S1,S2} when S1 > S2 -> 1
+    end;
+
+cmp([H1|T1], [H2|T2], Exact) ->
+    case cmp(H1,H2, Exact) of
+	0 -> cmp(T1,T2, Exact);
+	C -> C
+    end;
+
+cmp(M1, M2, Exact) when is_map(M1) andalso is_map(M2) ->
+    cmp_maps(M1,M2,Exact);
+cmp(M1, M2, Exact) ->
+    cmp_others(M1, M2, Exact).
+
+cmp_maps(M1, M2, Exact) ->
+    case {maps:size(M1),maps:size(M2)} of
+	{_S,_S} ->
+	    {K1,V1} = lists:unzip(term_sort(maps:to_list(M1))),
+	    {K2,V2} = lists:unzip(term_sort(maps:to_list(M2))),
+
+	    case cmp(K1, K2, true) of
+		0 -> cmp(V1, V2, Exact);
+		C -> C
+	    end;
+
+	{S1,S2} when S1 < S2 -> -1;
+	{S1,S2} when S1 > S2 -> 1
+    end.
+
+cmp_others(I, F, true) when is_integer(I), is_float(F) ->
+    -1;
+cmp_others(F, I, true) when is_float(F), is_integer(I) ->
+    1;
+cmp_others(T1, T2, _) ->
+    case {T1<T2, T1==T2} of
+	{true,false} -> -1;
+	{false,true} -> 0;
+	{false,false} -> 1
+    end.
+
+map_gen(Pairs, Size) ->
+    {_,L} = lists:foldl(fun(_, {Keys, Acc}) ->
+				KI = random:uniform(size(Keys)),
+				K = element(KI,Keys),
+				KV = element(random:uniform(size(K)), K),
+				{erlang:delete_element(KI,Keys), [KV | Acc]}
+			end,
+			{Pairs, []},
+			lists:seq(1,Size)),
+
+    maps:from_list(L).
+
+
+recursive_compare() ->
+    Leafs = {atom, 17, 16.9, 17.1, [], self(), spawn(fun() -> ok end), make_ref(), make_ref()},
+    {A, B} = term_gen_recursive(Leafs, 0, 0),
+    %%io:format("Recursive term A = ~p\n", [A]),
+    %%io:format("Recursive term B = ~p\n", [B]),
+
+    ?CHECK({true,false} =:=  case do_cmp(A, B, false) of
+				 -1 -> {A<B, A>=B};
+				 0 -> {A==B, A/=B};
+				 1 -> {A>B, A=<B}
+			     end,
+	   {A,B}),
+    A2 = copy_term(A),
+    ?CHECK(A == A2, {A,A2}),
+    ?CHECK(0 =:= cmp(A, A2, false), {A,A2}),
+
+    B2 = copy_term(B),
+    ?CHECK(B == B2, {B,B2}),
+    ?CHECK(0 =:= cmp(B, B2, false), {B,B2}),
+    ok.
+
+do_cmp(A, B, Exact) ->
+    C = cmp(A, B, Exact),
+    C.
+
+%% Generate two terms {A,B} that may only differ
+%% at float vs integer types.
+term_gen_recursive(Leafs, Flags, Depth) ->
+    MaxDepth = 10,
+    Rnd = case {Flags, Depth} of
+	      {_, MaxDepth} -> % Only leafs
+		  random:uniform(size(Leafs)) + 3;
+	      {0, 0} ->        % Only containers
+		  random:uniform(3);
+	      {0,_} ->         % Anything
+		  random:uniform(size(Leafs)+3)
+	  end,
+    case Rnd of
+	1 -> % Make map
+	    Size = random:uniform(size(Leafs)),
+	    lists:foldl(fun(_, {Acc1,Acc2}) ->
+				{K1,K2} = term_gen_recursive(Leafs, Flags,
+							     Depth+1),
+				{V1,V2} = term_gen_recursive(Leafs, Flags, Depth+1),
+				{maps:put(K1,V1, Acc1), maps:put(K2,V2, Acc2)}
+			end,
+			{maps:new(), maps:new()},
+			lists:seq(1,Size));
+	2 -> % Make cons
+	    {Car1,Car2} = term_gen_recursive(Leafs, Flags, Depth+1),
+	    {Cdr1,Cdr2} = term_gen_recursive(Leafs, Flags, Depth+1),
+	    {[Car1 | Cdr1], [Car2 | Cdr2]};
+	3 -> % Make tuple
+	    Size = random:uniform(size(Leafs)),
+	    L = lists:map(fun(_) -> term_gen_recursive(Leafs, Flags, Depth+1) end,
+			  lists:seq(1,Size)),
+	    {L1, L2} = lists:unzip(L),
+	    {list_to_tuple(L1), list_to_tuple(L2)};
+
+	N -> % Make leaf
+	    case element(N-3, Leafs) of
+		I when is_integer(I) ->
+		    case random:uniform(4) of
+			1 -> {I, float(I)};
+			2 -> {float(I), I};
+			_ -> {I,I}
+		    end;
+		T -> {T,T}
+	    end
+    end.
+
+%% BIFs
+t_bif_map_get(Config) when is_list(Config) ->
+    %% small map
+    1    = maps:get(a, #{ a=> 1}),
+    2    = maps:get(b, #{ a=> 1, b => 2}),
+    "hi" = maps:get("hello", #{ a=>1, "hello" => "hi"}),
+    "tuple hi" = maps:get({1,1.0}, #{ a=>a, {1,1.0} => "tuple hi"}),
+
+    M0    = #{ k1=>"v1", <<"k2">> => <<"v3">> },
+    "v4" = maps:get(<<"k2">>, M0#{<<"k2">> => "v4"}),
+
+    %% large map
+    M1   = maps:from_list([{I,I}||I<-lists:seq(1,100)] ++
+			  [{a,1},{b,2},{"hello","hi"},{{1,1.0},"tuple hi"},
+			   {k1,"v1"},{<<"k2">>,"v3"}]),
+    1    = maps:get(a, M1),
+    2    = maps:get(b, M1),
+    "hi" = maps:get("hello", M1),
+    "tuple hi" = maps:get({1,1.0}, M1),
+    "v3" = maps:get(<<"k2">>, M1),
+
+    %% error cases
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,get,_,_}|_]}} =
+			  (catch maps:get(a, T))
+	      end),
+
+    {'EXIT',{{badkey,{1,1}},[{maps,get,_,_}|_]}} =
+	(catch maps:get({1,1}, #{{1,1.0} => "tuple"})),
+    {'EXIT',{{badkey,a},[{maps,get,_,_}|_]}} = (catch maps:get(a, #{})),
+    {'EXIT',{{badkey,a},[{maps,get,_,_}|_]}} =
+	(catch maps:get(a, #{b=>1, c=>2})),
+    ok.
+
+t_bif_map_find(Config) when is_list(Config) ->
+    %% small map
+    {ok, 1}     = maps:find(a, #{ a=> 1}),
+    {ok, 2}     = maps:find(b, #{ a=> 1, b => 2}),
+    {ok, "int"} = maps:find(1, #{ 1   => "int"}),
+    {ok, "float"} = maps:find(1.0, #{ 1.0=> "float"}),
+
+    {ok, "hi"} = maps:find("hello", #{ a=>1, "hello" => "hi"}),
+    {ok, "tuple hi"} = maps:find({1,1.0}, #{ a=>a, {1,1.0} => "tuple hi"}),
+
+    M0 = #{ k1=>"v1", <<"k2">> => <<"v3">> },
+    {ok, "v4"} = maps:find(<<"k2">>, M0#{ <<"k2">> => "v4" }),
+
+    %% large map
+    M1   = maps:from_list([{I,I}||I<-lists:seq(1,100)] ++
+			  [{a,1},{b,2},{"hello","hi"},{{1,1.0},"tuple hi"},
+			   {k1,"v1"},{<<"k2">>,"v3"}]),
+    {ok, 1}    = maps:find(a, M1),
+    {ok, 2}    = maps:find(b, M1),
+    {ok, "hi"} = maps:find("hello", M1),
+    {ok, "tuple hi"} = maps:find({1,1.0}, M1),
+    {ok, "v3"} = maps:find(<<"k2">>, M1),
+
+    %% error case
+    error = maps:find(a,#{}),
+    error = maps:find(a,#{b=>1, c=>2}),
+    error = maps:find(1.0, #{ 1 => "int"}),
+    error = maps:find(1, #{ 1.0  => "float"}),
+    error = maps:find({1.0,1}, #{ a=>a, {1,1.0} => "tuple hi"}), % reverse types in tuple key
+
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,find,_,_}|_]}} =
+			  (catch maps:find(a, T))
+	      end),
+    ok.
+
+
+t_bif_map_is_key(Config) when is_list(Config) ->
+    M1 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>, 4 => number},
+
+    true  = maps:is_key("hi", M1),
+    true  = maps:is_key(int, M1),
+    true  = maps:is_key(<<"key">>, M1),
+    true  = maps:is_key(4, M1),
+
+    false = maps:is_key(5, M1),
+    false = maps:is_key(<<"key2">>, M1),
+    false = maps:is_key("h", M1),
+    false = maps:is_key("hello", M1),
+    false = maps:is_key(atom, M1),
+    false = maps:is_key(any, #{}),
+
+    false = maps:is_key("hi", maps:remove("hi", M1)),
+    true  = maps:is_key("hi", M1),
+    true  = maps:is_key(1, maps:put(1, "number", M1)),
+    false = maps:is_key(1.0, maps:put(1, "number", M1)),
+
+    %% error case
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,is_key,_,_}|_]}} =
+			  (catch maps:is_key(a, T))
+	      end),
+    ok.
+
+t_bif_map_keys(Config) when is_list(Config) ->
+    [] = maps:keys(#{}),
+
+    [1,2,3,4,5] = lists:sort(maps:keys(#{ 1 => a, 2 => b, 3 => c, 4 => d, 5 => e})),
+    [1,2,3,4,5] = lists:sort(maps:keys(#{ 4 => d, 5 => e, 1 => a, 2 => b, 3 => c})),
+
+    % values in key order: [4,int,"hi",<<"key">>]
+    M1 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>, 4 => number},
+    [4,int,"hi",<<"key">>] = lists:sort(maps:keys(M1)),
+
+    %% error case
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,keys,_,_}|_]}} =
+			  (catch maps:keys(T))
+	      end),
+    ok.
+
+t_bif_map_new(Config) when is_list(Config) ->
+    #{} = maps:new(),
+    0   = erlang:map_size(maps:new()),
+    ok.
+
+t_bif_map_merge(Config) when is_list(Config) ->
+    0   = erlang:map_size(maps:merge(#{},#{})),
+
+    M0 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+	4 => number, 18446744073709551629 => wat},
+
+    #{ "hi" := "hello", int := 3, <<"key">> := <<"value">>,
+	4 := number, 18446744073709551629 := wat} = maps:merge(#{}, M0),
+
+    #{ "hi" := "hello", int := 3, <<"key">> := <<"value">>,
+	4 := number, 18446744073709551629 := wat} = maps:merge(M0, #{}),
+
+    M1 = #{ "hi" => "hello again", float => 3.3, {1,2} => "tuple", 4 => integer },
+
+    #{4 := number, 18446744073709551629 := wat, float := 3.3, int := 3,
+	{1,2} := "tuple", "hi" := "hello", <<"key">> := <<"value">>} = maps:merge(M1,M0),
+
+    #{4 := integer, 18446744073709551629 := wat, float := 3.3, int := 3,
+	{1,2} := "tuple", "hi" := "hello again", <<"key">> := <<"value">>} = maps:merge(M0,M1),
+
+    %% try deep collisions
+    N  = 150000,
+    Is = lists:seq(1,N),
+    M2 = maps:from_list([{I,I}||I<-Is]),
+    150000 = maps:size(M2),
+    M3 = maps:from_list([{<<I:32>>,I}||I<-Is]),
+    150000 = maps:size(M3),
+    M4 = maps:merge(M2,M3),
+    300000 = maps:size(M4),
+    M5 = maps:from_list([{integer_to_list(I),I}||I<-Is]),
+    150000 = maps:size(M5),
+    M6 = maps:merge(M4,M5),
+    450000 = maps:size(M6),
+    M7 = maps:from_list([{float(I),I}||I<-Is]),
+    150000 = maps:size(M7),
+    M8 = maps:merge(M7,M6),
+    600000 = maps:size(M8),
+
+    #{      1 := 1,           "1" := 1,           <<1:32>> := 1      } = M8,
+    #{     10 := 10,         "10" := 10,         <<10:32>> := 10     } = M8,
+    #{    100 := 100,       "100" := 100,       <<100:32>> := 100    } = M8,
+    #{   1000 := 1000,     "1000" := 1000,     <<1000:32>> := 1000   } = M8,
+    #{  10000 := 10000,   "10000" := 10000,   <<10000:32>> := 10000  } = M8,
+    #{ 100000 := 100000, "100000" := 100000, <<100000:32>> := 100000 } = M8,
+
+    %% overlapping
+    M8 = maps:merge(M2,M8),
+    M8 = maps:merge(M3,M8),
+    M8 = maps:merge(M4,M8),
+    M8 = maps:merge(M5,M8),
+    M8 = maps:merge(M6,M8),
+    M8 = maps:merge(M7,M8),
+    M8 = maps:merge(M8,M8),
+
+    %% maps:merge/2 and mixed
+
+    Ks1 = [764492191,2361333849], %% deep collision
+    Ks2 = lists:seq(1,33),
+    M9  = maps:from_list([{K,K}||K <- Ks1]),
+    M10 = maps:from_list([{K,K}||K <- Ks2]),
+    M11 = maps:merge(M9,M10),
+    ok = check_keys_exist(Ks1 ++ Ks2, M11),
+
+    %% error case
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,merge,_,_}|_]}} =
+			  (catch maps:merge(#{}, T)),
+		      {'EXIT',{{badmap,T},[{maps,merge,_,_}|_]}} =
+			  (catch maps:merge(T, #{})),
+		      {'EXIT',{{badmap,T},[{maps,merge,_,_}|_]}} =
+			  (catch maps:merge(T, T))
+	      end),
+    ok.
+
+
+t_bif_map_put(Config) when is_list(Config) ->
+    M0 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+	4 => number, 18446744073709551629 => wat},
+
+    M1 = #{ "hi" := "hello"} = maps:put("hi", "hello", #{}),
+
+    true = is_members(["hi"],maps:keys(M1)),
+    true = is_members(["hello"],maps:values(M1)),
+
+    M2 = #{ int := 3 } = maps:put(int, 3, M1),
+
+    true = is_members([int,"hi"],maps:keys(M2)),
+    true = is_members([3,"hello"],maps:values(M2)),
+
+    M3 = #{ <<"key">> := <<"value">> } = maps:put(<<"key">>, <<"value">>, M2),
+
+    true = is_members([int,"hi",<<"key">>],maps:keys(M3)),
+    true = is_members([3,"hello",<<"value">>],maps:values(M3)),
+
+    M4 = #{ 18446744073709551629 := wat } = maps:put(18446744073709551629, wat, M3),
+
+    true = is_members([18446744073709551629,int,"hi",<<"key">>],maps:keys(M4)),
+    true = is_members([wat,3,"hello",<<"value">>],maps:values(M4)),
+
+    M0 = #{ 4 := number } = M5 = maps:put(4, number, M4),
+
+    true = is_members([4,18446744073709551629,int,"hi",<<"key">>],maps:keys(M5)),
+    true = is_members([number,wat,3,"hello",<<"value">>],maps:values(M5)),
+
+    M6 = #{ <<"key">> := <<"other value">> } = maps:put(<<"key">>, <<"other value">>, M5),
+
+    true = is_members([4,18446744073709551629,int,"hi",<<"key">>],maps:keys(M6)),
+    true = is_members([number,wat,3,"hello",<<"other value">>],maps:values(M6)),
+
+    %% error case
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,put,_,_}|_]}} =
+			  (catch maps:put(1, a, T))
+	      end),
+    ok.
+
+is_members(Ks,Ls) when length(Ks) =/= length(Ls) -> false;
+is_members(Ks,Ls) -> is_members_do(Ks,Ls).
+
+is_members_do([],[]) -> true;
+is_members_do([],_) -> false;
+is_members_do([K|Ks],Ls) ->
+    is_members_do(Ks, lists:delete(K,Ls)).
+
+t_bif_map_remove(Config) when is_list(Config) ->
+    0  = erlang:map_size(maps:remove(some_key, #{})),
+
+    M0 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+	4 => number, 18446744073709551629 => wat},
+
+    M1 = maps:remove("hi", M0),
+    true = is_members([4,18446744073709551629,int,<<"key">>],maps:keys(M1)),
+    true = is_members([number,wat,3,<<"value">>],maps:values(M1)),
+
+    M2 = maps:remove(int, M1),
+    true = is_members([4,18446744073709551629,<<"key">>],maps:keys(M2)),
+    true = is_members([number,wat,<<"value">>],maps:values(M2)),
+
+    M3 = maps:remove(<<"key">>, M2),
+    true = is_members([4,18446744073709551629],maps:keys(M3)),
+    true = is_members([number,wat],maps:values(M3)),
+
+    M4 = maps:remove(18446744073709551629, M3),
+    true = is_members([4],maps:keys(M4)),
+    true = is_members([number],maps:values(M4)),
+
+    M5 = maps:remove(4, M4),
+    [] = maps:keys(M5),
+    [] = maps:values(M5),
+
+    M0 = maps:remove(5,M0),
+    M0 = maps:remove("hi there",M0),
+
+    #{ "hi" := "hello", int := 3, 4 := number} = maps:remove(18446744073709551629,maps:remove(<<"key">>,M0)),
+
+    %% error case
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,remove,_,_}|_]}} =
+	(catch maps:remove(a, T))
+	      end),
+     ok.
+
+t_bif_map_update(Config) when is_list(Config) ->
+    M0 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>,
+	4 => number, 18446744073709551629 => wat},
+
+    #{ "hi" := "hello again", int := 3, <<"key">> := <<"value">>,
+	4 := number, 18446744073709551629 := wat} = maps:update("hi", "hello again", M0),
+
+    #{ "hi" := "hello", int := 1337, <<"key">> := <<"value">>,
+	4 := number, 18446744073709551629 := wat} = maps:update(int, 1337, M0),
+
+    #{ "hi" := "hello", int := 3, <<"key">> := <<"new value">>,
+	4 := number, 18446744073709551629 := wat} = maps:update(<<"key">>, <<"new value">>, M0),
+
+    #{ "hi" := "hello", int := 3, <<"key">> := <<"value">>,
+	4 := integer, 18446744073709551629 := wat} = maps:update(4, integer, M0),
+
+    #{ "hi" := "hello", int := 3, <<"key">> := <<"value">>,
+	4 := number, 18446744073709551629 := wazzup} = maps:update(18446744073709551629, wazzup, M0),
+
+    %% error case
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,update,_,_}|_]}} =
+			  (catch maps:update(1, none, T))
+	      end),
+    ok.
+
+
+
+t_bif_map_values(Config) when is_list(Config) ->
+
+    [] = maps:values(#{}),
+    [1] = maps:values(#{a=>1}),
+
+    true = is_members([a,b,c,d,e],maps:values(#{ 1 => a, 2 => b, 3 => c, 4 => d, 5 => e})),
+    true = is_members([a,b,c,d,e],maps:values(#{ 4 => d, 5 => e, 1 => a, 2 => b, 3 => c})),
+
+    M1 = #{ "hi" => "hello", int => 3, <<"key">> => <<"value">>, 4 => number},
+    M2 = M1#{ "hi" => "hello2", <<"key">> => <<"value2">> },
+    true = is_members([number,3,"hello2",<<"value2">>],maps:values(M2)),
+    true = is_members([number,3,"hello",<<"value">>],maps:values(M1)),
+
+    Vs = lists:seq(1000,20000),
+    M3 = maps:from_list([{K,K}||K<-Vs]),
+    M4 = maps:merge(M1,M3),
+    M5 = maps:merge(M2,M3),
+    true = is_members(Vs,maps:values(M3)),
+    true = is_members([number,3,"hello",<<"value">>]++Vs,maps:values(M4)),
+    true = is_members([number,3,"hello2",<<"value2">>]++Vs,maps:values(M5)),
+
+    %% error case
+    do_badmap(fun(T) ->
+		      {'EXIT',{{badmap,T},[{maps,values,_,_}|_]}} =
+			  (catch maps:values(T))
+	      end),
+    ok.
+
+t_erlang_hash(Config) when is_list(Config) ->
+    ok = t_bif_erlang_phash2(),
+    ok = t_bif_erlang_phash(),
+    ok.
+
+t_bif_erlang_phash2() ->
+
+    39679005 = erlang:phash2(#{}),
+    33667975 = erlang:phash2(#{ a => 1, "a" => 2, <<"a">> => 3, {a,b} => 4 }), % 78942764
+    95332690 = erlang:phash2(#{ 1 => a, 2 => "a", 3 => <<"a">>, 4 => {a,b} }), % 37338230
+    108954384 = erlang:phash2(#{ 1 => a }), % 14363616
+    59617982 = erlang:phash2(#{ a => 1 }), % 51612236
+
+    42770201 = erlang:phash2(#{{} => <<>>}), % 37468437
+    71687700 = erlang:phash2(#{<<>> => {}}), % 44049159
+
+    M0 = #{ a => 1, "key" => <<"value">> },
+    M1 = maps:remove("key",M0),
+    M2 = M1#{ "key" => <<"value">> },
+
+    70249457 = erlang:phash2(M0), % 118679416
+    59617982 = erlang:phash2(M1), % 51612236
+    70249457 = erlang:phash2(M2), % 118679416
+    ok.
+
+t_bif_erlang_phash() ->
+    Sz = 1 bsl 32,
+    1113425985 = erlang:phash(#{},Sz), % 268440612
+    1510068139 = erlang:phash(#{ a => 1, "a" => 2, <<"a">> => 3, {a,b} => 4 },Sz), % 1196461908
+    3182345590 = erlang:phash(#{ 1 => a, 2 => "a", 3 => <<"a">>, 4 => {a,b} },Sz), % 3944426064
+    2927531828 = erlang:phash(#{ 1 => a },Sz), % 1394238263
+    1670235874 = erlang:phash(#{ a => 1 },Sz), % 4066388227
+
+    3935089469 = erlang:phash(#{{} => <<>>},Sz), % 1578050717
+    71692856   = erlang:phash(#{<<>> => {}},Sz), % 1578050717
+
+    M0 = #{ a => 1, "key" => <<"value">> },
+    M1 = maps:remove("key",M0),
+    M2 = M1#{ "key" => <<"value">> },
+
+    2620391445 = erlang:phash(M0,Sz), % 3590546636
+    1670235874 = erlang:phash(M1,Sz), % 4066388227
+    2620391445 = erlang:phash(M2,Sz), % 3590546636
+    ok.
+
+t_map_encode_decode(Config) when is_list(Config) ->
+    <<131,116,0,0,0,0>> = erlang:term_to_binary(#{}),
+    Pairs = [
+	{a,b},{"key","values"},{<<"key">>,<<"value">>},
+	{1,b},{[atom,1],{<<"wat">>,1,2,3}},
+	{aa,"values"},
+	{1 bsl 64 + (1 bsl 50 - 1), sc1},
+	{99, sc2},
+	{1 bsl 65 + (1 bsl 51 - 1), sc3},
+	{88, sc4},
+	{1 bsl 66 + (1 bsl 52 - 1), sc5},
+	{77, sc6},
+	{1 bsl 67 + (1 bsl 53 - 1), sc3},
+	{75, sc6}, {-10,sc8},
+	{<<>>, sc9}, {3.14158, sc10},
+	{[3.14158], sc11}, {more_atoms, sc12},
+	{{more_tuples}, sc13}, {self(), sc14},
+	{{},{}},{[],[]}
+    ],
+    ok = map_encode_decode_and_match(Pairs,[],#{}),
+
+    %% check sorting
+
+    %% literally #{ b=>2, a=>1 } in the internal order
+    #{ a:=1, b:=2 } =
+	erlang:binary_to_term(<<131,116,0,0,0,2,100,0,1,98,97,2,100,0,1,97,97,1>>),
+
+
+    %% literally #{ "hi" => "value", a=>33, b=>55 } in the internal order
+    #{ a:=33, b:=55, "hi" := "value"} = erlang:binary_to_term(<<131,116,0,0,0,3,
+	107,0,2,104,105,            % "hi" :: list()
+	107,0,5,118,97,108,117,101, % "value" :: list()
+	100,0,1,97,                 % a :: atom()
+	97,33,                      % 33 :: integer()
+	100,0,1,98,                 % b :: atom()
+	97,55                       % 55 :: integer()
+	>>),
+
+    %% Maps of different sizes
+    lists:foldl(fun(Key, M0) ->
+			M1 = M0#{Key => Key},
+			case Key rem 17 of
+			    0 ->
+				M1 = binary_to_term(term_to_binary(M1));
+			    _ ->
+				ok
+			end,
+			M1
+		end,
+		#{},
+		lists:seq(1,10000)),
+
+    %% many maps in same binary
+    MapList = lists:foldl(fun(K, [M|_]=Acc) -> [M#{K => K} | Acc] end,
+			  [#{}],
+			  lists:seq(1,100)),
+    MapList = binary_to_term(term_to_binary(MapList)),
+    MapListR = lists:reverse(MapList),
+    MapListR = binary_to_term(term_to_binary(MapListR)),
+
+    %% error cases
+    %% template: <<131,116,0,0,0,2,100,0,1,97,100,0,1,98,97,1,97,1>>
+    %% which is: #{ a=>1, b=>1 }
+
+    %% uniqueness violation
+    %% literally #{ a=>1, "hi"=>"value", a=>2 }
+    {'EXIT',{badarg,[{_,_,_,_}|_]}} = (catch
+	erlang:binary_to_term(<<131,116,0,0,0,3,
+			       100,0,1,97,
+			       97,1,
+			       107,0,2,104,105,
+			       107,0,5,118,97,108,117,101,
+			       100,0,1,97,
+			       97,2>>)),
+
+    %% bad size (too large)
+    {'EXIT',{badarg,[{_,_,_,_}|_]}} = (catch
+	erlang:binary_to_term(<<131,116,0,0,0,12,100,0,1,97,97,1,100,0,1,98,97,1>>)),
+
+    %% bad size (too small) .. should fail just truncate it .. weird.
+    %% possibly change external format so truncated will be #{a:=1}
+    #{ a:=b } =
+	erlang:binary_to_term(<<131,116,0,0,0,1,100,0,1,97,100,0,1,98,97,1,97,1>>),
+
+    ok.
+
+map_encode_decode_and_match([{K,V}|Pairs], EncodedPairs, M0) ->
+    M1 = maps:put(K,V,M0),
+    B0 = erlang:term_to_binary(M1),
+    Ls = [{erlang:term_to_binary(K), erlang:term_to_binary(V)}|EncodedPairs],
+    ok = match_encoded_map(B0, length(Ls), Ls),
+    %% decode and match it
+    M1 = erlang:binary_to_term(B0),
+    map_encode_decode_and_match(Pairs,Ls,M1);
+map_encode_decode_and_match([],_,_) -> ok.
+
+match_encoded_map(<<131,116,Size:32,Encoded/binary>>,Size,Items) ->
+    match_encoded_map_stripped_size(Encoded,Items,Items);
+match_encoded_map(_,_,_) -> no_match_size.
+
+match_encoded_map_stripped_size(<<>>,_,_) -> ok;
+match_encoded_map_stripped_size(B0,[{<<131,K/binary>>,<<131,V/binary>>}|Items],Ls) ->
+    Ksz = byte_size(K),
+    Vsz = byte_size(V),
+    case B0 of
+	<<K:Ksz/binary,V:Vsz/binary,B1/binary>> ->
+	    match_encoded_map_stripped_size(B1,Ls,Ls);
+	_ ->
+	    match_encoded_map_stripped_size(B0,Items,Ls)
+    end;
+match_encoded_map_stripped_size(_,[],_) -> fail.
+
+
+t_bif_map_to_list(Config) when is_list(Config) ->
+    [] = maps:to_list(#{}),
+    [{a,1},{b,2}] = lists:sort(maps:to_list(#{a=>1,b=>2})),
+    [{a,1},{b,2},{c,3}] = lists:sort(maps:to_list(#{c=>3,a=>1,b=>2})),
+    [{a,1},{b,2},{g,3}] = lists:sort(maps:to_list(#{g=>3,a=>1,b=>2})),
+    [{a,1},{b,2},{g,3},{"c",4}] = lists:sort(maps:to_list(#{g=>3,a=>1,b=>2,"c"=>4})),
+    [{3,v2},{hi,v4},{{hi,3},v5},{"hi",v3},{<<"hi">>,v1}] =
+	lists:sort(maps:to_list(#{<<"hi">>=>v1,3=>v2,"hi"=>v3,hi=>v4,{hi,3}=>v5})),
+
+    [{3,v7},{hi,v9},{{hi,3},v10},{"hi",v8},{<<"hi">>,v6}] =
+	lists:sort(maps:to_list(#{<<"hi">>=>v1,3=>v2,"hi"=>v3,hi=>v4,{hi,3}=>v5,
+				  <<"hi">>=>v6,3=>v7,"hi"=>v8,hi=>v9,{hi,3}=>v10})),
+
+    %% error cases
+    do_badmap(fun(T) ->
+		      {'EXIT', {{badmap,T},_}} =
+			  (catch maps:to_list(T))
+	      end),
+    ok.
+
+
+t_bif_map_from_list(Config) when is_list(Config) ->
+    #{} = maps:from_list([]),
+    A   = maps:from_list([]),
+    0   = erlang:map_size(A),
+
+    #{a:=1,b:=2}      = maps:from_list([{a,1},{b,2}]),
+    #{c:=3,a:=1,b:=2} = maps:from_list([{a,1},{b,2},{c,3}]),
+    #{g:=3,a:=1,b:=2} = maps:from_list([{a,1},{b,2},{g,3}]),
+
+    #{a:=2} = maps:from_list([{a,1},{a,3},{a,2}]),
+
+    #{ <<"hi">>:=v1,3:=v3,"hi":=v6,hi:=v4,{hi,3}:=v5} =
+	maps:from_list([{3,v3},{"hi",v6},{hi,v4},{{hi,3},v5},{<<"hi">>,v1}]),
+
+    #{<<"hi">>:=v6,3:=v8,"hi":=v11,hi:=v9,{hi,3}:=v10} =
+	maps:from_list([ {{hi,3},v3}, {"hi",v0},{3,v1}, {<<"hi">>,v4}, {hi,v2},
+	    {<<"hi">>,v6}, {{hi,3},v10},{"hi",v11}, {hi,v9}, {3,v8}]),
+
+    %% repeated keys (large -> small)
+    Ps1 = [{a,I}|| I <- lists:seq(1,32)],
+    Ps2 = [{a,I}|| I <- lists:seq(33,64)],
+
+    M = maps:from_list(Ps1 ++ [{b,1},{c,1}] ++ Ps2),
+    #{ a := 64, b := 1, c := 1 } = M,
+
+    %% error cases
+    {'EXIT', {badarg,_}} = (catch maps:from_list([{a,b},b])),
+    {'EXIT', {badarg,_}} = (catch maps:from_list([{a,b},{b,b,3}])),
+    {'EXIT', {badarg,_}} = (catch maps:from_list([{a,b},<<>>])),
+    {'EXIT', {badarg,_}} = (catch maps:from_list([{a,b}|{b,a}])),
+    {'EXIT', {badarg,_}} = (catch maps:from_list(a)),
+    {'EXIT', {badarg,_}} = (catch maps:from_list(42)),
+    ok.
+
+t_bif_build_and_check(Config) when is_list(Config) ->
+    ok = check_build_and_remove(750,[
+				      fun(K) -> [K,K] end,
+				      fun(K) -> [float(K),K] end,
+				      fun(K) -> K end,
+				      fun(K) -> {1,K} end,
+				      fun(K) -> {K} end,
+				      fun(K) -> [K|K] end,
+				      fun(K) -> [K,1,2,3,4] end,
+				      fun(K) -> {K,atom} end,
+				      fun(K) -> float(K) end,
+				      fun(K) -> integer_to_list(K) end,
+				      fun(K) -> list_to_atom(integer_to_list(K)) end,
+				      fun(K) -> [K,{K,[K,{K,[K]}]}] end,
+				      fun(K) -> <<K:32>> end
+			      ]),
+
+    ok.
+
+check_build_and_remove(_,[]) -> ok;
+check_build_and_remove(N,[F|Fs]) ->
+    {M,Ks} = build_and_check(N, maps:new(), F, []),
+    ok     = remove_and_check(Ks,M),
+    check_build_and_remove(N,Fs).
+
+build_and_check(0, M0, _, Ks) -> {M0, Ks};
+build_and_check(N, M0, F, Ks) ->
+    K  = build_key(F,N),
+    M1 = maps:put(K,K,M0),
+    ok = check_keys_exist([I||{I,_} <- [{K,M1}|Ks]], M1),
+    M2 = maps:update(K,v,M1),
+    v  = maps:get(K,M2),
+    build_and_check(N-1,M1,F,[{K,M1}|Ks]).
+
+remove_and_check([],_) -> ok;
+remove_and_check([{K,Mc}|Ks], M0) ->
+    K     = maps:get(K,M0),
+    true  = maps:is_key(K,M0),
+    true  = Mc =:= M0,
+    true  = M0 == Mc,
+    M1    = maps:remove(K,M0),
+    false = M1 =:= Mc,
+    false = Mc == M1,
+    false = maps:is_key(K,M1),
+    true  = maps:is_key(K,M0),
+    ok    = check_keys_exist([I||{I,_} <- Ks],M1),
+    error = maps:find(K,M1),
+    remove_and_check(Ks, M1).
+
+build_key(F,N) when N rem 3 =:= 0 -> F(N);
+build_key(F,N) when N rem 3 =:= 1 -> K = F(N), {K,K};
+build_key(F,N) when N rem 3 =:= 2 -> K = F(N), [K,K].
+
+check_keys_exist([], _) -> ok;
+check_keys_exist([K|Ks],M) ->
+    true = maps:is_key(K,M),
+    check_keys_exist(Ks,M).
+
+t_bif_merge_and_check(Config) when is_list(Config) ->
+
+    io:format("rand:export_seed() -> ~p\n",[rand:export_seed()]),
+
+    %% simple disjunct ones
+    %% make sure all keys are unique
+    Kss = [[a,b,c,d],
+	   [1,2,3,4],
+	   [],
+	   ["hi"],
+	   [e],
+	   [build_key(fun(K) -> {small,K} end, I) || I <- lists:seq(1,32)],
+	   lists:seq(5, 28),
+	   lists:seq(29, 59),
+	   [build_key(fun(K) -> integer_to_list(K) end, I) || I <- lists:seq(2000,10000)],
+	   [build_key(fun(K) -> <<K:32>> end, I) || I <- lists:seq(1,80)],
+	   [build_key(fun(K) -> {<<K:32>>} end, I) || I <- lists:seq(100,1000)]],
+
+
+    KsMs = build_keys_map_pairs(Kss),
+    Cs   = [{CKs1,CM1,CKs2,CM2} || {CKs1,CM1} <- KsMs, {CKs2,CM2} <- KsMs],
+    ok   = merge_and_check_combo(Cs),
+
+    %% overlapping ones
+
+    KVs1 = [{a,1},{b,2},{c,3}],
+    KVs2 = [{b,3},{c,4},{d,5}],
+    KVs  = [{I,I} || I <- lists:seq(1,32)],
+    KVs3 = KVs1 ++ KVs,
+    KVs4 = KVs2 ++ KVs,
+
+    M1  = maps:from_list(KVs1),
+    M2  = maps:from_list(KVs2),
+    M3  = maps:from_list(KVs3),
+    M4  = maps:from_list(KVs4),
+
+    M12 = maps:merge(M1,M2),
+    ok  = check_key_values(KVs2 ++ [{a,1}], M12),
+    M21 = maps:merge(M2,M1),
+    ok  = check_key_values(KVs1 ++ [{d,5}], M21),
+
+    M34 = maps:merge(M3,M4),
+    ok  = check_key_values(KVs4 ++ [{a,1}], M34),
+    M43 = maps:merge(M4,M3),
+    ok  = check_key_values(KVs3 ++ [{d,5}], M43),
+
+    M14 = maps:merge(M1,M4),
+    ok  = check_key_values(KVs4 ++ [{a,1}], M14),
+    M41 = maps:merge(M4,M1),
+    ok  = check_key_values(KVs1 ++ [{d,5}] ++ KVs, M41),
+
+    [begin Ma = random_map(SzA, a),
+	   Mb = random_map(SzB, b),
+	   ok = merge_maps(Ma, Mb)
+     end || SzA <- [3,10,20,100,200,1000], SzB <- [3,10,20,100,200,1000]],
+
+    ok.
+
+% Generate random map with an average of Sz number of pairs: K -> {V,K}
+random_map(Sz, V) ->
+    random_map_insert(#{}, 0, V, Sz*2).
+
+random_map_insert(M0, K0, _, Sz) when K0 > Sz ->
+    M0;
+random_map_insert(M0, K0, V, Sz) ->
+    Key = K0 + rand:uniform(3),
+    random_map_insert(M0#{Key => {V,Key}}, Key, V, Sz).
+
+
+merge_maps(A, B) ->
+    AB = maps:merge(A, B),
+    %%io:format("A=~p\nB=~p\n",[A,B]),
+    maps_foreach(fun(K,VB) -> VB = maps:get(K, AB)
+		 end, B),
+    maps_foreach(fun(K,VA) ->
+			 case {maps:get(K, AB),maps:find(K, B)} of
+			     {VA, error} -> ok;
+			     {VB, {ok, VB}} -> ok
+			 end
+		 end, A),
+
+    maps_foreach(fun(K,V) ->
+			 case {maps:find(K, A),maps:find(K, B)} of
+			     {{ok, V}, error} -> ok;
+			     {error, {ok, V}} -> ok;
+			     {{ok,_}, {ok, V}} -> ok
+			 end
+		 end, AB),
+    ok.
+
+maps_foreach(Fun, Map) ->
+    maps:fold(fun(K,V,_) -> Fun(K,V) end, void, Map).
+
+
+check_key_values([],_) -> ok;
+check_key_values([{K,V}|KVs],M) ->
+    V = maps:get(K,M),
+    check_key_values(KVs,M).
+
+merge_and_check_combo([]) -> ok;
+merge_and_check_combo([{Ks1,M1,Ks2,M2}|Cs]) ->
+    M12 = maps:merge(M1,M2),
+    ok  = check_keys_exist(Ks1 ++ Ks2, M12),
+    M21 = maps:merge(M2,M1),
+    ok  = check_keys_exist(Ks1 ++ Ks2, M21),
+
+    true = M12 =:= M21,
+    M12  = M21,
+
+    merge_and_check_combo(Cs).
+
+build_keys_map_pairs([]) -> [];
+build_keys_map_pairs([Ks|Kss]) ->
+    M  = maps:from_list(keys_to_pairs(Ks)),
+    ok = check_keys_exist(Ks, M),
+    [{Ks,M}|build_keys_map_pairs(Kss)].
+
+keys_to_pairs(Ks) -> [{K,K} || K <- Ks].
+
+
+%% Maps module, not BIFs
+t_maps_fold(_Config) ->
+    Vs = lists:seq(1,100),
+    M  = maps:from_list([{{k,I},{v,I}}||I<-Vs]),
+
+    %% fold
+    5050 = maps:fold(fun({k,_},{v,V},A) -> V + A end, 0, M),
+
+    ok.
+
+t_maps_map(_Config) ->
+    Vs = lists:seq(1,100),
+    M1 = maps:from_list([{I,I}||I<-Vs]),
+    M2 = maps:from_list([{I,{token,I}}||I<-Vs]),
+
+    M2 = maps:map(fun(_K,V) -> {token,V} end, M1),
+    ok.
+
+t_maps_size(_Config) ->
+    Vs = lists:seq(1,100),
+    lists:foldl(fun(I,M) ->
+		M1 = maps:put(I,I,M),
+		I  = maps:size(M1),
+		M1
+	end, #{}, Vs),
+    ok.
+
+
+t_maps_without(_Config) ->
+    Ki = [11,22,33,44,55,66,77,88,99],
+    M0 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100)]),
+    M1 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100) -- Ki]),
+    M1 = maps:without([{k,I}||I <- Ki],M0),
+    ok.
+
+t_erts_internal_order(_Config) when is_list(_Config) ->
+    M = #{0 => 0,2147483648 => 0},
+    true = M =:= binary_to_term(term_to_binary(M)),
+
+    F1 = fun(_, _) -> 0 end,
+    F2 = fun(_, _) -> 1 end,
+    M0 = maps:from_list( [{-2147483649, 0}, {0,0}, {97, 0}, {false, 0}, {flower, 0}, {F1, 0}, {F2, 0}, {<<>>, 0}]),
+    M1 = maps:merge(M0, #{0 => 1}),
+    8  = maps:size(M1),
+    1  = maps:get(0,M1),
+    ok.
+
+t_erts_internal_hash(_Config) when is_list(_Config) ->
+    K1 = 0.0,
+    K2 = 0.0/-1,
+    M  = maps:from_list([{I,I}||I<-lists:seq(1,32)]),
+
+    M1 = M#{ K1 => a, K2 => b },
+    b  = maps:get(K2,M1),
+
+    M2 = M#{ K2 => a, K1 => b },
+    b  = maps:get(K1,M2),
+
+    %% test previously faulty hash list optimization
+
+    M3 = M#{[0] => a, [0,0] => b, [0,0,0] => c, [0,0,0,0] => d},
+    a  = maps:get([0],M3),
+    b  = maps:get([0,0],M3),
+    c  = maps:get([0,0,0],M3),
+    d  = maps:get([0,0,0,0],M3),
+
+    M4 = M#{{[0]} => a, {[0,0]} => b, {[0,0,0]} => c, {[0,0,0,0]} => d},
+    a  = maps:get({[0]},M4),
+    b  = maps:get({[0,0]},M4),
+    c  = maps:get({[0,0,0]},M4),
+    d  = maps:get({[0,0,0,0]},M4),
+
+    M5 = M3#{[0,0,0] => e, [0,0,0,0] => f, [0,0,0,0,0] => g,
+             [0,0,0,0,0,0] => h, [0,0,0,0,0,0,0] => i,
+             [0,0,0,0,0,0,0,0] => j, [0,0,0,0,0,0,0,0,0] => k},
+
+    a  = maps:get([0],M5),
+    b  = maps:get([0,0],M5),
+    e  = maps:get([0,0,0],M5),
+    f  = maps:get([0,0,0,0],M5),
+    g  = maps:get([0,0,0,0,0],M5),
+    h  = maps:get([0,0,0,0,0,0],M5),
+    i  = maps:get([0,0,0,0,0,0,0],M5),
+    j  = maps:get([0,0,0,0,0,0,0,0],M5),
+    k  = maps:get([0,0,0,0,0,0,0,0,0],M5),
+
+    M6 = M4#{{[0,0,0]} => e, {[0,0,0,0]} => f, {[0,0,0,0,0]} => g,
+             {[0,0,0,0,0,0]} => h, {[0,0,0,0,0,0,0]} => i,
+             {[0,0,0,0,0,0,0,0]} => j, {[0,0,0,0,0,0,0,0,0]} => k},
+
+    a  = maps:get({[0]},M6),
+    b  = maps:get({[0,0]},M6),
+    e  = maps:get({[0,0,0]},M6),
+    f  = maps:get({[0,0,0,0]},M6),
+    g  = maps:get({[0,0,0,0,0]},M6),
+    h  = maps:get({[0,0,0,0,0,0]},M6),
+    i  = maps:get({[0,0,0,0,0,0,0]},M6),
+    j  = maps:get({[0,0,0,0,0,0,0,0]},M6),
+    k  = maps:get({[0,0,0,0,0,0,0,0,0]},M6),
+
+    M7 = maps:merge(M5,M6),
+
+    a  = maps:get([0],M7),
+    b  = maps:get([0,0],M7),
+    e  = maps:get([0,0,0],M7),
+    f  = maps:get([0,0,0,0],M7),
+    g  = maps:get([0,0,0,0,0],M7),
+    h  = maps:get([0,0,0,0,0,0],M7),
+    i  = maps:get([0,0,0,0,0,0,0],M7),
+    j  = maps:get([0,0,0,0,0,0,0,0],M7),
+    k  = maps:get([0,0,0,0,0,0,0,0,0],M7),
+    a  = maps:get({[0]},M7),
+    b  = maps:get({[0,0]},M7),
+    e  = maps:get({[0,0,0]},M7),
+    f  = maps:get({[0,0,0,0]},M7),
+    g  = maps:get({[0,0,0,0,0]},M7),
+    h  = maps:get({[0,0,0,0,0,0]},M7),
+    i  = maps:get({[0,0,0,0,0,0,0]},M7),
+    j  = maps:get({[0,0,0,0,0,0,0,0]},M7),
+    k  = maps:get({[0,0,0,0,0,0,0,0,0]},M7),
+    ok.
+
+t_pdict(_Config) ->
+
+    put(#{ a => b, b => a},#{ c => d}),
+    put(get(#{ a => b, b => a}),1),
+    1 = get(#{ c => d}),
+    #{ c := d } = get(#{ a => b, b => a}).
+
+t_ets(_Config) ->
+
+    Tid = ets:new(map_table,[]),
+
+    [ets:insert(Tid,{maps:from_list([{I,-I}]),I}) || I <- lists:seq(1,100)],
+
+
+    [{#{ 2 := -2},2}] = ets:lookup(Tid,#{ 2 => -2 }),
+
+    %% Test equal
+    [3,4] = lists:sort(
+	      ets:select(Tid,[{{'$1','$2'},
+			       [{'or',{'==','$1',#{ 3 => -3 }},
+				 {'==','$1',#{ 4 => -4 }}}],
+			       ['$2']}])),
+    %% Test match
+    [30,50] = lists:sort(
+		ets:select(Tid,
+			   [{{#{ 30 => -30}, '$1'},[],['$1']},
+			    {{#{ 50 => -50}, '$1'},[],['$1']}]
+			  )),
+
+    ets:insert(Tid,{#{ a => b, b => c, c => a},transitivity}),
+
+    %% Test equal with map of different size
+    [] = ets:select(Tid,[{{'$1','_'},[{'==','$1',#{ b => c }}],['$_']}]),
+
+    %% Test match with map of different size
+    %[{#{ a := b },_}] = ets:select(Tid,[{{#{ b => c },'_'},[],['$_']}]),
+
+    %%% Test match with don't care value
+    %[{#{ a := b },_}] = ets:select(Tid,[{{#{ b => '_' },'_'},[],['$_']}]),
+
+    %% Test is_map bif
+    101 = length(ets:select(Tid,[{'$1',[{is_map,{element,1,'$1'}}],['$1']}])),
+    ets:insert(Tid,{not_a_map,2}),
+    101 = length(ets:select(Tid,[{'$1',[{is_map,{element,1,'$1'}}],['$1']}])),
+    ets:insert(Tid,{{nope,a,tuple},2}),
+    101 = length(ets:select(Tid,[{'$1',[{is_map,{element,1,'$1'}}],['$1']}])),
+
+    %% Test map_size bif
+    [3] = ets:select(Tid,[{{'$1','_'},[{'==',{map_size,'$1'},3}],
+			   [{map_size,'$1'}]}]),
+
+    true = ets:delete(Tid,#{50 => -50}),
+    [] = ets:lookup(Tid,#{50 => -50}),
+
+    ets:delete(Tid),
+    ok.
+
+t_dets(_Config) ->
+    ok.
+
+t_tracing(_Config) ->
+
+    dbg:stop_clear(),
+    {ok,Tracer} = dbg:tracer(process,{fun trace_collector/2, self()}),
+    dbg:p(self(),c),
+
+    %% Test basic map call
+    {ok,_} = dbg:tpl(?MODULE,id,x),
+    #{ a => b },
+    {trace,_,call,{?MODULE,id,[#{ a := b }]}} = getmsg(Tracer),
+    {trace,_,return_from,{?MODULE,id,1},#{ a := b }} = getmsg(Tracer),
+    dbg:ctpl(),
+
+    %% Test equals in argument list
+    {ok,_} = dbg:tpl(?MODULE,id,[{['$1'],[{'==','$1',#{ b => c}}],
+				  [{return_trace}]}]),
+    #{ a => b },
+    #{ b => c },
+    {trace,_,call,{?MODULE,id,[#{ b := c }]}} = getmsg(Tracer),
+    {trace,_,return_from,{?MODULE,id,1},#{ b := c }} = getmsg(Tracer),
+    dbg:ctpl(),
+
+    %% Test match in head
+    {ok,_} = dbg:tpl(?MODULE,id,[{[#{b => c}],[],[]}]),
+    #{ a => b },
+    #{ b => c },
+    {trace,_,call,{?MODULE,id,[#{ b := c }]}} = getmsg(Tracer),
+    dbg:ctpl(),
+
+    % Test map guard bifs
+    {ok,_} = dbg:tpl(?MODULE,id,[{['$1'],[{is_map,{element,1,'$1'}}],[]}]),
+    #{ a => b },
+    {1,2},
+    {#{ a => b},2},
+    {trace,_,call,{?MODULE,id,[{#{ a := b },2}]}} = getmsg(Tracer),
+    dbg:ctpl(),
+
+    {ok,_} = dbg:tpl(?MODULE,id,[{['$1'],[{'==',{map_size,{element,1,'$1'}},2}],[]}]),
+    #{ a => b },
+    {1,2},
+    {#{ a => b},2},
+    {#{ a => b, b => c},atom},
+    {trace,_,call,{?MODULE,id,[{#{ a := b, b := c },atom}]}} = getmsg(Tracer),
+    dbg:ctpl(),
+
+    %MS = dbg:fun2ms(fun([A]) when A == #{ a => b} -> ok end),
+    %dbg:tpl(?MODULE,id,MS),
+    %#{ a => b },
+    %#{ b => c },
+    %{trace,_,call,{?MODULE,id,[#{ a := b }]}} = getmsg(Tracer),
+    %dbg:ctpl(),
+
+    %% Check to extra messages
+    timeout = getmsg(Tracer),
+
+    dbg:stop_clear(),
+    ok.
+
+getmsg(_Tracer) ->
+    receive V -> V after 100 -> timeout end.
+
+trace_collector(Msg,Parent) ->
+    io:format("~p~n",[Msg]),
+    Parent ! Msg,
+    Parent.
+
+t_has_map_fields(Config) when is_list(Config) ->
+    true = has_map_fields_1(#{one=>1}),
+    true = has_map_fields_1(#{one=>1,two=>2}),
+    false = has_map_fields_1(#{two=>2}),
+    false = has_map_fields_1(#{}),
+
+    true = has_map_fields_2(#{c=>1,b=>2,a=>3}),
+    true = has_map_fields_2(#{c=>1,b=>2,a=>3,x=>42}),
+    false = has_map_fields_2(#{b=>2,c=>1}),
+    false = has_map_fields_2(#{x=>y}),
+    false = has_map_fields_2(#{}),
+
+    true = has_map_fields_3(#{c=>1,b=>2,a=>3}),
+    true = has_map_fields_3(#{c=>1,b=>2,a=>3,[]=>42}),
+    true = has_map_fields_3(#{b=>2,a=>3,[]=>42,42.0=>43}),
+    true = has_map_fields_3(#{a=>3,[]=>42,42.0=>43}),
+    true = has_map_fields_3(#{[]=>42,42.0=>43}),
+    false = has_map_fields_3(#{b=>2,c=>1}),
+    false = has_map_fields_3(#{[]=>y}),
+    false = has_map_fields_3(#{42.0=>x,a=>99}),
+    false = has_map_fields_3(#{}),
+
+    ok.
+
+has_map_fields_1(#{one:=_}) -> true;
+has_map_fields_1(#{}) -> false.
+
+has_map_fields_2(#{a:=_,b:=_,c:=_}) -> true;
+has_map_fields_2(#{}) -> false.
+
+has_map_fields_3(#{a:=_,b:=_}) -> true;
+has_map_fields_3(#{[]:=_,42.0:=_}) -> true;
+has_map_fields_3(#{}) -> false.
+
+y_regs(Config) when is_list(Config) ->
+    Val = [length(Config)],
+    Map0 = y_regs_update(#{}, Val),
+    Map2 = y_regs_update(Map0, Val),
+
+    Map3 = maps:from_list([{I,I*I} || I <- lists:seq(1, 100)]),
+    Map4 = y_regs_update(Map3, Val),
+
+    true = is_map(Map2) andalso is_map(Map4),
+
+    ok.
+
+y_regs_update(Map0, Val0) ->
+    Val1 = {t,Val0},
+    K1 = {key,1},
+    K2 = {key,2},
+    Map1 = Map0#{K1=>K1,
+		 a=>Val0,b=>Val0,c=>Val0,d=>Val0,e=>Val0,
+		 f=>Val0,g=>Val0,h=>Val0,i=>Val0,j=>Val0,
+		 k=>Val0,l=>Val0,m=>Val0,n=>Val0,o=>Val0,
+		 p=>Val0,q=>Val0,r=>Val0,s=>Val0,t=>Val0,
+		 u=>Val0,v=>Val0,w=>Val0,x=>Val0,y=>Val0,
+		 z=>Val0,
+		 aa=>Val0,ab=>Val0,ac=>Val0,ad=>Val0,ae=>Val0,
+		 af=>Val0,ag=>Val0,ah=>Val0,ai=>Val0,aj=>Val0,
+		 ak=>Val0,al=>Val0,am=>Val0,an=>Val0,ao=>Val0,
+		 ap=>Val0,aq=>Val0,ar=>Val0,as=>Val0,at=>Val0,
+		 au=>Val0,av=>Val0,aw=>Val0,ax=>Val0,ay=>Val0,
+		 az=>Val0,
+		 K2=>[a,b,c]},
+    Map2 = Map1#{K1=>K1,
+		 a:=Val1,b:=Val1,c:=Val1,d:=Val1,e:=Val1,
+		 f:=Val1,g:=Val1,h:=Val1,i:=Val1,j:=Val1,
+		 k:=Val1,l:=Val1,m:=Val1,n:=Val1,o:=Val1,
+		 p:=Val1,q:=Val1,r:=Val1,s:=Val1,t:=Val1,
+		 u:=Val1,v:=Val1,w:=Val1,x:=Val1,y:=Val1,
+		 z:=Val1,
+		 aa:=Val1,ab:=Val1,ac:=Val1,ad:=Val1,ae:=Val1,
+		 af:=Val1,ag:=Val1,ah:=Val1,ai:=Val1,aj:=Val1,
+		 ak:=Val1,al:=Val1,am:=Val1,an:=Val1,ao:=Val1,
+		 ap:=Val1,aq:=Val1,ar:=Val1,as:=Val1,at:=Val1,
+		 au:=Val1,av:=Val1,aw:=Val1,ax:=Val1,ay:=Val1,
+		 az:=Val1,
+		 K2=>[a,b,c]},
+
+    %% Traverse the maps to validate them.
+    _ = erlang:phash2({Map1,Map2}, 100000),
+
+    _ = {K1,K2,Val0,Val1},			%Force use of Y registers.
+    Map2.
+
+do_badmap(Test) ->
+    Terms = [Test,fun erlang:abs/1,make_ref(),self(),0.0/-1,
+	     <<0:1024>>,<<1:1>>,<<>>,<<1,2,3>>,
+	     [],{a,b,c},[a,b],atom,10.0,42,(1 bsl 65) + 3],
+    [Test(T) || T <- Terms].
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/order.erl b/lib/dialyzer/test/indent_SUITE_data/src/order.erl
new file mode 100644
index 0000000000..51868d7e94
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/order.erl
@@ -0,0 +1,56 @@
+-module(order).
+
+-export([t1/0, t2/0, t3/0, t4/0, t5/0, t6/0]).
+
+t1() ->
+    case maps:get(a, #{a=>1, a=>b}) of
+	Int when is_integer(Int) -> fail;
+	Atom when is_atom(Atom) -> error(ok);
+	_Else -> fail
+    end.
+
+t2() ->
+    case maps:get(a, #{a=>id_1(1), a=>id_b(b)}) of
+	Int when is_integer(Int) -> fail;
+	Atom when is_atom(Atom) -> error(ok);
+	_Else -> fail
+    end.
+
+t3() ->
+    case maps:get(a, #{a=>id_1(1), id_a(a)=>id_b(b)}) of
+	Int when is_integer(Int) -> fail;
+	Atom when is_atom(Atom) -> error(ok);
+	_Else -> fail
+    end.
+
+t4() ->
+    case maps:get(a, #{a=>id_1(1), a_or_b()=>id_b(b)}) of
+	Int when is_integer(Int) -> ok;
+	Atom when is_atom(Atom) -> ok;
+	_Else -> fail
+    end.
+
+t5() ->
+    case maps:get(c, #{c=>id_1(1), a_or_b()=>id_b(b)}) of
+	Int when is_integer(Int) -> error(ok);
+	Atom when is_atom(Atom) -> fail;
+	_Else -> fail
+    end.
+
+t6() ->
+    case maps:get(a, #{a_or_b()=>id_1(1), id_a(a)=>id_b(b)}) of
+	Int when is_integer(Int) -> fail;
+	Atom when is_atom(Atom) -> error(ok);
+	_Else -> fail
+    end.
+
+id_1(X) -> X.
+
+id_a(X) -> X.
+
+id_b(X) -> X.
+
+any() -> binary_to_term(<<>>).
+
+-spec a_or_b() -> a | b.
+a_or_b() -> any().
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/queue_use.erl b/lib/dialyzer/test/indent_SUITE_data/src/queue_use.erl
new file mode 100644
index 0000000000..8d46bdb989
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/queue_use.erl
@@ -0,0 +1,65 @@
+-module(queue_use).
+
+-export([ok1/0, ok2/0]).
+-export([wrong1/0, wrong2/0, wrong3/0, wrong4/0, wrong5/0, wrong6/0, wrong7/0, wrong8/0]).
+
+ok1() ->
+    queue:is_empty(queue:new()).
+
+ok2() ->
+    Q0 = queue:new(),
+    Q1 = queue:in(42, Q0),
+    {{value, 42}, Q2} = queue:out(Q1),
+    queue:is_empty(Q2).
+
+%%--------------------------------------------------
+
+wrong1() ->
+    queue:is_empty({[],[]}).
+
+wrong2() ->
+    Q0 = {[],[]},
+    queue:in(42, Q0).
+
+wrong3() ->
+    Q0 = queue:new(),
+    Q1 = queue:in(42, Q0),
+    {[42],Q2} = Q1,
+    Q2.
+
+wrong4() ->
+    Q0 = queue:new(),
+    Q1 = queue:in(42, Q0),
+    Q1 =:= {[42],[]}.
+
+wrong5() ->
+    {F, _R} = queue:new(),
+    F.
+
+wrong6() ->
+    {{value, 42}, Q2} = queue:out({[42],[]}),
+    Q2.
+
+%%--------------------------------------------------
+
+-record(db, {p, q}).
+
+wrong7() ->
+    add_unique(42, #db{p = [], q = queue:new()}).
+
+add_unique(E, DB) ->
+    case is_in_queue(E, DB) of
+	true -> DB;
+	false -> DB#db{q = queue:in(E, DB#db.q)}
+    end.
+
+is_in_queue(P, #db{q = {L1,L2}}) ->
+    lists:member(P, L1) orelse lists:member(P, L2).
+
+%%--------------------------------------------------
+
+wrong8() ->
+    tuple_queue({42, gazonk}).
+
+tuple_queue({F, Q}) ->
+    queue:in(F, Q).
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/rec/rec_adt.erl b/lib/dialyzer/test/indent_SUITE_data/src/rec/rec_adt.erl
new file mode 100644
index 0000000000..f01cc5e519
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/rec/rec_adt.erl
@@ -0,0 +1,22 @@
+-module(rec_adt).
+
+-export([new/0, get_a/1, get_b/1, set_a/2, set_b/2]).
+
+-record(rec, {a :: atom(), b = 0 :: integer()}).
+
+-opaque rec() :: #rec{}.
+
+-spec new() -> rec().
+new() -> #rec{a = gazonk, b = 42}.
+
+-spec get_a(rec()) -> atom().
+get_a(#rec{a = A}) -> A.
+
+-spec get_b(rec()) -> integer().
+get_b(#rec{b = B}) -> B.
+
+-spec set_a(rec(), atom()) -> rec().
+set_a(R, A) -> R#rec{a = A}.
+
+-spec set_b(rec(), integer()) -> rec().
+set_b(R, B) -> R#rec{b = B}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/rec/rec_use.erl b/lib/dialyzer/test/indent_SUITE_data/src/rec/rec_use.erl
new file mode 100644
index 0000000000..358e9f918c
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/rec/rec_use.erl
@@ -0,0 +1,30 @@
+-module(rec_use).
+
+-export([ok1/0, ok2/0, wrong1/0, wrong2/0, wrong3/0, wrong4/0]).
+
+ok1() ->
+    rec_adt:set_a(rec_adt:new(), foo).
+
+ok2() ->
+    R1 = rec_adt:new(),
+    B1 = rec_adt:get_b(R1),
+    R2 = rec_adt:set_b(R1, 42),
+    B2 = rec_adt:get_b(R2),
+    B1 =:= B2.
+
+wrong1() ->
+    case rec_adt:new() of
+	{rec, _, 42} -> weird1;
+	R when tuple_size(R) =:= 3 -> weird2
+    end.
+
+wrong2() ->
+    R = list_to_tuple([rec, a, 42]),
+    rec_adt:get_a(R).
+
+wrong3() ->
+    R = rec_adt:new(),
+    R =:= {rec, gazonk, 42}.
+
+wrong4() ->
+    tuple_size(rec_adt:new()).
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/record_construct.erl b/lib/dialyzer/test/indent_SUITE_data/src/record_construct.erl
new file mode 100644
index 0000000000..b250c6ee65
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/record_construct.erl
@@ -0,0 +1,21 @@
+-module(record_construct).
+-export([t_loc/0, t_opa/0, t_rem/0]).
+
+-record(r_loc, {a = gazonk :: integer(), b = 42 :: atom()}).
+
+t_loc() ->
+  #r_loc{}.
+
+-record(r_opa, {a                 :: atom(),
+		b = gb_sets:new() :: gb_sets:set(),
+		c = 42            :: boolean(),
+		d,	% untyped on purpose
+		e = false         :: boolean()}).
+
+t_opa() ->
+  #r_opa{}.
+
+-record(r_rem, {a = gazonk :: string()}).
+
+t_rem() ->
+  #r_rem{}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/record_creation_diffs.erl b/lib/dialyzer/test/indent_SUITE_data/src/record_creation_diffs.erl
new file mode 100644
index 0000000000..e813459f8e
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/record_creation_diffs.erl
@@ -0,0 +1,11 @@
+-module(record_creation_diffs).
+
+-export([foo/1]).
+
+-record(bar, {
+          some_atom :: atom(),
+          some_list :: list()
+         }).
+
+foo(Input) ->
+    #bar{some_atom = Input, some_list = {this,is,a,tuple}}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/record_match.erl b/lib/dialyzer/test/indent_SUITE_data/src/record_match.erl
new file mode 100644
index 0000000000..8e9b91937f
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/record_match.erl
@@ -0,0 +1,17 @@
+-module(record_match).
+
+-export([select/0]).
+
+-record(b_literal, {val}).
+-record(b_remote, {mod,name,arity}).
+-record(b_local, {name,arity}).
+
+-type b_remote()   :: #b_remote{}.
+-type b_local()    :: #b_local{}.
+
+-type argument()   :: b_remote() | b_local().
+
+-record(b_set, {args=[] :: [argument()]}).
+
+select() ->
+    #b_set{args=[#b_remote{},#b_literal{}]}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/record_pat.erl b/lib/dialyzer/test/indent_SUITE_data/src/record_pat.erl
new file mode 100644
index 0000000000..3308641571
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/record_pat.erl
@@ -0,0 +1,15 @@
+%%%-------------------------------------------------------------------
+%%% File    : record_pat.erl
+%%% Author  : Tobias Lindahl <>
+%%% Description : Emit warning if a pattern violates the record type
+%%%
+%%% Created : 21 Oct 2008 by Tobias Lindahl <>
+%%%-------------------------------------------------------------------
+-module(record_pat).
+
+-export([t/1]).
+
+-record(foo, {bar :: integer()}).
+
+t(#foo{bar=baz}) -> no_way;
+t(#foo{bar=1}) -> ok.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/record_send_test.erl b/lib/dialyzer/test/indent_SUITE_data/src/record_send_test.erl
new file mode 100644
index 0000000000..87cd97bd85
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/record_send_test.erl
@@ -0,0 +1,32 @@
+%%-------------------------------------------------------------------
+%% File    : record_send_test.erl
+%% Author  : Kostis Sagonas <kostis@it.uu.se>
+%% Description : A test inspired by a post of Mkcael Remond to the
+%%		 Erlang mailing list suggesting thst Dialyzer should
+%%		 be reporting sends to records rather than to pids.
+%%		 Dialyzer v1.3.0 indeed reports one of the dicrepancies
+%%		 (the one with the 4-tuple) but not the one where the
+%%		 message is sent to a pair which is a record.
+%%		 This should be fixed.
+%%
+%% Created : 10 Apr 2005 by Kostis Sagonas <kostis@it.uu.se>
+%%-------------------------------------------------------------------
+-module(record_send_test).
+
+-export([t/0]).
+
+-record(rec1, {a=a, b=b, c=c}).
+-record(rec2, {a}).
+
+t() ->
+  t(#rec1{}).
+
+t(Rec1 = #rec1{b=B}) ->
+  Rec2 = some_mod:some_function(),
+  if
+    is_record(Rec2, rec2) ->
+      Rec2 ! hello;	%% currently this one is not found
+    true ->
+      Rec1 ! hello_again
+  end,
+  B.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/record_test.erl b/lib/dialyzer/test/indent_SUITE_data/src/record_test.erl
new file mode 100644
index 0000000000..48a00b172e
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/record_test.erl
@@ -0,0 +1,22 @@
+%%%-------------------------------------------------------------------
+%%% File    : record_test.erl
+%%% Author  : Tobias Lindahl <tobiasl@it.uu.se>
+%%% Description :
+%%%
+%%% Created : 22 Oct 2004 by Tobias Lindahl <tobiasl@it.uu.se>
+%%%-------------------------------------------------------------------
+-module(record_test).
+
+-export([t/0]).
+
+-record(foo, {bar}).
+
+t() ->
+  doit(foo).
+
+doit(X) ->
+  case X of
+    #foo{} -> error1;
+    foo -> ok;
+    _ -> error2
+  end.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/record_update.erl b/lib/dialyzer/test/indent_SUITE_data/src/record_update.erl
new file mode 100644
index 0000000000..bad7a0a929
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/record_update.erl
@@ -0,0 +1,10 @@
+-module(record_update).
+
+-export([quux/2]).
+
+-record(foo, {bar :: atom()}).
+
+-spec quux(#foo{}, string()) -> #foo{}.
+
+quux(Foo, NotBar) ->
+  Foo#foo{ bar = NotBar }.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_behaviour.erl b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_behaviour.erl
new file mode 100644
index 0000000000..116980986b
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_behaviour.erl
@@ -0,0 +1,13 @@
+-module(sample_behaviour).
+
+-type custom() :: 1..42.
+
+-callback sample_callback_1() -> term().
+-callback sample_callback_2() -> atom().
+-callback sample_callback_3() -> {'ok', custom()} | 'fail'.
+
+-callback sample_callback_4(term()) -> 'ok'.
+-callback sample_callback_5(custom()) -> 'ok' | 'fail'.
+
+-callback sample_callback_6(custom(), custom(), string()) ->
+    {'ok', custom()} | 'fail'.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct.erl b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct.erl
new file mode 100644
index 0000000000..ab0378e6f0
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct.erl
@@ -0,0 +1,32 @@
+-module(sample_callback_correct).
+
+-behaviour(sample_behaviour).
+
+-export([
+	 sample_callback_1/0,
+	 sample_callback_2/0,
+	 sample_callback_3/0,
+	 sample_callback_4/1,
+	 sample_callback_5/1,
+	 sample_callback_6/3
+	]).
+
+sample_callback_1() -> 42.       % This is a valid return.
+sample_callback_2() -> foo.      % This is a valid return.
+sample_callback_3() -> {ok, 17}. % This is a valid return.
+sample_callback_4(Input) ->
+    put(mine, Input+1),          % This is valid handling of the input
+    ok.                          % This is a valid return.
+sample_callback_5(Input) ->
+    case Input - 1 < 22 of       % This is valid handling of the input
+	true  -> ok;             % This is a valid return.
+	false -> fail            % This is a valid return.
+    end.
+sample_callback_6(OldNr, NewNr, Reason) ->
+    Diff = NewNr - OldNr,                         % This is valid handling of the input
+    Msg = string:join(["Reason: ", Reason], ","), % This is valid handling of the input
+    case Diff > 0 of
+	true -> put(mine, {NewNr, Msg}),
+		{ok, NewNr};                      % This is a valid return.
+	false -> fail                             % This is a valid return.
+    end.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct_2.erl b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct_2.erl
new file mode 100644
index 0000000000..c218174e58
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_correct_2.erl
@@ -0,0 +1,38 @@
+-module(sample_callback_correct_2).
+
+-behaviour(sample_behaviour).
+
+-export([
+	 sample_callback_1/0,
+	 sample_callback_2/0,
+	 sample_callback_3/0,
+	 sample_callback_4/1,
+	 sample_callback_5/1,
+	 sample_callback_6/3,
+	 common_infrastructure/1
+	]).
+
+sample_callback_1() -> 42.       % This is a valid return.
+sample_callback_2() -> halt().   % Crashes are also allowed.
+sample_callback_3() -> {ok, 17}. % This is a valid return.
+sample_callback_4(Input) ->
+    case Input of
+	1 -> common_infrastructure(Input); % This is 'correct' input for
+	_ -> ok                            % common_infrastructure.
+    end.
+sample_callback_5(Input) ->
+    case get(Input) of % This is valid handling of a more generic input
+	true  -> ok;   % This is a valid return.
+	false -> fail  % This is a valid return.
+    end.
+sample_callback_6(OldNr, NewNr, Reason) ->
+    Diff = NewNr - OldNr,                         % This is valid handling of the input
+    Msg = string:join(["Reason: ", Reason], ","), % This is valid handling of the input
+    case Diff > 0 of
+	true -> put(mine, {NewNr, Msg}),
+		{ok, NewNr};                 % This is a valid return.
+	false -> fail                        % This is a valid return.
+    end.
+
+common_infrastructure( 1) ->   'ok';
+common_infrastructure(42) -> 'fail'.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_wrong.erl b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_wrong.erl
new file mode 100644
index 0000000000..430494c48c
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/sample_behaviour/sample_callback_wrong.erl
@@ -0,0 +1,26 @@
+-module(sample_callback_wrong).
+
+%% This attribute uses the american spelling of 'behaviour'.
+-behavior(sample_behaviour).
+
+-export([
+%	 sample_callback_1/0,
+	 sample_callback_2/0,
+	 sample_callback_3/0,
+	 sample_callback_4/1,
+	 sample_callback_5/1,
+	 sample_callback_6/3
+	]).
+
+% sample_callback_1() -> 41.  % We can't really break this contract so: missing!
+sample_callback_2() -> 42.    % This is not an atom().
+sample_callback_3() -> fair.  % This is probably a typo.
+sample_callback_4(_) ->       % We cannot break the input.
+    fail.                     % We can definitely return a wrong value however. :)
+sample_callback_5(Input) ->   % Input is treated as an atom, result is a list.
+    atom_to_list(Input).      % Both violate the contract.
+sample_callback_6(OldNr, NewNr, Reason) ->
+    Diff = NewNr - OldNr, % This is valid handling of the input
+    %% Reason should have been treated as a string.
+    Msg = string:join(["Reason: ", atom_to_list(Reason)], ","),
+    {okk, NewNr}. %% This, too, is a typo.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/exact_adt.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/exact_adt.erl
new file mode 100644
index 0000000000..7103847ae7
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/exact_adt.erl
@@ -0,0 +1,17 @@
+-module(exact_adt).
+
+-export([exact_adt_set_type/1, exact_adt_set_type2/1]).
+
+-export_type([exact_adt/0]).
+
+-record(exact_adt, {}).
+
+-opaque exact_adt() :: #exact_adt{}.
+
+-spec exact_adt_set_type(_) -> exact_adt().
+
+exact_adt_set_type(G) -> G.
+
+-spec exact_adt_set_type2(exact_adt()) -> exact_adt().
+
+exact_adt_set_type2(G) -> G.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/exact_api.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/exact_api.erl
new file mode 100644
index 0000000000..597460ce77
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/exact_api.erl
@@ -0,0 +1,60 @@
+-module(exact_api).
+
+-export([new/0, exact_api_test/1, exact_api_new/1,
+         exact_adt_test/1, exact_adt_new/1]).
+
+-export_type([exact_api/0]).
+
+-record(digraph, {vtab = notable :: ets:tab(),
+		  etab = notable :: ets:tab(),
+		  ntab = notable :: ets:tab(),
+	          cyclic = true  :: boolean()}).
+
+-spec new() -> digraph:graph().
+
+new() ->
+    A = #digraph{},
+    set_type(A), % does not have an opaque term as 1st argument
+    A.
+
+-spec set_type(digraph:graph()) -> true.
+
+set_type(G) ->
+    digraph:delete(G).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%%% The derived spec of exact_api_new() is
+%%% -spec exact_api_new(exact_api:exact_api()) -> exact_api:exact_api().
+%%% This won't happen unless dialyzer_typesig uses
+%%% t_is_exactly_equal() rather than t_is_equal().
+%%% [As of R17B the latter considers two types equal if nothing but
+%%%  their ?opaque tags differ.]
+
+-record(exact_api, {}).
+
+-opaque exact_api() :: #exact_api{}.
+
+exact_api_test(X) ->
+    #exact_api{} = exact_api_set_type(X). % OK
+
+exact_api_new(A) ->
+    A = #exact_api{},
+    _ = exact_api_set_type(A), % OK (the opaque type is local)
+    A.
+
+-spec exact_api_set_type(exact_api()) -> exact_api().
+
+exact_api_set_type(#exact_api{}=E) -> E.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+-record(exact_adt, {}).
+
+exact_adt_test(X) ->
+    #exact_adt{} = exact_adt:exact_adt_set_type(X). % breaks the opacity
+
+exact_adt_new(A) ->
+    A = #exact_adt{},
+    _ = exact_adt:exact_adt_set_type2(A), % does not have an opaque term as 1st argument
+    A.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl
new file mode 100644
index 0000000000..b906431b44
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl
@@ -0,0 +1,65 @@
+-module(is_rec).
+
+-export([ri1/0, ri11/0, ri13/0, ri14/0, ri2/0, ri3/0, ri4/0, ri5/0,
+         ri6/0, ri7/0, ri8/0]).
+
+-record(r, {f1 :: integer()}).
+
+ri1() ->
+    A = simple1_adt:d1(),
+    is_record(A, r). % opaque term 1
+
+ri11() ->
+    A = simple1_adt:d1(),
+    I = '1-3'(),
+    is_record(A, r, I). % opaque term 1
+
+ri13() ->
+    A = simple1_adt:d1(),
+    if is_record(A, r) -> true end. % breaks the opacity
+
+ri14() ->
+    A = simple1_adt:d1(),
+    if is_record({A, 1}, r) -> true end. % breaks the opacity
+
+-type '1-3-t'() :: 1..3.
+
+-spec '1-3'() -> '1-3-t'().
+
+'1-3'() ->
+    random:uniform(3).
+
+
+-spec 'Atom'() -> atom().
+
+'Atom'() ->
+    a.
+
+ri2() ->
+    A = simple1_adt:d1(),
+    R = 'Atom'(),
+    is_record(A, R). % opaque term 1
+
+ri3() ->
+    A = simple1_adt:d1(),
+    is_record(A, A, 1). % opaque term 2
+
+ri4() ->
+    A = simple1_adt:d1(),
+    is_record(A, hipp:hopp(), 1). % opaque term 1
+
+ri5() ->
+    A = simple1_adt:d1(),
+    is_record(A, A, hipp:hopp()). % opaque term 2
+
+ri6() ->
+    A = simple1_adt:d1(),
+    if is_record(A, r) -> true end. % breaks opacity
+
+ri7() ->
+    A = simple1_adt:d1(),
+    if is_record({r, A}, r) -> true end. % A violates #r{}
+
+ri8() ->
+    A = simple1_adt:d1(),
+    is_record({A, 1}, r). % opaque term 1
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/rec_adt.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/rec_adt.erl
new file mode 100644
index 0000000000..ff80d6e99b
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/rec_adt.erl
@@ -0,0 +1,28 @@
+-module(rec_adt).
+
+-export([f/0, r1/0]).
+
+-export_type([r1/0]).
+
+-export_type([f/0, op_t/0, a/0]).
+
+-opaque a() :: a | b.
+
+-record(r1,
+        {f1 :: a()}).
+
+-opaque r1() :: #r1{}.
+
+-opaque f() :: fun((_) -> _).
+
+-opaque op_t() :: integer().
+
+-spec f() -> f().
+
+f() ->
+    fun(_) -> 3 end.
+
+-spec r1() -> r1().
+
+r1() ->
+    #r1{f1 = a}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/rec_api.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/rec_api.erl
new file mode 100644
index 0000000000..59b9e0fec4
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/rec_api.erl
@@ -0,0 +1,123 @@
+-module(rec_api).
+
+-export([t1/0, t2/0, t3/0, adt_t1/0, adt_t1/1, adt_r1/0,
+         t/1, t_adt/0, r/0, r_adt/0, u1/0, u2/0, u3/0, v1/0, v2/0, v3/0]).
+
+-export_type([{a,0},{r1,0}, r2/0, r3/0]).
+
+-export_type([f/0, op_t/0, r/0, tup/0]).
+
+-opaque a() :: a | b.
+
+-record(r1,
+        {f1 :: a()}).
+
+-opaque r1() :: #r1{}.
+
+t1() ->
+    A = #r1{f1 = a},
+    {r1, a} = A.
+
+t2() ->
+    A = {r1, 10},
+    {r1, 10} = A,
+    A = #r1{f1 = 10}, % violates the type of field f1
+    #r1{f1 = 10} = A.
+
+t3() ->
+    A = {r1, 10},
+    #r1{f1 = 10} = A. % violates the type of #r1{}
+
+adt_t1() ->
+    R = rec_adt:r1(),
+    {r1, a} = R. % breaks the opacity
+
+-spec adt_t1(rec_adt:r1()) -> rec_adt:r1(). % invalid type spec
+
+adt_t1(R) ->
+    {r1, a} = R.
+
+-spec adt_r1() -> rec_adt:r1(). % invalid type spec
+
+adt_r1() ->
+    #r1{f1 = a}.
+
+-opaque f() :: fun((_) -> _).
+
+-opaque op_t() :: integer().
+
+-spec t(f()) -> _.
+
+t(A) ->
+    T = term(),
+    %% 3(T), % cannot test this: dialyzer_dep deliberately crashes
+    A(T).
+
+-spec term() -> op_t().
+
+term() ->
+    3.
+
+t_adt() ->
+    A = rec_adt:f(),
+    T = term(),
+    A(T).
+
+-record(r, {f = fun(_) -> 3 end :: f(), o = 1 :: op_t()}).
+
+-opaque r() :: #r{}.
+
+-opaque tup() :: {'r', f(), op_t()}.
+
+-spec r() -> _.
+
+r() ->
+    {{r, f(), 2},
+     #r{f = f(), o = 2}}. % OK, f() is a local opaque type
+
+-spec f() -> f().
+
+f() ->
+    fun(_) -> 3 end.
+
+r_adt() ->
+    {{r, rec_adt:f(), 2},
+     #r{f = rec_adt:f(), o = 2}}. % breaks the opacity
+
+-record(r2, % like #r1{}, but with initial value
+        {f1 = a :: a()}).
+
+-opaque r2() :: #r2{}.
+
+u1() ->
+    A = #r2{f1 = a},
+    {r2, a} = A.
+
+u2() ->
+    A = {r2, 10},
+    {r2, 10} = A,
+    A = #r2{f1 = 10}, % violates the type of field f1
+    #r2{f1 = 10} = A.
+
+u3() ->
+    A = {r2, 10},
+    #r2{f1 = 10} = A. % violates the type of #r2{}
+
+-record(r3, % like #r1{}, but an opaque type
+        {f1 = queue:new():: queue:queue()}).
+
+-opaque r3() :: #r3{}.
+
+v1() ->
+    A = #r3{f1 = queue:new()},
+    {r3, a} = A. % breaks the opacity
+
+v2() ->
+    A = {r3, 10},
+    {r3, 10} = A,
+    A = #r3{f1 = 10}, % violates the type of field f1
+    #r3{f1 = 10} = A.
+
+v3() ->
+    A = {r3, 10},
+    #r3{f1 = 10} = A. % breaks the opacity
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_adt.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_adt.erl
new file mode 100644
index 0000000000..21a277c1e9
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_adt.erl
@@ -0,0 +1,138 @@
+-module(simple1_adt).
+
+-export([d1/0, d2/0, i/0, n1/0, n2/0, o1/0, o2/0,
+         c1/0, c2/0, bit1/0, a/0, i1/0, tuple/0,
+         b1/0, b2/0, ty_i1/0]).
+
+-export_type([o1/0, o2/0, d1/0, d2/0]).
+
+-export_type([i1/0, i2/0, di1/0, di2/0]).
+
+-export_type([ty_i1/0, c1/0, c2/0]).
+
+-export_type([b1/0, b2/0]).
+
+-export_type([bit1/0]).
+
+-export_type([tuple1/0, a/0, i/0]).
+
+%% Equal:
+
+-opaque o1() :: a | b | c.
+
+-opaque o2() :: a | b | c.
+
+%% Disjoint:
+
+-opaque d1() :: a | b | c.
+
+-opaque d2() :: d | e | f.
+
+%% One common element:
+
+-opaque c1() :: a | b | c.
+
+-opaque c2() :: c | e | f.
+
+%% Equal integer range:
+
+-opaque i1() :: 1 | 2.
+
+-opaque i2() :: 1 | 2.
+
+%% Disjoint integer range:
+
+-opaque di1() :: 1 | 2.
+
+-opaque di2() :: 3 | 4.
+
+
+-type ty_i1() :: 1 | 2.
+
+%% Boolean types
+
+-opaque b1() :: boolean().
+
+-opaque b2() :: boolean().
+
+%% Binary types
+
+-opaque bit1() :: binary().
+
+%% Tuple types
+
+-opaque tuple1() :: tuple().
+
+%% Atom type
+
+-opaque a() :: atom().
+
+-opaque i() :: integer().
+
+-spec d1() -> d1().
+
+d1() -> a.
+
+-spec d2() -> d2().
+
+d2() -> d.
+
+-spec i() -> i().
+
+i() ->
+    1.
+
+-spec n1() -> o1().
+
+n1() -> a.
+
+-spec n2() -> o2().
+
+n2() -> a.
+
+-spec o1() -> o1().
+
+o1() -> a.
+
+-spec o2() -> o2().
+
+o2() -> a.
+
+-spec c1() -> c1().
+
+c1() -> a.
+
+-spec c2() -> c2().
+
+c2() -> e.
+
+-spec bit1() -> bit1().
+
+bit1() ->
+    <<"hej">>.
+
+-spec a() -> a().
+
+a() ->
+    e.
+
+-spec i1() -> i1().
+
+i1() -> 1.
+
+-spec tuple() -> tuple1().
+
+tuple() -> {1,2}.
+
+-spec b1() -> b1().
+
+b1() -> true.
+
+-spec b2() -> b2().
+
+b2() -> false.
+
+-spec ty_i1() -> ty_i1().
+
+ty_i1() ->
+    1.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_api.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_api.erl
new file mode 100644
index 0000000000..d67aa913d8
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/simple1_api.erl
@@ -0,0 +1,571 @@
+-module(simple1_api).
+
+-export([t1/1, adt_t1/1, t2/1, adt_t2/1, tup/0, t3/0, t4/0, t5/0, t6/0, t7/0,
+         t8/0, adt_t3/0, adt_t4/0, adt_t7/0, adt_t8/0, adt_t5/0,
+         c1/2, c2/2, c2/0, c3/0, c4/0, tt1/0, tt2/0,
+         cmp1/0, cmp2/0, cmp3/0, cmp4/0,
+         ty_cmp1/0, ty_cmp2/0, ty_cmp3/0, ty_cmp4/0,
+         f1/0, f2/0, adt_f1/0, adt_f2/0, f3/0, f4/0, adt_f3/0, adt_f4/0,
+         adt_f4_a/0, adt_f4_b/0,
+         bool_t1/0, bool_t2/0, bool_t3/0, bool_t4/0, bool_t5/1, bool_t6/1,
+         bool_t7/0, bool_adt_t1/0, bool_adt_t2/0, bool_adt_t5/1,
+         bool_adt_t6/1, bool_t8/0, bool_adt_t8/2, bool_t9/0, bool_adt_t9/2,
+         bit_t1/0, bit_adt_t1/0, bit_t3/1, bit_adt_t2/0, bit_adt_t3/1,
+         bit_t5/1, bit_t4/1, bit_adt_t4/1, bit_t5/0, bit_adt_t5/0,
+         call_f/1, call_f_adt/1, call_m_adt/1, call_m/1, call_f_i/1,
+         call_m_i/1, call_m_adt_i/1, call_f_adt_i/1,
+         eq1/0, eq2/0, c5/0, c6/2, c7/2, c8/0]).
+
+%%% Equal opaque types
+
+-export_type([o1/0, o2/0]).
+
+-export_type([d1/0, d2/0]).
+
+-opaque o1() :: a | b | c.
+
+-opaque o2() :: a | b | c.
+
+-export_type([i1/0, i2/0, di1/0, di2/0]).
+
+-export_type([b1/0, b2/0]).
+
+-export_type([bit1/0]).
+
+-export_type([a/0, i/0]).
+
+%% The derived spec is
+%%  -spec t1('a' | 'b') -> simple1_api:o1('a') | simple1_api:o2('a').
+%% but that is not tested...
+
+t1(a) ->
+    o1();
+t1(b) ->
+    o2().
+
+-spec o1() -> o1().
+
+o1() -> a.
+
+-spec o2() -> o2().
+
+o2() -> a.
+
+%% The derived spec is
+%% -spec adt_t1('a' | 'b') -> simple1_adt:o1('a') | simple1_adt:o2('a').
+%% but that is not tested...
+
+adt_t1(a) ->
+    simple1_adt:o1();
+adt_t1(b) ->
+    simple1_adt:o2().
+
+%%% Disjunct opaque types
+
+-opaque d1() :: a | b | c.
+
+-opaque d2() :: d | e | f.
+
+%% -spec t2('a' | 'b') -> simple1_api:d1('a') | simple1_api:d2('d').
+
+t2(a) ->
+    d1();
+t2(b) ->
+    d2().
+
+-spec d1() -> d1().
+
+d1() -> a.
+
+-spec d2() -> d2().
+
+d2() -> d.
+
+%% -spec adt_t2('a' | 'b') -> simple1_adt:d1('a') | simple1_adt:d2('d').
+
+adt_t2(a) ->
+    simple1_adt:d1();
+adt_t2(b) ->
+    simple1_adt:d2().
+
+-spec tup() -> simple1_adt:tuple1(). % invalid type spec
+
+tup() ->
+    {a, b}.
+
+%%% Matching equal opaque types with different names
+
+t3() ->
+    A = n1(),
+    B = n2(),
+    A = A, % OK, of course
+    A = B. % OK since o1() and o2() are local opaque types
+
+t4() ->
+    A = n1(),
+    B = n2(),
+    true = A =:= A, % OK, of course
+    A =:= B. % OK since o1() and o2() are local opaque types
+
+t5() ->
+    A = d1(),
+    B = d2(),
+    A =:= B. % can never evaluate to true
+
+t6() ->
+    A = d1(),
+    B = d2(),
+    A = B. % can never succeed
+
+t7() ->
+    A = d1(),
+    B = d2(),
+    A =/= B. % OK (always true?)
+
+t8() ->
+    A = d1(),
+    B = d2(),
+    A /= B. % OK (always true?)
+
+-spec n1() -> o1().
+
+n1() -> a.
+
+-spec n2() -> o2().
+
+n2() -> a.
+
+adt_t3() ->
+    A = simple1_adt:n1(),
+    B = simple1_adt:n2(),
+    true = A =:= A, % OK.
+    A =:= B. % opaque test, not OK
+
+adt_t4() ->
+    A = simple1_adt:n1(),
+    B = simple1_adt:n2(),
+    A = A, % OK
+    A = B. % opaque terms
+
+adt_t7() ->
+    A = simple1_adt:n1(),
+    B = simple1_adt:n2(),
+    false = A =/= A, % OK
+    A =/= B. % opaque test, not OK
+
+adt_t8() ->
+    A = simple1_adt:n1(),
+    B = simple1_adt:n2(),
+    false = A /= A, % OK
+    A /= B. % opaque test, not OK
+
+adt_t5() ->
+    A = simple1_adt:c1(),
+    B = simple1_adt:c2(),
+    A =:= B. % opaque test, not OK
+
+%% Comparison in guard
+
+-spec c1(simple1_adt:d1(), simple1_adt:d2()) -> boolean().
+
+c1(A, B) when A =< B -> true. % succ type of A and B is any() (type spec is OK)
+
+-spec c2(simple1_adt:d1(), simple1_adt:d2()) -> boolean().
+
+c2(A, B) ->
+    if A =< B -> true end. % succ type of A and B is any() (type spec is OK)
+
+c2() ->
+    A = simple1_adt:d1(),
+    B = simple1_adt:d2(),
+    if A =< B -> ok end. % opaque terms
+
+c3() ->
+    B = simple1_adt:d2(),
+    if a =< B -> ok end. % opaque term
+
+c4() ->
+    A = simple1_adt:d1(),
+    if A =< d -> ok end. % opaque term
+
+tt1() ->
+    A = o1(),
+    is_integer(A). % OK
+
+tt2() ->
+    A = simple1_adt:d1(),
+    is_integer(A). % breaks the opacity
+
+%% Comparison with integers
+
+-opaque i1() :: 1 | 2.
+
+-opaque i2() :: 1 | 2.
+
+-opaque di1() :: 1 | 2.
+
+-opaque di2() :: 3 | 4.
+
+-spec i1() -> i1().
+
+i1() -> 1.
+
+-type ty_i1() :: 1 | 2.
+
+-spec ty_i1() -> ty_i1().
+
+ty_i1() -> 1.
+
+cmp1() ->
+    A = i1(),
+    if A > 3 -> ok end. % can never succeed
+
+cmp2() ->
+    A = simple1_adt:i1(),
+    if A > 3 -> ok end. % opaque term
+
+cmp3() ->
+    A = i1(),
+    if A < 3 -> ok end.
+
+cmp4() ->
+    A = simple1_adt:i1(),
+    if A < 3 -> ok end. % opaque term
+
+%% -type
+
+ty_cmp1() ->
+    A = ty_i1(),
+    if A > 3 -> ok end. % can never succeed
+
+ty_cmp2() ->
+    A = simple1_adt:ty_i1(),
+    if A > 3 -> ok end. % can never succeed
+
+ty_cmp3() ->
+    A = ty_i1(),
+    if A < 3 -> ok end.
+
+ty_cmp4() ->
+    A = simple1_adt:ty_i1(),
+    if A < 3 -> ok end.
+
+%% is_function
+
+f1() ->
+    T = n1(),
+    if is_function(T) -> ok end. % can never succeed
+
+f2() ->
+    T = n1(),
+    is_function(T). % ok
+
+adt_f1() ->
+    T = simple1_adt:n1(),
+    if is_function(T) -> ok end. % breaks the opacity
+
+adt_f2() ->
+    T = simple1_adt:n1(),
+    is_function(T). % breaks the opacity
+
+f3() ->
+    A = i1(),
+    T = n1(),
+    if is_function(T, A) -> ok end. % can never succeed
+
+f4() ->
+    A = i1(),
+    T = n1(),
+    is_function(T, A). % ok
+
+adt_f3() ->
+    A = simple1_adt:i1(),
+    T = simple1_adt:n1(),
+    if is_function(T, A) -> ok end. % breaks the opacity
+
+adt_f4() ->
+    A = simple1_adt:i1(),
+    T = simple1_adt:n1(),
+    is_function(T, A). % breaks the opacity
+
+adt_f4_a() ->
+    A = simple1_adt:i1(),
+    T = n1(),
+    is_function(T, A). % opaque term
+
+
+adt_f4_b() ->
+    A = i1(),
+    T = simple1_adt:n1(),
+    is_function(T, A). % breaks the opacity
+
+%% A few Boolean examples
+
+bool_t1() ->
+    B = b2(),
+    if B -> ok end. % B =:= true can never succeed
+
+bool_t2() ->
+    A = b1(),
+    B = b2(),
+    if A and not B -> ok end.
+
+bool_t3() ->
+    A = b1(),
+    if not A -> ok end. % can never succeed
+
+bool_t4() ->
+    A = n1(),
+    if not ((A >= 1) and not (A < 1)) -> ok end. % can never succeed
+
+-spec bool_t5(i1()) -> integer().
+
+bool_t5(A) ->
+    if [not (A > 1)] =:=
+       [false]-> 1 end.
+
+-spec bool_t6(b1()) -> integer().
+
+bool_t6(A) ->
+    if [not A] =:=
+       [false]-> 1 end.
+
+-spec bool_t7() -> integer().
+
+bool_t7() ->
+    A = i1(),
+    if [not A] =:= % cannot succeed
+       [false]-> 1 end.
+
+bool_adt_t1() ->
+    B = simple1_adt:b2(),
+    if B -> ok end. % opaque term
+
+bool_adt_t2() ->
+    A = simple1_adt:b1(),
+    B = simple1_adt:b2(),
+    if A and not B -> ok end. % opaque term
+
+-spec bool_adt_t5(simple1_adt:i1()) -> integer().
+
+bool_adt_t5(A) ->
+    if [not (A > 1)] =:= % succ type of A is any() (type spec is OK)
+       [false]-> 1 end.
+
+-spec bool_adt_t6(simple1_adt:b1()) -> integer(). % invalid type spec
+
+bool_adt_t6(A) ->
+    if [not A] =:= % succ type of A is 'true'
+       [false]-> 1 end.
+
+-spec bool_t8() -> integer().
+
+bool_t8() ->
+    A = i1(),
+    if [A and A] =:= % cannot succeed
+       [false]-> 1 end.
+
+-spec bool_adt_t8(simple1_adt:b1(), simple1_adt:b2()) -> integer(). % invalid
+
+bool_adt_t8(A, B) ->
+    if [A and B] =:=
+       [false]-> 1 end.
+
+-spec bool_t9() -> integer().
+
+bool_t9() ->
+    A = i1(),
+    if [A or A] =:= % cannot succeed
+       [false]-> 1 end.
+
+-spec bool_adt_t9(simple1_adt:b1(), simple1_adt:b2()) -> integer(). % invalid
+
+bool_adt_t9(A, B) ->
+    if [A or B] =:=
+       [false]-> 1 end.
+
+-opaque b1() :: boolean().
+
+-opaque b2() :: boolean().
+
+-spec b1() -> b1().
+
+b1() -> true.
+
+-spec b2() -> b2().
+
+b2() -> false.
+
+%% Few (very few...) examples with bit syntax
+
+bit_t1() ->
+    A = i1(),
+    <<100:(A)>>.
+
+bit_adt_t1() ->
+    A = simple1_adt:i1(),
+    <<100:(A)>>. % breaks the opacity
+
+bit_t3(A) ->
+    B = i1(),
+    case none:none() of
+        <<A:B>> -> 1
+    end.
+
+bit_adt_t2() ->
+    A = simple1_adt:i1(),
+    case <<"hej">> of
+        <<_:A>> -> ok % breaks the opacity (but the message is strange)
+    end.
+
+
+bit_adt_t3(A) ->
+    B = simple1_adt:i1(),
+    case none:none() of
+        <<A:  % breaks the opacity (the message is less than perfect)
+          B>> -> 1
+    end.
+
+bit_t5(A) ->
+    B = o1(),
+    case none:none() of % the type is any(); should fix that XXX
+        <<A:B>> -> 1 % can never match (local opaque type is OK)
+    end.
+
+-spec bit_t4(<<_:1>>) -> integer().
+
+bit_t4(A) ->
+    Sz = i1(),
+    case A of
+        <<_:Sz>> -> 1
+    end.
+
+-spec bit_adt_t4(<<_:1>>) -> integer().
+
+bit_adt_t4(A) ->
+    Sz = simple1_adt:i1(),
+    case A of
+        <<_:Sz>> -> 1 % breaks the opacity
+    end.
+
+bit_t5() ->
+    A = bit1(),
+    case A of
+        <<_/binary>> -> 1
+    end.
+
+bit_adt_t5() ->
+    A = simple1_adt:bit1(),
+    case A of
+        <<_/binary>> -> 1 % breaks the opacity
+    end.
+
+-opaque bit1() :: binary().
+
+-spec bit1() -> bit1().
+
+bit1() ->
+    <<"hej">>.
+
+%% Calls with variable module or function
+
+call_f(A) ->
+    A = a(),
+    foo:A(A).
+
+call_f_adt(A) ->
+    A = simple1_adt:a(),
+    foo:A(A). % breaks the opacity
+
+call_m(A) ->
+    A = a(),
+    A:foo(A).
+
+call_m_adt(A) ->
+    A = simple1_adt:a(),
+    A:foo(A). % breaks the opacity
+
+-opaque a() :: atom().
+
+-opaque i() :: integer().
+
+-spec a() -> a().
+
+a() ->
+    e.
+
+call_f_i(A) ->
+    A = i(),
+    foo:A(A). % A is not atom() but i()
+
+call_f_adt_i(A) ->
+    A = simple1_adt:i(),
+    foo:A(A). % A is not atom() but simple1_adt:i()
+
+call_m_i(A) ->
+    A = i(),
+    A:foo(A). % A is not atom() but i()
+
+call_m_adt_i(A) ->
+    A = simple1_adt:i(),
+    A:foo(A). % A is not atom() but simple1_adt:i()
+
+-spec eq1() -> integer().
+
+eq1() ->
+    A = simple1_adt:d2(),
+    B = simple1_adt:d1(),
+    if
+        A == B -> % opaque terms
+            0;
+        A == A ->
+            1;
+        A =:= A -> % compiler finds this one cannot match
+            2;
+        true -> % compiler finds this one cannot match
+            3
+    end.
+
+eq2() ->
+    A = simple1_adt:d1(),
+    if
+        {A} >= {A} ->
+            1;
+        A >= 3 -> % opaque term
+            2;
+        A == 3 -> % opaque term
+            3;
+        A =:= 3 -> % opaque term
+            4;
+        A == A ->
+            5;
+        A =:= A -> % compiler finds this one cannot match
+            6
+    end.
+
+c5() ->
+    A = simple1_adt:d1(),
+    A < 3. % opaque term
+
+c6(A, B) ->
+    A = simple1_adt:d1(),
+    B = simple1_adt:d1(),
+    A =< B. % same type - no warning
+
+c7(A, B) ->
+    A = simple1_adt:d1(),
+    B = simple1_adt:d2(),
+    A =< B. % opaque terms
+
+c8() ->
+    D = digraph:new(),
+    E = ets:new(foo, []),
+    if {D, a} > {D, E} -> true; % OK
+       {1.0, 2} > {{D}, {E}} -> true; % OK
+       {D, 3} > {D, E} -> true  % opaque term 2
+    end.
+
+-spec i() -> i().
+
+i() ->
+    1.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/simple/simple2_api.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/simple2_api.erl
new file mode 100644
index 0000000000..c86f6fd0b5
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/simple2_api.erl
@@ -0,0 +1,125 @@
+-module(simple2_api).
+
+-export([c1/2, c2/0, c3/0, c4/1, c5/1, c6/0, c6_b/0, c7/0, c7_b/0,
+         c7_c/0, c8/0, c9/0, c10/0, c11/0, c12/0, c13/0, c14/0, c15/0,
+         c16/0, c17/0, c18/0, c19/0, c20/0, c21/0, c22/0, c23/0,
+         c24/0, c25/0, c26/0]).
+
+-spec c1(simple1_adt:d1(), simple1_adt:d2()) -> boolean().
+
+c1(A, B) ->
+    {A} =< {B}. % succ type of A and B is any()
+
+c2() ->
+    A = simple1_adt:d1(),
+    erlang:make_tuple(1, A). % ok
+
+c3() ->
+    A = simple1_adt:d1(),
+    setelement(1, {A}, A). % ok
+
+c4(_) ->
+    A = simple1_adt:d1(),
+    halt(A). % ok (BIF fails...)
+
+c5(_) ->
+    A = simple1_adt:d1(),
+    [A] -- [A]. % ok
+
+c6() ->
+    A = simple1_adt:d1(),
+    A ! foo. % opaque term
+
+c6_b() ->
+    A = simple1_adt:d1(),
+    erlang:send(A, foo). % opaque term
+
+c7() ->
+    A = simple1_adt:d1(),
+    foo ! A. % ok
+
+c7_b() ->
+    A = simple1_adt:d1(),
+    erlang:send(foo, A). % ok
+
+c7_c() ->
+    A = simple1_adt:d1(),
+    erlang:send(foo, A, []). % ok
+
+c8() ->
+    A = simple1_adt:d1(),
+    A < 3. % opaque term
+
+c9() ->
+    A = simple1_adt:d1(),
+    lists:keysearch(A, 1, []). % ok
+
+c10() ->
+    A = simple1_adt:d1(),
+    lists:keysearch(1, A, []). % opaque term 2
+
+c11() ->
+    A = simple1_adt:tuple(),
+    lists:keysearch(key, 1, [A]). % ok
+
+c12() ->
+    A = simple1_adt:tuple(),
+    lists:keysearch(key, 1, A). % opaque term 3
+
+c13() ->
+    A = simple1_adt:tuple(),
+    lists:keysearch(key, 1, [{A,2}]). % ok
+
+c14() ->
+    A = simple1_adt:tuple(),
+    lists:keysearch(key, 1, [{2,A}]). % ok
+
+c15() ->
+    A = simple1_adt:d1(),
+    lists:keysearch(key, 1, [A]). % ok
+
+c16() ->
+    A = simple1_adt:tuple(),
+    erlang:send(foo, A). % ok
+
+c17() ->
+    A = simple1_adt:tuple(),
+    lists:reverse([A]). % ok
+
+c18() ->
+    A = simple1_adt:tuple(),
+    lists:keyreplace(a, 1, [A], {1,2}). % ok
+
+c19() ->
+    A = simple1_adt:tuple(),
+    %% Problem. The spec says argument 4 is a tuple(). Fix that!
+    lists:keyreplace(a, 1, [{1,2}], A). % opaque term 4
+
+c20() ->
+    A = simple1_adt:tuple(),
+    lists:flatten(A). % opaque term 1
+
+c21() ->
+    A = simple1_adt:tuple(),
+    lists:flatten([[{A}]]). % ok
+
+c22() ->
+    A = simple1_adt:tuple(),
+    lists:flatten([[A]]). % ok
+
+c23() ->
+    A = simple1_adt:tuple(),
+    lists:flatten([A]). % ok
+
+c24() ->
+    A = simple1_adt:tuple(),
+    lists:flatten({A}). % will never return
+
+c25() ->
+    A = simple1_adt:d1(),
+    B = simple1_adt:tuple(),
+    if {A,3} > {A,B} -> true end. % opaque 2nd argument
+
+c26() ->
+    B = simple1_adt:tuple(),
+    tuple_to_list(B). % opaque term 1
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/suppress_request.erl b/lib/dialyzer/test/indent_SUITE_data/src/suppress_request.erl
new file mode 100644
index 0000000000..c4275fa110
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/suppress_request.erl
@@ -0,0 +1,50 @@
+-module(suppress_request).
+
+-export([test1/1, test1_b/1, test2/0, test2_b/0,
+         test3/0, test3_b/0, test4/0, test4_b/0]).
+
+-dialyzer({[specdiffs], test1/1}).
+-spec test1(a | b) -> ok. % spec is subtype
+test1(A) ->
+    ok = test1_1(A).
+
+-spec test1_b(a | b) -> ok. % spec is subtype (suppressed by default)
+test1_b(A) ->
+    ok = test1_1(A).
+
+-spec test1_1(a | b | c) -> ok.
+test1_1(_) ->
+    ok.
+
+-dialyzer(unmatched_returns).
+test2() ->
+    tuple(), % unmatched
+    ok.
+
+test2_b() ->
+    tuple(), % unmatched
+    ok.
+
+-dialyzer({[no_return, no_match], [test3/0]}).
+test3() -> % no local return (suppressed)
+    A = fun(_) ->
+                1
+        end,
+    A = 2. % can never succeed (suppressed)
+
+test3_b() -> % no local return (requested by default)
+    A = fun(_) ->
+                1
+        end,
+    A = 2. % can never succeed (requested by default)
+
+-dialyzer(no_improper_lists).
+test4() ->
+    [1 | 2]. % improper list (suppressed)
+
+-dialyzer({no_improper_lists, test4_b/0}).
+test4_b() ->
+    [1 | 2]. % improper list (suppressed)
+
+tuple() ->
+    {a, b}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/trec.erl b/lib/dialyzer/test/indent_SUITE_data/src/trec.erl
new file mode 100644
index 0000000000..516358f7c6
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/trec.erl
@@ -0,0 +1,39 @@
+%%
+%% The current treatment of typed records leaves much to be desired.
+%% These are not made up examples; I have cases like that the branch
+%% of the HiPE compiler with types in records. I get very confusing
+%% warnings which require a lot of effort to find their cause and why
+%% a function has no local return.
+%%
+-module(trec).
+-export([test/0, mk_foo_exp/2]).
+
+-record(foo, {a :: integer() | 'undefined', b :: [atom()]}).
+
+%%
+%% For these functions we currently get the following warnings:
+%%   1. Function test/0 has no local return
+%%   2. The call trec:mk_foo_loc(42,any()) will fail since it differs
+%%      in argument position 1 from the success typing arguments:
+%%      ('undefined',atom())
+%%   3. Function mk_foo_loc/2 has no local return
+%%
+%% Arguably, the second warning is not what most users have in mind when
+%% they wrote the type declarations in the 'foo' record, so no doubt
+%% they'll find it confusing. But note that it is also quite confusing!
+%% Many users may be wondering: How come there is a success typing for a
+%% function that has no local return? Running typer on this module
+%% reveals a success typing for this function that is interesting indeed.
+%%
+test() ->
+   mk_foo_loc(42, some_mod:some_function()).
+
+mk_foo_loc(A, B) ->
+    #foo{a = A, b = [A,B]}.
+
+%%
+%% For this function we used to get a "has no local return" warning
+%% but we got no reason. This has now been fixed.
+%%
+mk_foo_exp(A, B) when is_integer(A) ->
+    #foo{a = A, b = [A,B]}.
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/whereis_control_flow1.erl b/lib/dialyzer/test/indent_SUITE_data/src/whereis_control_flow1.erl
new file mode 100644
index 0000000000..e65f6c3e23
--- /dev/null
+++ b/lib/dialyzer/test/indent_SUITE_data/src/whereis_control_flow1.erl
@@ -0,0 +1,17 @@
+%% This tests the presence of possible races due to a whereis/register
+%% combination. It takes into account control flow that might exist.
+
+-module(whereis_control_flow1).
+-export([start/2]).
+
+start(AnAtom, Fun) ->
+  case whereis(AnAtom) of
+    undefined ->
+      Pid = spawn(Fun),
+      case Pid =:= self() of
+        true -> ok;
+        false -> register(AnAtom, Pid)
+      end;
+    P when is_pid(P) ->
+      ok
+  end.
diff --git a/lib/dialyzer/test/map_SUITE_data/dialyzer_options b/lib/dialyzer/test/map_SUITE_data/dialyzer_options
index 02425c33f2..1ddeb02c27 100644
--- a/lib/dialyzer/test/map_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/map_SUITE_data/dialyzer_options
@@ -1,2 +1,2 @@
-{dialyzer_options, []}.
+{dialyzer_options, [{indent_opt, false}]}.
 {time_limit, 30}.
diff --git a/lib/dialyzer/test/opaque_SUITE_data/dialyzer_options b/lib/dialyzer/test/opaque_SUITE_data/dialyzer_options
index cb301ff6a1..8551a47541 100644
--- a/lib/dialyzer/test/opaque_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/opaque_SUITE_data/dialyzer_options
@@ -1,2 +1,2 @@
-{dialyzer_options, [{warnings, [no_unused, no_return]}]}.
+{dialyzer_options, [{indent_opt, false}, {warnings, [no_unused, no_return]}]}.
 {time_limit, 40}.
diff --git a/lib/dialyzer/test/options1_SUITE_data/dialyzer_options b/lib/dialyzer/test/options1_SUITE_data/dialyzer_options
index c612e77d3e..ef5887a1eb 100644
--- a/lib/dialyzer/test/options1_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/options1_SUITE_data/dialyzer_options
@@ -1,2 +1,2 @@
-{dialyzer_options, [{include_dirs, ["my_include"]}, {defines, [{'COMPILER_VSN', 42}]}, {warnings, [no_improper_lists]}]}.
+{dialyzer_options, [{indent_opt, false}, {include_dirs, ["my_include"]}, {defines, [{'COMPILER_VSN', 42}]}, {warnings, [no_improper_lists]}]}.
 {time_limit, 30}.
diff --git a/lib/dialyzer/test/options2_SUITE_data/dialyzer_options b/lib/dialyzer/test/options2_SUITE_data/dialyzer_options
index be57e2de72..6492098d01 100644
--- a/lib/dialyzer/test/options2_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/options2_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, [{defines, [{'vsn', 4}]}, {warnings, [unknown, no_return]}]}.
+{dialyzer_options, [{indent_opt, false}, {defines, [{'vsn', 4}]}, {warnings, [unknown, no_return]}]}.
diff --git a/lib/dialyzer/test/overspecs_SUITE_data/dialyzer_options b/lib/dialyzer/test/overspecs_SUITE_data/dialyzer_options
index ff4517e59d..f581ad6607 100644
--- a/lib/dialyzer/test/overspecs_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/overspecs_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, [{warnings, [overspecs]}]}.
+{dialyzer_options, [{indent_opt, false}, {warnings, [overspecs]}]}.
diff --git a/lib/dialyzer/test/r9c_SUITE_data/dialyzer_options b/lib/dialyzer/test/r9c_SUITE_data/dialyzer_options
index e00e23bb66..ab6c9439ad 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/r9c_SUITE_data/dialyzer_options
@@ -1,2 +1,2 @@
-{dialyzer_options, [{defines, [{vsn, 42}]}]}.
+{dialyzer_options, [{indent_opt, false}, {defines, [{vsn, 42}]}]}.
 {time_limit, 20}.
diff --git a/lib/dialyzer/test/race_SUITE_data/dialyzer_options b/lib/dialyzer/test/race_SUITE_data/dialyzer_options
index 44e1720715..2be2f47dda 100644
--- a/lib/dialyzer/test/race_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/race_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, [{warnings, [race_conditions]}]}.
+{dialyzer_options, [{indent_opt, false}, {warnings, [race_conditions]}]}.
diff --git a/lib/dialyzer/test/small_SUITE_data/dialyzer_options b/lib/dialyzer/test/small_SUITE_data/dialyzer_options
index 50991c9bc5..8413436b67 100644
--- a/lib/dialyzer/test/small_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/small_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, []}.
+{dialyzer_options, [{indent_opt, false}]}.
diff --git a/lib/dialyzer/test/specdiffs_SUITE_data/dialyzer_options b/lib/dialyzer/test/specdiffs_SUITE_data/dialyzer_options
index 56b36f2ed4..f7076e34da 100644
--- a/lib/dialyzer/test/specdiffs_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/specdiffs_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, [{warnings, [specdiffs]}]}.
+{dialyzer_options, [{indent_opt, false}, {warnings, [specdiffs]}]}.
diff --git a/lib/dialyzer/test/underspecs_SUITE_data/dialyzer_options b/lib/dialyzer/test/underspecs_SUITE_data/dialyzer_options
index f7197ac30f..1a9734deb2 100644
--- a/lib/dialyzer/test/underspecs_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/underspecs_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, [{warnings, [underspecs]}]}.
+{dialyzer_options, [{indent_opt, false}, {warnings, [underspecs]}]}.
diff --git a/lib/dialyzer/test/unmatched_returns_SUITE_data/dialyzer_options b/lib/dialyzer/test/unmatched_returns_SUITE_data/dialyzer_options
index 49ac917f61..7de9d6f962 100644
--- a/lib/dialyzer/test/unmatched_returns_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/unmatched_returns_SUITE_data/dialyzer_options
@@ -1 +1 @@
-{dialyzer_options, [{warnings, [unmatched_returns]}]}.
+{dialyzer_options, [{indent_opt, false}, {warnings, [unmatched_returns]}]}.
diff --git a/lib/dialyzer/test/user_SUITE_data/dialyzer_options b/lib/dialyzer/test/user_SUITE_data/dialyzer_options
index 513ed7752b..0a944966f0 100644
--- a/lib/dialyzer/test/user_SUITE_data/dialyzer_options
+++ b/lib/dialyzer/test/user_SUITE_data/dialyzer_options
@@ -1,2 +1,2 @@
-{dialyzer_options, []}.
+{dialyzer_options, [{indent_opt, false}]}.
 {time_limit, 3}.
\ No newline at end of file
-- 
2.16.4

openSUSE Build Service is sponsored by