@@ -15,7 +15,7 @@ defmodule Code do
1515 """
1616
1717 @ doc """
18- Returns all the loaded files.
18+ Returns all loaded files.
1919 """
2020 def loaded_files do
2121 :elixir_code_server . call :loaded
@@ -32,32 +32,32 @@ defmodule Code do
3232 end
3333
3434 @ doc """
35- Appends a path to Erlang VM code path.
36- The path is expanded with `Path.expand` before being appended.
35+ Appends a path to the Erlang VM code path.
36+ The path is expanded with `Path.expand/1 ` before being appended.
3737 """
3838 def append_path ( path ) do
3939 :code . add_pathz ( Path . expand to_char_list ( path ) )
4040 end
4141
4242 @ doc """
43- Prepends a path to Erlang VM code path.
44- The path is expanded with `Path.expand` before being prepended.
43+ Prepends a path to the Erlang VM code path.
44+ The path is expanded with `Path.expand/1 ` before being prepended.
4545 """
4646 def prepend_path ( path ) do
4747 :code . add_patha ( Path . expand to_char_list ( path ) )
4848 end
4949
5050 @ doc """
51- Deletes a path from Erlang VM code path.
52- The path is expanded with `Path.expand` before being deleted.
51+ Deletes a path from the Erlang VM code path.
52+ The path is expanded with `Path.expand/1 ` before being deleted.
5353 """
5454 def delete_path ( path ) do
5555 :code . del_path ( Path . expand to_char_list ( path ) )
5656 end
5757
5858 @ doc """
59- Evaluates the contents given by string. The second argument is the
60- binding (which should be a keyword) , followed by a keyword list of
59+ Evaluates the contents given by ` string` . The second argument is
60+ a keyword list of variable bindings , followed by a keyword list of
6161 environment options. Those options can be:
6262
6363 * `:file` - the file to be considered in the evaluation
@@ -71,28 +71,39 @@ defmodule Code do
7171 * `:requires` - a list of modules required
7272 * `:functions` - a list of tuples where the first element is a module
7373 and the second a list of imported function names and arity. The list
74- of function names and arity must be sorted;
74+ of function names and arity must be sorted
7575 * `:macros` - a list of tuples where the first element is a module
7676 and the second a list of imported macro names and arity. The list
77- of function names and arity must be sorted;
77+ of function names and arity must be sorted
7878
79- Notice that setting any of the values above overrides Elixir default
79+ Notice that setting any of the values above overrides Elixir's default
8080 values. For example, setting `:requires` to `[]`, will no longer
8181 automatically require the `Kernel` module; in the same way setting
8282 `:macros` will no longer auto-import `Kernel` macros like `if`, `case`,
8383 etc.
8484
85+ Returns a tuple of the form `{ value, binding }`,
86+ where `value` is the the value returned from evaluating `string`; `binding`
87+ is a keyword list with the value of all variable bindings after evaluating
88+ `string`. If an error occurs while evaluating `string` an exception will be raised.
89+
8590 ## Examples
8691
8792 iex> Code.eval_string("a + b", [a: 1, b: 2], file: __ENV__.file, line: __ENV__.line)
88- { 3, [ {:a, 1}, {:b, 2} ] }
93+ {3, [a: 1, b: 2]}
94+
95+ iex> Code.eval_string("c = a + b", [a: 1, b: 2], __ENV__)
96+ {3, [a: 1, b: 2, c: 3]}
97+
98+ iex> Code.eval_string("a = a + b", [a: 1, b: 2])
99+ {3, [a: 3, b: 2]}
89100
90- For convenience, you can pass `__ENV__` as an argument and
91- all imports, requires and aliases will be automatically carried
92- over:
101+ For convenience, you can pass `__ENV__` as the `opts` argument and
102+ all imports, requires and aliases defined in the current environment
103+ will be automatically carried over:
93104
94105 iex> Code.eval_string("a + b", [a: 1, b: 2], __ENV__)
95- { 3, [ {:a, 1}, {:b, 2} ] }
106+ {3, [a: 1, b: 2] }
96107
97108 """
98109 def eval_string ( string , binding // [ ] , opts // [ ] )
@@ -115,21 +126,20 @@ defmodule Code do
115126 @ doc """
116127 Evaluates the quoted contents.
117128
118- This function accepts a list of environment options.
119- Check `Code.eval_string` for more information.
129+ See `eval_string/3` for a description of arguments and return values.
120130
121131 ## Examples
122132
123133 iex> contents = quote(hygiene: [vars: false], do: a + b)
124134 ...> Code.eval_quoted(contents, [a: 1, b: 2], file: __ENV__.file, line: __ENV__.line)
125- { 3, [ {:a, 1}, {:b, 2} ] }
135+ {3, [a: 1, b: 2] }
126136
127- For convenience, you can pass `__ENV__` as an argument and
128- all options will be automatically extracted from the environment:
137+ For convenience, you can pass `__ENV__` as the `opts` argument and
138+ all options will be automatically extracted from the current environment:
129139
130140 iex> contents = quote(hygiene: [vars: false], do: a + b)
131141 ...> Code.eval_quoted(contents, [a: 1, b: 2], __ENV__)
132- { 3, [ {:a, 1}, {:b, 2} ] }
142+ {3, [a: 1, b: 2] }
133143
134144 """
135145 def eval_quoted ( quoted , binding // [ ] , opts // [ ] )
@@ -193,17 +203,17 @@ defmodule Code do
193203 ## Options
194204
195205 * `:file` - The filename to be used in stacktraces
196- and the file reported in the __ENV__ variable.
206+ and the file reported in the ` __ENV__` variable.
197207
198- * `:line` - The line reported in the __ENV__ variable.
208+ * `:line` - The line reported in the ` __ENV__` variable.
199209
200- * `:existing_atoms_only` - When true, raises an error
210+ * `:existing_atoms_only` - When ` true` , raises an error
201211 when non-existing atoms are found by the tokenizer.
202212
203213 ## Macro.to_string/1
204214
205215 The opposite of converting a string to its quoted form is
206- `Macro.to_string`, which converts a quoted form to a string/binary
216+ `Macro.to_string/1 `, which converts a quoted form to a string/binary
207217 representation.
208218 """
209219 def string_to_quoted ( string , opts // [ ] ) do
@@ -219,11 +229,11 @@ defmodule Code do
219229
220230 @ doc """
221231 Converts the given string to its quoted form. It returns the ast if it succeeds,
222- raises an exception otherwise. The exception is a TokenMissingError
232+ raises an exception otherwise. The exception is a ` TokenMissingError`
223233 in case a token is missing (usually because the expression is incomplete),
224- SyntaxError otherwise.
234+ ` SyntaxError` otherwise.
225235
226- Check `Code. string_to_quoted/2` for options information.
236+ Check `string_to_quoted/2` for options information.
227237 """
228238 def string_to_quoted! ( string , opts // [ ] ) do
229239 file = Keyword . get opts , :file , "nofile"
@@ -239,14 +249,14 @@ defmodule Code do
239249 @ doc """
240250 Loads the given `file`. Accepts `relative_to` as an argument to tell where
241251 the file is located. If the file was already required/loaded, loads it again.
242- It returns a list of tuples { ModuleName, <<byte_code>> }, one tuple for each
252+ It returns a list of tuples ` { ModuleName, <<byte_code>> }` , one tuple for each
243253 module defined in the file.
244254
245255 Notice that if `load_file` is invoked by different processes
246256 concurrently, the target file will be invoked concurrently
247257 many times. I.e. if `load_file` is called N times with
248258 a given file, the given file will be loaded N times. Check
249- `require_file` if you don't want a file to be loaded concurrently.
259+ `require_file/2 ` if you don't want a file to be loaded concurrently.
250260 """
251261 def load_file ( file , relative_to // nil ) when is_binary ( file ) do
252262 file = find_file ( file , relative_to )
@@ -258,16 +268,16 @@ defmodule Code do
258268
259269 @ doc """
260270 Requires the given `file`. Accepts `relative_to` as an argument to tell where
261- the file is located. The return value is the same as that of `load_file`. If
271+ the file is located. The return value is the same as that of `load_file/2 `. If
262272 the file was already required/loaded, doesn't do anything and returns nil.
263273
264274 Notice that if `require_file` is invoked by different processes concurrently,
265275 the first process to invoke `require_file` acquires a lock and the remaining
266276 ones will block until the file is available. I.e. if `require_file` is called
267277 N times with a given file, it will be loaded only once. The first process to
268- call `require_file` will get the list of loaded modules, others will get nil.
278+ call `require_file` will get the list of loaded modules, others will get ` nil` .
269279
270- Check `load_file` if you want a file to be loaded concurrently.
280+ Check `load_file/2 ` if you want a file to be loaded concurrently.
271281 """
272282 def require_file ( file , relative_to // nil ) when is_binary ( file ) do
273283 file = find_file ( file , relative_to )
@@ -298,17 +308,17 @@ defmodule Code do
298308
299309 Available options are:
300310
301- * `:docs` - when true, retain documentation in the compiled module,
302- true by default;
311+ * `:docs` - when ` true` , retain documentation in the compiled module,
312+ ` true` by default;
303313
304- * `:debug_info` - when true, retain debug information in the compiled module.
314+ * `:debug_info` - when ` true` , retain debug information in the compiled module.
305315 This allows a developer to reconstruct the original source
306- code, for such reasons, false by default;
316+ code, for such reasons, ` false` by default;
307317
308- * `:ignore_module_conflict` - when true, override modules that were already defined
309- without raising errors, false by default;
318+ * `:ignore_module_conflict` - when ` true` , override modules that were already defined
319+ without raising errors, ` false` by default;
310320
311- * `:warnings_as_errors` - cause compilation to fail when warnings are spewed ;
321+ * `:warnings_as_errors` - cause compilation to fail when warnings are generated ;
312322
313323 """
314324 def compiler_options ( opts ) do
@@ -337,7 +347,7 @@ defmodule Code do
337347
338348 @ doc """
339349 Ensures the given module is loaded. If the module is already
340- loaded, it works as no-op. If the module was not loaded yet,
350+ loaded, it works as no-op. If the module was not yet loaded ,
341351 it tries to load it.
342352
343353 If it succeeds loading the module, it returns
@@ -352,9 +362,9 @@ defmodule Code do
352362 are loaded as needed. In embedded mode the opposite happens, as all
353363 modules need to be loaded upfront or explicitly.
354364
355- Therefore, this function is useful to check if a module is loaded
356- before using it and react accordingly. For example, the `URI` module
357- uses this function to check if a specific parser exists for a given
365+ Therefore, this function is used to check if a module is loaded
366+ before using it and allows one to react accordingly. For example, the `URI`
367+ module uses this function to check if a specific parser exists for a given
358368 URI scheme.
359369
360370 ## Code.ensure_compiled
@@ -363,15 +373,15 @@ defmodule Code do
363373 superset of `ensure_loaded/1`.
364374
365375 Since Elixir's compilation happens in parallel, in some situations
366- you may need to use a module but it was not compiled yet, therefore
376+ you may need to use a module but that was not yet compiled , therefore
367377 it can't even be loaded.
368378
369- `ensure_compiled/1` puts a halt in the current process until the
379+ `ensure_compiled/1` halts the current process until the
370380 module we are depending on is available.
371381
372- In most of the cases, `ensure_loaded` is enough. `ensure_compiled`
373- must be used just in same rare conditions , usually involving macros
374- that needs to invoke a module for callback information.
382+ In most cases, `ensure_loaded` is enough. `ensure_compiled`
383+ must be used in some rare cases , usually involving macros
384+ that need to invoke a module for callback information.
375385 """
376386 def ensure_loaded ( module ) when is_atom ( module ) do
377387 :code . ensure_loaded ( module )
@@ -388,7 +398,7 @@ defmodule Code do
388398 @ doc """
389399 Ensures the given module is compiled and loaded. If the module
390400 is already loaded, it works as no-op. If the module was not
391- loaded yet, it checks if it needs to be compiled first and just
401+ loaded yet, it checks if it needs to be compiled first and
392402 then tries to load it.
393403
394404 If it succeeds loading the module, it returns
0 commit comments