@@ -5,7 +5,7 @@ defmodule Module.ParallelChecker do
55
66 @ type cache ( ) :: { pid ( ) , :ets . tid ( ) }
77 @ type warning ( ) :: term ( )
8- @ type mode ( ) :: :elixir | :erlang
8+ @ type mode ( ) :: :erlang | : elixir | :protocol
99
1010 @ doc """
1111 Initializes the parallel checker process.
@@ -51,7 +51,7 @@ defmodule Module.ParallelChecker do
5151 # Protocols may have been consolidated. So if we know their beam location,
5252 # we discard their module map on purpose and start from file.
5353 info =
54- if beam_location != [ ] and List . keymember ?( module_map . attributes , :__protocol__ , 0 ) do
54+ if beam_location != [ ] and Keyword . has_key ?( module_map . attributes , :__protocol__ ) do
5555 List . to_string ( beam_location )
5656 else
5757 cache_from_module_map ( table , module_map )
@@ -204,20 +204,28 @@ defmodule Module.ParallelChecker do
204204
205205 @ doc """
206206 Returns the export kind and deprecation reason for the given MFA from
207- the cache. If the module does not exist return `{:error, :module} `,
208- or if the function does not exist return `{:error, :function }`.
207+ the cache. If the module does not exist return `:badmodule `,
208+ or if the function does not exist return `{:badfunction, mode }`.
209209 """
210- @ spec fetch_export ( cache ( ) , module ( ) , atom ( ) , arity ( ) ) ::
210+ @ spec fetch_export ( cache ( ) , module ( ) , atom ( ) , arity ( ) , boolean ( ) ) ::
211211 { :ok , mode ( ) , binary ( ) | nil , { :infer , [ term ( ) ] | nil , [ term ( ) ] } | :none }
212212 | :badmodule
213213 | { :badfunction , mode ( ) }
214- def fetch_export ( { checker , table } , module , fun , arity ) do
214+ def fetch_export ( { checker , table } , module , fun , arity , force? ) do
215215 case :ets . lookup ( table , module ) do
216216 [ ] ->
217+ if force? do
218+ cache_module ( { checker , table } , module )
219+ fetch_export ( { checker , table } , module , fun , arity , false )
220+ else
221+ :badmodule
222+ end
223+
224+ [ { _key , :uncached } ] ->
217225 cache_module ( { checker , table } , module )
218- fetch_export ( { checker , table } , module , fun , arity )
226+ fetch_export ( { checker , table } , module , fun , arity , false )
219227
220- [ { _key , false } ] ->
228+ [ { _key , :not_found } ] ->
221229 :badmodule
222230
223231 [ { _key , mode } ] ->
@@ -389,40 +397,47 @@ defmodule Module.ParallelChecker do
389397 if lock ( checker , module ) do
390398 object_code = :code . get_object_code ( module )
391399
392- # The chunk has more information, so that's our preference
393- with { ^ module , binary , _filename } <- object_code ,
394- { :ok , { ^ module , [ { ~c" ExCk" , chunk } ] } } <- :beam_lib . chunks ( binary , [ ~c" ExCk" ] ) ,
395- { :elixir_checker_v1 , contents } <- :erlang . binary_to_term ( chunk ) do
396- cache_chunk ( table , module , contents . exports )
397- else
398- _ ->
399- # Otherwise, if the module is loaded, use its info
400- case :erlang . module_loaded ( module ) do
401- true ->
402- { mode , exports } = info_exports ( module )
403- deprecated = info_deprecated ( module )
404- cache_info ( table , module , exports , deprecated , % { } , mode )
405-
406- false ->
407- # Or load exports from chunk
408- with { ^ module , binary , _filename } <- object_code ,
409- { :ok , { ^ module , [ exports: exports ] } } <- :beam_lib . chunks ( binary , [ :exports ] ) do
410- cache_info ( table , module , exports , % { } , % { } , :erlang )
411- else
412- _ ->
413- :ets . insert ( table , { module , false } )
414- end
415- end
416- end
400+ mode =
401+ with { ^ module , binary , _filename } <- object_code ,
402+ { :ok , { ^ module , [ { ~c" ExCk" , chunk } ] } } <- :beam_lib . chunks ( binary , [ ~c" ExCk" ] ) ,
403+ { :elixir_checker_v1 , contents } <- :erlang . binary_to_term ( chunk ) do
404+ # The chunk has more information, so that's our preference
405+ cache_chunk ( table , module , contents )
406+ else
407+ _ ->
408+ # Otherwise, if the module is loaded, use its info
409+ case :erlang . module_loaded ( module ) do
410+ true ->
411+ { mode , exports } = info_exports ( module )
412+ deprecated = info_deprecated ( module )
413+ cache_info ( table , module , exports , deprecated , % { } , mode )
414+
415+ false ->
416+ # Or load exports from chunk
417+ with { ^ module , binary , _filename } <- object_code ,
418+ { :ok , { ^ module , [ exports: exports ] } } <- :beam_lib . chunks ( binary , [ :exports ] ) do
419+ cache_info ( table , module , exports , % { } , % { } , :erlang )
420+ else
421+ _ ->
422+ :ets . insert ( table , { module , :not_found } )
423+ nil
424+ end
425+ end
426+ end
417427
418- unlock ( checker , module )
428+ unlock ( checker , module , mode )
419429 end
420430 end
421431
422432 defp info_exports ( module ) do
423- { :elixir , behaviour_exports ( module ) ++ module . __info__ ( :functions ) }
424- rescue
425- _ -> { :erlang , module . module_info ( :exports ) }
433+ try do
434+ module . __info__ ( :functions )
435+ rescue
436+ _ -> { :erlang , module . module_info ( :exports ) }
437+ else
438+ functions ->
439+ { elixir_mode ( module . module_info ( :attributes ) ) , behaviour_exports ( module ) ++ functions }
440+ end
426441 end
427442
428443 defp info_deprecated ( module ) do
@@ -431,12 +446,24 @@ defmodule Module.ParallelChecker do
431446 _ -> % { }
432447 end
433448
449+ defp elixir_mode ( attributes ) do
450+ if Keyword . has_key? ( attributes , :__protocol__ ) , do: :protocol , else: :elixir
451+ end
452+
434453 defp cache_from_module_map ( table , map ) do
435454 exports =
436455 behaviour_exports ( map ) ++
437456 for ( { function , :def , _meta , _clauses } <- map . definitions , do: function )
438457
439- cache_info ( table , map . module , exports , Map . new ( map . deprecated ) , map . signatures , :elixir )
458+ cache_info (
459+ table ,
460+ map . module ,
461+ exports ,
462+ Map . new ( map . deprecated ) ,
463+ map . signatures ,
464+ elixir_mode ( map . attributes )
465+ )
466+
440467 module_map_to_module_tuple ( map )
441468 end
442469
@@ -447,10 +474,11 @@ defmodule Module.ParallelChecker do
447474 end )
448475
449476 :ets . insert ( table , { module , mode } )
477+ mode
450478 end
451479
452- defp cache_chunk ( table , module , exports ) do
453- Enum . each ( exports , fn { { fun , arity } , info } ->
480+ defp cache_chunk ( table , module , contents ) do
481+ Enum . each ( contents . exports , fn { { fun , arity } , info } ->
454482 sig =
455483 case info do
456484 % { sig: { key , _ , _ } = sig } when key in [ :infer , :strong ] -> sig
@@ -463,7 +491,9 @@ defmodule Module.ParallelChecker do
463491 )
464492 end )
465493
466- :ets . insert ( table , { module , :elixir } )
494+ mode = Map . get ( contents , :mode , :elixir )
495+ :ets . insert ( table , { module , mode } )
496+ mode
467497 end
468498
469499 defp behaviour_exports ( % { defines_behaviour: true } ) , do: [ { :behaviour_info , 1 } ]
@@ -481,8 +511,8 @@ defmodule Module.ParallelChecker do
481511 :gen_server . call ( server , { :lock , module } , :infinity )
482512 end
483513
484- defp unlock ( server , module ) do
485- :gen_server . call ( server , { :unlock , module } , :infinity )
514+ defp unlock ( server , module , mode ) do
515+ :gen_server . call ( server , { :unlock , module , mode } , :infinity )
486516 end
487517
488518 defp register ( server , pid , ref ) do
@@ -495,17 +525,42 @@ defmodule Module.ParallelChecker do
495525 table = :ets . new ( __MODULE__ , [ :set , :public , { :read_concurrency , true } ] )
496526 :proc_lib . init_ack ( { :ok , { self ( ) , table } } )
497527
528+ case :elixir_config . get ( :infer_signatures ) do
529+ false ->
530+ false
531+
532+ applications ->
533+ for application <- applications do
534+ case :application . get_key ( application , :modules ) do
535+ { :ok , modules } ->
536+ :ets . insert ( table , Enum . map ( modules , & { & 1 , :uncached } ) )
537+
538+ :undefined ->
539+ IO . warn (
540+ "cannot infer signatures from #{ inspect ( application ) } because it is not loaded" ,
541+ [ ]
542+ )
543+ end
544+ end
545+ end
546+
498547 state = % {
499548 waiting: % { } ,
500549 modules: [ ] ,
501550 spawned: 0 ,
502- schedulers: schedulers || max ( :erlang . system_info ( :schedulers_online ) , 2 )
551+ schedulers: schedulers || max ( :erlang . system_info ( :schedulers_online ) , 2 ) ,
552+ protocols: [ ] ,
553+ table: table
503554 }
504555
505556 :gen_server . enter_loop ( __MODULE__ , [ ] , state )
506557 end
507558
508- def handle_call ( :start , _from , % { modules: modules } = state ) do
559+ def handle_call ( :start , _from , % { modules: modules , protocols: protocols , table: table } = state ) do
560+ for protocol <- protocols do
561+ :ets . delete ( table , protocol )
562+ end
563+
509564 for { pid , ref } <- modules do
510565 send ( pid , { ref , :cache } )
511566 end
@@ -516,7 +571,7 @@ defmodule Module.ParallelChecker do
516571 end
517572 end
518573
519- { :reply , length ( modules ) , run_checkers ( state ) }
574+ { :reply , length ( modules ) , run_checkers ( % { state | protocols: [ ] } ) }
520575 end
521576
522577 def handle_call ( { :lock , module } , from , % { waiting: waiting } = state ) do
@@ -531,11 +586,14 @@ defmodule Module.ParallelChecker do
531586 end
532587 end
533588
534- def handle_call ( { :unlock , module } , _from , % { waiting: waiting } = state ) do
589+ def handle_call ( { :unlock , module , mode } , _from , state ) do
590+ % { waiting: waiting , protocols: protocols } = state
535591 from_list = Map . fetch! ( waiting , module )
536592 Enum . each ( from_list , & :gen_server . reply ( & 1 , false ) )
593+
537594 waiting = Map . delete ( waiting , module )
538- { :reply , :ok , % { state | waiting: waiting } }
595+ protocols = if mode == :protocol , do: [ module | protocols ] , else: protocols
596+ { :reply , :ok , % { state | waiting: waiting , protocols: protocols } }
539597 end
540598
541599 def handle_info ( { __MODULE__ , :done } , state ) do
0 commit comments