3232
3333-export ([args_file /1 , evil_args_file /1 , missing_args_file /1 , env /1 , args_file_env /1 ,
3434 otp_7461 /1 , otp_7461_remote /1 , argument_separation /1 , argument_with_option /1 ,
35- zdbbl_dist_buf_busy_limit /1 , long_path_env /1 , long_path_env_when_rootdir_not_present / 1 ]).
35+ zdbbl_dist_buf_busy_limit /1 , long_path_env /1 ]).
3636
3737-include_lib (" stdlib/include/assert.hrl" ).
3838
@@ -43,7 +43,7 @@ suite() ->
4343all () ->
4444 [args_file , evil_args_file , missing_args_file , env , args_file_env ,
4545 otp_7461 , argument_separation , argument_with_option , zdbbl_dist_buf_busy_limit ,
46- long_path_env , long_path_env_when_rootdir_not_present ].
46+ long_path_env ].
4747
4848init_per_suite (Config ) ->
4949 [{suite_erl_flags , save_env ()} | Config ].
@@ -444,60 +444,91 @@ zdbbl_dist_buf_busy_limit(Config) when is_list(Config) ->
444444 ok = cleanup_node (SNameS , 10 ),
445445 ok .
446446
447+
448+ % % This testcase checks that erlexec does not crash with a huge PATH
449+ % % there used to be issues when the path was larger than 1024*10 on
450+ % % non-windows. (Windows truncates such long paths so no problem there).
447451long_path_env (Config ) when is_list (Config ) ->
448- BinPath = os :getenv (" BINDIR" ),
452+
453+ {ok , BinPath } = init :get_argument (bindir ),
449454 ActualPath = os :getenv (" PATH" ),
450455
456+ IsWindows = element (1 , os :type ()) =:= win32 ,
457+
458+ LongPathLength =
459+ if IsWindows ->
460+ % % Windows truncates larger PATHs
461+ 10 ;
462+ true ->
463+ 40
464+ end ,
465+
466+ % % Each individual segment cannot be larger than 255 on docker,
467+ % % so we limit for all system to that.
468+ LongPath = lists :flatten (
469+ lists :join (pathsep (),
470+ lists :duplicate (LongPathLength ,
471+ lists :duplicate (250 , " x" )))),
472+
473+ % % In order to run this on windows we do a bit of trickery, namely
474+ % % get the program name, add the potential extension using find_executable,
475+ % % and then get the name at the end using basename.
476+ [PName | Rest ] = string :split (ct :get_progname ()," " ),
477+ FullPathPName = os :find_executable (PName ),
478+ PNameWExt = filename :basename (FullPathPName ),
479+
451480 PathComponents = string :split (ActualPath , pathsep (), all ),
452- ActualPathNoBinPath = path_var_join (lists :filter (fun (Path ) ->
453- Path =/= BinPath
454- end , PathComponents )),
481+ {ActualNoErl , ActualErl } =
482+ lists :partition (fun (Path ) ->
483+ os :find_executable (PName ,[Path ]) =/= false
484+ end , PathComponents ),
485+
486+ ActualPathNoErl = path_var_join (ActualNoErl ),
487+ ActualPathErl = path_var_join ([P || P <- ActualErl , string :prefix (P , code :root_dir ()) =:= nomatch ]),
488+
455489 ct :log (" BINDIR: ~ts " , [BinPath ]),
456490 ct :log (" PATH: ~ts " , [ActualPath ]),
491+ ct :log (" PATH_MAX: '~ts '" , [string :trim (os :cmd (" getconf PATH_MAX /" ))]),
492+ ct :log (" NAME_MAX: '~ts '" , [string :trim (os :cmd (" getconf NAME_MAX /" ))]),
457493
458- LongPath = lists :flatten (lists :duplicate (10240 , " x" )),
459- {ok , [[PName ]]} = init :get_argument (progname ),
460- Cmd = PName ++ " -noshell -eval 'io:format(\" ~ts \" , [os:getenv(\" PATH\" )]),erlang:halt()'" ,
461-
462- compare_erl_path (Cmd , BinPath , ActualPath ),
463- compare_erl_path (Cmd , BinPath , path_var_join ([ActualPath , LongPath ])),
464- compare_erl_path (Cmd , BinPath , path_var_join ([ActualPath , LongPath , BinPath ])),
465- compare_erl_path (Cmd , BinPath , path_var_join ([BinPath , ActualPath , LongPath ])),
466- compare_erl_path (Cmd , BinPath , path_var_join ([BinPath , ActualPath , LongPath , BinPath ])),
494+ CmdArgs = " " ++ Rest ++ ~S ' -noshell -eval "io:format(\"~ts \", [os:getenv(\"PATH\")]),erlang:halt()"' ,
467495
468- Output = compare_erl_path (Cmd , BinPath , path_var_join ([ActualPathNoBinPath , LongPath ])),
469- ? assertEqual (string :find (Output , LongPath ), LongPath ),
470496
471- ok .
497+ % % Test that erlexec does not crash with long path segments in various positions
498+ RelCmd = PNameWExt ++ CmdArgs ,
472499
473- long_path_env_when_rootdir_not_present (Config ) when is_list (Config ) ->
474- BinPath = os :getenv (" BINDIR" ),
475- RootPath = os :getenv (" ROOTDIR" ),
476- RootPathWithBin = filename :join (RootPath , " bin" ),
477- ActualPath = os :getenv (" PATH" ),
478- LongPathLength = 10240 ,
500+ compare_erl_path (PName , RelCmd , BinPath , ActualPath ),
501+ compare_erl_path (PName , RelCmd , BinPath , path_var_join ([ActualPath , LongPath ])),
502+ compare_erl_path (PName , RelCmd , BinPath , path_var_join ([ActualPath , LongPath , BinPath ])),
503+ compare_erl_path (PName , RelCmd , BinPath , path_var_join ([BinPath , ActualPath , LongPath ])),
504+ compare_erl_path (PName , RelCmd , BinPath , path_var_join ([BinPath , ActualPath , LongPath , BinPath ])),
479505
480- LongPath = lists : flatten ( lists : duplicate ( LongPathLength , " x " )),
481- { ok , [[ PName ]]} = init : get_argument ( progname ),
482- Cmd = " \" " ++ filename : join ( RootPathWithBin , PName ) ++ " \" " ++ " -noshell -eval 'io:format( \" ~ts \" , [os:getenv( \" PATH \" )]),erlang:halt()' " ,
506+ % % Test that the LongPath is there
507+ RelOutput = compare_erl_path ( PName , RelCmd , BinPath , path_var_join ([ ActualPathNoErl , BinPath , ActualPathErl , LongPath ]) ),
508+ ? assertNotEqual ( nomatch , string : find ( RelOutput , LongPath )) ,
483509
484- PathComponents = string :split (ActualPath , pathsep (), all ),
485- ActualPathNoRoot = path_var_join (lists :filter (fun (Path ) ->
486- (Path =/= RootPathWithBin ) and (Path =/= (RootPathWithBin ++ " /" )) and (Path =/= BinPath )
487- end , PathComponents )),
488510
489- os :putenv (" PATH" , path_var_join ([ActualPathNoRoot , LongPath , LongPath ])),
490- Output = os :cmd (Cmd ),
511+ % % Test that we can run using an absolute path and a long PATH
512+ AbsCmd = [$" || not IsWindows ] ++ os :find_executable (PName ) ++ [$" || not IsWindows ] ++ CmdArgs ,
513+ AbsOutput = compare_erl_path (PName , AbsCmd , BinPath , path_var_join ([ActualPathNoErl , ActualPathErl , LongPath , LongPath ])),
514+ ? assertNotEqual (nomatch , string :find (AbsOutput , path_var_join ([LongPath , LongPath ]))),
491515
492- ? assertEqual (string :length (string :find (Output , LongPath ++ pathsep () ++ LongPath )), (LongPathLength * 2 ) + string :length (pathsep ())),
493516 ok .
494517
495- compare_erl_path (Cmd , BinPath , Path ) ->
518+ compare_erl_path (Pname , Cmd , BinPath , Path ) ->
496519 os :putenv (" PATH" , Path ),
497520 Output = os :cmd (Cmd ),
521+ ct :log (" Cmd: ~ts~n BinPath: ~ts~n PATH: ~ts~n Output: ~ts " ,[Cmd , BinPath , Path , Output ]),
522+
523+ [BinDir | Rest ] = string :split (Output , pathsep (), all ),
524+
498525 % BinPath is at the front of PATH and nowhere else
499- ? assertEqual (string :find (Output , BinPath ++ " :" ), Output ),
500- ? assertEqual (string :find (Output , " :" ++ BinPath ), nomatch ),
526+ ? assertNotEqual (os :find_executable (Pname , [BinDir ]), false ),
527+ case os :find_executable (Pname , Rest ) of
528+ false -> ok ;
529+ AbsPname ->
530+ ? assertEqual (string :prefix (AbsPname , code :root_dir ()), nomatch )
531+ end ,
501532 Output .
502533
503534pathsep () ->
0 commit comments