Skip to content

Commit f461a51

Browse files
committed
Replace keyword with concrete keyword lists in specs for all functions taking options argument
Add missing documentation for some of the supported options Add specs for functions with options argumnet
1 parent 237263c commit f461a51

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

67 files changed

+1225
-146
lines changed

lib/eex/lib/eex.ex

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -118,6 +118,15 @@ defmodule EEx do
118118
| {:expr | :start_expr | :middle_expr | :end_expr, marker, charlist, metadata}
119119
| {:eof, metadata}
120120

121+
@type tokenize_opt ::
122+
{:file, binary()}
123+
| {:line, line}
124+
| {:column, column}
125+
| {:indentation, non_neg_integer}
126+
| {:trim, boolean()}
127+
128+
@type compile_opt :: tokenize_opt | {:engine, module()} | {:parser_options, Code.parser_opts()}
129+
121130
@doc """
122131
Generates a function definition from the given string.
123132
@@ -220,7 +229,7 @@ defmodule EEx do
220229
"3"
221230
222231
"""
223-
@spec compile_string(String.t(), keyword) :: Macro.t()
232+
@spec compile_string(String.t(), [compile_opt]) :: Macro.t()
224233
def compile_string(source, options \\ []) when is_binary(source) and is_list(options) do
225234
case tokenize(source, options) do
226235
{:ok, tokens} ->
@@ -259,7 +268,7 @@ defmodule EEx do
259268
#=> "3"
260269
261270
"""
262-
@spec compile_file(Path.t(), keyword) :: Macro.t()
271+
@spec compile_file(Path.t(), [compile_opt]) :: Macro.t()
263272
def compile_file(filename, options \\ []) when is_list(options) do
264273
filename = IO.chardata_to_string(filename)
265274
options = Keyword.merge([file: filename, line: 1], options)
@@ -277,7 +286,7 @@ defmodule EEx do
277286
"foo baz"
278287
279288
"""
280-
@spec eval_string(String.t(), keyword, keyword) :: String.t()
289+
@spec eval_string(String.t(), keyword, [compile_opt]) :: String.t()
281290
def eval_string(source, bindings \\ [], options \\ [])
282291
when is_binary(source) and is_list(bindings) and is_list(options) do
283292
compiled = compile_string(source, options)
@@ -299,7 +308,7 @@ defmodule EEx do
299308
#=> "foo baz"
300309
301310
"""
302-
@spec eval_file(Path.t(), keyword, keyword) :: String.t()
311+
@spec eval_file(Path.t(), keyword, [compile_opt]) :: String.t()
303312
def eval_file(filename, bindings \\ [], options \\ [])
304313
when is_list(bindings) and is_list(options) do
305314
filename = IO.chardata_to_string(filename)
@@ -339,7 +348,7 @@ defmodule EEx do
339348
Note new tokens may be added in the future.
340349
"""
341350
@doc since: "1.14.0"
342-
@spec tokenize([char()] | String.t(), opts :: keyword) ::
351+
@spec tokenize([char()] | String.t(), [tokenize_opt]) ::
343352
{:ok, [token()]} | {:error, String.t(), metadata()}
344353
def tokenize(contents, opts \\ []) do
345354
EEx.Compiler.tokenize(contents, opts)

lib/eex/lib/eex/compiler.ex

Lines changed: 17 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,22 @@ defmodule EEx.Compiler do
1010
@h_spaces [?\s, ?\t]
1111
@all_spaces [?\s, ?\t, ?\n, ?\r]
1212

13+
@typedoc """
14+
Options for EEx compilation functions.
15+
16+
These options control various aspects of EEx template compilation including
17+
file information, parsing behavior, and the template engine to use.
18+
"""
19+
@type compile_opts :: [
20+
file: String.t(),
21+
line: pos_integer(),
22+
column: pos_integer(),
23+
indentation: non_neg_integer(),
24+
trim: boolean(),
25+
parser_options: Code.parser_opts(),
26+
engine: module()
27+
]
28+
1329
@doc """
1430
Tokenize EEx contents.
1531
"""
@@ -290,7 +306,7 @@ defmodule EEx.Compiler do
290306
and the engine together by handling the tokens and invoking
291307
the engine every time a full expression or text is received.
292308
"""
293-
@spec compile([EEx.token()], String.t(), keyword) :: Macro.t()
309+
@spec compile([EEx.token()], String.t(), compile_opts) :: Macro.t()
294310
def compile(tokens, source, opts) do
295311
file = opts[:file] || "nofile"
296312
line = opts[:line] || 1

lib/eex/lib/eex/engine.ex

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,12 +14,29 @@ defmodule EEx.Engine do
1414

1515
@type state :: term
1616

17+
@typedoc """
18+
Options passed to engine initialization.
19+
20+
These are the same options passed to `EEx.Compiler.compile/3`,
21+
allowing engines to access compilation settings and customize
22+
their behavior accordingly.
23+
"""
24+
@type init_opts :: [
25+
file: String.t(),
26+
line: pos_integer(),
27+
column: pos_integer(),
28+
indentation: non_neg_integer(),
29+
trim: boolean(),
30+
parser_options: Code.parser_opts(),
31+
engine: module()
32+
]
33+
1734
@doc """
1835
Called at the beginning of every template.
1936
2037
It must return the initial state.
2138
"""
22-
@callback init(opts :: keyword) :: state
39+
@callback init(opts :: init_opts) :: state
2340

2441
@doc """
2542
Called at the end of every template.

lib/elixir/lib/calendar.ex

Lines changed: 17 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -162,6 +162,22 @@ defmodule Calendar do
162162
"""
163163
@type time_zone_database :: module()
164164

165+
@typedoc """
166+
Options for formatting dates and times with `strftime/3`.
167+
"""
168+
@type strftime_opts :: [
169+
preferred_datetime: String.t(),
170+
preferred_date: String.t(),
171+
preferred_time: String.t(),
172+
am_pm_names: (:am | :pm -> String.t()) | (:am | :pm, map() -> String.t()),
173+
month_names: (pos_integer() -> String.t()) | (pos_integer(), map() -> String.t()),
174+
abbreviated_month_names:
175+
(pos_integer() -> String.t()) | (pos_integer(), map() -> String.t()),
176+
day_of_week_names: (pos_integer() -> String.t()) | (pos_integer(), map() -> String.t()),
177+
abbreviated_day_of_week_names:
178+
(pos_integer() -> String.t()) | (pos_integer(), map() -> String.t())
179+
]
180+
165181
@doc """
166182
Returns how many days there are in the given month of the given year.
167183
"""
@@ -617,7 +633,7 @@ defmodule Calendar do
617633
618634
"""
619635
@doc since: "1.11.0"
620-
@spec strftime(map(), String.t(), keyword()) :: String.t()
636+
@spec strftime(map(), String.t(), strftime_opts()) :: String.t()
621637
def strftime(date_or_time_or_datetime, string_format, user_options \\ [])
622638
when is_map(date_or_time_or_datetime) and is_binary(string_format) do
623639
parse(

lib/elixir/lib/calendar/duration.ex

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -161,6 +161,22 @@ defmodule Duration do
161161
"""
162162
@type duration :: t | [unit_pair]
163163

164+
@typedoc """
165+
Options for `Duration.to_string/2`.
166+
"""
167+
@type to_string_opts :: [
168+
units: [
169+
year: String.t(),
170+
month: String.t(),
171+
week: String.t(),
172+
day: String.t(),
173+
hour: String.t(),
174+
minute: String.t(),
175+
second: String.t()
176+
],
177+
separator: String.t()
178+
]
179+
164180
@microseconds_per_second 1_000_000
165181

166182
@doc """
@@ -436,6 +452,7 @@ defmodule Duration do
436452
437453
"""
438454
@doc since: "1.18.0"
455+
@spec to_string(t, to_string_opts) :: String.t()
439456
def to_string(%Duration{} = duration, opts \\ []) do
440457
units = Keyword.get(opts, :units, [])
441458
separator = Keyword.get(opts, :separator, " ")

lib/elixir/lib/code.ex

Lines changed: 72 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -248,6 +248,49 @@ defmodule Code do
248248
"""
249249
@type position() :: line() | {line :: pos_integer(), column :: pos_integer()}
250250

251+
@typedoc """
252+
Options for code formatting functions.
253+
"""
254+
@type format_opts :: [
255+
file: binary(),
256+
line: pos_integer(),
257+
line_length: pos_integer(),
258+
locals_without_parens: keyword(),
259+
force_do_end_blocks: boolean(),
260+
migrate: boolean(),
261+
migrate_bitstring_modifiers: boolean(),
262+
migrate_call_parens_on_pipe: boolean(),
263+
migrate_charlists_as_sigils: boolean(),
264+
migrate_unless: boolean()
265+
]
266+
267+
@typedoc """
268+
Options for parsing functions that convert strings to quoted expressions.
269+
"""
270+
@type parser_opts :: [
271+
file: binary(),
272+
line: pos_integer(),
273+
column: pos_integer(),
274+
indentation: non_neg_integer(),
275+
columns: boolean(),
276+
unescape: boolean(),
277+
existing_atoms_only: boolean(),
278+
token_metadata: boolean(),
279+
literal_encoder: (term(), Macro.metadata() -> term()),
280+
static_atoms_encoder: (atom() -> term()),
281+
emit_warnings: boolean()
282+
]
283+
284+
@typedoc """
285+
Options for environment evaluation functions like eval_string/3 and eval_quoted/3.
286+
"""
287+
@type env_eval_opts :: [
288+
file: binary(),
289+
line: pos_integer(),
290+
module: module(),
291+
prune_binding: boolean()
292+
]
293+
251294
@boolean_compiler_options [
252295
:docs,
253296
:debug_info,
@@ -560,7 +603,7 @@ defmodule Code do
560603
[a: 1, b: 2]
561604
562605
"""
563-
@spec eval_string(List.Chars.t(), binding, Macro.Env.t() | keyword) :: {term, binding}
606+
@spec eval_string(List.Chars.t(), binding, Macro.Env.t() | env_eval_opts) :: {term, binding}
564607
def eval_string(string, binding \\ [], opts \\ [])
565608

566609
def eval_string(string, binding, %Macro.Env{} = env) do
@@ -615,7 +658,8 @@ defmodule Code do
615658
616659
"""
617660
@doc since: "1.15.0"
618-
@spec with_diagnostics(keyword(), (-> result)) :: {result, [diagnostic(:warning | :error)]}
661+
@spec with_diagnostics([log: boolean()], (-> result)) ::
662+
{result, [diagnostic(:warning | :error)]}
619663
when result: term()
620664
def with_diagnostics(opts \\ [], fun) do
621665
value = :erlang.get(:elixir_code_diagnostics)
@@ -648,7 +692,7 @@ defmodule Code do
648692
Defaults to `true`.
649693
"""
650694
@doc since: "1.15.0"
651-
@spec print_diagnostic(diagnostic(:warning | :error), keyword()) :: :ok
695+
@spec print_diagnostic(diagnostic(:warning | :error), snippet: boolean()) :: :ok
652696
def print_diagnostic(diagnostic, opts \\ []) do
653697
read_snippet? = Keyword.get(opts, :snippet, true)
654698
:elixir_errors.print_diagnostic(diagnostic, read_snippet?)
@@ -1035,7 +1079,7 @@ defmodule Code do
10351079
address the deprecation warnings.
10361080
"""
10371081
@doc since: "1.6.0"
1038-
@spec format_string!(binary, keyword) :: iodata
1082+
@spec format_string!(binary, format_opts) :: iodata
10391083
def format_string!(string, opts \\ []) when is_binary(string) and is_list(opts) do
10401084
line_length = Keyword.get(opts, :line_length, 98)
10411085

@@ -1060,7 +1104,7 @@ defmodule Code do
10601104
available options.
10611105
"""
10621106
@doc since: "1.6.0"
1063-
@spec format_file!(binary, keyword) :: iodata
1107+
@spec format_file!(binary, format_opts) :: iodata
10641108
def format_file!(file, opts \\ []) when is_binary(file) and is_list(opts) do
10651109
string = File.read!(file)
10661110
formatted = format_string!(string, [file: file, line: 1] ++ opts)
@@ -1098,7 +1142,7 @@ defmodule Code do
10981142
[a: 1, b: 2]
10991143
11001144
"""
1101-
@spec eval_quoted(Macro.t(), binding, Macro.Env.t() | keyword) :: {term, binding}
1145+
@spec eval_quoted(Macro.t(), binding, Macro.Env.t() | env_eval_opts) :: {term, binding}
11021146
def eval_quoted(quoted, binding \\ [], env_or_opts \\ []) do
11031147
{value, binding, _env} =
11041148
eval_verify(:eval_quoted, [quoted, binding, env_for_eval(env_or_opts)])
@@ -1129,8 +1173,15 @@ defmodule Code do
11291173
* `:line` - the line on which the script starts
11301174
11311175
* `:module` - the module to run the environment on
1176+
1177+
* `:prune_binding` - (since v1.14.2) prune binding to keep only
1178+
variables read or written by the evaluated code. Note that
1179+
variables used by modules are always pruned, even if later used
1180+
by the modules. You can submit to the `:on_module` tracer event
1181+
and access the variables used by the module from its environment.
11321182
"""
11331183
@doc since: "1.14.0"
1184+
@spec env_for_eval(Macro.Env.t() | env_eval_opts) :: Macro.Env.t()
11341185
def env_for_eval(env_or_opts), do: :elixir.env_for_eval(env_or_opts)
11351186

11361187
@doc """
@@ -1144,15 +1195,11 @@ defmodule Code do
11441195
11451196
## Options
11461197
1147-
* `:prune_binding` - (since v1.14.2) prune binding to keep only
1148-
variables read or written by the evaluated code. Note that
1149-
variables used by modules are always pruned, even if later used
1150-
by the modules. You can submit to the `:on_module` tracer event
1151-
and access the variables used by the module from its environment.
1198+
It accepts the same options as `env_for_eval/1`.
11521199
11531200
"""
11541201
@doc since: "1.14.0"
1155-
@spec eval_quoted_with_env(Macro.t(), binding, Macro.Env.t(), keyword) ::
1202+
@spec eval_quoted_with_env(Macro.t(), binding, Macro.Env.t(), env_eval_opts) ::
11561203
{term, binding, Macro.Env.t()}
11571204
def eval_quoted_with_env(quoted, binding, %Macro.Env{} = env, opts \\ [])
11581205
when is_list(binding) do
@@ -1263,7 +1310,7 @@ defmodule Code do
12631310
{:error, {[line: 1, column: 4], "syntax error before: ", "\"3\""}}
12641311
12651312
"""
1266-
@spec string_to_quoted(List.Chars.t(), keyword) ::
1313+
@spec string_to_quoted(List.Chars.t(), parser_opts) ::
12671314
{:ok, Macro.t()} | {:error, {location :: keyword, binary | {binary, binary}, binary}}
12681315
def string_to_quoted(string, opts \\ []) when is_list(opts) do
12691316
file = Keyword.get(opts, :file, "nofile")
@@ -1290,7 +1337,7 @@ defmodule Code do
12901337
12911338
Check `string_to_quoted/2` for options information.
12921339
"""
1293-
@spec string_to_quoted!(List.Chars.t(), keyword) :: Macro.t()
1340+
@spec string_to_quoted!(List.Chars.t(), parser_opts) :: Macro.t()
12941341
def string_to_quoted!(string, opts \\ []) when is_list(opts) do
12951342
file = Keyword.get(opts, :file, "nofile")
12961343
line = Keyword.get(opts, :line, 1)
@@ -1341,7 +1388,7 @@ defmodule Code do
13411388
13421389
"""
13431390
@doc since: "1.13.0"
1344-
@spec string_to_quoted_with_comments(List.Chars.t(), keyword) ::
1391+
@spec string_to_quoted_with_comments(List.Chars.t(), parser_opts) ::
13451392
{:ok, Macro.t(), list(map())} | {:error, {location :: keyword, term, term}}
13461393
def string_to_quoted_with_comments(string, opts \\ []) when is_list(opts) do
13471394
charlist = to_charlist(string)
@@ -1371,7 +1418,7 @@ defmodule Code do
13711418
Check `string_to_quoted/2` for options information.
13721419
"""
13731420
@doc since: "1.13.0"
1374-
@spec string_to_quoted_with_comments!(List.Chars.t(), keyword) :: {Macro.t(), list(map())}
1421+
@spec string_to_quoted_with_comments!(List.Chars.t(), parser_opts) :: {Macro.t(), list(map())}
13751422
def string_to_quoted_with_comments!(string, opts \\ []) do
13761423
charlist = to_charlist(string)
13771424

@@ -1456,6 +1503,9 @@ defmodule Code do
14561503
14571504
## Options
14581505
1506+
This function accepts all options supported by `format_string!/2` for controlling
1507+
code formatting, plus these additional options:
1508+
14591509
* `:comments` - the list of comments associated with the quoted expression.
14601510
Defaults to `[]`. It is recommended that both `:token_metadata` and
14611511
`:literal_encoder` options are given to `string_to_quoted_with_comments/2`
@@ -1466,17 +1516,14 @@ defmodule Code do
14661516
`string_to_quoted/2`, setting this option to `false` will prevent it from
14671517
escaping the sequences twice. Defaults to `true`.
14681518
1469-
* `:locals_without_parens` - a keyword list of name and arity
1470-
pairs that should be kept without parens whenever possible.
1471-
The arity may be the atom `:*`, which implies all arities of
1472-
that name. The formatter already includes a list of functions
1473-
and this option augments this list.
1474-
1475-
* `:syntax_colors` - a keyword list of colors the output is colorized.
1476-
See `Inspect.Opts` for more information.
1519+
See `format_string!/2` for the full list of formatting options including
1520+
`:file`, `:line`, `:line_length`, `:locals_without_parens`, `:force_do_end_blocks`,
1521+
`:syntax_colors`, and all migration options like `:migrate_charlists_as_sigils`.
14771522
"""
14781523
@doc since: "1.13.0"
1479-
@spec quoted_to_algebra(Macro.t(), keyword) :: Inspect.Algebra.t()
1524+
@spec quoted_to_algebra(Macro.t(), [
1525+
Code.Formatter.to_algebra_opt() | Code.Normalizer.normalize_opt()
1526+
]) :: Inspect.Algebra.t()
14801527
def quoted_to_algebra(quoted, opts \\ []) do
14811528
quoted
14821529
|> Code.Normalizer.normalize(opts)

0 commit comments

Comments
 (0)