@@ -1272,24 +1272,22 @@ run_dir(Opts = #opts{logdir = LogDir,
12721272 true -> D end || D <- Dirs ],
12731273 reformat_result (catch do_run (tests (Dirs1 ), [], Opts1 , StartOpts ));
12741274
1275- {Dir = [Hd |_ ],undefined ,[]} when is_list (Dir ) and is_integer (Hd ) ->
1275+ {Dir = [Hd |_ ],undefined ,[]} when is_list (Dir ), is_integer (Hd ) ->
12761276 reformat_result (catch do_run (tests (Dir ), [], Opts1 , StartOpts ));
12771277
1278- {Dir ,undefined ,[]} when is_atom (Dir ) and ( Dir /= undefined ) ->
1278+ {Dir ,undefined ,[]} when is_atom (Dir ), Dir /= undefined ->
12791279 reformat_result (catch do_run (tests (atom_to_list (Dir )),
12801280 [], Opts1 , StartOpts ));
12811281
12821282 {undefined ,Suites = [Hd |_ ],[]} when not is_integer (Hd ) ->
12831283 Suites1 = [suite_to_test (S ) || S <- Suites ],
12841284 reformat_result (catch do_run (tests (Suites1 ), [], Opts1 , StartOpts ));
12851285
1286- {undefined ,Suite ,[]} when is_atom (Suite ) and
1287- (Suite /= undefined ) ->
1286+ {undefined ,Suite ,[]} when is_atom (Suite ), Suite /= undefined ->
12881287 {Dir ,Mod } = suite_to_test (Suite ),
12891288 reformat_result (catch do_run (tests (Dir , Mod ), [], Opts1 , StartOpts ));
12901289
1291- {undefined ,Suite ,GsAndCs } when is_atom (Suite ) and
1292- (Suite /= undefined ) ->
1290+ {undefined ,Suite ,GsAndCs } when is_atom (Suite ), Suite /= undefined ->
12931291 {Dir ,Mod } = suite_to_test (Suite ),
12941292 reformat_result (catch do_run (tests (Dir , Mod , GsAndCs ),
12951293 [], Opts1 , StartOpts ));
@@ -1298,8 +1296,8 @@ run_dir(Opts = #opts{logdir = LogDir,
12981296 exit ({error ,multiple_suites_and_cases });
12991297
13001298 {undefined ,Suite = [Hd |Tl ],GsAndCs } when is_integer (Hd ) ;
1301- ( is_list (Hd ) and ( Tl == [])) ;
1302- ( is_atom (Hd ) and ( Tl == [])) ->
1299+ is_list (Hd ), Tl == [] ;
1300+ is_atom (Hd ), Tl == [] ->
13031301 {Dir ,Mod } = suite_to_test (Suite ),
13041302 reformat_result (catch do_run (tests (Dir , Mod , GsAndCs ),
13051303 [], Opts1 , StartOpts ));
@@ -1311,18 +1309,18 @@ run_dir(Opts = #opts{logdir = LogDir,
13111309 exit ({error ,incorrect_start_options });
13121310
13131311 {Dir ,Suite ,GsAndCs } when is_integer (hd (Dir )) ;
1314- ( is_atom (Dir ) and (Dir /= undefined ) ) ;
1315- (( length (Dir ) == 1 ) and is_atom (hd (Dir ) )) ;
1316- (( length (Dir ) == 1 ) and is_list (hd (Dir ) )) ->
1312+ is_atom (Dir ), (Dir /= undefined ) ;
1313+ length (Dir ) == 1 , is_atom (hd (Dir )) ;
1314+ length (Dir ) == 1 , is_list (hd (Dir )) ->
13171315 Dir1 = if is_atom (Dir ) -> atom_to_list (Dir );
13181316 true -> Dir end ,
13191317 if Suite == undefined ->
13201318 exit ({error ,incorrect_start_options });
13211319
13221320 is_integer (hd (Suite )) ;
1323- ( is_atom (Suite ) and (Suite /= undefined ) ) ;
1324- (( length (Suite ) == 1 ) and is_atom (hd (Suite ) )) ;
1325- (( length (Suite ) == 1 ) and is_list (hd (Suite ) )) ->
1321+ is_atom (Suite ), (Suite /= undefined ) ;
1322+ length (Suite ) == 1 , is_atom (hd (Suite )) ;
1323+ length (Suite ) == 1 , is_list (hd (Suite )) ->
13261324 {Dir2 ,Mod } = suite_to_test (Dir1 , Suite ),
13271325 case GsAndCs of
13281326 [] ->
@@ -1608,20 +1606,19 @@ suite_to_test(Dir, Suite) when is_list(Suite) ->
16081606 {DirName ,list_to_atom (filename :rootname (File ))}
16091607 end .
16101608
1611- groups_and_cases (Gs , Cs ) when (( Gs == undefined ) or ( Gs == [])) and
1612- (( Cs == undefined ) or ( Cs == []) ) ->
1609+ groups_and_cases (Gs , Cs ) when (Gs == undefined orelse Gs == []),
1610+ (Cs == undefined orelse Cs == []) ->
16131611 [];
16141612groups_and_cases (Gs , Cs ) when Gs == undefined ; Gs == [] ->
1615- if ( Cs == all ) or ( Cs == [all ]) or ( Cs == [" all" ]) -> all ;
1613+ if Cs == all ; Cs == [all ] ; Cs == [" all" ] -> all ;
16161614 true -> [ensure_atom (C ) || C <- listify (Cs )]
16171615 end ;
16181616groups_and_cases (GOrGs , Cs ) when (is_atom (GOrGs ) orelse
16191617 (is_list (GOrGs ) andalso
16201618 (is_atom (hd (GOrGs )) orelse
16211619 (is_list (hd (GOrGs )) andalso
16221620 is_atom (hd (hd (GOrGs ))))))) ->
1623- if (Cs == undefined ) or (Cs == []) or
1624- (Cs == all ) or (Cs == [all ]) or (Cs == [" all" ]) ->
1621+ if Cs == undefined ; Cs == [] ; Cs == all ; Cs == [all ] ; Cs == [" all" ] ->
16251622 [{GOrGs ,all }];
16261623 true ->
16271624 [{GOrGs ,[ensure_atom (C ) || C <- listify (Cs )]}]
@@ -1630,7 +1627,7 @@ groups_and_cases(Gs, Cs) when is_integer(hd(hd(Gs))) ->
16301627 % % if list of strings, this comes from 'ct_run -group G1 G2 ...' and
16311628 % % we need to parse the strings
16321629 Gs1 =
1633- if ( Gs == [all ]) or ( Gs == [" all" ]) ->
1630+ if Gs == [all ] ; Gs == [" all" ] ->
16341631 all ;
16351632 true ->
16361633 lists :map (fun (G ) ->
@@ -2358,7 +2355,7 @@ start_cover(Opts=#opts{coverspec=CovData,cover_stop=CovStop},LogDir) ->
23582355 [TsCoverInfo ]),
23592356
23602357 % % start cover on specified nodes
2361- if ( CovNodes /= []) and ( CovNodes /= undefined ) ->
2358+ if CovNodes /= [], CovNodes /= undefined ->
23622359 ct_logs :log (" COVER INFO" ,
23632360 " Nodes included in cover "
23642361 " session: ~tw " ,
0 commit comments