diff --git a/lib/kernel/doc/kernel_app.md b/lib/kernel/doc/kernel_app.md
index 432d67882369..d94146f5daa7 100644
--- a/lib/kernel/doc/kernel_app.md
+++ b/lib/kernel/doc/kernel_app.md
@@ -417,6 +417,11 @@ For more information about configuration parameters, see file
 
   Defaults to `false`.
 
+- **`shell_docs_ansi = boolean()`{: #shell_docs_ansi }** - Specifies whether
+  the documentation rendered in the shell should use ANSI escape codes.
+
+  See also `t:shell_docs:config/0`.
+
 - **`shell_history = enabled | disabled | module()`{: #shell_history }** -
   Specifies whether shell history should be logged to disk between usages of
   `erl` (`enabled`), not logged at all (`disabled`), or a user-specified module
diff --git a/lib/stdlib/doc/stdlib_app.md b/lib/stdlib/doc/stdlib_app.md
index 01184b36cbba..aa863dba3f26 100644
--- a/lib/stdlib/doc/stdlib_app.md
+++ b/lib/stdlib/doc/stdlib_app.md
@@ -40,6 +40,11 @@ For more information about configuration parameters, see the
 - **`shell_catch_exception = boolean()`{: #shell_catch_exception }** - Can be
   used to set the exception handling of the evaluator process of Erlang shell.
 
+- **`shell_docs_columns = pos_integer()`{: #shell_docs_columns }** -
+  Configures how wide the documentation should be rendered in the shell.
+
+  See also `t:shell_docs:config/0`.
+
 - **`shell_expand_location = above | below`{: #shell_expand_location }** - Sets
   where the tab expansion text should appear in the shell. The default is
   `below`. This will open a pager below the cursor that is scrollable one line
diff --git a/lib/stdlib/src/shell_docs.erl b/lib/stdlib/src/shell_docs.erl
index 99d372b8b323..97f0171fb036 100644
--- a/lib/stdlib/src/shell_docs.erl
+++ b/lib/stdlib/src/shell_docs.erl
@@ -116,7 +116,9 @@ The configuration of how the documentation should be rendered.
 
 - **columns** - Configure how wide the target documentation should be rendered.
   By default `shell_docs` used the value returned by
-  [`io:columns()`](`io:columns/0`).
+  [`io:columns()`](`io:columns/0`). It is possible to override this default
+  by setting the stdlib configuration parameter `shell_docs_columns`
+  to a `t:pos_integer/0` value.
 """.
 -doc #{ since => ~"OTP 23.2" }.
 -type config() :: #{ encoding => unicode | latin1,
@@ -919,12 +921,7 @@ init_config(D, Config) when is_map(Config) ->
     Columns =
         case maps:find(columns, Config) of
             error ->
-                case io:columns() of
-                    {ok, C} ->
-                        C;
-                    _ ->
-                        80
-                end;
+                get_columns();
             {ok, C} ->
                 C
         end,
@@ -936,6 +933,19 @@ init_config(D, Config) when is_map(Config) ->
 init_config(D, Config) ->
     Config#config{ docs = D }.
 
+get_columns() ->
+    case application:get_env(stdlib, shell_docs_columns) of
+        {ok, C} when is_integer(C), C > 0 ->
+            C;
+        _ ->
+            case io:columns() of
+                 {ok, C} ->
+                     C;
+                 _ ->
+                     80
+             end
+    end.
+
 render_docs(Elems,State,Pos,Ind,D) when is_list(Elems) ->
     lists:mapfoldl(fun(Elem,P) ->
                           render_docs(Elem,State,P,Ind,D)
diff --git a/lib/stdlib/test/shell_docs_SUITE.erl b/lib/stdlib/test/shell_docs_SUITE.erl
index dd613d15eb91..8b6fe16f8789 100644
--- a/lib/stdlib/test/shell_docs_SUITE.erl
+++ b/lib/stdlib/test/shell_docs_SUITE.erl
@@ -19,10 +19,10 @@
 %%
 -module(shell_docs_SUITE).
 -export([all/0, suite/0, groups/0, init_per_suite/1, end_per_suite/1,
-   init_per_group/2, end_per_group/2]).
+   init_per_group/2, end_per_group/2, init_per_testcase/2, end_per_testcase/2]).
 
 -export([render/1, render_smoke/1, links/1, normalize/1, render_prop/1,
-         render_non_native/1]).
+         render_non_native/1, ansi/1, columns/1]).
 
 -export([render_all/1, update_render/0, update_render/1]).
 
@@ -33,7 +33,8 @@ suite() ->
     [{timetrap,{minutes,20}}].
 
 all() ->
-    [render_smoke, render, render_non_native, links, normalize, {group, prop}].
+    [render_smoke, render, render_non_native, links, normalize,
+     {group, prop}, ansi, columns].
 
 groups() ->
     [{prop,[],[render_prop]}].
@@ -55,8 +56,23 @@ init_per_group(prop, Config) ->
 init_per_group(_GroupName, Config) ->
     Config.
 
-end_per_group(_GroupName, Config) ->
-    Config.
+end_per_group(_GroupName, _Config) ->
+    ok.
+
+init_per_testcase(_TestCase, Config) ->
+    Env = [{App, Key, application:get_env(App, Key)}
+           || {App, Key} <- [{kernel, shell_docs_ansi},
+                             {stdlib, shell_docs_columns}]],
+    [{env, Env} | Config].
+
+end_per_testcase(_TestCase, Config) ->
+    lists:foreach(
+      fun({App, Key, undefined}) ->
+              application:unset_env(App, Key);
+         ({App, Key, {ok, Val}}) ->
+              application:set_env(App, Key, Val)
+      end,
+      proplists:get_value(env, Config)).
 
 %% We keep the docs of a couple of complex modules
 %% in the data_dir in order to compare then with the original
@@ -403,3 +419,57 @@ docsmap(Fun) ->
                       end
               end
       end, code:all_available()).
+
+ansi(_Config) ->
+    {ok, Docs} = code:get_doc(?MODULE),
+
+    HasESC =
+        fun(Config) ->
+                Doc = shell_docs:render(?MODULE, Docs, Config),
+                string:find(Doc, "\e") =/= nomatch
+        end,
+
+    application:set_env(kernel, shell_docs_ansi, true),
+    ?assert(HasESC(#{})),
+    ?assertNot(HasESC(#{ansi => false})),
+    ?assert(HasESC(#{ansi => true})),
+
+    application:set_env(kernel, shell_docs_ansi, false),
+    ?assertNot(HasESC(#{})),
+    ?assertNot(HasESC(#{ansi => false})),
+    ?assert(HasESC(#{ansi => true})),
+
+    ok.
+
+-doc """
+Doc doc doc doc doc doc doc doc doc doc doc doc doc doc doc.
+""".
+columns(_Config) ->
+    {ok, Docs} = code:get_doc(?MODULE),
+
+    MaxColumns =
+        fun(Config0) ->
+                Config = maps:merge(#{ansi => false}, Config0),
+                Doc = shell_docs:render(?MODULE, ?FUNCTION_NAME, Docs, Config),
+                Lines = string:split(Doc, "\n", all),
+                lists:max(lists:map(fun string:length/1, Lines))
+        end,
+
+    application:set_env(stdlib, shell_docs_columns, 30),
+    ?assert(MaxColumns(#{}) =< 30),
+    ?assert(MaxColumns(#{columns => 20}) =< 20),
+
+    application:set_env(stdlib, shell_docs_columns, not_an_integer),
+    ?assert(MaxColumns(#{}) > 30),
+
+    application:set_env(stdlib, shell_docs_columns, 0),
+    ?assert(MaxColumns(#{}) > 30),
+
+    application:set_env(stdlib, shell_docs_columns, -30),
+    ?assert(MaxColumns(#{}) > 30),
+
+    application:unset_env(stdlib, shell_docs_columns),
+    ?assert(MaxColumns(#{}) > 30),
+    ?assert(MaxColumns(#{columns => 20}) =< 20),
+
+    ok.