@@ -83,7 +83,7 @@ defmodule IEx.Helpers do
8383 Shows the documentation for IEx.Helpers.
8484 """
8585 def h ( ) do
86- __help__ ( IEx.Helpers )
86+ IEx.Introspection . h ( IEx.Helpers )
8787 end
8888
8989 @ doc """
@@ -105,193 +105,34 @@ defmodule IEx.Helpers do
105105 """
106106 defmacro h ( { :/ , _ , [ { { :. , _ , [ mod , fun ] } , _ , [ ] } , arity ] } ) do
107107 quote do
108- IEx.Helpers . __help__ ( unquote ( mod ) , unquote ( fun ) , unquote ( arity ) )
108+ IEx.Introspection . h ( unquote ( mod ) , unquote ( fun ) , unquote ( arity ) )
109109 end
110110 end
111111
112112 defmacro h ( { { :. , _ , [ mod , fun ] } , _ , [ ] } ) do
113113 quote do
114- IEx.Helpers . __help__ ( unquote ( mod ) , unquote ( fun ) )
114+ IEx.Introspection . h ( unquote ( mod ) , unquote ( fun ) )
115115 end
116116 end
117117
118118 defmacro h ( { :/ , _ , [ { fun , _ , args } , arity ] } ) when args == [ ] or is_atom ( args ) do
119119 quote do
120- IEx.Helpers . __help__ ( unquote ( fun ) , unquote ( arity ) )
120+ IEx.Introspection . h ( unquote ( fun ) , unquote ( arity ) )
121121 end
122122 end
123123
124124 defmacro h ( { name , _ , args } ) when args == [ ] or is_atom ( args ) do
125125 quote do
126- IEx.Helpers . __help__ ( [ unquote ( __MODULE__ ) , Kernel , Kernel.SpecialForms ] , unquote ( name ) )
126+ IEx.Introspection . h ( [ unquote ( __MODULE__ ) , Kernel , Kernel.SpecialForms ] , unquote ( name ) )
127127 end
128128 end
129129
130130 defmacro h ( other ) do
131131 quote do
132- IEx.Helpers . __help__ ( unquote ( other ) )
132+ IEx.Introspection . h ( unquote ( other ) )
133133 end
134134 end
135135
136- # Handles documentation for modules
137- @ doc false
138- def __help__ ( module ) when is_atom ( module ) do
139- case Code . ensure_loaded ( module ) do
140- { :module , _ } ->
141- case module . __info__ ( :moduledoc ) do
142- { _ , binary } when is_binary ( binary ) ->
143- IO . puts IO.ANSI . escape ( "%{yellow}# #{ inspect module } \n " )
144- IO . write IO.ANSI . escape ( "%{yellow}#{ binary } " )
145- { _ , _ } ->
146- IO . puts IO.ANSI . escape ( "%{red}No docs for #{ inspect module } have been found" )
147- _ ->
148- IO . puts IO.ANSI . escape ( "%{red}#{ inspect module } was not compiled with docs" )
149- end
150- { :error , reason } ->
151- IO . puts IO.ANSI . escape ( "%{red}Could not load module #{ inspect module } : #{ reason } " )
152- end
153- end
154-
155- def __help__ ( _ ) do
156- IO . puts IO.ANSI . escape ( "%{red}Invalid arguments for h helper" )
157- end
158-
159- # Help for function+arity or module+function
160- @ doc false
161- def __help__ ( modules , function ) when is_list ( modules ) and is_atom ( function ) do
162- result =
163- Enum . reduce modules , :not_found , fn
164- module , :not_found -> help_mod_fun ( module , function )
165- _module , acc -> acc
166- end
167-
168- unless result == :ok , do:
169- IO . puts IO.ANSI . escape ( "%{red}No docs for #{ function } have been found" )
170-
171- :ok
172- end
173-
174- def __help__ ( module , function ) when is_atom ( module ) and is_atom ( function ) do
175- case help_mod_fun ( module , function ) do
176- :ok ->
177- :ok
178- :no_docs ->
179- IO . puts IO.ANSI . escape ( "%{red}#{ inspect module } was not compiled with docs" )
180- :not_found ->
181- IO . puts IO.ANSI . escape ( "%{red}No docs for #{ inspect module } .#{ function } have been found" )
182- end
183-
184- :ok
185- end
186-
187- def __help__ ( function , arity ) when is_atom ( function ) and is_integer ( arity ) do
188- __help__ ( [ __MODULE__ , Kernel , Kernel.SpecialForms ] , function , arity )
189- end
190-
191- def __help__ ( _ , _ ) do
192- IO . puts IO.ANSI . escape ( "%{red}Invalid arguments for h helper" )
193- end
194-
195- defp help_mod_fun ( mod , fun ) when is_atom ( mod ) and is_atom ( fun ) do
196- if docs = mod . __info__ ( :docs ) do
197- result = lc { { f , arity } , _line , _type , _args , doc } in list docs , fun == f , doc != false do
198- __help__ ( mod , fun , arity )
199- IO . puts ""
200- end
201-
202- if result != [ ] , do: :ok , else: :not_found
203- else
204- :no_docs
205- end
206- end
207-
208- # Help for module+function+arity
209- @ doc false
210- def __help__ ( modules , function , arity ) when is_list ( modules ) and is_atom ( function ) and is_integer ( arity ) do
211- result =
212- Enum . reduce modules , :not_found , fn
213- module , :not_found -> help_mod_fun_arity ( module , function , arity )
214- _module , acc -> acc
215- end
216-
217- unless result == :ok , do:
218- IO . puts IO.ANSI . escape ( "%{red}No docs for #{ function } /#{ arity } have been found" )
219-
220- :ok
221- end
222-
223- def __help__ ( module , function , arity ) when is_atom ( module ) and is_atom ( function ) and is_integer ( arity ) do
224- case help_mod_fun_arity ( module , function , arity ) do
225- :ok ->
226- :ok
227- :no_docs ->
228- IO . puts IO.ANSI . escape ( "%{red}#{ inspect module } was not compiled with docs" )
229- :not_found ->
230- IO . puts IO.ANSI . escape ( "%{red}No docs for #{ inspect module } .#{ function } /#{ arity } have been found" )
231- end
232-
233- :ok
234- end
235-
236- def __help__ ( _ , _ , _ ) do
237- IO . puts IO.ANSI . escape ( "%{red}Invalid arguments for h helper" )
238- end
239-
240- defp help_mod_fun_arity ( mod , fun , arity ) when is_atom ( mod ) and is_atom ( fun ) and is_integer ( arity ) do
241- if docs = mod . __info__ ( :docs ) do
242- doc =
243- cond do
244- d = find_doc ( docs , fun , arity ) -> d
245- d = find_default_doc ( docs , fun , arity ) -> d
246- true -> nil
247- end
248-
249- if doc do
250- print_doc ( doc )
251- :ok
252- else
253- :not_found
254- end
255- else
256- :no_docs
257- end
258- end
259-
260- defp find_doc ( docs , function , arity ) do
261- if doc = List . keyfind ( docs , { function , arity } , 0 ) do
262- case elem ( doc , 4 ) do
263- false -> nil
264- _ -> doc
265- end
266- end
267- end
268-
269- defp find_default_doc ( docs , function , min ) do
270- Enum . find docs , fn ( doc ) ->
271- case elem ( doc , 0 ) do
272- { ^ function , max } when max > min ->
273- defaults = Enum . count elem ( doc , 3 ) , match? ( { :// , _ , _ } , & 1 )
274- min + defaults >= max
275- _ ->
276- false
277- end
278- end
279- end
280-
281- defp print_doc ( { { fun , _ } , _line , kind , args , doc } ) do
282- args = Enum . map_join ( args , ", " , print_doc_arg ( & 1 ) )
283- IO . puts IO.ANSI . escape ( "%{yellow}* #{ kind } #{ fun } (#{ args } )\n " )
284- IO . write IO.ANSI . escape ( "%{yellow}#{ doc } " )
285- end
286-
287- defp print_doc_arg ( { :// , _ , [ left , right ] } ) do
288- print_doc_arg ( left ) <> " // " <> Macro . to_binary ( right )
289- end
290-
291- defp print_doc_arg ( { var , _ , _ } ) do
292- atom_to_binary ( var )
293- end
294-
295136 @ doc """
296137 Prints all types for the given module or prints out a specified type's
297138 specification
@@ -305,61 +146,20 @@ defmodule IEx.Helpers do
305146 """
306147 defmacro t ( { :/ , _ , [ { { :. , _ , [ mod , fun ] } , _ , [ ] } , arity ] } ) do
307148 quote do
308- IEx.Helpers . __type__ ( unquote ( mod ) , unquote ( fun ) , unquote ( arity ) )
149+ IEx.Introspection . t ( unquote ( mod ) , unquote ( fun ) , unquote ( arity ) )
309150 end
310151 end
311152
312153 defmacro t ( { { :. , _ , [ mod , fun ] } , _ , [ ] } ) do
313154 quote do
314- IEx.Helpers . __type__ ( unquote ( mod ) , unquote ( fun ) )
155+ IEx.Introspection . t ( unquote ( mod ) , unquote ( fun ) )
315156 end
316157 end
317158
318159 defmacro t ( module ) do
319160 quote do
320- IEx.Helpers . __type__ ( unquote ( module ) )
321- end
322- end
323-
324- @ doc false
325- def __type__ ( module ) do
326- types = lc type inlist Kernel.Typespec . beam_types ( module ) , do: print_type ( type )
327-
328- if types == [ ] do
329- IO . puts IO.ANSI . escape ( "%{red}No types for #{ inspect module } have been found" )
330- end
331-
332- :ok
333- end
334-
335- @ doc false
336- def __type__ ( module , type ) when is_atom ( type ) do
337- types = lc { _ , { t , _ , _args } } = typespec inlist Kernel.Typespec . beam_types ( module ) ,
338- t == type do
339- print_type ( typespec )
340- typespec
341- end
342-
343- if types == [ ] do
344- IO . puts IO.ANSI . escape ( "%{red}No types for #{ inspect module } .#{ type } have been found" )
345- end
346-
347- :ok
348- end
349-
350- @ doc false
351- def __type__ ( module , type , arity ) do
352- types = lc { _ , { t , _ , args } } = typespec inlist Kernel.Typespec . beam_types ( module ) ,
353- length ( args ) == arity and t == type , do: typespec
354-
355- case types do
356- [ ] ->
357- IO . puts IO.ANSI . escape ( "%{red}No types for #{ inspect module } .#{ type } /#{ arity } have been found" )
358- [ type ] ->
359- print_type ( type )
161+ IEx.Introspection . t ( unquote ( module ) )
360162 end
361-
362- :ok
363163 end
364164
365165 @ doc """
@@ -376,93 +176,32 @@ defmodule IEx.Helpers do
376176 """
377177 defmacro s ( { :/ , _ , [ { { :. , _ , [ mod , fun ] } , _ , [ ] } , arity ] } ) do
378178 quote do
379- IEx.Helpers . __spec__ ( unquote ( mod ) , unquote ( fun ) , unquote ( arity ) )
179+ IEx.Introspection . s ( unquote ( mod ) , unquote ( fun ) , unquote ( arity ) )
380180 end
381181 end
382182
383183 defmacro s ( { { :. , _ , [ mod , fun ] } , _ , [ ] } ) do
384184 quote do
385- IEx.Helpers . __spec__ ( unquote ( mod ) , unquote ( fun ) )
185+ IEx.Introspection . s ( unquote ( mod ) , unquote ( fun ) )
386186 end
387187 end
388188
389189 defmacro s ( { fun , _ , args } ) when args == [ ] or is_atom ( args ) do
390190 quote do
391- IEx.Helpers . __spec__ ( Kernel , unquote ( fun ) )
191+ IEx.Introspection . s ( Kernel , unquote ( fun ) )
392192 end
393193 end
394194
395195 defmacro s ( { :/ , _ , [ { fun , _ , args } , arity ] } ) when args == [ ] or is_atom ( args ) do
396196 quote do
397- IEx.Helpers . __spec__ ( Kernel , unquote ( fun ) , unquote ( arity ) )
197+ IEx.Introspection . s ( Kernel , unquote ( fun ) , unquote ( arity ) )
398198 end
399199 end
400200
401201 defmacro s ( module ) do
402202 quote do
403- IEx.Helpers . __spec__ ( unquote ( module ) )
404- end
405- end
406-
407- @ doc false
408- def __spec__ ( module ) do
409- specs = lc spec inlist beam_specs ( module ) , do: print_spec ( spec )
410-
411- if specs == [ ] do
412- IO . puts IO.ANSI . escape ( "%{red}No specs for #{ inspect module } have been found" )
413- end
414-
415- :ok
416- end
417-
418- @ doc false
419- def __spec__ ( module , function ) when is_atom ( function ) do
420- specs = lc { _kind , { { f , _arity } , _spec } } = spec inlist beam_specs ( module ) ,
421- f == function do
422- print_spec ( spec )
423- spec
424- end
425-
426- if specs == [ ] do
427- IO . puts IO.ANSI . escape ( "%{red}No specs for #{ inspect module } .#{ function } have been found" )
428- end
429-
430- :ok
431- end
432-
433- @ doc false
434- def __spec__ ( module , function , arity ) do
435- specs = lc { _kind , { { f , a } , _spec } } = spec inlist beam_specs ( module ) ,
436- f == function and a == arity do
437- print_spec ( spec )
438- spec
439- end
440-
441- if specs == [ ] do
442- IO . puts IO.ANSI . escape ( "%{red}No specs for #{ inspect module } .#{ function } have been found" )
443- end
444-
445- :ok
446- end
447-
448- defp beam_specs ( module ) do
449- specs = Enum . map ( Kernel.Typespec . beam_specs ( module ) , { :spec , & 1 } )
450- callbacks = Enum . map ( Kernel.Typespec . beam_callbacks ( module ) , { :callback , & 1 } )
451- List . concat ( specs , callbacks )
452- end
453-
454- defp print_type ( { kind , type } ) do
455- ast = Kernel.Typespec . type_to_ast ( type )
456- IO . puts IO.ANSI . escape ( "%{yellow}@#{ kind } #{ Macro . to_binary ( ast ) } " )
457- true
458- end
459-
460- defp print_spec ( { kind , { { name , _arity } , specs } } ) do
461- Enum . each specs , fn ( spec ) ->
462- binary = Macro . to_binary Kernel.Typespec . spec_to_ast ( name , spec )
463- IO . puts IO.ANSI . escape ( "%{yellow}@#{ kind } #{ binary } " )
203+ IEx.Introspection . s ( unquote ( module ) )
464204 end
465- true
466205 end
467206
468207 @ doc """
0 commit comments