@@ -1274,24 +1274,22 @@ run_dir(Opts = #opts{logdir = LogDir,
12741274 true -> D end || D <- Dirs ],
12751275 reformat_result (catch do_run (tests (Dirs1 ), [], Opts1 , StartOpts ));
12761276
1277- {Dir = [Hd |_ ],undefined ,[]} when is_list (Dir ) and is_integer (Hd ) ->
1277+ {Dir = [Hd |_ ],undefined ,[]} when is_list (Dir ), is_integer (Hd ) ->
12781278 reformat_result (catch do_run (tests (Dir ), [], Opts1 , StartOpts ));
12791279
1280- {Dir ,undefined ,[]} when is_atom (Dir ) and ( Dir /= undefined ) ->
1280+ {Dir ,undefined ,[]} when is_atom (Dir ), Dir /= undefined ->
12811281 reformat_result (catch do_run (tests (atom_to_list (Dir )),
12821282 [], Opts1 , StartOpts ));
12831283
12841284 {undefined ,Suites = [Hd |_ ],[]} when not is_integer (Hd ) ->
12851285 Suites1 = [suite_to_test (S ) || S <- Suites ],
12861286 reformat_result (catch do_run (tests (Suites1 ), [], Opts1 , StartOpts ));
12871287
1288- {undefined ,Suite ,[]} when is_atom (Suite ) and
1289- (Suite /= undefined ) ->
1288+ {undefined ,Suite ,[]} when is_atom (Suite ), Suite /= undefined ->
12901289 {Dir ,Mod } = suite_to_test (Suite ),
12911290 reformat_result (catch do_run (tests (Dir , Mod ), [], Opts1 , StartOpts ));
12921291
1293- {undefined ,Suite ,GsAndCs } when is_atom (Suite ) and
1294- (Suite /= undefined ) ->
1292+ {undefined ,Suite ,GsAndCs } when is_atom (Suite ), Suite /= undefined ->
12951293 {Dir ,Mod } = suite_to_test (Suite ),
12961294 reformat_result (catch do_run (tests (Dir , Mod , GsAndCs ),
12971295 [], Opts1 , StartOpts ));
@@ -1300,8 +1298,8 @@ run_dir(Opts = #opts{logdir = LogDir,
13001298 exit ({error ,multiple_suites_and_cases });
13011299
13021300 {undefined ,Suite = [Hd |Tl ],GsAndCs } when is_integer (Hd ) ;
1303- ( is_list (Hd ) and ( Tl == [])) ;
1304- ( is_atom (Hd ) and ( Tl == [])) ->
1301+ is_list (Hd ), Tl == [] ;
1302+ is_atom (Hd ), Tl == [] ->
13051303 {Dir ,Mod } = suite_to_test (Suite ),
13061304 reformat_result (catch do_run (tests (Dir , Mod , GsAndCs ),
13071305 [], Opts1 , StartOpts ));
@@ -1313,18 +1311,18 @@ run_dir(Opts = #opts{logdir = LogDir,
13131311 exit ({error ,incorrect_start_options });
13141312
13151313 {Dir ,Suite ,GsAndCs } when is_integer (hd (Dir )) ;
1316- ( is_atom (Dir ) and (Dir /= undefined ) ) ;
1317- (( length (Dir ) == 1 ) and is_atom (hd (Dir ) )) ;
1318- (( length (Dir ) == 1 ) and is_list (hd (Dir ) )) ->
1314+ is_atom (Dir ), (Dir /= undefined ) ;
1315+ length (Dir ) == 1 , is_atom (hd (Dir )) ;
1316+ length (Dir ) == 1 , is_list (hd (Dir )) ->
13191317 Dir1 = if is_atom (Dir ) -> atom_to_list (Dir );
13201318 true -> Dir end ,
13211319 if Suite == undefined ->
13221320 exit ({error ,incorrect_start_options });
13231321
13241322 is_integer (hd (Suite )) ;
1325- ( is_atom (Suite ) and (Suite /= undefined ) ) ;
1326- (( length (Suite ) == 1 ) and is_atom (hd (Suite ) )) ;
1327- (( length (Suite ) == 1 ) and is_list (hd (Suite ) )) ->
1323+ is_atom (Suite ), (Suite /= undefined ) ;
1324+ length (Suite ) == 1 , is_atom (hd (Suite )) ;
1325+ length (Suite ) == 1 , is_list (hd (Suite )) ->
13281326 {Dir2 ,Mod } = suite_to_test (Dir1 , Suite ),
13291327 case GsAndCs of
13301328 [] ->
@@ -1610,20 +1608,19 @@ suite_to_test(Dir, Suite) when is_list(Suite) ->
16101608 {DirName ,list_to_atom (filename :rootname (File ))}
16111609 end .
16121610
1613- groups_and_cases (Gs , Cs ) when (( Gs == undefined ) or ( Gs == [])) and
1614- (( Cs == undefined ) or ( Cs == []) ) ->
1611+ groups_and_cases (Gs , Cs ) when (Gs == undefined orelse Gs == []),
1612+ (Cs == undefined orelse Cs == []) ->
16151613 [];
16161614groups_and_cases (Gs , Cs ) when Gs == undefined ; Gs == [] ->
1617- if ( Cs == all ) or ( Cs == [all ]) or ( Cs == [" all" ]) -> all ;
1615+ if Cs == all ; Cs == [all ] ; Cs == [" all" ] -> all ;
16181616 true -> [ensure_atom (C ) || C <- listify (Cs )]
16191617 end ;
16201618groups_and_cases (GOrGs , Cs ) when (is_atom (GOrGs ) orelse
16211619 (is_list (GOrGs ) andalso
16221620 (is_atom (hd (GOrGs )) orelse
16231621 (is_list (hd (GOrGs )) andalso
16241622 is_atom (hd (hd (GOrGs ))))))) ->
1625- if (Cs == undefined ) or (Cs == []) or
1626- (Cs == all ) or (Cs == [all ]) or (Cs == [" all" ]) ->
1623+ if Cs == undefined ; Cs == [] ; Cs == all ; Cs == [all ] ; Cs == [" all" ] ->
16271624 [{GOrGs ,all }];
16281625 true ->
16291626 [{GOrGs ,[ensure_atom (C ) || C <- listify (Cs )]}]
@@ -1632,7 +1629,7 @@ groups_and_cases(Gs, Cs) when is_integer(hd(hd(Gs))) ->
16321629 % % if list of strings, this comes from 'ct_run -group G1 G2 ...' and
16331630 % % we need to parse the strings
16341631 Gs1 =
1635- if ( Gs == [all ]) or ( Gs == [" all" ]) ->
1632+ if Gs == [all ] ; Gs == [" all" ] ->
16361633 all ;
16371634 true ->
16381635 lists :map (fun (G ) ->
@@ -2360,7 +2357,7 @@ start_cover(Opts=#opts{coverspec=CovData,cover_stop=CovStop},LogDir) ->
23602357 [TsCoverInfo ]),
23612358
23622359 % % start cover on specified nodes
2363- if ( CovNodes /= []) and ( CovNodes /= undefined ) ->
2360+ if CovNodes /= [], CovNodes /= undefined ->
23642361 ct_logs :log (" COVER INFO" ,
23652362 " Nodes included in cover "
23662363 " session: ~tw " ,
0 commit comments