@@ -12,7 +12,8 @@ defmodule Kernel.CLI do
1212 errors: [ ] ,
1313 verbose_compile: false ,
1414 profile: nil ,
15- pry: false
15+ pry: false ,
16+ mode: :elixir
1617 }
1718
1819 @ standalone_opts [ ~c" -h" , ~c" --help" , ~c" --short-version" ]
@@ -76,7 +77,16 @@ defmodule Kernel.CLI do
7677 Process CLI commands. Made public for testing.
7778 """
7879 def process_commands ( config ) do
79- results = Enum . map ( Enum . reverse ( config . commands ) , & process_command ( & 1 , config ) )
80+ commands =
81+ case config do
82+ % { mode: :elixirc , compile: compile , commands: commands } ->
83+ [ { :compile , compile } | commands ]
84+
85+ % { commands: commands } ->
86+ commands
87+ end
88+
89+ results = Enum . map ( Enum . reverse ( commands ) , & process_command ( & 1 , config ) )
8090 errors = for { :error , msg } <- results , do: msg
8191 Enum . reverse ( config . errors , errors )
8292 end
@@ -162,17 +172,6 @@ defmodule Kernel.CLI do
162172 defp to_exit ( :error , reason , stack ) , do: { reason , stack }
163173 defp to_exit ( :exit , reason , _stack ) , do: reason
164174
165- defp shared_option? ( list , config , callback ) do
166- case parse_shared ( list , config ) do
167- { [ h | hs ] , _ } when h == hd ( list ) ->
168- new_config = % { config | errors: [ "#{ h } : Unknown option" | config . errors ] }
169- callback . ( hs , new_config )
170-
171- { new_list , new_config } ->
172- callback . ( new_list , new_config )
173- end
174- end
175-
176175 ## Error handling
177176
178177 defp print_error ( kind , reason , stacktrace ) do
@@ -217,19 +216,30 @@ defmodule Kernel.CLI do
217216 [ ]
218217 end
219218
220- # Parse shared options
219+ # Process init options
221220
222- defp halt_standalone ( opt ) do
223- IO . puts ( :stderr , "#{ opt } : Standalone options can't be combined with other options" )
224- System . halt ( 1 )
221+ defp parse_argv ( [ ~c" --" | t ] , config ) do
222+ { config , t }
225223 end
226224
227- defp parse_shared ( [ opt | _ ] , _config ) when opt in @ standalone_opts do
225+ defp parse_argv ( [ ~c" +elixirc" | t ] , config ) do
226+ parse_argv ( t , % { config | mode: :elixirc } )
227+ end
228+
229+ defp parse_argv ( [ ~c" +iex" | t ] , config ) do
230+ parse_argv ( t , % { config | mode: :iex } )
231+ end
232+
233+ defp parse_argv ( [ ~c" -S" , h | t ] , config ) do
234+ { % { config | commands: [ { :script , h } | config . commands ] } , t }
235+ end
236+
237+ defp parse_argv ( [ opt | _ ] , _config ) when opt in @ standalone_opts do
228238 halt_standalone ( opt )
229239 end
230240
231- defp parse_shared ( [ opt | t ] , _config ) when opt in [ ~c" -v" , ~c" --version" ] do
232- if function_exported? ( IEx , :started? , 0 ) and IEx . started? ( ) do
241+ defp parse_argv ( [ opt | t ] , config ) when opt in [ ~c" -v" , ~c" --version" ] do
242+ if config . mode == :iex do
233243 IO . puts ( "IEx " <> System . build_info ( ) [ :build ] )
234244 else
235245 IO . puts ( :erlang . system_info ( :system_version ) )
@@ -243,193 +253,142 @@ defmodule Kernel.CLI do
243253 end
244254 end
245255
246- defp parse_shared ( [ ~c" -pa" , h | t ] , config ) do
256+ defp parse_argv ( [ ~c" -pa" , h | t ] , config ) do
247257 paths = expand_code_path ( h )
248258 Code . prepend_paths ( paths )
249- parse_shared ( t , config )
259+ parse_argv ( t , config )
250260 end
251261
252- defp parse_shared ( [ ~c" -pz" , h | t ] , config ) do
262+ defp parse_argv ( [ ~c" -pz" , h | t ] , config ) do
253263 paths = expand_code_path ( h )
254264 Code . append_paths ( paths )
255- parse_shared ( t , config )
265+ parse_argv ( t , config )
256266 end
257267
258- defp parse_shared ( [ ~c" --no-halt" | t ] , config ) do
259- parse_shared ( t , % { config | no_halt: true } )
268+ defp parse_argv ( [ ~c" --no-halt" | t ] , config ) do
269+ parse_argv ( t , % { config | no_halt: true } )
260270 end
261271
262- defp parse_shared ( [ ~c" -e" , h | t ] , config ) do
263- parse_shared ( t , % { config | commands: [ { :eval , h } | config . commands ] } )
272+ defp parse_argv ( [ ~c" -e" , h | t ] , config ) do
273+ parse_argv ( t , % { config | commands: [ { :eval , h } | config . commands ] } )
264274 end
265275
266- defp parse_shared ( [ ~c" --eval" , h | t ] , config ) do
267- parse_shared ( t , % { config | commands: [ { :eval , h } | config . commands ] } )
276+ defp parse_argv ( [ ~c" --eval" , h | t ] , config ) do
277+ parse_argv ( t , % { config | commands: [ { :eval , h } | config . commands ] } )
268278 end
269279
270- defp parse_shared ( [ ~c" --rpc-eval" , node , h | t ] , config ) do
280+ defp parse_argv ( [ ~c" --rpc-eval" , node , h | t ] , config ) do
271281 node = append_hostname ( node )
272- parse_shared ( t , % { config | commands: [ { :rpc_eval , node , h } | config . commands ] } )
282+ parse_argv ( t , % { config | commands: [ { :rpc_eval , node , h } | config . commands ] } )
273283 end
274284
275- defp parse_shared ( [ ~c" --rpc-eval" | _ ] , config ) do
285+ defp parse_argv ( [ ~c" --rpc-eval" | _ ] , config ) do
276286 new_config = % { config | errors: [ "--rpc-eval : wrong number of arguments" | config . errors ] }
277- { [ ] , new_config }
287+ { new_config , [ ] }
278288 end
279289
280- defp parse_shared ( [ ~c" -r" , h | t ] , config ) do
281- parse_shared ( t , % { config | commands: [ { :require , h } | config . commands ] } )
290+ defp parse_argv ( [ ~c" -r" , h | t ] , config ) do
291+ parse_argv ( t , % { config | commands: [ { :require , h } | config . commands ] } )
282292 end
283293
284- defp parse_shared ( [ ~c" -pr" , h | t ] , config ) do
285- parse_shared ( t , % { config | commands: [ { :parallel_require , h } | config . commands ] } )
294+ defp parse_argv ( [ ~c" -pr" , h | t ] , config ) do
295+ parse_argv ( t , % { config | commands: [ { :parallel_require , h } | config . commands ] } )
286296 end
287297
288- defp parse_shared ( list , config ) do
289- { list , config }
290- end
291-
292- defp append_hostname ( node ) do
293- with false <- ?@ in node ,
294- [ _ | _ ] = suffix <- :string . find ( Atom . to_charlist ( :net_kernel . nodename ( ) ) , ~c" @" ) do
295- node ++ suffix
296- else
297- _ -> node
298- end
299- end
300-
301- defp expand_code_path ( path ) do
302- path = Path . expand ( path )
303-
304- case Path . wildcard ( path ) do
305- [ ] -> [ to_charlist ( path ) ]
306- list -> Enum . map ( list , & to_charlist / 1 )
307- end
308- end
309-
310- # Process init options
311-
312- defp parse_argv ( [ ~c" --" | t ] , config ) do
313- { config , t }
314- end
315-
316- defp parse_argv ( [ ~c" +elixirc" | t ] , config ) do
317- parse_compiler ( t , config )
318- end
298+ ## Compiler
319299
320- defp parse_argv ( [ ~c" +iex " | t ] , config ) do
321- parse_iex ( t , config )
300+ defp parse_argv ( [ ~c" -o " , h | t ] , % { mode: :elixirc } = config ) do
301+ parse_argv ( t , % { config | output: h } )
322302 end
323303
324- defp parse_argv ( [ ~c" -S " , h | t ] , config ) do
325- { % { config | commands : [ { :script , h } | config . commands ] } , t }
304+ defp parse_argv ( [ ~c" --no-docs " | t ] , % { mode: :elixirc } = config ) do
305+ parse_argv ( t , % { config | compiler_options : [ { :docs , false } | config . compiler_options ] } )
326306 end
327307
328- defp parse_argv ( [ h | t ] = list , config ) do
329- case h do
330- [ ?- | _ ] ->
331- shared_option? ( list , config , & parse_argv ( & 1 , & 2 ) )
332-
333- _ ->
334- if List . keymember? ( config . commands , :eval , 0 ) do
335- { config , list }
336- else
337- { % { config | commands: [ { :file , h } | config . commands ] } , t }
338- end
339- end
308+ defp parse_argv ( [ ~c" --no-debug-info" | t ] , % { mode: :elixirc } = config ) do
309+ compiler_options = [ { :debug_info , false } | config . compiler_options ]
310+ parse_argv ( t , % { config | compiler_options: compiler_options } )
340311 end
341312
342- defp parse_argv ( [ ] , config ) do
343- { config , [ ] }
313+ defp parse_argv ( [ ~c" --ignore-module-conflict" | t ] , % { mode: :elixirc } = config ) do
314+ compiler_options = [ { :ignore_module_conflict , true } | config . compiler_options ]
315+ parse_argv ( t , % { config | compiler_options: compiler_options } )
344316 end
345317
346- # Parse compiler options
347-
348- defp parse_compiler ( [ ~c" --" | t ] , config ) do
349- { config , t }
318+ defp parse_argv ( [ ~c" --warnings-as-errors" | t ] , % { mode: :elixirc } = config ) do
319+ compiler_options = [ { :warnings_as_errors , true } | config . compiler_options ]
320+ parse_argv ( t , % { config | compiler_options: compiler_options } )
350321 end
351322
352- defp parse_compiler ( [ ~c" -o " , h | t ] , config ) do
353- parse_compiler ( t , % { config | output: h } )
323+ defp parse_argv ( [ ~c" --verbose " | t ] , % { mode: :elixirc } = config ) do
324+ parse_argv ( t , % { config | verbose_compile: true } )
354325 end
355326
356- defp parse_compiler ( [ ~c" --no-docs " | t ] , config ) do
357- parse_compiler ( t , % { config | compiler_options: [ { :docs , false } | config . compiler_options ] } )
327+ defp parse_argv ( [ ~c" --profile " , "time" | t ] , % { mode: :elixirc } = config ) do
328+ parse_argv ( t , % { config | profile: :time } )
358329 end
359330
360- defp parse_compiler ( [ ~c" --no-debug-info " | t ] , config ) do
361- compiler_options = [ { :debug_info , false } | config . compiler_options ]
362- parse_compiler ( t , % { config | compiler_options: compiler_options } )
363- end
331+ defp parse_argv ( [ ~c" --dbg " , backend | t ] , % { mode: :iex } = config ) do
332+ case backend do
333+ ~c " pry " ->
334+ parse_argv ( t , % { config | pry: true } )
364335
365- defp parse_compiler ( [ ~c" --ignore-module-conflict" | t ] , config ) do
366- compiler_options = [ { :ignore_module_conflict , true } | config . compiler_options ]
367- parse_compiler ( t , % { config | compiler_options: compiler_options } )
368- end
336+ ~c" kernel" ->
337+ parse_argv ( t , % { config | pry: false } )
369338
370- defp parse_compiler ( [ ~c" --warnings-as-errors" | t ] , config ) do
371- compiler_options = [ { :warnings_as_errors , true } | config . compiler_options ]
372- parse_compiler ( t , % { config | compiler_options: compiler_options } )
339+ _ ->
340+ error = "--dbg : Unknown dbg backend #{ inspect ( backend ) } "
341+ parse_argv ( t , % { config | errors: [ error | config . errors ] } )
342+ end
373343 end
374344
375- defp parse_compiler ( [ ~c" --verbose" | t ] , config ) do
376- parse_compiler ( t , % { config | verbose_compile: true } )
377- end
345+ defp parse_argv ( [ ~c" --dot-iex" , _ | t ] , % { mode: :iex } = config ) , do: parse_argv ( t , config )
346+ defp parse_argv ( [ ~c" --remsh" , _ | t ] , % { mode: :iex } = config ) , do: parse_argv ( t , config )
378347
379- # Private compiler options
348+ ## Fallback
380349
381- defp parse_compiler ( [ ~c" --profile" , "time" | t ] , config ) do
382- parse_compiler ( t , % { config | profile: :time } )
350+ defp parse_argv ( [ h | t ] , % { mode: :elixirc } = config ) do
351+ pattern = if File . dir? ( h ) , do: "#{ h } /**/*.ex" , else: h
352+ parse_argv ( t , % { config | compile: [ pattern | config . compile ] } )
383353 end
384354
385- defp parse_compiler ( [ h | t ] = list , config ) do
386- case h do
387- [ ?- | _ ] ->
388- shared_option? ( list , config , & parse_compiler ( & 1 , & 2 ) )
389-
390- _ ->
391- pattern = if File . dir? ( h ) , do: "#{ h } /**/*.ex" , else: h
392- parse_compiler ( t , % { config | compile: [ pattern | config . compile ] } )
355+ defp parse_argv ( [ h | t ] , config ) do
356+ if List . keymember? ( config . commands , :eval , 0 ) do
357+ { config , [ h | t ] }
358+ else
359+ { % { config | commands: [ { :file , h } | config . commands ] } , t }
393360 end
394361 end
395362
396- defp parse_compiler ( [ ] , config ) do
397- { % { config | commands: [ { :compile , config . compile } | config . commands ] } , [ ] }
363+ defp parse_argv ( [ ] , config ) do
364+ { config , [ ] }
398365 end
399366
400- # Parse IEx options
367+ # Parse helpers
401368
402- defp parse_iex ( [ ~c" --" | t ] , config ) do
403- { config , t }
404- end
405-
406- defp parse_iex ( [ ~c" -S" , h | t ] , config ) do
407- { % { config | commands: [ { :script , h } | config . commands ] } , t }
369+ defp halt_standalone ( opt ) do
370+ IO . puts ( :stderr , "#{ opt } : Standalone options can't be combined with other options" )
371+ System . halt ( 1 )
408372 end
409373
410- # These clauses are here so that Kernel.CLI does not error out with "unknown option"
411- defp parse_iex ( [ ~c " --dbg " , backend | t ] , config ) do
412- case backend do
413- ~c " pry " -> parse_iex ( t , % { config | pry: true } )
414- ~c " kernel " -> parse_iex ( t , % { config | pry: false } )
415- _ -> { :error , "--dbg : Unknown dbg backend #{ inspect ( backend ) } " }
374+ defp append_hostname ( node ) do
375+ with false <- ?@ in node ,
376+ [ _ | _ ] = suffix <- :string . find ( Atom . to_charlist ( :net_kernel . nodename ( ) ) , ~c " @ " ) do
377+ node ++ suffix
378+ else
379+ _ -> node
416380 end
417381 end
418382
419- defp parse_iex ( [ ~c " --dot-iex " , _ | t ] , config ) , do: parse_iex ( t , config )
420- defp parse_iex ( [ ~c " --remsh " , _ | t ] , config ) , do: parse_iex ( t , config )
383+ defp expand_code_path ( path ) do
384+ path = Path . expand ( path )
421385
422- defp parse_iex ( [ h | t ] = list , config ) do
423- case h do
424- [ ?- | _ ] -> shared_option? ( list , config , & parse_iex ( & 1 , & 2 ) )
425- _ -> { % { config | commands: [ { :file , h } | config . commands ] } , t }
386+ case Path . wildcard ( path ) do
387+ [ ] -> [ to_charlist ( path ) ]
388+ list -> Enum . map ( list , & to_charlist / 1 )
426389 end
427390 end
428391
429- defp parse_iex ( [ ] , config ) do
430- { config , [ ] }
431- end
432-
433392 # Process commands
434393
435394 defp process_command ( { :eval , expr } , _config ) when is_list ( expr ) do
0 commit comments