summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--perl_checker.src/Makefile2
-rw-r--r--perl_checker.src/common.ml11
-rw-r--r--perl_checker.src/common.mli3
-rw-r--r--perl_checker.src/flags.ml37
-rw-r--r--perl_checker.src/flags.mli18
-rw-r--r--perl_checker.src/global_checks.ml48
-rw-r--r--perl_checker.src/lexer.mll40
-rw-r--r--perl_checker.src/parser.mly26
-rw-r--r--perl_checker.src/parser_helper.ml227
-rw-r--r--perl_checker.src/parser_helper.mli31
-rw-r--r--perl_checker.src/perl_checker.ml43
-rw-r--r--perl_checker.src/test/syntax_restrictions.t2
-rw-r--r--perl_checker.src/tree.ml35
-rw-r--r--perl_checker.src/tree.mli3
-rw-r--r--perl_checker.src/types.mli17
15 files changed, 319 insertions, 224 deletions
diff --git a/perl_checker.src/Makefile b/perl_checker.src/Makefile
index b639e6c..22a45a6 100644
--- a/perl_checker.src/Makefile
+++ b/perl_checker.src/Makefile
@@ -4,7 +4,7 @@ YFLAGS = -v
TRASH = parser.output perl_checker.html TAGS
RESULT = perl_checker
BCSUFFIX = _debug
-SOURCES = build.ml common.ml flags.ml config_file.ml types.mli info.ml parser_helper.ml parser.mly lexer.mll tree.ml global_checks.ml perl_checker.ml
+SOURCES = types.mli build.ml common.ml flags.ml config_file.ml info.ml parser_helper.ml parser.mly lexer.mll tree.ml global_checks.ml perl_checker.ml
LIBS = unix
VENDORLIB = $(shell dirname `pwd`)
DEBUG = 1
diff --git a/perl_checker.src/common.ml b/perl_checker.src/common.ml
index 8a0d27e..dd2f6b1 100644
--- a/perl_checker.src/common.ml
+++ b/perl_checker.src/common.ml
@@ -228,6 +228,13 @@ let rec lfix_point f e =
if e = e' then e :: lfix_point f e' else [e]
*)
+let fluid_let ref value f =
+ let previous_val = !ref in
+ ref := value ;
+ let v = f() in
+ ref := previous_val ;
+ v
+
let do0_withenv doit f env l =
let r_env = ref env in
doit (fun e -> r_env := f !r_env e) l ;
@@ -882,9 +889,7 @@ let rec updir dir nb =
let (string_of_ref : 'a ref -> string) = fun r ->
Printf.sprintf "0x%x" (Obj.magic r : int)
-let print_endline_flush_quiet = ref false
-let print_endline_flush s = if not !print_endline_flush_quiet then (print_endline s ; flush stdout)
-let print_endline_flush_always s = print_endline s ; flush stdout
+let print_endline_flush s = print_endline s ; flush stdout
let is_int n = n = floor n
diff --git a/perl_checker.src/common.mli b/perl_checker.src/common.mli
index 17b0ca5..86a13cd 100644
--- a/perl_checker.src/common.mli
+++ b/perl_checker.src/common.mli
@@ -52,6 +52,7 @@ val fix_point : ('a -> 'a) -> 'a -> 'a
val fix_point_withenv : ('a -> 'b -> 'b * 'a) -> 'a -> 'b -> 'b * 'a
val fix_point_ : int -> ('a -> 'a) -> 'a -> 'a * int
val group_by_2 : 'a list -> ('a * 'a) list
+val fluid_let : 'a ref -> 'a -> (unit -> 'b) -> 'b
val do0_withenv :
(('a -> unit) -> 'b -> 'c) -> ('d -> 'a -> 'd) -> 'd -> 'b -> 'd
val do0_withenv2 :
@@ -219,9 +220,7 @@ val expand_symlinks : string -> string
val mtime : string -> float
val updir : string -> int -> string
val string_of_ref : 'a ref -> string
-val print_endline_flush_quiet : bool ref
val print_endline_flush : string -> unit
-val print_endline_flush_always : string -> unit
val is_int : float -> bool
val compare_lists : ('a -> 'b -> int) -> 'a list -> 'b list -> int
val compare_best : int -> int -> int
diff --git a/perl_checker.src/flags.ml b/perl_checker.src/flags.ml
index fdedc95..187c140 100644
--- a/perl_checker.src/flags.ml
+++ b/perl_checker.src/flags.ml
@@ -1,8 +1,43 @@
open Common
+open Types
let verbose = ref false
let quiet = ref false
let generate_pot = ref false
let expand_tabs = ref (Some 8)
-let check_unused_global_vars = ref false
let no_cache = ref false
+
+let check_unused_global_vars = ref false
+let check_white_space = ref true
+let check_suggest_simpler = ref true
+let check_void = ref true
+let check_context = ref true
+let check_strange = ref true
+let check_traps = ref true
+let check_complex_expressions = ref true
+let normalized_expressions = ref true
+let check_help_perl_checker = ref true
+let suggest_functional = ref true
+let check_prototypes = ref true
+let check_names = ref true
+let check_import_export = ref true
+let allow_MDK_Common = ref true
+
+let is_warning_type_set = function
+ | Warn_white_space -> !check_white_space
+ | Warn_suggest_simpler -> !check_suggest_simpler
+ | Warn_unused_global_vars -> !check_unused_global_vars
+ | Warn_void -> !check_void
+ | Warn_context -> !check_context
+ | Warn_strange -> !check_strange
+ | Warn_traps -> !check_traps
+ | Warn_complex_expressions -> !check_complex_expressions
+ | Warn_normalized_expressions -> !normalized_expressions
+ | Warn_suggest_functional -> !suggest_functional
+ | Warn_prototypes -> !check_prototypes
+ | Warn_names -> !check_names
+ | Warn_import_export -> !check_import_export
+ | Warn_MDK_Common -> !allow_MDK_Common
+ | Warn_help_perl_checker -> !check_help_perl_checker
+
+let are_warning_types_set l = not !quiet && List.for_all is_warning_type_set l
diff --git a/perl_checker.src/flags.mli b/perl_checker.src/flags.mli
index b3d8ffa..2dc3b26 100644
--- a/perl_checker.src/flags.mli
+++ b/perl_checker.src/flags.mli
@@ -2,5 +2,21 @@ val verbose : bool ref
val quiet : bool ref
val generate_pot : bool ref
val expand_tabs : int option ref
-val check_unused_global_vars : bool ref
val no_cache : bool ref
+val check_unused_global_vars : bool ref
+val check_white_space : bool ref
+val check_suggest_simpler : bool ref
+val check_void : bool ref
+val check_context : bool ref
+val check_strange : bool ref
+val check_traps : bool ref
+val check_complex_expressions : bool ref
+val normalized_expressions : bool ref
+val check_help_perl_checker : bool ref
+val suggest_functional : bool ref
+val check_prototypes : bool ref
+val check_names : bool ref
+val check_import_export : bool ref
+val allow_MDK_Common : bool ref
+val is_warning_type_set : Types.warning -> bool
+val are_warning_types_set : Types.warning list -> bool
diff --git a/perl_checker.src/global_checks.ml b/perl_checker.src/global_checks.ml
index 5875dce..7b24d50 100644
--- a/perl_checker.src/global_checks.ml
+++ b/perl_checker.src/global_checks.ml
@@ -36,7 +36,7 @@ let rec get_imported state current_package (package_name, (imports, pos)) =
try
sndter3 (List.assoc var (get_imports state package_used))
with Not_found ->
- warn_with_pos pos (sprintf "name %s is not defined in package %s" (variable2s var) package_name) ;
+ warn_with_pos [Warn_import_export] pos (sprintf "name %s is not defined in package %s" (variable2s var) package_name) ;
ref Access_various, None
in
var, (package_name, b, prototype)
@@ -59,12 +59,12 @@ let rec get_imported state current_package (package_name, (imports, pos)) =
| I_raw, tag ->
(try
List.assoc tag exports.export_tags
- with Not_found -> warn_with_pos pos (sprintf "package %s doesn't export tag %s" package_name tag) ; [])
+ with Not_found -> warn_with_pos [Warn_import_export] pos (sprintf "package %s doesn't export tag %s" package_name tag) ; [])
| variable ->
if List.mem variable exports.export_ok || List.mem variable exports.export_auto then
[ variable ]
else
- (warn_with_pos pos (sprintf "package %s doesn't export %s" package_name (variable2s variable)) ; [])
+ (warn_with_pos [Warn_import_export] pos (sprintf "package %s doesn't export %s" package_name (variable2s variable)) ; [])
) l
in
List.map get_var_by_name imports_vars
@@ -99,8 +99,8 @@ let check_para_comply_with_prototype para proto =
| None -> ()
| Some(pos, para) ->
match do_para_comply_with_prototype para proto with
- | -1 -> warn_with_pos pos "not enough parameters"
- | 1 -> warn_with_pos pos "too many parameters"
+ | -1 -> warn_with_pos [Warn_prototypes] pos "not enough parameters"
+ | 1 -> warn_with_pos [Warn_prototypes] pos "too many parameters"
| _ -> ()
let is_anonymous_variable_name s = String.length s > 1 && s.[0] = '_'
@@ -192,18 +192,18 @@ let is_global_var context ident =
let check_variable (context, var) vars para =
match var with
| Ident(_, s, pos) when context <> I_func && is_anonymous_variable_name s && s <> "__FILE__" && s <> "__LINE__" ->
- warn_with_pos pos (sprintf "variable %s must not be used\n (variable with name _XXX are reserved for unused variables)" (variable2s(context, string_of_Ident var)))
+ warn_with_pos [Warn_normalized_expressions] pos (sprintf "variable %s must not be used\n (variable with name _XXX are reserved for unused variables)" (variable2s(context, string_of_Ident var)))
| Ident(Some pkg, _, _) when uses_external_package pkg || List.mem pkg !ignored_packages -> ()
| Ident(None, ident, pos) ->
if is_my_declared vars (context, ident) || is_our_declared vars (context, ident) || is_var_declared vars (context, ident) para || is_global_var context ident
then ()
- else warn_with_pos pos (if context = I_func then "unknown function " ^ ident else "undeclared variable " ^ variable2s(context, ident))
+ else warn_with_pos [Warn_names] pos (if context = I_func then "unknown function " ^ ident else "undeclared variable " ^ variable2s(context, ident))
| Ident(Some fq, name, pos) ->
if (fq = "CORE") && is_global_var context name || is_global_var_declared vars (context, fq, name) para
then ()
else
if context = I_func then
- warn_with_pos pos ("unknown function " ^ string_of_Ident var)
+ warn_with_pos [Warn_names] pos ("unknown function " ^ string_of_Ident var)
else
lpush vars.state.global_vars_used ((context, fq, name), pos)
| _ -> ()
@@ -216,7 +216,7 @@ let declare_My vars (mys, pos) =
) mys in
let l_pre = List.hd vars.my_vars in
List.iter (fun v ->
- if List.mem_assoc v l_pre then warn_with_pos pos (sprintf "redeclared variable %s" (variable2s v))
+ if List.mem_assoc v l_pre then warn_with_pos [Warn_names] pos (sprintf "redeclared variable %s" (variable2s v))
) l_new ;
{ vars with my_vars = (List.map (fun v -> v, (pos, ref Access_none, None)) l_new @ l_pre) :: List.tl vars.my_vars }
@@ -225,7 +225,7 @@ let declare_Our vars (ours, pos) =
| [] -> vars (* we're at the toplevel, already declared in vars_declared *)
| l_pre :: other ->
List.iter (fun v ->
- if List.mem_assoc v l_pre && v <> (I_scalar, "_") then warn_with_pos pos (sprintf "redeclared variable %s" (variable2s v))
+ if List.mem_assoc v l_pre && v <> (I_scalar, "_") then warn_with_pos [Warn_names] pos (sprintf "redeclared variable %s" (variable2s v))
) ours ;
{ vars with our_vars = (List.map (fun v -> v, (pos, ref Access_none, None)) ours @ l_pre) :: other }
@@ -246,11 +246,11 @@ let check_unused_local_variables vars =
match s with
| "BEGIN" | "END" | "DESTROY" -> ()
| "_" when context = I_array ->
- warn_with_pos pos "if the function doesn't take any parameters, please use the empty prototype.\nexample \"sub foo() { ... }\""
+ warn_with_pos [Warn_normalized_expressions] pos "if the function doesn't take any parameters, please use the empty prototype.\nexample \"sub foo() { ... }\""
| _ ->
if s.[0] != '_' || s = "_" then
let msg = if !used = Access_write_only then sprintf "variable %s assigned, but not read" else sprintf "unused variable %s" in
- warn_with_pos pos (msg (variable2s v))
+ warn_with_pos [Warn_names] pos (msg (variable2s v))
) (List.hd vars.my_vars)
let check_variables vars t =
@@ -287,7 +287,7 @@ let check_variables vars t =
(* special warning if @_ is unbound *)
check_variable (I_func, ident) vars None ;
if not (is_my_declared vars (I_array, "_")) then
- warn_with_pos pos (sprintf "replace %s(@_) with &%s" (string_of_Ident ident) (string_of_Ident ident)) ;
+ warn_with_pos [Warn_suggest_simpler] pos (sprintf "replace %s(@_) with &%s" (string_of_Ident ident) (string_of_Ident ident)) ;
Some vars
| Call(Deref(I_func, Ident(None, "require", _)), [Ident _]) -> Some vars
@@ -308,7 +308,7 @@ let check_variables vars t =
let vars = check_variables_ vars l in
let vars' = { vars with my_vars = [] :: vars.my_vars ; our_vars = [(I_scalar, "_"), (pos, ref Access_various, None)] :: vars.our_vars } in
let vars' = check_variables_ vars' expr in
- if List.hd(vars'.my_vars) <> [] then warn_with_pos pos "you can't declare variables in foreach infix";
+ if List.hd(vars'.my_vars) <> [] then warn_with_pos [Warn_traps] pos "you can't declare variables in foreach postfix";
Some vars
| Call_op("foreach my", [my; expr; Block block], _) ->
@@ -379,7 +379,7 @@ let check_variables vars t =
(* check e first *)
let vars = check_variables_ vars e in
List.iter (fun (context, var) ->
- if non_scalar_context context then warn_with_pos pos (sprintf "%s takes all the arguments, %s is undef in any case" (variable2s (context, var)) (variable2s (last mys)))
+ if non_scalar_context context then warn_with_pos [Warn_prototypes] pos (sprintf "%s takes all the arguments, %s is undef in any case" (variable2s (context, var)) (variable2s (last mys)))
) (removelast mys) ; (* mys is never empty *)
Some(declare_My_our vars (my_or_our, mys, pos))
@@ -387,7 +387,7 @@ let check_variables vars t =
| Call_op(op, List (My_our _ :: _) :: _, pos)
| Call_op(op, My_our _ :: _, pos)
| Call_op(op, Call_op("local", _, _) :: _, pos) ->
- if op <> "=" then warn_with_pos pos (sprintf "applying %s on a new initialized variable is wrong" op);
+ if op <> "=" then warn_with_pos [Warn_traps] pos (sprintf "applying %s on a new initialized variable is wrong" op);
None
| Call_op("=", [ Deref(context, (Ident _ as var)) ; para], _) ->
@@ -429,8 +429,8 @@ let check_variables vars t =
in
(try
if not (uses_external_package pkg || List.mem pkg !ignored_packages || search pkg || method_ = "bootstrap") then
- warn_with_pos pos (sprintf "unknown method %s starting in package %s" method_ pkg);
- with Not_found -> warn_with_pos pos (sprintf "unknown package %s" pkg));
+ warn_with_pos [Warn_import_export] pos (sprintf "unknown method %s starting in package %s" method_ pkg);
+ with Not_found -> warn_with_pos [Warn_import_export] pos (sprintf "unknown package %s" pkg));
Some vars
| Method_call(o, Raw_string(method_, pos), para) ->
@@ -443,16 +443,16 @@ let check_variables vars t =
match List.filter (fun (_, n) -> n = 0) l_and with
| [] ->
(match uniq (List.map snd l_and) with
- | [-1] -> warn_with_pos pos "not enough parameters"
- | [ 1] -> warn_with_pos pos "too many parameters"
- | _ -> warn_with_pos pos "not enough or too many parameters") ;
+ | [-1] -> warn_with_pos [Warn_prototypes] pos "not enough parameters"
+ | [ 1] -> warn_with_pos [Warn_prototypes] pos "too many parameters"
+ | _ -> warn_with_pos [Warn_prototypes] pos "not enough or too many parameters") ;
l_and
| l -> l
in
List.iter (fun (used, _) -> used := Access_various) l_and
with Not_found ->
if not (List.mem method_ [ "isa"; "can" ]) then
- warn_with_pos pos ("unknown method " ^ method_)) ;
+ warn_with_pos [Warn_names] pos ("unknown method " ^ method_)) ;
Some vars
| _ -> None
@@ -462,7 +462,7 @@ let check_variables vars t =
let check_tree state package =
let vars = { my_vars = [[]]; our_vars = []; locally_imported = []; required_vars = []; current_package = package; state = state; is_toplevel = true; write_only = false } in
- if !Flags.verbose then print_endline_flush_always ("checking package " ^ package.package_name) ;
+ if !Flags.verbose then print_endline_flush ("checking package " ^ package.package_name) ;
let vars = check_variables vars package.body in
check_unused_local_variables vars ;
()
@@ -501,7 +501,7 @@ let add_file_to_files per_files file =
let check_unused_vars package =
Hashtbl.iter (fun (context, name) (pos, is_used, _proto) ->
if not (!is_used != Access_various || List.mem name ["BEGIN"; "END"; "DESTROY"; "ISA"; "AUTOLOAD"; "EXPORT"; "EXPORT_OK"; "EXPORT_TAGS"]) then
- warn_with_pos pos (sprintf "unused %s%s::%s" (if context = I_func then "function " else "variable " ^ context2s context) package.package_name name)
+ warn_with_pos [Warn_unused_global_vars] pos (sprintf "unused %s%s::%s" (if context = I_func then "function " else "variable " ^ context2s context) package.package_name name)
) package.vars_declared
let arrange_global_vars_declared global_vars_declared state =
diff --git a/perl_checker.src/lexer.mll b/perl_checker.src/lexer.mll
index 8d6714c..ebd183e 100644
--- a/perl_checker.src/lexer.mll
+++ b/perl_checker.src/lexer.mll
@@ -62,8 +62,8 @@ let pos lexbuf = lexeme_start lexbuf, lexeme_end lexbuf
let pos2sfull_with start end_ = Info.pos2sfull (!current_file, start, end_)
let pos2sfull lexbuf = pos2sfull_with (lexeme_start lexbuf) (lexeme_end lexbuf)
-let warn_with_pos (start, end_) err = print_endline_flush (pos2sfull_with start end_ ^ err)
-let warn lexbuf err = warn_with_pos (pos lexbuf) err
+let warn_with_pos warn_types (start, end_) err = if Flags.are_warning_types_set warn_types then print_endline_flush (pos2sfull_with start end_ ^ err)
+let warn warn_types lexbuf err = warn_with_pos warn_types (pos lexbuf) err
let die lexbuf err = failwith (pos2sfull_with (lexeme_start lexbuf) (lexeme_end lexbuf) ^ err)
let rec concat_bareword_paren accu = function
@@ -81,7 +81,7 @@ let rec concat_bareword_paren accu = function
| BAREWORD("N_", _) :: PAREN(_) :: _ ->
concat_bareword_paren (e :: accu) l
| _ ->
- warn_with_pos pos "N(...) must follow the #-PO: comment, with nothing in between" ;
+ warn_with_pos [Warn_MDK_Common] pos "N(...) must follow the #-PO: comment, with nothing in between" ;
concat_bareword_paren accu l)
| [] -> List.rev accu
| e :: l ->
@@ -267,7 +267,7 @@ let current_string_start_line = ref 0
let die_in_string lexbuf err = failwith (pos2sfull_with !current_string_start_pos (lexeme_end lexbuf) ^ err)
let warn_escape_unneeded lexbuf c =
- let s = String.make 1 c in warn lexbuf ("you can replace \\" ^ s ^ " with " ^ s)
+ let s = String.make 1 c in warn [Warn_suggest_simpler] lexbuf ("you can replace \\" ^ s ^ " with " ^ s)
let next_interpolated toks =
let r = Stack.top building_current_string in
Queue.push (!r, toks) (Stack.top building_current_interpolated_string) ;
@@ -301,7 +301,7 @@ let ins_to_string t lexbuf =
(match !string_escape_useful, s with
| Right c, [ _, [] ] ->
let s = String.make 1 c in
- warn_with_pos pos ("you can replace \"xxx\\" ^ s ^ "xxx\" with 'xxx" ^ s ^ "xxx', that way you don't need to escape <" ^ s ^ ">")
+ warn_with_pos [Warn_suggest_simpler] pos ("you can replace \"xxx\\" ^ s ^ "xxx\" with 'xxx" ^ s ^ "xxx', that way you don't need to escape <" ^ s ^ ">")
| _ ->
if !string_quote_escape then
let full_s = String.concat "" (List.map fst s) in
@@ -311,7 +311,7 @@ let ins_to_string t lexbuf =
if c = ')' then nb - 1 else nb
) 0 full_s in
if nb = 0 then
- warn_with_pos pos "you can replace \"xxx\\\"xxx\" with qq(xxx\"xxx), that way you don't need to escape <\">"
+ warn_with_pos [Warn_suggest_simpler] pos "you can replace \"xxx\\\"xxx\" with qq(xxx\"xxx), that way you don't need to escape <\">"
);
not_ok_for_match := lexeme_end lexbuf;
@@ -326,8 +326,8 @@ let next t lexbuf = next_s (lexeme lexbuf) t lexbuf
let ins_re re_delimited_string lexbuf =
let s, pos = ins re_delimited_string lexbuf in
List.iter (fun (s, _) ->
- if str_contains s "[^\\s]" then warn lexbuf "you can replace [^\\s] with \\S";
- if str_contains s "[^\\w]" then warn lexbuf "you can replace [^\\w] with \\W"
+ if str_contains s "[^\\s]" then warn [Warn_suggest_simpler] lexbuf "you can replace [^\\s] with \\S";
+ if str_contains s "[^\\w]" then warn [Warn_suggest_simpler] lexbuf "you can replace [^\\w] with \\W"
) s ;
s, pos
@@ -404,8 +404,8 @@ let set_delimit_char lexbuf op =
let c = lexeme_char lexbuf (String.length op) in
delimit_char := c;
match c with
- | '@' -> warn lexbuf ("don't use " ^ op ^ "@...@, replace @ with / ! , or |")
- | ':' -> warn lexbuf ("don't use " ^ op ^ ":...:, replace : with / ! , or |")
+ | '@' -> warn [Warn_complex_expressions] lexbuf ("don't use " ^ op ^ "@...@, replace @ with / ! , or |")
+ | ':' -> warn [Warn_complex_expressions] lexbuf ("don't use " ^ op ^ ":...:, replace : with / ! , or |")
| _ -> ()
let set_delimit_char_open lexbuf op =
@@ -417,9 +417,9 @@ let set_delimit_char_open lexbuf op =
| _ -> internal_error "set_delimit_char_open"
in
if op = "qx" then
- warn lexbuf (Printf.sprintf "don't use qx%c...%c, use `...` instead" char_open char_close)
+ warn [Warn_complex_expressions] lexbuf (Printf.sprintf "don't use qx%c...%c, use `...` instead" char_open char_close)
else if char_open = '{' then
- warn lexbuf ("don't use " ^ op ^ "{...}, use " ^ op ^ "(...) instead");
+ warn [Warn_complex_expressions] lexbuf ("don't use " ^ op ^ "{...}, use " ^ op ^ "(...) instead");
delimit_char_open := char_open;
delimit_char_close := char_close
}
@@ -498,7 +498,7 @@ rule token = parse
| "=" | "+=" | "-=" | "*=" | ".=" | "|=" | "&=" | "^=" | "||=" | "&&=" { ASSIGN(lexeme lexbuf, pos lexbuf) }
| "<<=" | ">>=" | "**=" {
- warn lexbuf (Printf.sprintf "don't use \"%s\", use the expanded version instead" (lexeme lexbuf)) ;
+ warn [Warn_complex_expressions] lexbuf (Printf.sprintf "don't use \"%s\", use the expanded version instead" (lexeme lexbuf)) ;
ASSIGN(lexeme lexbuf, pos lexbuf)
}
@@ -634,7 +634,7 @@ rule token = parse
set_delimit_char lexbuf "qw" ;
current_string_start_line := !current_file_current_line;
let s, pos = raw_ins delimited_string lexbuf in
- warn_with_pos pos (Printf.sprintf "don't use qw%c...%c, use qw(...) instead" !delimit_char !delimit_char) ;
+ warn_with_pos [Warn_complex_expressions] pos (Printf.sprintf "don't use qw%c...%c, use qw(...) instead" !delimit_char !delimit_char) ;
QUOTEWORDS(s, pos)
}
@@ -918,7 +918,7 @@ and string_escape = parse
| Qq -> if c <> !delimit_char_open && c <> !delimit_char_close then warn_escape_unneeded lexbuf c
| Here_doc -> warn_escape_unneeded lexbuf c
| Delimited -> if c = !delimit_char then
- warn lexbuf ("change the delimit character " ^ String.make 1 !delimit_char ^ " to get rid of this escape")
+ warn [Warn_suggest_simpler] lexbuf ("change the delimit character " ^ String.make 1 !delimit_char ^ " to get rid of this escape")
else warn_escape_unneeded lexbuf c);
let s = if c = '"' then String.make 1 c else "\\" ^ String.make 1 c in
next_s s (Stack.pop next_rule) lexbuf
@@ -938,7 +938,7 @@ and re_string_escape = parse
| _ {
let c = lexeme_char lexbuf 0 in
if c = !delimit_char then
- warn lexbuf ("change the delimit character " ^ String.make 1 !delimit_char ^ " to get rid of this escape")
+ warn [Warn_suggest_simpler] lexbuf ("change the delimit character " ^ String.make 1 !delimit_char ^ " to get rid of this escape")
else warn_escape_unneeded lexbuf c ;
next_s ("\\" ^ lexeme lexbuf) (Stack.pop next_rule) lexbuf
}
@@ -956,7 +956,7 @@ and string_interpolate_scalar = parse
| ident "->"? '{'
| '"' { putback lexbuf 1; next_s "$" (Stack.pop next_rule) lexbuf }
| eof { next_s "$" (Stack.pop next_rule) lexbuf }
-| _ { warn lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf)); next_s ("$" ^ lexeme lexbuf) (Stack.pop next_rule) lexbuf }
+| _ { warn [Warn_strange] lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf)); next_s ("$" ^ lexeme lexbuf) (Stack.pop next_rule) lexbuf }
and delimited_string_interpolate_scalar = parse (* needed for delimited string like m!foo$! where $! should not be taken as is... *)
| '$' ident
@@ -978,7 +978,7 @@ and delimited_string_interpolate_scalar = parse (* needed for delimited string l
| eof { next_s "$" (Stack.pop next_rule) lexbuf }
| _ {
let c = lexeme_char lexbuf 0 in
- if c <> !delimit_char && c <> '|' && c<>')' && c<>'/' && c<>' ' then warn lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf));
+ if c <> !delimit_char && c <> '|' && c<>')' && c<>'/' && c<>' ' then warn [Warn_strange] lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf));
putback lexbuf 1;
next_s "$" (Stack.pop next_rule) lexbuf
}
@@ -991,7 +991,7 @@ and string_interpolate_array = parse
| [ '@' '*' '<' '>' ']' '.' '(' ' ' ] { next_s ("@" ^ lexeme lexbuf) (Stack.pop next_rule) lexbuf }
| '"' { putback lexbuf 1; next_s "@" (Stack.pop next_rule) lexbuf }
| eof { next_s "@" (Stack.pop next_rule) lexbuf }
-| _ { warn lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf)); next_s ("@" ^ lexeme lexbuf) (Stack.pop next_rule) lexbuf }
+| _ { warn [Warn_strange] lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf)); next_s ("@" ^ lexeme lexbuf) (Stack.pop next_rule) lexbuf }
and delimited_string_interpolate_array = parse
| '$' ident
@@ -1003,7 +1003,7 @@ and delimited_string_interpolate_array = parse
| eof { next_s "@" (Stack.pop next_rule) lexbuf }
| _ {
let c = lexeme_char lexbuf 0 in
- if c <> !delimit_char then warn lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf));
+ if c <> !delimit_char then warn [Warn_strange] lexbuf (Printf.sprintf "weird \"%s\" in string" (lexeme lexbuf));
putback lexbuf 1;
next_s "@" (Stack.pop next_rule) lexbuf
}
diff --git a/perl_checker.src/parser.mly b/perl_checker.src/parser.mly
index 4b3f70c..88dca94 100644
--- a/perl_checker.src/parser.mly
+++ b/perl_checker.src/parser.mly
@@ -156,7 +156,7 @@ sideff: /* An expression which may have a side-effect */
decl:
| FORMAT BAREWORD ASSIGN {to_Call_op M_none "format" [Raw_string($2.any, get_pos $2) ; to_String false (new_1esp (fst $1.any) $1)] $1 $3}
| FORMAT ASSIGN {new_esp M_none Too_complex $1 $2}
-| func_decl semi_colon {if snd $1.any = None then die_rule "there is no need to pre-declare in Perl!" else (warn_rule "please don't use prototype pre-declaration" ; new_esp M_special Too_complex $1 $2) }
+| func_decl semi_colon {if snd $1.any = None then die_rule "there is no need to pre-declare in Perl!" else (warn_rule [Warn_normalized_expressions] "please don't use prototype pre-declaration" ; new_esp M_special Too_complex $1 $2) }
| func_decl BRACKET BRACKET_END {sp_n($2); sp_0_or_cr($3); let name, proto = $1.any in new_esp M_none (sub_declaration (name, proto) [] Real_sub_declaration) $1 $3}
| func_decl BRACKET lines BRACKET_END {sp_n($2); check_block_sub $3 $4; new_esp M_none (sub_declaration $1.any $3.any Real_sub_declaration) $1 $4}
| func_decl BRACKET BRACKET expr BRACKET_END BRACKET_END {sp_n($2); sp_p($3); sp_p($4); sp_p($5); sp_p($6); new_esp M_none (sub_declaration $1.any [hash_ref $4] Real_sub_declaration) $1 $6}
@@ -182,7 +182,7 @@ use_revision:
func_decl:
| SUB word { new_esp M_none ($2.any, None) $1 $2}
-| SUB BAREWORD_PAREN PAREN PAREN_END { warn_rule "remove carriage return between \"sub\" and the function name"; new_esp M_none (Ident(None, $2.any, get_pos $2), Some "") $1 $4 }
+| SUB BAREWORD_PAREN PAREN PAREN_END { warn_rule [Warn_white_space] "remove carriage return between \"sub\" and the function name"; new_esp M_none (Ident(None, $2.any, get_pos $2), Some "") $1 $4 }
| FUNC_DECL_WITH_PROTO {new_1esp (Ident(fst3 $1.any, snd3 $1.any, get_pos $1), Some (ter3 $1.any)) $1 }
listexpr: /* Basic list expressions */
@@ -242,15 +242,15 @@ term:
| term PATTERN_MATCH PATTERN_SUBST {sp_n($2); sp_p($3); check_unneeded_var_dollar_s ($1); to_Call_op_ (M_mixed[M_none; M_int]) P_expr "s///" ($1.any.expr :: from_PATTERN_SUBST $3) $1 $3}
| term PATTERN_MATCH_NOT PATTERN_SUBST {die_with_rawpos $2.pos "use =~ instead of !~ and negate the return value"}
-| term PATTERN_MATCH QR_PATTERN {warn $3.pos "use m/.../ or /.../ instead of qr/.../ when you do a pattern matching"; to_Call_op_ M_array P_expr "m//" ($1.any.expr :: from_PATTERN $3) $1 $3}
-| term PATTERN_MATCH_NOT QR_PATTERN {warn $3.pos "use m/.../ or /.../ instead of qr/.../ when you do a pattern matching"; to_Call_op_ M_int P_expr "!m//" ($1.any.expr :: from_PATTERN $3) $1 $3}
+| term PATTERN_MATCH QR_PATTERN {warn [Warn_traps] $3.pos "use m/.../ or /.../ instead of qr/.../ when you do a pattern matching"; to_Call_op_ M_array P_expr "m//" ($1.any.expr :: from_PATTERN $3) $1 $3}
+| term PATTERN_MATCH_NOT QR_PATTERN {warn [Warn_traps] $3.pos "use m/.../ or /.../ instead of qr/.../ when you do a pattern matching"; to_Call_op_ M_int P_expr "!m//" ($1.any.expr :: from_PATTERN $3) $1 $3}
| term PATTERN_MATCH scalar { new_pesp M_array P_expr (Call(Too_complex, [$1.any.expr ; $3.any ])) $1 $3}
| term PATTERN_MATCH_NOT scalar { new_pesp M_int P_expr (Call(Too_complex, [$1.any.expr ; $3.any ])) $1 $3}
-| term PATTERN_MATCH RAW_STRING {warn $3.pos "use a regexp, not a string"; to_Call_op_ M_array P_expr "m//" [ $1.any.expr; to_Raw_string $3 ] $1 $3}
-| term PATTERN_MATCH_NOT RAW_STRING {warn $3.pos "use a regexp, not a string"; to_Call_op_ M_int P_expr "!m//" [ $1.any.expr; to_Raw_string $3 ] $1 $3}
-| term PATTERN_MATCH STRING {warn $3.pos "use a regexp, not a string"; to_Call_op_ M_array P_expr "m//" [ $1.any.expr; to_String false $3 ] $1 $3}
-| term PATTERN_MATCH_NOT STRING {warn $3.pos "use a regexp, not a string"; to_Call_op_ M_int P_expr "!m//" [ $1.any.expr; to_String false $3 ] $1 $3}
+| term PATTERN_MATCH RAW_STRING {warn [Warn_complex_expressions] $3.pos "use a regexp, not a string"; to_Call_op_ M_array P_expr "m//" [ $1.any.expr; to_Raw_string $3 ] $1 $3}
+| term PATTERN_MATCH_NOT RAW_STRING {warn [Warn_complex_expressions] $3.pos "use a regexp, not a string"; to_Call_op_ M_int P_expr "!m//" [ $1.any.expr; to_Raw_string $3 ] $1 $3}
+| term PATTERN_MATCH STRING {warn [Warn_complex_expressions] $3.pos "use a regexp, not a string"; to_Call_op_ M_array P_expr "m//" [ $1.any.expr; to_String false $3 ] $1 $3}
+| term PATTERN_MATCH_NOT STRING {warn [Warn_complex_expressions] $3.pos "use a regexp, not a string"; to_Call_op_ M_int P_expr "!m//" [ $1.any.expr; to_String false $3 ] $1 $3}
| term QUESTION_MARK term COLON term {sp_p($2); sp_p($3); sp_p($4); sp_p($5); mcontext_check M_bool $1; to_Call_op_ (mcontext_merge $3.mcontext $5.mcontext) P_ternary "?:" (check_ternary_paras(prio_lo P_ternary $1, prio_lo_after P_ternary $3, prio_lo_after P_ternary $5)) $1 $5}
@@ -263,13 +263,13 @@ term:
sp_0($2);
match $1.any with
| "+" ->
- warn_rule "don't use unary +" ;
+ warn_rule [Warn_normalized_expressions] "don't use unary +" ;
to_Call_op_ (mcontext_float_or_int [$2.mcontext]) P_tight "+ unary" [$2.any.expr] $1 $2
| "-" ->
(match $2.any.expr with
| Ident(_, _, pos) when $2.spaces = Space_0 ->
let s = "-" ^ string_of_Ident $2.any.expr in
- warn_rule (Printf.sprintf "don't use %s, use '%s' instead" s s);
+ warn_rule [Warn_complex_expressions] (Printf.sprintf "don't use %s, use '%s' instead" s s);
new_pesp M_string P_tok (Raw_string(s, pos)) $1 $2
| _ -> to_Call_op_ (mcontext_float_or_int [$2.mcontext]) P_tight "- unary" [$2.any.expr] $1 $2)
| _ -> die_rule "syntax error"
@@ -280,7 +280,7 @@ term:
| DECR term {sp_0($2); mcontext_check M_int $2; to_Call_op_ (M_mixed [M_int ; M_none]) P_tight "--" [$2.any.expr] $1 $2}
| term INCR {sp_0($2); mcontext_check M_int $1; to_Call_op_ (M_mixed [M_int ; M_none]) P_tight "++ post" [$1.any.expr] $1 $2}
| term DECR {sp_0($2); mcontext_check M_int $1; to_Call_op_ (M_mixed [M_int ; M_none]) P_tight "-- post" [$1.any.expr] $1 $2}
-| NOT argexpr {warn_rule "don't use \"not\", use \"!\" instead"; mcontext_check_unop_l M_bool $2; to_Call_op_ M_bool P_and "not" ($2.any.expr) $1 $2}
+| NOT argexpr {warn_rule [Warn_normalized_expressions] "don't use \"not\", use \"!\" instead"; mcontext_check_unop_l M_bool $2; to_Call_op_ M_bool P_and "not" ($2.any.expr) $1 $2}
/* Constructors for anonymous data */
@@ -340,7 +340,7 @@ term:
| word BRACKET BRACKET expr BRACKET_END BRACKET_END listexpr %prec LSTOP {sp_n($2); sp_p($3); sp_p($4); sp_p($5); sp_p($6); new_pesp M_unknown (if $7.any.expr = [] then P_tok else P_call_no_paren) (call(Deref(I_func, $1.any), anonymous_sub None (new_esp (M_ref M_hash) [ hash_ref $4 ] $4 $4) :: $7.any.expr)) $1 $7} /* map { { foo } } @bar */
| word BRACKET BRACKET expr BRACKET_END semi_colon BRACKET_END listexpr %prec LSTOP {sp_n($2); sp_p($3); sp_p($4); sp_p($5); sp_p($7); new_pesp M_unknown (if $8.any.expr = [] then P_tok else P_call_no_paren) (call(Deref(I_func, $1.any), anonymous_sub None (new_esp (M_ref M_hash) [ hash_ref $4; Semi_colon ] $4 $4) :: $8.any.expr)) $1 $8} /* map { { foo }; } @bar */
-| term ARROW word_or_scalar parenthesized {sp_0($2); sp_0($3); sp_0($4); if $4.any.expr = [] then warn $4.pos "remove these unneeded parentheses"; new_pesp M_unknown P_tok (to_Method_call($1.any.expr, $3.any, $4.any.expr)) $1 $4} /* $foo->bar(list) */
+| term ARROW word_or_scalar parenthesized {sp_0($2); sp_0($3); sp_0($4); if $4.any.expr = [] then warn [Warn_suggest_simpler] $4.pos "remove these unneeded parentheses"; new_pesp M_unknown P_tok (to_Method_call($1.any.expr, $3.any, $4.any.expr)) $1 $4} /* $foo->bar(list) */
| term ARROW word_or_scalar {sp_0($2); sp_0($3); new_pesp M_unknown P_tok (to_Method_call($1.any.expr, $3.any, [])) $1 $3} /* $foo->bar */
| NEW word { sp_n($2); new_pesp (M_ref M_unknown) P_expr (to_Method_call ($2.any, Ident(None, "new", get_pos $1), [])) $1 $2} /* new Class */
@@ -405,7 +405,7 @@ restricted_subscripted: /* Some kind of subscripted expression */
| restricted_subscripted arrayref {sp_0($2); new_esp M_unknown_scalar (to_Deref_with(I_array, I_scalar, $1.any, only_one_array_ref $2)) $1 $2} /* $foo->[$bar][$baz] */
| restricted_subscripted parenthesized {sp_0($2); new_esp M_unknown (to_Deref_with(I_func , I_scalar, $1.any, List($2.any.expr))) $1 $2} /* $foo->{bar}(@args) */
-| restricted_subscripted ARROW word_or_scalar parenthesized {sp_0($2); sp_0($3); sp_0($4); if $4.any.expr = [] then warn $4.pos "remove these unneeded parentheses"; new_esp M_unknown (to_Method_call($1.any, $3.any, $4.any.expr)) $1 $4} /* $foo->bar(list) */
+| restricted_subscripted ARROW word_or_scalar parenthesized {sp_0($2); sp_0($3); sp_0($4); if $4.any.expr = [] then warn [Warn_suggest_simpler] $4.pos "remove these unneeded parentheses"; new_esp M_unknown (to_Method_call($1.any, $3.any, $4.any.expr)) $1 $4} /* $foo->bar(list) */
| restricted_subscripted ARROW word_or_scalar {sp_0($2); sp_0($3); new_esp M_unknown (to_Method_call($1.any, $3.any, [])) $1 $3} /* $foo->bar */
arrayref:
diff --git a/perl_checker.src/parser_helper.ml b/perl_checker.src/parser_helper.ml
index b4afdaf..bc22dd9 100644
--- a/perl_checker.src/parser_helper.ml
+++ b/perl_checker.src/parser_helper.ml
@@ -215,17 +215,16 @@ let rec get_pos_from_expr = function
let msg_with_rawpos (start, end_) msg = Info.pos2sfull_current start end_ ^ msg
let die_with_rawpos raw_pos msg = failwith (msg_with_rawpos raw_pos msg)
-let warn raw_pos msg = print_endline_flush (msg_with_rawpos raw_pos msg)
+let warn warn_types raw_pos msg = if Flags.are_warning_types_set warn_types then print_endline_flush (msg_with_rawpos raw_pos msg)
let die_rule msg = die_with_rawpos (Parsing.symbol_start(), Parsing.symbol_end()) msg
-let warn_rule msg = warn (Parsing.symbol_start(), Parsing.symbol_end()) msg
-let debug msg = if true then print_endline_flush msg
+let warn_rule warn_types msg = warn warn_types (Parsing.symbol_start(), Parsing.symbol_end()) msg
-let warn_verb pos msg = if not !Flags.quiet then warn (pos, pos) msg
-let warn_too_many_space start = warn_verb start "you should have only one space here"
-let warn_no_space start = warn_verb start "you should have a space here"
-let warn_cr start = warn_verb start "you should not have a carriage-return (\\n) here"
-let warn_space start = warn_verb start "you should not have a space here"
+let warn_verb warn_types pos msg = if not !Flags.quiet then warn warn_types (pos, pos) msg
+let warn_too_many_space start = warn_verb [Warn_white_space] start "you should have only one space here"
+let warn_no_space start = warn_verb [Warn_white_space] start "you should have a space here"
+let warn_cr start = warn_verb [Warn_white_space] start "you should not have a carriage-return (\\n) here"
+let warn_space start = warn_verb [Warn_white_space] start "you should not have a space here"
let rec prio_less = function
| P_none, _ | _, P_none -> internal_error "prio_less"
@@ -285,13 +284,13 @@ let prio_lo_check pri_out pri_in pos expr =
| P_paren pri_in' ->
if pri_in' <> pri_out &&
prio_less(pri_in', pri_out) && not_complex (un_parenthesize expr) then
- warn pos "unneeded parentheses"
+ warn [Warn_suggest_simpler] pos "unneeded parentheses"
| _ -> ())
else
(match expr with
| Call_op ("print", [Deref (I_star, Ident (None, "STDOUT", _)); Deref(I_scalar, ident)], _) ->
- warn pos (sprintf "use parentheses: replace \"print $%s ...\" with \"print($%s ...)\"" (string_of_Ident ident) (string_of_Ident ident))
- | _ -> warn pos "missing parentheses (needed for clarity)")
+ warn [Warn_traps] pos (sprintf "use parentheses: replace \"print $%s ...\" with \"print($%s ...)\"" (string_of_Ident ident) (string_of_Ident ident))
+ | _ -> warn [Warn_traps] pos "missing parentheses (needed for clarity)")
let prio_lo pri_out in_ = prio_lo_check pri_out in_.any.priority in_.pos in_.any.expr ; in_.any.expr
@@ -347,7 +346,7 @@ let sp_cr esp =
| Space_none -> ()
| Space_0
| Space_1
- | Space_n -> warn_verb (get_pos_start esp) "you should have a carriage-return (\\n) here"
+ | Space_n -> warn_verb [Warn_white_space] (get_pos_start esp) "you should have a carriage-return (\\n) here"
| Space_cr -> ()
let sp_same esp1 esp2 =
@@ -393,10 +392,10 @@ let word_alone esp =
Deref(I_func, word)
| "hex" | "ref" ->
- warn_rule (sprintf "please use \"%s $_\" instead of \"%s\"" f f) ;
+ warn_rule [Warn_complex_expressions] (sprintf "please use \"%s $_\" instead of \"%s\"" f f) ;
Call(Deref(I_func, word), [ Raw_string(" ", pos) ; var_dollar_ pos ])
| "time" | "wantarray" | "fork" | "getppid" | "arch" ->
- warn_rule (sprintf "please use %s() instead of %s" f f) ;
+ warn_rule [Warn_complex_expressions] (sprintf "please use %s() instead of %s" f f) ;
Deref(I_func, word)
| _ -> word
in
@@ -429,9 +428,9 @@ let check_parenthesized_first_argexpr_with_Ident ident esp =
| Ident(Some _, _, _) ->
(match esp.any.expr with
| [e] when is_parenthesized e -> ()
- | _ -> warn_rule "use parentheses around argument (otherwise it might cause syntax errors if the package is \"require\"d and not \"use\"d")
+ | _ -> warn_rule [Warn_suggest_simpler] "use parentheses around argument (otherwise it might cause syntax errors if the package is \"require\"d and not \"use\"d")
| Ident(None, word, _) when List.mem word ["ref" ; "readlink"] ->
- if esp.any.priority <> P_tok then warn_rule "use parentheses around argument"
+ if esp.any.priority <> P_tok then warn_rule [Warn_complex_expressions] "use parentheses around argument"
| _ -> ());
check_parenthesized_first_argexpr (string_of_Ident ident) esp
@@ -442,19 +441,19 @@ let check_hash_subscript esp =
char_is_alpha s.[0] && (String.length s = 1 || string_forall_with char_is_alphanumerical_ 1 s)
in
match esp.any.expr with
- | List [String ([(s, List [])], _)] when can_be_raw_string s -> warn esp.pos (sprintf "{\"%s\"} can be written {%s}" s s)
- | List [Raw_string(s, _)] when can_be_raw_string s -> warn esp.pos (sprintf "{'%s'} can be written {%s}" s s)
+ | List [String ([(s, List [])], _)] when can_be_raw_string s -> warn [Warn_suggest_simpler] esp.pos (sprintf "{\"%s\"} can be written {%s}" s s)
+ | List [Raw_string(s, _)] when can_be_raw_string s -> warn [Warn_suggest_simpler] esp.pos (sprintf "{'%s'} can be written {%s}" s s)
| _ -> ()
let check_arrow_needed esp1 esp2 =
match esp1.any.expr with
| Deref_with(I_array, I_scalar, List [List [Call _]], _) -> () (* "->" needed for (f())[0]->{XX} *)
- | Deref_with _ -> warn esp2.pos "the arrow \"->\" is unneeded"
+ | Deref_with _ -> warn [Warn_suggest_simpler] esp2.pos "the arrow \"->\" is unneeded"
| _ -> ()
let check_scalar_subscripted esp =
match esp.any with
- | Deref(I_scalar, Deref _) -> warn_rule "for complex dereferencing, use \"->\""
+ | Deref(I_scalar, Deref _) -> warn_rule [Warn_complex_expressions] "for complex dereferencing, use \"->\""
| _ -> ()
let negatable_ops = collect (fun (a, b) -> [ a, b ; b, a ]) [
@@ -465,13 +464,13 @@ let negatable_ops = collect (fun (a, b) -> [ a, b ; b, a ]) [
let check_negatable_expr esp =
match un_parenthesize_full esp.any.expr with
| Call_op("m//", var :: _, _) when not (is_var_dollar_ var) ->
- warn_rule "!($var =~ /.../) is better written $var !~ /.../"
+ warn_rule [Warn_suggest_simpler] "!($var =~ /.../) is better written $var !~ /.../"
| Call_op("!m//", var :: _, _) when not (is_var_dollar_ var) ->
- warn_rule "!($var !~ /.../) is better written $var =~ /.../"
+ warn_rule [Warn_suggest_simpler] "!($var !~ /.../) is better written $var =~ /.../"
| Call_op(op, _, _) ->
(try
let neg_op = List.assoc op negatable_ops in
- warn_rule (Printf.sprintf "!($foo %s $bar) is better written $foo %s $bar" op neg_op)
+ warn_rule [Warn_suggest_simpler] (Printf.sprintf "!($foo %s $bar) is better written $foo %s $bar" op neg_op)
with Not_found -> ())
| _ -> ()
@@ -495,42 +494,42 @@ let check_ternary_paras(cond, a, b) =
| e -> dont_need_short_circuit_rec e
in
let check_ternary_para = function
- | List [] -> warn_rule "you may use if_() here\n beware that the short-circuit semantic of ?: is not kept\n if you want to keep the short-circuit behaviour, replace () with @{[]} and there will be no warning anymore"
+ | List [] -> warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you may use if_() here\n beware that the short-circuit semantic of ?: is not kept\n if you want to keep the short-circuit behaviour, replace () with @{[]} and there will be no warning anymore"
| _ -> ()
in
if dont_need_short_circuit a || is_same_fromparser cond a then check_ternary_para b;
if dont_need_short_circuit b || is_same_fromparser cond b then check_ternary_para a;
- if is_same_fromparser cond a && is_a_scalar a && is_a_scalar b then warn_rule "you can replace \"$foo ? $foo : $bar\" with \"$foo || $bar\"";
+ if is_same_fromparser cond a && is_a_scalar a && is_a_scalar b then warn_rule [Warn_suggest_simpler] "you can replace \"$foo ? $foo : $bar\" with \"$foo || $bar\"";
[ cond; a; b ]
let check_unneeded_var_dollar_ esp =
- if is_var_dollar_ esp.any.expr then warn esp.pos "\"$_ =~ /regexp/\" can be written \"/regexp/\"" else
- if is_var_number_match esp.any.expr then warn esp.pos "do not use the result of a match (eg: $1) to match another pattern"
+ if is_var_dollar_ esp.any.expr then warn [Warn_suggest_simpler] esp.pos "\"$_ =~ /regexp/\" can be written \"/regexp/\"" else
+ if is_var_number_match esp.any.expr then warn [Warn_complex_expressions] esp.pos "do not use the result of a match (eg: $1) to match another pattern"
let check_unneeded_var_dollar_not esp =
- if is_var_dollar_ esp.any.expr then warn esp.pos "\"$_ !~ /regexp/\" can be written \"!/regexp/\"" else
- if is_var_number_match esp.any.expr then warn esp.pos "do not use the result of a match (eg: $1) to match another pattern"
+ if is_var_dollar_ esp.any.expr then warn [Warn_suggest_simpler] esp.pos "\"$_ !~ /regexp/\" can be written \"!/regexp/\"" else
+ if is_var_number_match esp.any.expr then warn [Warn_complex_expressions] esp.pos "do not use the result of a match (eg: $1) to match another pattern"
let check_unneeded_var_dollar_s esp =
let expr = esp.any.expr in
- if is_var_dollar_ expr then warn esp.pos "\"$_ =~ s/regexp/.../\" can be written \"s/regexp/.../\"" else
- if is_var_number_match expr then die_with_rawpos esp.pos "do not modify the result of a match (eg: $1)" else
+ if is_var_dollar_ expr then warn [Warn_suggest_simpler] esp.pos "\"$_ =~ s/regexp/.../\" can be written \"s/regexp/.../\"" else
+ if is_var_number_match expr then warn [Warn_traps] esp.pos "do not modify the result of a match (eg: $1)" else
let expr = match expr with
| List [List [Call_op("=", [ expr; _], _)]] -> expr (* check $xx in ($xx = ...) =~ ... *)
| _ -> expr in
- if is_a_string expr || not (is_a_scalar expr) then warn esp.pos "you can only use s/// on a variable"
+ if is_a_string expr || not (is_a_scalar expr) then warn [Warn_complex_expressions] esp.pos "you can only use s/// on a variable"
let check_my esp = if esp.any <> "my" then die_rule "syntax error"
-let check_foreach esp = if esp.any = "for" then warn esp.pos "write \"foreach\" instead of \"for\""
-let check_for esp = if esp.any = "foreach" then warn esp.pos "write \"for\" instead of \"foreach\""
+let check_foreach esp = if esp.any = "for" then warn [Warn_normalized_expressions] esp.pos "write \"foreach\" instead of \"for\""
+let check_for esp = if esp.any = "foreach" then warn [Warn_normalized_expressions] esp.pos "write \"for\" instead of \"foreach\""
let check_for_foreach esp arg =
match arg.any.expr with
| List [ Deref(I_scalar, _) ] ->
- if esp.any = "foreach" then warn esp.pos "you are using the special fpons trick to locally set $_ with a value, for this please use \"for\" instead of \"foreach\""
+ if esp.any = "foreach" then warn [Warn_normalized_expressions] esp.pos "you are using the special trick to locally set $_ with a value, for this please use \"for\" instead of \"foreach\""
| List [ Deref_with(context, I_scalar, _, _) ] when context <> I_func ->
- if esp.any = "foreach" then warn esp.pos "you are using the special fpons trick to locally set $_ with a value, for this please use \"for\" instead of \"foreach\""
+ if esp.any = "foreach" then warn [Warn_normalized_expressions] esp.pos "you are using the special trick to locally set $_ with a value, for this please use \"for\" instead of \"foreach\""
| List [ Deref(I_hash, _) ] ->
- warn esp.pos "foreach with a hash is usually an error"
+ warn [Warn_traps] esp.pos "foreach with a hash is usually an error"
| _ ->
- if esp.any = "for" then warn esp.pos "write \"foreach\" instead of \"for\""
+ if esp.any = "for" then warn [Warn_normalized_expressions] esp.pos "write \"foreach\" instead of \"for\""
let check_block_sub esp_lines esp_BRACKET_END =
match esp_lines.any with
@@ -541,7 +540,7 @@ let check_block_sub esp_lines esp_BRACKET_END =
sp_p esp_BRACKET_END ;
if esp_BRACKET_END.spaces <> Space_cr then
- (if last l = Semi_colon then warn_verb (get_pos_end esp_lines) "spurious \";\" before closing block")
+ (if last l = Semi_colon then warn_verb [Warn_white_space] (get_pos_end esp_lines) "spurious \";\" before closing block")
let check_block_ref esp_lines esp_BRACKET_END =
let l = esp_lines.any in
@@ -550,11 +549,11 @@ let check_block_ref esp_lines esp_BRACKET_END =
else sp_same esp_lines esp_BRACKET_END ;
if esp_BRACKET_END.spaces <> Space_cr then
- (if l <> [] && last l = Semi_colon then warn_verb (get_pos_end esp_lines) "spurious \";\" before closing block")
+ (if l <> [] && last l = Semi_colon then warn_verb [Warn_white_space] (get_pos_end esp_lines) "spurious \";\" before closing block")
let check_unless_else elsif else_ =
- if elsif.any <> [] then warn elsif.pos "don't use \"elsif\" with \"unless\" (replace \"unless\" with \"if\")";
- if else_.any <> [] then warn else_.pos "don't use \"else\" with \"unless\" (replace \"unless\" with \"if\")"
+ if elsif.any <> [] then warn [Warn_complex_expressions] elsif.pos "don't use \"elsif\" with \"unless\" (replace \"unless\" with \"if\")";
+ if else_.any <> [] then warn [Warn_complex_expressions] else_.pos "don't use \"else\" with \"unless\" (replace \"unless\" with \"if\")"
let check_my_our_paren { any = ((comma_closed, _), l) } after_esp =
(if l = [] then sp_0 else sp_1) after_esp ;
@@ -566,7 +565,7 @@ let check_simple_pattern = function
st.[0] = '^' && st.[String.length st - 1] = '$' then
let st = skip_n_char_ 1 1 st in
if string_forall_with char_is_alphanumerical_ 0 st then
- warn_rule (sprintf "\"... =~ /^%s$/\" is better written \"... eq '%s'\"" st st)
+ warn_rule [Warn_suggest_simpler] (sprintf "\"... =~ /^%s$/\" is better written \"... eq '%s'\"" st st)
| _ -> ()
let rec only_one esp =
@@ -580,7 +579,7 @@ let only_one_array_ref esp =
let e = only_one esp in
(match e with
| Call_op("last_array_index", [Deref(I_array, e)], _) ->
- warn esp.pos (sprintf "you can replace $#%s with -1" (string_of_Ident e))
+ warn [Warn_suggest_simpler] esp.pos (sprintf "you can replace $#%s with -1" (string_of_Ident e))
| _ -> ());
e
@@ -610,7 +609,7 @@ let deref_raw context e =
let fq, ident = split_name_or_fq_name s in
Ident(fq, ident, pos)
| Deref(I_scalar, (Ident _ as ident)) ->
- warn_rule (sprintf "%s{$%s} can be written %s$%s" (context2s context) (string_of_Ident ident) (context2s context) (string_of_Ident ident));
+ warn_rule [Warn_suggest_simpler] (sprintf "%s{$%s} can be written %s$%s" (context2s context) (string_of_Ident ident) (context2s context) (string_of_Ident ident));
e
| _ -> e
in Deref(context, e)
@@ -623,7 +622,7 @@ let to_Method_call (object_, method_, para) =
| Ident(Some _, _, _) -> Call(Deref(I_func, method_), maybe_to_Raw_string object_ :: para)
| _ -> Method_call(maybe_to_Raw_string object_, maybe_to_Raw_string method_, para)
let to_Deref_with(from_context, to_context, ref_, para) =
- if is_not_a_scalar ref_ then warn_rule "bad deref";
+ if is_not_a_scalar ref_ then warn_rule [] "bad deref";
Deref_with(from_context, to_context, ref_, para)
@@ -660,73 +659,73 @@ let remove_call_with_same_para_special = function
let check_My_under_condition msg = function
| List [ My_our("my", _, _) ] ->
- warn_rule "this is stupid"
+ warn_rule [Warn_traps] "this is stupid"
| List [ Call_op("=", [ My_our("my", _, _); _ ], _) ] ->
- warn_rule msg
+ warn_rule [Warn_traps] msg
| _ -> ()
let cook_call_op op para pos =
(match op with
| "le" | "ge" | "eq" | "ne" | "gt" | "lt" | "cmp" ->
if List.exists (function Num _ -> true | _ -> false) para then
- warn_rule (sprintf "you should use a number operator, not the string operator \"%s\" (or replace the number with a string)" op)
+ warn_rule [Warn_traps] (sprintf "you should use a number operator, not the string operator \"%s\" (or replace the number with a string)" op)
| "." ->
if List.exists (function Call(Deref(I_func, Ident(None, "N_", _)), _) -> true | _ -> false) para then
- warn_rule "N_(\"xxx\") . \"yyy\" is dumb since the string \"xxx\" will never get translated"
+ warn_rule [Warn_MDK_Common; Warn_traps] "N_(\"xxx\") . \"yyy\" is dumb since the string \"xxx\" will never get translated"
| _ -> ());
(match op, para with
| "if", List [Call_op ("=", [ _; e ], _)] :: _ when is_always_true e || is_always_false e ->
- warn_rule "are you sure you did not mean \"==\" instead of \"=\"?"
+ warn_rule [Warn_traps] "are you sure you did not mean \"==\" instead of \"=\"?"
| "foreach", [ _; Block [ expr ; Semi_colon ] ]
| "foreach", [ _; Block [ expr ] ] ->
(match expr with
| Call_op("if infix", [ List [ Call(Deref(I_func, Ident(None, "push", _)), [ Deref(I_array, (Ident _ as l)) ; Deref(I_scalar, Ident(None, "_", _)) ]) ] ; _ ], _) ->
let l = string_of_Ident l in
- warn_rule (sprintf "use \"push @%s, grep { ... } ...\" instead of \"foreach (...) { push @%s, $_ if ... }\"\n or sometimes \"@%s = grep { ... } ...\"" l l l)
+ warn_rule [Warn_suggest_functional] (sprintf "use \"push @%s, grep { ... } ...\" instead of \"foreach (...) { push @%s, $_ if ... }\"\n or sometimes \"@%s = grep { ... } ...\"" l l l)
| Call_op("if infix", [ List [ Call(Deref(I_func, Ident(None, "push", _)), [ Deref(I_array, (Ident _ as l)); _ ]) ] ; _ ], _) ->
let l = string_of_Ident l in
- warn_rule (sprintf "use \"push @%s, map { ... ? ... : () } ...\" instead of \"foreach (...) { push @%s, ... if ... }\"\n or sometimes \"@%s = map { ... ? ... : () } ...\"\n or sometimes \"@%s = map { if_(..., ...) } ...\"" l l l l)
+ warn_rule [Warn_suggest_functional] (sprintf "use \"push @%s, map { ... ? ... : () } ...\" instead of \"foreach (...) { push @%s, ... if ... }\"\n or sometimes \"@%s = map { ... ? ... : () } ...\"\n or sometimes \"@%s = map { if_(..., ...) } ...\"" l l l l)
| List [ Call(Deref(I_func, Ident(None, "push", _)), [ Deref(I_array, (Ident _ as l)); _ ]) ] ->
let l = string_of_Ident l in
- warn_rule (sprintf "use \"push @%s, map { ... } ...\" instead of \"foreach (...) { push @%s, ... }\"\n or sometimes \"@%s = map { ... } ...\"" l l l)
+ warn_rule [Warn_suggest_functional] (sprintf "use \"push @%s, map { ... } ...\" instead of \"foreach (...) { push @%s, ... }\"\n or sometimes \"@%s = map { ... } ...\"" l l l)
| _ -> ())
| "=", [My_our _; Ident(None, "undef", _)] ->
- warn pos "no need to initialize variable, it's done by default"
+ warn [Warn_suggest_simpler] pos "no need to initialize variable, it's done by default"
| "=", [My_our _; List[]] ->
- if Info.is_on_same_line_current pos then warn pos "no need to initialize variables, it's done by default"
+ if Info.is_on_same_line_current pos then warn [Warn_suggest_simpler] pos "no need to initialize variables, it's done by default"
| "=", [ Deref_with(I_array, I_scalar, id, Deref(I_array, id_)); _ ] when is_same_fromparser id id_ ->
- warn_rule "\"$a[@a] = ...\" is better written \"push @a, ...\""
+ warn_rule [Warn_suggest_simpler] "\"$a[@a] = ...\" is better written \"push @a, ...\""
| "=", [ Deref(I_star, String ([(sf1, List [])], _)); _ ] ->
- warn_rule (sprintf "write *{'%s'} instead of *{\"%s\"}" sf1 sf1)
+ warn_rule [Warn_help_perl_checker] (sprintf "write *{'%s'} instead of *{\"%s\"}" sf1 sf1)
| "||=", List [ List _ ] :: _
- | "&&=", List [ List _ ] :: _ -> warn_rule "remove the parentheses"
+ | "&&=", List [ List _ ] :: _ -> warn_rule [Warn_complex_expressions] "remove the parentheses"
| "||=", e :: _
- | "&&=", e :: _ -> if is_not_a_scalar e then warn_rule (sprintf "\"%s\" is only useful with a scalar" op)
+ | "&&=", e :: _ -> if is_not_a_scalar e then warn_rule [Warn_traps] (sprintf "\"%s\" is only useful with a scalar" op)
| "==", [Call_op("last_array_index", _, _); Num(n, _)] ->
- warn_rule (sprintf "$#x == %s is better written @x == %d" n (1 + int_of_string n))
+ warn_rule [Warn_suggest_simpler] (sprintf "$#x == %s is better written @x == %d" n (1 + int_of_string n))
| "==", [Call_op("last_array_index", _, _); Call_op("- unary", [Num (n, _)], _)] ->
- warn_rule (sprintf "$#x == -%s is better written @x == %d" n (1 - int_of_string n))
+ warn_rule [Warn_suggest_simpler] (sprintf "$#x == -%s is better written @x == %d" n (1 - int_of_string n))
- | "||", e :: _ when is_always_true e -> warn_rule "<constant> || ... is the same as <constant>"
- | "&&", e :: _ when is_always_false e -> warn_rule "<constant> && ... is the same as <constant>"
- | "||", e :: _ when is_always_false e -> warn_rule "<constant> || ... is the same as ..."
- | "&&", e :: _ when is_always_true e -> warn_rule "<constant> && ... is the same as ..."
+ | "||", e :: _ when is_always_true e -> warn_rule [Warn_strange] "<constant> || ... is the same as <constant>"
+ | "&&", e :: _ when is_always_false e -> warn_rule [Warn_strange] "<constant> && ... is the same as <constant>"
+ | "||", e :: _ when is_always_false e -> warn_rule [Warn_strange] "<constant> || ... is the same as ..."
+ | "&&", e :: _ when is_always_true e -> warn_rule [Warn_strange] "<constant> && ... is the same as ..."
- | "or", e :: _ when is_always_true (un_parenthesize_full e) -> warn_rule "<constant> or ... is the same as <constant>"
- | "and", e :: _ when is_always_false (un_parenthesize_full e) -> warn_rule "<constant> and ... is the same as <constant>"
- | "or", e :: _ when is_always_false (un_parenthesize_full e) -> warn_rule "<constant> or ... is the same as ..."
- | "and", e :: _ when is_always_true (un_parenthesize_full e) -> warn_rule "<constant> and ... is the same as ..."
+ | "or", e :: _ when is_always_true (un_parenthesize_full e) -> warn_rule [Warn_strange] "<constant> or ... is the same as <constant>"
+ | "and", e :: _ when is_always_false (un_parenthesize_full e) -> warn_rule [Warn_strange] "<constant> and ... is the same as <constant>"
+ | "or", e :: _ when is_always_false (un_parenthesize_full e) -> warn_rule [Warn_strange] "<constant> or ... is the same as ..."
+ | "and", e :: _ when is_always_true (un_parenthesize_full e) -> warn_rule [Warn_strange] "<constant> and ... is the same as ..."
| "or", [ List [ Deref(I_scalar, id) ]; List [ Call_op("=", [ Deref(I_scalar, id_); _], _) ] ] when is_same_fromparser id id_ ->
- warn_rule "\"$foo or $foo = ...\" can be written \"$foo ||= ...\""
+ warn_rule [Warn_suggest_simpler] "\"$foo or $foo = ...\" can be written \"$foo ||= ...\""
| "and", [ _cond ; expr ] -> check_My_under_condition "replace \"<cond> and my $foo = ...\" with \"my $foo = <cond> && ...\"" expr
| "or", [ _cond ; expr ] -> check_My_under_condition "replace \"<cond> or my $foo = ...\" with \"my $foo = !<cond> && ...\"" expr
@@ -736,11 +735,11 @@ let cook_call_op op para pos =
match op, para with
| "=", [ Deref(I_star, (Ident _ as f1)); Deref(I_star, (Ident _ as f2)) ] ->
let s1, s2 = string_of_Ident f1, string_of_Ident f2 in
- warn pos (sprintf "\"*%s = *%s\" is better written \"*%s = \\&%s\"" s1 s2 s1 s2) ;
+ warn [Warn_complex_expressions] pos (sprintf "\"*%s = *%s\" is better written \"*%s = \\&%s\"" s1 s2 s1 s2) ;
sub_declaration (f1, None) [ call_with_same_para_special(Deref(I_func, f2)) ] Glob_assign
| "=", [ Deref(I_star, Raw_string(sf1, pos_f1)); Deref(I_star, (Ident _ as f2)) ] ->
let s2 = string_of_Ident f2 in
- warn pos (sprintf "\"*{'%s'} = *%s\" is better written \"*{'%s'} = \\&%s\"" sf1 s2 sf1 s2) ;
+ warn [Warn_help_perl_checker] pos (sprintf "\"*{'%s'} = *%s\" is better written \"*{'%s'} = \\&%s\"" sf1 s2 sf1 s2) ;
sub_declaration (Ident(None, sf1, pos_f1), None) [ call_with_same_para_special(Deref(I_func, f2)) ] Glob_assign
| "=", [ Deref(I_star, (Ident _ as f1)); Ref(I_scalar, Deref(I_func, (Ident _ as f2))) ] ->
@@ -760,7 +759,7 @@ let to_Call_op_ mcontext prio op para esp_start esp_end =
let pos = raw_pos_range esp_start esp_end in
new_any mcontext { priority = prio ; expr = cook_call_op op para pos } esp_start.spaces pos
let to_Call_assign_op_ mcontext prio op left right esp_left esp_end =
- if not (is_lvalue left) then warn esp_left.pos "invalid lvalue";
+ if not (is_lvalue left) then warn [Warn_strange] esp_left.pos "invalid lvalue";
to_Call_op_ mcontext prio op [ left ; right ] esp_left esp_end
let followed_by_comma expr true_comma =
@@ -784,10 +783,10 @@ let check_format_a_la_printf s pos =
| '%' -> contexts
| 'd' -> M_int :: contexts
| 's' | 'c' -> M_string :: contexts
- | c -> warn (pos + i', pos + i') (sprintf "invalid command %%%c" c); contexts
+ | c -> warn [Warn_strange] (pos + i', pos + i') (sprintf "invalid command %%%c" c); contexts
in
check_format_a_la_printf_ contexts (i' + 2)
- with Invalid_argument _ -> warn (pos + i', pos + i') "invalid command %" ; contexts
+ with Invalid_argument _ -> warn [Warn_strange] (pos + i', pos + i') "invalid command %" ; contexts
with Not_found -> contexts
in check_format_a_la_printf_ [] 0
@@ -851,18 +850,18 @@ let check_system_call = function
let has_p = List.exists (str_begins_with "-p") l in
let has_m = List.exists (str_begins_with "-m") l in
if has_p && has_m then ()
- else if has_p then warn_rule "you can replace system(\"mkdir -p ...\") with mkdir_p(...)"
- else if has_m then warn_rule "you can replace system(\"mkdir -m <mode> ...\") with mkdir(..., <mode>)"
- else warn_rule "you can replace system(\"mkdir ...\") with mkdir(...)"
+ else if has_p then warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace system(\"mkdir -p ...\") with mkdir_p(...)"
+ else if has_m then warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace system(\"mkdir -m <mode> ...\") with mkdir(..., <mode>)"
+ else warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace system(\"mkdir ...\") with mkdir(...)"
| _ -> ()
let call_raw force_non_builtin_func (e, para) =
let check_anonymous_block f = function
| [ Anonymous_sub _ ; Deref (I_hash, _) ] ->
- warn_rule ("a hash is not a valid parameter to function " ^ f)
+ warn_rule [Warn_strange] ("a hash is not a valid parameter to function " ^ f)
| Anonymous_sub _ :: _ -> ()
- | _ -> warn_rule (sprintf "always use \"%s\" with a block (eg: %s { ... } @list)" f f)
+ | _ -> warn_rule [Warn_complex_expressions] (sprintf "always use \"%s\" with a block (eg: %s { ... } @list)" f f)
in
match e with
@@ -870,21 +869,21 @@ let call_raw force_non_builtin_func (e, para) =
(match f with
| "join" ->
(match un_parenthesize_full_l para with
- | e :: _ when not (is_a_scalar e) -> warn_rule "first argument of join() must be a scalar";
- | [_] -> warn_rule "not enough parameters"
- | [_; e] when is_a_scalar e -> warn_rule "join('...', $foo) is the same as $foo"
+ | e :: _ when not (is_a_scalar e) -> warn_rule [Warn_traps] "first argument of join() must be a scalar";
+ | [_] -> warn_rule [Warn_traps] "not enough parameters"
+ | [_; e] when is_a_scalar e -> warn_rule [Warn_traps] "join('...', $foo) is the same as $foo"
| _ -> ())
| "length" ->
- if para = [] then warn_rule "length() with no parameter !?" else
- if is_not_a_scalar (List.hd para) then warn_rule "never use \"length @l\", it returns the length of the string int(@l)" ;
+ if para = [] then warn_rule [Warn_complex_expressions] (sprintf "please use \"%s $_\" instead of \"%s\"" f f) else
+ if is_not_a_scalar (List.hd para) then warn_rule [Warn_traps] "never use \"length @l\", it returns the length of the string int(@l)" ;
| "open" ->
(match para with
| [ List(Ident(None, name, _) :: _) ]
| Ident(None, name, _) :: _ ->
if not (List.mem name [ "STDIN" ; "STDOUT" ; "STDERR" ]) then
- warn_rule (sprintf "use a scalar instead of a bareword (eg: occurrences of %s with $%s)" name name)
+ warn_rule [Warn_complex_expressions] (sprintf "use a scalar instead of a bareword (eg: occurrences of %s with $%s)" name name)
| _ -> ())
| "N" | "N_" ->
@@ -897,9 +896,9 @@ let call_raw force_non_builtin_func (e, para) =
let contexts = check_format_a_la_printf s pos_offset in
if f = "N" then
if List.length para < List.length contexts then
- warn_rule "not enough parameters"
+ warn_rule [Warn_traps; Warn_MDK_Common] "not enough parameters"
else if List.length para > List.length contexts then
- warn_rule "too many parameters" ;
+ warn_rule [Warn_traps; Warn_MDK_Common] "too many parameters" ;
(*if String.contains s '\t' then warn_rule "tabulation in translated string must be written \\\\t";*)
(*if count_matching_char s '\n' > 10 then warn_rule "long string";*)
| [ List(String _ :: _) ] -> die_rule "don't use interpolated translated string, use %s or %d instead"
@@ -907,7 +906,7 @@ let call_raw force_non_builtin_func (e, para) =
| "if_" ->
(match para with
- | [ List [ _ ] ] -> warn_rule "not enough parameters";
+ | [ List [ _ ] ] -> warn_rule [Warn_traps; Warn_MDK_Common] "not enough parameters";
| _ -> ())
| "map" ->
@@ -915,15 +914,15 @@ let call_raw force_non_builtin_func (e, para) =
| Anonymous_sub(None, Block [ List [ Call(Deref(I_func, Ident(None, "if_", _)),
[ List [ _ ; Deref(I_scalar, Ident(None, "_", _)) ] ]) ] ], _) :: _ ->
- warn_rule "you can replace \"map { if_(..., $_) }\" with \"grep { ... }\""
+ warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace \"map { if_(..., $_) }\" with \"grep { ... }\""
| _ -> check_anonymous_block f para)
| "grep" ->
(match para with
| [ Anonymous_sub(None, Block [ List [ Call_op("not", [ Call(Deref(I_func, Ident(None, "member", _)), [ List(Deref(I_scalar, Ident(None, "_", _)) :: _) ]) ], _) ] ], _); _ ] ->
- warn_rule "you can replace \"grep { !member($_, ...) } @l\" with \"difference2([ @l ], [ ... ])\""
+ warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace \"grep { !member($_, ...) } @l\" with \"difference2([ @l ], [ ... ])\""
| [ Anonymous_sub(None, Block [ List [ Call(Deref(I_func, Ident(None, "member", _)), [ List(Deref(I_scalar, Ident(None, "_", _)) :: _) ]) ] ], _); _ ] ->
- warn_rule "you can replace \"grep { member($_, ...) } @l\" with \"intersection([ @l ], [ ... ])\""
+ warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace \"grep { member($_, ...) } @l\" with \"intersection([ @l ], [ ... ])\""
| _ -> check_anonymous_block f para)
| "any" ->
@@ -931,7 +930,7 @@ let call_raw force_non_builtin_func (e, para) =
[Anonymous_sub (None, Block
[ List [ Call_op("eq", [Deref(I_scalar, Ident(None, "_", _)); _ ], _) ] ],
_); _ ] ->
- warn_rule "you can replace \"any { $_ eq ... } @l\" with \"member(..., @l)\""
+ warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace \"any { $_ eq ... } @l\" with \"member(..., @l)\""
| _ -> check_anonymous_block f para)
| "grep_index" | "map_index" | "partition" | "uniq_"
@@ -943,7 +942,7 @@ let call_raw force_non_builtin_func (e, para) =
| "member" ->
(match para with
[ List [ _; Call(Deref(I_func, Ident(None, "keys", _)), _) ] ] ->
- warn_rule "you can replace \"member($xxx, keys %yyy)\" with \"exists $yyy{$xxx}\""
+ warn_rule [Warn_suggest_simpler; Warn_MDK_Common] "you can replace \"member($xxx, keys %yyy)\" with \"exists $yyy{$xxx}\""
| _ -> ())
| "pop" | "shift" ->
@@ -951,14 +950,14 @@ let call_raw force_non_builtin_func (e, para) =
| []
| [ Deref(I_array, _) ]
| [ List [ Deref(I_array, _) ] ] -> ()
- | _ -> warn_rule (f ^ " is expecting an array and nothing else"))
+ | _ -> warn_rule [Warn_traps] (f ^ " is expecting an array and nothing else"))
| "push" | "unshift" ->
(match para with
| Deref(I_array, _) :: l
| [ List (Deref(I_array, _) :: l) ] ->
- if l = [] then warn_rule ("you must give some arguments to " ^ f)
- | _ -> warn_rule (f ^ " is expecting an array"))
+ if l = [] then warn_rule [Warn_traps] ("you must give some arguments to " ^ f)
+ | _ -> warn_rule [Warn_traps] (f ^ " is expecting an array"))
| "system" ->
(match un_parenthesize_full_l para with
@@ -967,7 +966,7 @@ let call_raw force_non_builtin_func (e, para) =
| Some s ->
if List.exists (String.contains s) [ '\'' ; char_quote ] &&
not (List.exists (String.contains s) [ '<' ; '>' ; '&' ; ';']) then
- warn_rule "instead of quoting parameters you should give a list of arguments";
+ warn_rule [Warn_complex_expressions] "instead of quoting parameters you should give a list of arguments";
check_system_call (split_at ' ' s)
| None -> ())
| l ->
@@ -1037,7 +1036,7 @@ let call_one_scalar_para { any = e ; pos = pos } para esp_start esp_end =
if e = "shift" || e = "pop" then
[] (* can't decide here *)
else
- (if not (List.mem e [ "length" ]) then warn_rule (sprintf "please use \"%s $_\" instead of \"%s\"" e e) ;
+ (if not (List.mem e [ "length" ]) then warn_rule [Warn_complex_expressions] (sprintf "please use \"%s $_\" instead of \"%s\"" e e) ;
[var_dollar_ (raw_pos2pos pos)])
| _ -> para
in
@@ -1072,13 +1071,13 @@ let to_String parse strict { any = l ; pos = pos } =
let l' = parse_interpolated parse l in
(match l' with
| [ "", List [Deref(I_scalar, Ident(None, ident, _))]] ->
- if ident <> "!" && strict then warn pos (sprintf "%s is better written without the double quotes" (variable2s(I_scalar, ident)))
+ if ident <> "!" && strict then warn [Warn_suggest_simpler] pos (sprintf "%s is better written without the double quotes" (variable2s(I_scalar, ident)))
| [ "", List [Deref(I_hash, _)]] ->
- warn pos "don't use a hash in string context"
+ warn [Warn_traps] pos "don't use a hash in string context"
| [ "", List [Deref(I_array, _)]] ->
()
| [("", _)] ->
- if strict then warn pos "double quotes are unneeded"
+ if strict then warn [Warn_suggest_simpler] pos "double quotes are unneeded"
| _ -> ());
String(l', raw_pos2pos pos)
@@ -1087,9 +1086,9 @@ let from_PATTERN parse { any = (s, opts) ; pos = pos } =
(match List.rev re with
| (s, List []) :: _ ->
if str_ends_with s ".*" then
- warn_rule (sprintf "you can remove \"%s\" at the end of your regexp" ".*")
+ warn_rule [Warn_suggest_simpler] (sprintf "you can remove \"%s\" at the end of your regexp" ".*")
else if str_ends_with s ".*$" then
- warn_rule (sprintf "you can remove \"%s\" at the end of your regexp" ".*$")
+ warn_rule [Warn_suggest_simpler] (sprintf "you can remove \"%s\" at the end of your regexp" ".*$")
| _ -> ());
let pattern = [ String(re, raw_pos2pos pos) ; Raw_string(opts, raw_pos2pos pos) ] in
check_simple_pattern pattern;
@@ -1213,7 +1212,7 @@ let mcontext_lmaybe esp = if esp.any = [] then [] else [esp.mcontext]
let mcontext_check_raw wanted_mcontext mcontext =
if not (mcontext_lower mcontext wanted_mcontext) then
- warn_rule (sprintf "context %s is not compatible with context %s" (mcontext2s mcontext) (mcontext2s wanted_mcontext))
+ warn_rule [Warn_context] (sprintf "context %s is not compatible with context %s" (mcontext2s mcontext) (mcontext2s wanted_mcontext))
let mcontext_check wanted_mcontext esp =
(match wanted_mcontext with
@@ -1221,7 +1220,7 @@ let mcontext_check wanted_mcontext esp =
| _ ->
match un_parenthesize_full esp.any.expr with
| Call(Deref(I_func, Ident(None, "grep", _)), _) ->
- warn_rule (if wanted_mcontext = M_bool then
+ warn_rule [Warn_suggest_simpler; Warn_help_perl_checker] (if wanted_mcontext = M_bool then
"in boolean context, use \"any\" instead of \"grep\"" else
"you may use \"find\" instead of \"grep\"")
| _ -> ());
@@ -1231,7 +1230,7 @@ let mcontext_check_unop_l wanted_mcontext esp =
mcontext_check wanted_mcontext { esp with any = { esp.any with expr = List esp.any.expr } }
let mcontext_check_non_none esp =
- if esp.mcontext = M_none then warn_rule "() context not accepted here"
+ if esp.mcontext = M_none then warn_rule [Warn_context] "() context not accepted here"
let mcontext_check_none msg expr esp =
let rec mcontext_check_none_rec msg expr = function
@@ -1253,8 +1252,8 @@ let mcontext_check_none msg expr esp =
match expr with
| [List [Num("1", _)]; Semi_colon] -> () (* allow "1;" for package return value. It would be much better to check we are at toplevel, but hell i don't want to wire this information up to here *)
| [List [Call_op ("<>", [Ident (None, "STDIN", _)], _)]; Semi_colon] -> () (* allow <STDIN> to ask "press return" *)
- | [List [Call(Deref(I_func, Ident(None, "map", _)), _)]; Semi_colon] -> warn_rule "if you don't use the return value, use \"foreach\" instead of \"map\""
- | _ -> warn esp.pos msg
+ | [List [Call(Deref(I_func, Ident(None, "map", _)), _)]; Semi_colon] -> warn_rule [Warn_void] "if you don't use the return value, use \"foreach\" instead of \"map\""
+ | _ -> warn [Warn_void] esp.pos msg
in
mcontext_check_none_rec msg expr esp.mcontext
@@ -1298,7 +1297,7 @@ let call_op_if_infix left right esp_start esp_end =
| List [Call_op("=", [Deref(context, _); _], _)], _ when non_scalar_context context -> ()
| List [Call_op("=", [v; _], _)],
List [Call_op("not", [v'], _)] when is_same_fromparser v v' ->
- warn_rule "\"$foo = ... if !$foo\" can be written \"$foo ||= ...\""
+ warn_rule [Warn_suggest_simpler] "\"$foo = ... if !$foo\" can be written \"$foo ||= ...\""
| _ -> ());
mcontext_check_none "value is dropped" [left] esp_start;
@@ -1313,12 +1312,12 @@ let call_op_unless_infix left right esp_start esp_end =
(match left, right with
| List [Call_op("=", [Deref(context, _); _], _)], _ when non_scalar_context context -> ()
| List [Call_op("=", [v; _], _)], List [v'] when is_same_fromparser v v' ->
- warn_rule "\"$foo = ... unless $foo\" can be written \"$foo ||= ...\""
+ warn_rule [Warn_suggest_simpler] "\"$foo = ... unless $foo\" can be written \"$foo ||= ...\""
| _ -> ());
(match right with
| List [Call_op(op, _, _)] ->
(match op with
- | "&&" | "||" | "not" | "ne" | "?:" -> warn_rule "don't use \"unless\" when the condition is complex, use \"if\" instead"
+ | "&&" | "||" | "not" | "ne" | "?:" -> warn_rule [Warn_complex_expressions] "don't use \"unless\" when the condition is complex, use \"if\" instead"
| _ -> ());
| _ -> ());
@@ -1337,7 +1336,7 @@ let symops pri para_context return_context op_str left op right =
in
if op_str <> "==" && op_str <> "!=" && para_context = M_float then
(match un_parenthesize_full left.any.expr with
- | Call_op("last_array_index", _, _) -> warn_rule "change your expression to use @xxx instead of $#xxx"
+ | Call_op("last_array_index", _, _) -> warn_rule [Warn_complex_expressions] "change your expression to use @xxx instead of $#xxx"
| _ -> ());
if not skip_context_check then
diff --git a/perl_checker.src/parser_helper.mli b/perl_checker.src/parser_helper.mli
index ecd5095..952963a 100644
--- a/perl_checker.src/parser_helper.mli
+++ b/perl_checker.src/parser_helper.mli
@@ -57,11 +57,10 @@ val from_array : Types.fromparser Types.any_spaces_pos -> Types.fromparser
val get_pos_from_expr : Types.fromparser -> Types.pos
val msg_with_rawpos : int * int -> string -> string
val die_with_rawpos : int * int -> string -> 'a
-val warn : int * int -> string -> unit
+val warn : Types.warning list -> int * int -> string -> unit
val die_rule : string -> 'a
-val warn_rule : string -> unit
-val debug : string -> unit
-val warn_verb : int -> string -> unit
+val warn_rule : Types.warning list -> string -> unit
+val warn_verb : Types.warning list -> int -> string -> unit
val warn_too_many_space : int -> unit
val warn_no_space : int -> unit
val warn_cr : int -> unit
@@ -167,6 +166,7 @@ val anonymous_sub :
Types.fromparser list Types.any_spaces_pos -> Types.fromparser
val call_with_same_para_special : Types.fromparser -> Types.fromparser
val remove_call_with_same_para_special : Types.fromparser -> Types.fromparser
+val check_My_under_condition : string -> Types.fromparser -> unit
val cook_call_op :
string -> Types.fromparser list -> int * int -> Types.fromparser
val to_Call_op :
@@ -199,6 +199,9 @@ val po_comments : string list ref
val po_comment : string Types.any_spaces_pos -> unit
val check_format_a_la_printf : string -> int -> Types.maybe_context list
val generate_pot : string -> unit
+val fake_string_from_String_l : (string * 'a) list -> string
+val fake_string_option_from_expr : Types.fromparser -> string option
+val check_system_call : string list -> unit
val call_raw :
bool -> Types.fromparser * Types.fromparser list -> Types.fromparser
val call : Types.fromparser * Types.fromparser list -> Types.fromparser
@@ -230,16 +233,6 @@ val call_one_scalar_para :
'a Types.any_spaces_pos ->
'b Types.any_spaces_pos ->
Types.fromparser Types.prio_anyexpr Types.any_spaces_pos
-val call_op_if_infix :
- Types.fromparser ->
- Types.fromparser ->
- 'a Types.any_spaces_pos ->
- 'b Types.any_spaces_pos -> Types.fromparser Types.any_spaces_pos
-val call_op_unless_infix :
- Types.fromparser ->
- Types.fromparser ->
- 'a Types.any_spaces_pos ->
- 'b Types.any_spaces_pos -> Types.fromparser Types.any_spaces_pos
val current_lexbuf : Lexing.lexbuf option ref
val list2tokens : ((int * int) * 'a) list -> Lexing.lexbuf -> 'a
val parse_tokens :
@@ -292,6 +285,16 @@ val mcontext_op_assign :
Types.maybe_context
val mtuple_context_concat :
Types.maybe_context -> Types.maybe_context -> Types.maybe_context
+val call_op_if_infix :
+ Types.fromparser ->
+ Types.fromparser ->
+ 'a Types.any_spaces_pos ->
+ 'b Types.any_spaces_pos -> Types.fromparser Types.any_spaces_pos
+val call_op_unless_infix :
+ Types.fromparser ->
+ Types.fromparser ->
+ 'a Types.any_spaces_pos ->
+ 'b Types.any_spaces_pos -> Types.fromparser Types.any_spaces_pos
val symops :
Types.priority ->
Types.maybe_context ->
diff --git a/perl_checker.src/perl_checker.ml b/perl_checker.src/perl_checker.ml
index cc75816..98664e0 100644
--- a/perl_checker.src/perl_checker.ml
+++ b/perl_checker.src/perl_checker.ml
@@ -22,7 +22,7 @@ let set_basedir per_files file =
let rec parse_file from_basedir require_name per_files file =
try
- if !Flags.verbose then print_endline_flush_always ("parsing " ^ file) ;
+ if !Flags.verbose then print_endline_flush ("parsing " ^ file) ;
let build_time = Unix.time() in
let command =
match !Flags.expand_tabs with
@@ -42,7 +42,7 @@ let rec parse_file from_basedir require_name per_files file =
let required_packages = collect (fun package -> package.required_packages) per_file.packages in
required_packages, per_files
with Failure s -> (
- print_endline_flush_always s ;
+ print_endline_flush s ;
exit 1
)
with
@@ -67,7 +67,7 @@ and parse_package_if_needed per_files (package_name, pos) =
| Some required_packages -> required_packages, per_files
| None -> parse_file (dir = !basedir) (Some package_name) per_files file
with Not_found ->
- warn_with_pos_always pos (Printf.sprintf "can't find package %s" package_name) ;
+ print_endline_flush (Info.pos2sfull pos ^ Printf.sprintf "can't find package %s" package_name) ;
[], per_files
let rec parse_required_packages state already_done = function
@@ -94,12 +94,33 @@ let parse_options =
"-v", Arg.Set Flags.verbose, " be verbose" ;
"-q", Arg.Set Flags.quiet, " be quiet" ;
"-t", Arg.Int (fun i -> Flags.expand_tabs := Some i), " set the tabulation width (default is 8)" ;
- "--check-unused", Arg.Set Flags.check_unused_global_vars, " check unused global functions & variables" ;
"--restrict-to-files", Arg.Set restrict_to_files, " only display warnings concerning the file(s) given on command line" ;
"--no-cache", Arg.Set Flags.no_cache, " do not use cache" ;
- "--generate-pot", Arg.String generate_pot_chosen, "" ;
+ "--generate-pot", Arg.String generate_pot_chosen,
+ "\n" ;
+
+ "--check-unused-global-vars", Arg.Set Flags.check_unused_global_vars, " disable unused global functions & variables check" ^
+ "\nBasic warnings:";
+ "--no-check-white-space", Arg.Clear Flags.check_white_space, " disable white space check" ;
+ "--no-suggest-simpler", Arg.Clear Flags.check_suggest_simpler, " disable simpler code suggestion" ;
+ "--no-suggest-functional", Arg.Clear Flags.suggest_functional, " disable Functional Programming suggestions" ^
+ "\nNormalisation warnings:";
+ "--no-check-strange", Arg.Clear Flags.check_strange, " disable strange code check" ;
+ "--no-check-complex-expressions", Arg.Clear Flags.check_complex_expressions, " disable complex expressions check" ;
+ "--no-check-normalized-expressions", Arg.Clear Flags.normalized_expressions, " don't warn about non normalized expressions" ;
+ "--no-help-perl-checker", Arg.Clear Flags.check_help_perl_checker, " beware, perl_checker doesn't understand all perl expressions, so those warnings *are* important" ^
+ "\nCommon warnings:";
+ "--no-check-void", Arg.Clear Flags.check_void, " disable dropped value check" ;
+ "--no-check-names", Arg.Clear Flags.check_names, " disable variable & function usage check" ;
+ "--no-check-prototypes", Arg.Clear Flags.check_prototypes, " disable prototypes check" ;
+ "--no-check-import-export", Arg.Clear Flags.check_import_export, " disable inter modules check" ^
+ "\nImportant warnings:";
+ "--no-check-context", Arg.Clear Flags.check_context, " disable context check" ;
+ "--no-check-traps", Arg.Clear Flags.check_traps, " disable traps (errors) check" ^
+ "\n";
+
] in
- let usage = "Usage: perl_checker [-v] [-q] <files>\nOptions are:" in
+ let usage = "Usage: perl_checker [<options>] <files>\nOptions are:" in
Arg.parse options (lpush args_r) usage;
let files = if !args_r = [] && Build.debugging then ["../t.pl"] else !args_r in
@@ -110,10 +131,11 @@ let parse_options =
if !Flags.generate_pot then Parser_helper.generate_pot !pot_file else (
- if !restrict_to_files then Common.print_endline_flush_quiet := true ;
- let per_files, required_packages = parse_required_packages per_files [] required_packages in
+ let per_files, required_packages =
+ fluid_let Flags.quiet (!restrict_to_files || !Flags.quiet)
+ (fun () ->
+ parse_required_packages per_files [] required_packages) in
let l_required_packages = List.map fst required_packages in
- if !restrict_to_files then Common.print_endline_flush_quiet := false ;
write_packages_cache per_files !basedir ;
@@ -133,7 +155,8 @@ let parse_options =
let package_name_to_file_name = hashtbl_collect (fun _ per_file -> List.map (fun pkg -> pkg.package_name, per_file.file_name) per_file.packages) per_files in
Hashtbl.iter (fun _ pkg ->
let file_name = List.assoc pkg.package_name package_name_to_file_name in
- get_vars_declaration global_vars_declared file_name pkg
+ fluid_let Flags.quiet (!restrict_to_files || !Flags.quiet)
+ (fun () -> get_vars_declaration global_vars_declared file_name pkg)
) state.per_packages ;
arrange_global_vars_declared global_vars_declared state
in
diff --git a/perl_checker.src/test/syntax_restrictions.t b/perl_checker.src/test/syntax_restrictions.t
index 6641b7b..eb186d8 100644
--- a/perl_checker.src/test/syntax_restrictions.t
+++ b/perl_checker.src/test/syntax_restrictions.t
@@ -34,7 +34,7 @@ foreach ($xxx = 0; $xxx < 9; $xxx++) {} write "for" instead of "foreach"
foreach $xxx (@l) {} don't use for without "my"ing the iteration variable
-foreach ($xxx) {} you are using the special fpons trick to locally set $_ with a value, for this please use "for" instead of "foreach"
+foreach ($xxx) {} you are using the special trick to locally set $_ with a value, for this please use "for" instead of "foreach"
unless ($xxx) {} else {} don't use "else" with "unless" (replace "unless" with "if")
diff --git a/perl_checker.src/tree.ml b/perl_checker.src/tree.ml
index 2d630c1..dd62174 100644
--- a/perl_checker.src/tree.ml
+++ b/perl_checker.src/tree.ml
@@ -51,8 +51,7 @@ let ignore_package pkg =
lpush ignored_packages pkg
let die_with_pos pos msg = failwith (Info.pos2sfull pos ^ msg)
-let warn_with_pos pos msg = print_endline_flush (Info.pos2sfull pos ^ msg)
-let warn_with_pos_always pos msg = print_endline_flush_always (Info.pos2sfull pos ^ msg)
+let warn_with_pos warn_types pos msg = if Flags.are_warning_types_set warn_types then print_endline_flush (Info.pos2sfull pos ^ msg)
let s2context s =
match s.[0] with
@@ -77,13 +76,13 @@ let get_current_package t =
in
bundled_packages [] (string_of_Ident ident) [] body
| _ ->
- if str_ends_with !Info.current_file ".pm" then warn_with_pos (!Info.current_file, 0, 0) (sprintf "module %s does not have \"package xxxx;\" on its first line" (Info.absolute_file_to_file !Info.current_file)) ;
+ if str_ends_with !Info.current_file ".pm" then warn_with_pos [Warn_normalized_expressions] (!Info.current_file, 0, 0) (sprintf "module %s does not have \"package xxxx;\" on its first line" (Info.absolute_file_to_file !Info.current_file)) ;
[ None, t ]
let from_qw_raw = function
| String([s, List []], pos) -> [ s, pos ]
| String(_, pos) ->
- warn_with_pos pos "not recognised yet" ;
+ warn_with_pos [] pos "not recognised yet" ;
[]
| Raw_string(s, pos) ->
[ s, pos ]
@@ -93,9 +92,9 @@ let from_qw_raw = function
| String([s, List []], pos)
| Raw_string(s, pos) -> Some(s, pos)
| Ident(_, _, pos) as ident -> Some(string_of_Ident ident, pos)
- | e -> warn_with_pos (get_pos_from_expr e) "not recognised yet"; None
+ | e -> warn_with_pos [] (get_pos_from_expr e) "not recognised yet"; None
) l)) []
- | e -> warn_with_pos (get_pos_from_expr e) "not recognised yet"; []
+ | e -> warn_with_pos [] (get_pos_from_expr e) "not recognised yet"; []
let from_qw e =
List.map (fun (s, pos) ->
@@ -103,7 +102,7 @@ let from_qw e =
let context =
match context with
| I_raw -> if s'.[0] = ':' then I_raw else I_func
- | I_func -> warn_with_pos pos "weird, exported name with a function context especially given"; I_func
+ | I_func -> warn_with_pos [Warn_import_export] pos "weird, exported name with a function context especially given"; I_func
| _ -> context
in context, s'
) (from_qw_raw e)
@@ -113,12 +112,12 @@ let get_exported t =
match e with
| List [ Call_op("=", [ Deref(I_array, Ident(None, "EXPORT", _)); Call _ ], pos) ]
| List [ Call_op("=", [ My_our("our", [(I_array, "EXPORT")], _); Call _ ], pos) ] ->
- if exports.special_export = None then warn_with_pos pos "unrecognised @EXPORT" ;
+ if exports.special_export = None then warn_with_pos [Warn_import_export] pos "unrecognised @EXPORT" ;
exports
| List [ Call_op("=", [ Deref(I_array, Ident(None, "EXPORT", _)); v ], pos)]
| List [ Call_op("=", [ My_our("our", [(I_array, "EXPORT")], _); v ], pos)] ->
- if exports.export_auto <> [] then warn_with_pos pos "weird, @EXPORT set twice" ;
+ if exports.export_auto <> [] then warn_with_pos [Warn_import_export] pos "weird, @EXPORT set twice" ;
{ exports with export_auto = from_qw v }
| Perl_checker_comment("RE-EXPORT-ALL", _) -> { exports with special_export = Some Re_export_all }
@@ -126,7 +125,7 @@ let get_exported t =
| List [ Call_op("=", [ Deref(I_array, Ident(None, "EXPORT_OK", _)); v ], pos)]
| List [ Call_op("=", [ My_our("our", [(I_array, "EXPORT_OK")], _); v ], pos)] ->
- if exports.export_ok <> [] then warn_with_pos pos "weird, @EXPORT_OK set twice" ;
+ if exports.export_ok <> [] then warn_with_pos [Warn_import_export] pos "weird, @EXPORT_OK set twice" ;
(match v with
| Call(Deref(I_func, Ident(None, "map", _)),
[ Anonymous_sub(_, Block [List [Deref(I_array, Deref(I_scalar, Ident (None, "_", _)))]], _);
@@ -152,10 +151,10 @@ let get_exported t =
) (group_by_2 l)
| _ -> raise Not_found
in
- if exports.export_tags <> [] then warn_with_pos pos "weird, %EXPORT_TAGS set twice" ;
+ if exports.export_tags <> [] then warn_with_pos [Warn_import_export] pos "weird, %EXPORT_TAGS set twice" ;
{ exports with export_tags = export_tags }
with _ ->
- warn_with_pos pos "unrecognised %EXPORT_TAGS" ;
+ warn_with_pos [Warn_import_export] pos "unrecognised %EXPORT_TAGS" ;
exports)
(* $EXPORT_TAGS{all} = [ map { @$_ } values %EXPORT_TAGS ]; *)
@@ -280,8 +279,8 @@ let get_proto perl_proto body =
map_option (fun (mys, pos, _) ->
let scalars, others = break_at (fun (context, _) -> context <> I_scalar) mys in
(match others with
- | (I_array, _) :: _ :: _ -> warn_with_pos pos "an array must be the last variable in a prototype"
- | (I_hash, _) :: _ :: _ -> warn_with_pos pos "an hash must be the last variable in a prototype"
+ | (I_array, _) :: _ :: _ -> warn_with_pos [Warn_prototypes] pos "an array must be the last variable in a prototype"
+ | (I_hash, _) :: _ :: _ -> warn_with_pos [Warn_prototypes] pos "an hash must be the last variable in a prototype"
| _ -> ());
let is_optional (_, s) =
String.length s > 2 && (s.[0] = 'o' || s.[0] = 'b') && s.[1] = '_' ||
@@ -289,7 +288,7 @@ let get_proto perl_proto body =
in
let must_have, optional = break_at is_optional scalars in
if not (List.for_all is_optional optional) then
- warn_with_pos pos "an non-optional argument must not follow an optional argument";
+ warn_with_pos [Warn_prototypes] pos "an non-optional argument must not follow an optional argument";
let min = List.length must_have in
{ proto_nb_min = min; proto_nb_max = if others = [] then Some(min + List.length optional) else None }
) (has_proto perl_proto body)
@@ -315,7 +314,7 @@ let get_vars_declaration global_vars_declared file_name package =
| List [ Method_call(Raw_string(pkg, pos), Raw_string("bootstrap", _), _) ] ->
if pkg <> package.package_name then
- warn_with_pos pos "strange bootstrap (the package name is not the same as the current package)"
+ warn_with_pos [Warn_import_export] pos "strange bootstrap (the package name is not the same as the current package)"
else
if not (read_xs_extension_from_c global_vars_declared file_name package pos) then
if not (read_xs_extension_from_so global_vars_declared package pos) then
@@ -388,9 +387,9 @@ let get_global_info_from_package from_basedir require_name build_time t =
let isa, exporter = get_isa t in
(match exporter with
| None ->
- if exporting_something() then warn_with_pos (!Info.current_file, 0, 0) "you must have \"@ISA = qw(Exporter)\" to EXPORT something"
+ if exporting_something() then warn_with_pos [Warn_import_export] (!Info.current_file, 0, 0) "you must have \"@ISA = qw(Exporter)\" to EXPORT something"
| Some pos ->
- if not (exporting_something()) then warn_with_pos pos "Inheritating from Exporter without EXPORTing anything");
+ if not (exporting_something()) then warn_with_pos [Warn_import_export] pos "Inheritating from Exporter without EXPORTing anything");
let uses = List.rev (get_uses t) in
let required_packages = List.map (fun (s, (_, pos)) -> s, pos) uses in
diff --git a/perl_checker.src/tree.mli b/perl_checker.src/tree.mli
index 60edc37..3cdf219 100644
--- a/perl_checker.src/tree.mli
+++ b/perl_checker.src/tree.mli
@@ -51,8 +51,7 @@ val has_proto : string option -> fromparser -> ((context * string) list * pos *
val get_vars_declaration : (context * string * string, pos * prototype option) Hashtbl.t -> string -> per_package -> unit
val die_with_pos : string * int * int -> string -> 'a
-val warn_with_pos : string * int * int -> string -> unit
-val warn_with_pos_always : string * int * int -> string -> unit
+val warn_with_pos : Types.warning list -> string * int * int -> string -> unit
val fold_tree : ('a -> fromparser -> 'a option) -> 'a -> fromparser -> 'a
val from_qw : fromparser -> (context * string) list
diff --git a/perl_checker.src/types.mli b/perl_checker.src/types.mli
index 0a5e62b..15f97cd 100644
--- a/perl_checker.src/types.mli
+++ b/perl_checker.src/types.mli
@@ -105,3 +105,20 @@ type 'a prio_anyexpr = {
type prio_expr_spaces_pos = fromparser prio_anyexpr any_spaces_pos
type prio_lexpr_spaces_pos = fromparser list prio_anyexpr any_spaces_pos
+
+type warning =
+ | Warn_white_space
+ | Warn_suggest_simpler
+ | Warn_unused_global_vars
+ | Warn_void
+ | Warn_context
+ | Warn_strange
+ | Warn_traps
+ | Warn_complex_expressions
+ | Warn_normalized_expressions
+ | Warn_suggest_functional
+ | Warn_prototypes
+ | Warn_import_export
+ | Warn_names
+ | Warn_MDK_Common
+ | Warn_help_perl_checker
/span> msgid "" "This dialog is used to select which services you wish to start at boot\n" "time.\n" "\n" "DrakX will list all services available on the current installation. Review\n" "each one of them carefully and uncheck those which are not needed at boot\n" "time.\n" "\n" "A short explanatory text will be displayed about a service when it is\n" "selected. However, if you're not sure whether a service is useful or not,\n" "it is safer to leave the default behavior.\n" "\n" "!! At this stage, be very careful if you intend to use your machine as a\n" "server: you probably do not want to start any services which you do not " "need.\n" "Please remember that some services can be dangerous if they're enabled on a\n" "server. In general, select only those services you really need. !!" msgstr "" "Nüüd saate valida, millised teenused peaks käivitama alglaadimisel.\n" "\n" "Siin on üles loetud kõik teenused, mis on saadaval antud paigalduse puhul.\n" "Uurige neid hoolega ja jätke valimata kõik, mida ei ole alglaadimise ajal\n" "tingimata vajalik käivitada.\n" "\n" "Konkreetset teenust valides näete selle kohta lühikest seletavat teksti.\n" "Kui Te ei ole aga kindel, kas teenus on kasulik või mitte, on mõistlik\n" "jätta kehtima vaikevalik (olgu see siis lubav või mitte).\n" "\n" "NB! Kui kavatsete oma süsteemi kasutada serverina, olge eriti " "tähelepanelik:\n" "tõenäoliselt ei soovi Te käivitada mittevajalikke teenuseid. Pidage meeles,\n" "et mõned teenused võivad serveris kasutatuna olla isegi ohtlikud. Üldiselt\n" "tasub valida ainult neid teenuseid, mida Teil tõesti vaja läheb." #: ../help.pm:209 #, c-format msgid "" "GNU/Linux manages time in GMT (Greenwich Mean Time) and translates it to\n" "local time according to the time zone you selected. If the clock on your\n" "motherboard is set to local time, you may deactivate this by unselecting\n" "\"%s\", which will let GNU/Linux know that the system clock and the\n" "hardware clock are in the same time zone. This is useful when the machine\n" "also hosts another operating system.\n" "\n" "The \"%s\" option will automatically regulate the system clock by\n" "connecting to a remote time server on the Internet. For this feature to\n" "work, you must have a working Internet connection. We recommend that you\n" "choose a time server located near you. This option actually installs a time\n" "server which can be used by other machines on your local network as well." msgstr "" "GNU/Linux kasutab GMT (Greenwichi) aega ning teisendab selle\n" "kohalikuks ajaks vastavalt Teie valitud ajavööndile. Seda võib siiski\n" "ka välja lülitada, kui jätta märkimata \"%s\". Sellisel juhul kajastab\n" "arvutikell sama aega, mis süsteemi kell. See võib olla kasulik, kui\n" "masinas on veel mõni operatsioonisüsteem, näiteks Windows.\n" "\n" "Võimalus \"%s\" võimaldab kellaaega reguleerida,\n" "ühendudes Internetis mõne ajaserveriga. Pakutavas nimekirjas valige mõni\n" "lähemal asuv server. Mõistagi peab selle võimaluse kasutamiseks olema ka\n" "Internetiühendus. Tegelikult paigaldab see Teie arvutisse ajaserveri,\n" "mida saab kasutada isegi teiste kohtvõrgus olevate masinate aja\n" "täpsustamiseks." #: ../help.pm:213 #, c-format msgid "Hardware clock set to GMT" msgstr "Riistvaraline kell kasutab GMT aega" #: ../help.pm:213 #, c-format msgid "Automatic time synchronization" msgstr "Aja automaatne sünkroniseerimine" #: ../help.pm:223 #, c-format msgid "" "Graphic Card\n" "\n" " The installer will normally automatically detect and configure the\n" "graphic card installed on your machine. If this is not correct, you can\n" "choose from this list the card you actually have installed.\n" "\n" " In the situation where different servers are available for your card,\n" "with or without 3D acceleration, you're asked to choose the server which\n" "best suits your needs." msgstr "" "Videokaart\n" "\n" " Paigaldaja tuvastab ja seadistab tavaliselt automaatselt masinasse\n" "paigaldatud videokaardi. Kui see ei õnnestu, saate nimekirjast valida\n" "kaardi, mis tegelikult on masinass paigaldatud.\n" "\n" " Juhul, kui Teie kaardile peaks saada olema erinevaid servereid nii 3D\n" "kiirendusega kui ilma, saate valida serveri, mis Teie vajadustele\n" "kõige enam vastab." #: ../help.pm:234 #, fuzzy, c-format msgid "" "X (for X Window System) is the heart of the GNU/Linux graphical interface\n" "on which all the graphical environments (KDE, GNOME, AfterStep,\n" "WindowMaker, etc.) bundled with Mageia rely upon.\n" "\n" "You'll see a list of different parameters to change to get an optimal\n" "graphical display.\n" "\n" "Graphic Card\n" "\n" " The installer will normally automatically detect and configure the\n" "graphic card installed on your machine. If this is not correct, you can\n" "choose from this list the card you actually have installed.\n" "\n" " In the situation where different servers are available for your card,\n" "with or without 3D acceleration, you're asked to choose the server which\n" "best suits your needs.\n" "\n" "\n" "\n" "Monitor\n" "\n" " Normally the installer will automatically detect and configure the\n" "monitor connected to your machine. If it is not correct, you can choose\n" "from this list the monitor which is connected to your computer.\n" "\n" "\n" "\n" "Resolution\n" "\n" " Here you can choose the resolutions and color depths available for your\n" "graphics hardware. Choose the one which best suits your needs (you will be\n" "able to make changes after the installation). A sample of the chosen\n" "configuration is shown in the monitor picture.\n" "\n" "\n" "\n" "Test\n" "\n" " Depending on your hardware, this entry might not appear.\n" "\n" " The system will try to open a graphical screen at the desired\n" "resolution. If you see the test message during the test and answer \"%s\",\n" "then DrakX will proceed to the next step. If you do not see it, then it\n" "means that some part of the auto-detected configuration was incorrect and\n" "the test will automatically end after 12 seconds and return you to the\n" "menu. Change settings until you get a correct graphical display.\n" "\n" "\n" "\n" "Options\n" "\n" " This steps allows you to choose whether you want your machine to\n" "automatically switch to a graphical interface at boot. Obviously, you may\n" "want to check \"%s\" if your machine is to act as a server, or if you were\n" "not successful in getting the display configured." msgstr "" "X (ehk X Window System) kujutab endast GNU/Linuxi graafilise " "kasutajaliidese\n" "tuuma ja südant, millele toetuvad kõik Mageiaiga kaasas käivad\n" "graafilised töökeskkonnad (KDE, GNOME, AfterStep, WindowMaker jne).\n" "\n" "Siin näidatakse Teile tervet nimekirja parameetreid, mida saab muuta,\n" "et graafiline kasutajaliides oleks just Teile meelepärane:\n" "\n" "Videokaart\n" "\n" " Paigaldaja tuvastab ja seadistab tavaliselt automaatselt masinasse\n" "paigaldatud videokaardi. Kui see ei õnnestu, saate nimekirjast valida\n" "kaardi, mis tegelikult on masinas paigaldatud.\n" "\n" " Juhul, kui Teie kaardile peaks saada olema erinevaid servereid nii 3D\n" "kiirendusega kui ilma, saate valida serveri, mis Teie vajadustele\n" "kõige enam vastab.\n" "\n" "\n" "\n" "Monitor\n" "\n" " Paigaldaja tuvastab ja seadistab tavaliselt automaatselt Teie masinaga\n" "ühendatud monitori. Kui see ei peaks siiski õnnestuma, saate siin toodud\n" "nimekirjast valida monitori, mis Teil tegelikult on.\n" "\n" "\n" "\n" "Ekraanilahutus\n" "\n" " Siin saate valida Teie riistvaraga sobiva ekraanilahutuse ja " "värvisügavuse.\n" "Kui Te paigaldamise järel leiate, et siin valitu siiski ei kõlba, saate " "seda\n" "hiljem muuta. Valitud seadistust näidatakse monitoril.\n" "\n" "\n" "\n" "Test\n" "\n" " Sõltuvalt Teie riistvarast ei pruugi seda näha olla.\n" "\n" " süsteem püüab avada graafilist akent soovitud ekraanilahutusega. Kui " "näete\n" "testi ajal sõnumit ja vastate \"%s\", suundub DrakX järgmise sammu juurde.\n" "Kui Te sõnumit ei näe, tähendab see, et miski automaatselt tuvastatud\n" "seadistuses oli mäda ja test lõpeb automaatselt 12 sekundi pärast, tuues\n" "Teid menüüsse tagasi. Seal saate muuta seadistusi, kuni Teil õnnestub\n" "leida see, mis tagab korrektse ja meelepärase graaafilise kasutajaliidese.\n" "\n" "\n" "\n" "Eelistused\n" "\n" " Siin saab määrata, kas soovite, et masin käivitaks alglaadimise ajal\n" "automaatselt graafilise kasutajaliidese. Ilmselt on Teie vastus \"%s\",\n" "kui soovite, et masin toimiks serverina, või kui Teid ei kippunud\n" "seadistamise ajal edu saatma." #: ../help.pm:291 #, c-format msgid "" "Monitor\n" "\n" " Normally the installer will automatically detect and configure the\n" "monitor connected to your machine. If it is not correct, you can choose\n" "from this list the monitor which is connected to your computer." msgstr "" "Monitor\n" "\n" " Paigaldaja tuvastab ja seadistab tavaliselt automaatselt Teie masinaga\n" "ühendatud monitori. Kui see ei peaks siiski õnnestuma, saate siin toodud\n" "nimekirjast valida monitori, mis Teil tegelikult on." #: ../help.pm:298 #, c-format msgid "" "Resolution\n" "\n" " Here you can choose the resolutions and color depths available for your\n" "graphics hardware. Choose the one which best suits your needs (you will be\n" "able to make changes after the installation). A sample of the chosen\n" "configuration is shown in the monitor picture." msgstr "" "Ekraanilahutus\n" "\n" " Siin saate valida Teie riistvaraga sobiva ekraanilahutuse ja " "värvisügavuse.\n" "Kui Te paigaldamise järel leiate, et siin valitu siiski ei kõlba, saate " "seda\n" "hiljem muuta. Valitud seadistust näidatakse monitoril." #: ../help.pm:306 #, c-format msgid "" "In the situation where different servers are available for your card, with\n" "or without 3D acceleration, you're asked to choose the server which best\n" "suits your needs." msgstr "" "Juhul, kui Teie kaardile peaks saada olema erinevaid servereid nii 3D\n" "kiirendusega kui ilma, saate valida serveri, mis Teie vajadustele\n" "kõige enam vastab." #: ../help.pm:311 #, c-format msgid "" "Options\n" "\n" " This steps allows you to choose whether you want your machine to\n" "automatically switch to a graphical interface at boot. Obviously, you may\n" "want to check \"%s\" if your machine is to act as a server, or if you were\n" "not successful in getting the display configured." msgstr "" "Eelistused\n" "\n" " Siin saab valida, kas soovite kasutada graafilist töökeskkonda\n" "kohe alglaadimisel. Pange tähele, et seda päritakse ka siis, kui Te ei " "proovinudki\n" "seadistusi testida. On üsna ilmne, et vastus kõlab \"%s\", kui masina " "ülesanne\n" "on tegutseda serverina või kui Teid ei kippunud seadistamise ajal edu saatma." #: ../help.pm:319 #, fuzzy, c-format msgid "" "You now need to decide where you want to install the Mageia\n" "operating system on your hard drive. If your hard drive is empty or if an\n" "existing operating system is using all the available space you will have to\n" "partition the drive. Basically, partitioning a hard drive means to\n" "logically divide it to create the space needed to install your new\n" "Mageia system.\n" "\n" "Because the process of partitioning a hard drive is usually irreversible\n" "and can lead to data losses, partitioning can be intimidating and stressful\n" "for the inexperienced user. Fortunately, DrakX includes a wizard which\n" "simplifies this process. Before continuing with this step, read through the\n" "rest of this section and above all, take your time.\n" "\n" "Depending on the configuration of your hard drive, several options are\n" "available:\n" "\n" " * \"%s\". This option will perform an automatic partitioning of your blank\n" "drive(s). If you use this option there will be no further prompts.\n" "\n" " * \"%s\". The wizard has detected one or more existing Linux partitions on\n" "your hard drive. If you want to use them, choose this option. You will then\n" "be asked to choose the mount points associated with each of the partitions.\n" "The legacy mount points are selected by default, and for the most part it's\n" "a good idea to keep them.\n" "\n" " * \"%s\". If Microsoft Windows is installed on your hard drive and takes\n" "all the space available on it, you will have to create free space for\n" "GNU/Linux. To do so, you can delete your Microsoft Windows partition and\n" "data (see ``Erase entire disk'' solution) or resize your Microsoft Windows\n" "FAT or NTFS partition. Resizing can be performed without the loss of any\n" "data, provided you've previously defragmented the Windows partition.\n" "Backing up your data is strongly recommended. Using this option is\n" "recommended if you want to use both Mageia and Microsoft Windows on\n" "the same computer.\n" "\n" " Before choosing this option, please understand that after this\n" "procedure, the size of your Microsoft Windows partition will be smaller\n" "than when you started. You'll have less free space under Microsoft Windows\n" "to store your data or to install new software.\n" "\n" " * \"%s\". If you want to delete all data and all partitions present on\n" "your hard drive and replace them with your new Mageia system, choose\n" "this option. Be careful, because you will not be able to undo this " "operation\n" "after you confirm.\n" "\n" " !! If you choose this option, all data on your disk will be deleted. !!\n" "\n" " * \"%s\". This option appears when the hard drive is entirely taken by\n" "Microsoft Windows. Choosing this option will simply erase everything on the\n" "drive and begin fresh, partitioning everything from scratch.\n" "\n" " !! If you choose this option, all data on your disk will be lost. !!\n" "\n" " * \"%s\". Choose this option if you want to manually partition your hard\n" "drive. Be careful -- it is a powerful but dangerous choice and you can very\n" "easily lose all your data. That's why this option is really only\n" "recommended if you have done something like this before and have some\n" "experience. For more instructions on how to use the DiskDrake utility,\n" "refer to the ``Managing Your Partitions'' section in the ``Starter Guide''." msgstr "" "Olete jõudnud punkti, kus peate otsustama, kuhu täpselt Mageia\n" "oma kõvakettal paigaldada. Kui kõvaketas on tühi või mõni muu\n" "operatsioonisüsteem seda täielikult kasutab, on vaja see osadeks jagada\n" "ehk partitsioneerida.\n" "Partitsioneerimine on tegevus, mille käigus tekitatakse kettale loogilised\n" "piirkonnad Teie uue Mageiai süsteemi paigaldamiseks.\n" "\n" "Kuna kõvaketta jagamine on pöördumatu protsess, siis peab kogemusteta\n" "kasutaja olema iseäranis ettevaatlik! Selle tegevuse lihtsustamiseks ja\n" "vigade vähendamiseks on Teie jaoks loodudki käesolev nõustaja. Siiski,\n" "palun varuge natuke ettevalmistusaega.\n" "\n" "Sõltuvalt kõvaketta omadustest on ketta jagamiseks ehk partitsioneerimiseks\n" "mitmeid võimalusi.\n" "\n" " * \"%s\": see jagab lihtsalt Teie tühja(d) kõvaketta(d).\n" "Mingeid edasisi küsimusi ei esitata.\n" "\n" " * \"%s\": nõustaja leidis kõvakettalt vähemalt\n" "ühe Linuxi partitsiooni. Kui soovite seda/neid kasutada, valige see " "võimalus.\n" "Seejärel palutakse valida iga partitsiooniga seotud haakepunktid. Vaikimisi\n" "valitakse need juba ette ära ja üldiselt oleks mõistlik neid mitte muuta.\n" "\n" " * \"%s\": kui kõvakettale on paigaldatud\n" "Microsoft Windows ja see haarab enda alla kogu kõvaketta, tuleb Teil " "tekitada\n" "vaba ruum GNU/Linuxi andmetele. Selleks võib hävitada Microsoft Windowsi\n" "partitsiooni koos andmetega (vaata võimalusi \"Puhasta kogu ketas\" või\n" "\"Ekspertrežiim\") või selle suurust muuta. Viimast on võimalik sooritada " "ilma\n" "andmeid kaotamata, seda küll eeldusel, et olete varem Windowsi partitsiooni\n" "defragmenteerinud. Siiski ei tule kindlasti kahjuks ka andmetest varukoopia\n" "valmistamine... See lahendus on soovitatav, kui tahate kasutada ühes " "arvutis\n" "nii Mageiait kui Microsoft Windowsit.\n" "\n" " Enne selle valiku kasuks otsustamist pidage silmas, et kirjeldatud " "protseduuri\n" "järel on Teie Microsoft Windowsi partitsioon senisest väiksem, mis tähendab, " "et\n" "sellel on ka vähem ruumi andmete salvestamiseks või uue tarkvara " "paigaldamiseks.\n" "\n" " * \"%s\": kui soovite kustutada kõik andmed ja partitsioonid, mis\n" "kõvakettal parajasti on, ning asendada need uue Mageiai süsteemiga, " "on\n" "see õige valik. Aga tasub olla ettevaatlik, sest pärast selle valiku " "langetamist\n" "tagasiteed enam ei ole...\n" "\n" " NB! Kui valite selle võimaluse, kaotate kõik kõvakettal olevad " "andmed. !!\n" "\n" " * \"%s\": see puhastab kõvaketta senistest andmetest ja\n" "käivitab uue paigaldusprotsessi, luues kõik partitsioonid uuesti. Kaovad ka\n" "kõik kettal olnud andmed.\n" "\n" " NB! Kui valite selle võimaluse, kaotate kõik kõvakettal olevad " "andmed. !!\n" "\n" " * \"%s\": valige see, kui soovite ise kontrollida kõvaketta jagamist.\n" "Kuid olge ettevaatlik - see on küll võimas, aga ohte sisaldav\n" "valik, mille puhul võib kergesti kaotada olemasolevad andmed. Seepärast ei\n" "peaks seda valima, kui Te pole endas päris kindel. Täpsemalt saab teada,\n" "kuidas kasutada DiskDrake'i võimalusi, \"Põhiteadmiste käsiraamatu" "\" (\"Starter\n" "Guide\") alapeatükist \"Partitsioonide haldamine\"." #: ../help.pm:377 #, c-format msgid "Use existing partition" msgstr "Olemasolevate partitsioonide kasutamine" #: ../help.pm:370 #, c-format msgid "Use the free space on the Microsoft Windows® partition" msgstr "Vaba ruumi kasutamine Microsoft Windows® partitsioonil" #: ../help.pm:370 #, c-format msgid "Erase entire disk" msgstr "Kogu ketta tühjendamine" #: ../help.pm:380 #, c-format msgid "" "There you are. Installation is now complete and your GNU/Linux system is\n" "ready to be used. Just click on \"%s\" to reboot the system. Do not forget\n" "to remove the installation media (CD-ROM or floppy). The first thing you\n" "should see after your computer has finished doing its hardware tests is the\n" "boot-loader menu, giving you the choice of which operating system to start.\n" "\n" "The \"%s\" button shows two more buttons to:\n" "\n" " * \"%s\": enables you to create an installation floppy disk which will\n" "automatically perform a whole installation without the help of an operator,\n" "similar to the installation you've just configured.\n" "\n" " Note that two different options are available after clicking on that\n" "button:\n" "\n" " * \"%s\". This is a partially automated installation. The partitioning\n" "step is the only interactive procedure.\n" "\n" " * \"%s\". Fully automated installation: the hard disk is completely\n" "rewritten, all data is lost.\n" "\n" " This feature is very handy when installing on a number of similar\n" "machines. See the Auto install section on our web site for more\n" "information.\n" "\n" " * \"%s\"(*): saves a list of the packages selected in this installation.\n" "To use this selection with another installation, insert the floppy and\n" "start the installation. At the prompt, press the [F1] key, type >>linux\n" "defcfg=\"floppy\"<< and press the [Enter] key.\n" "\n" "(*) You need a FAT-formatted floppy. To create one under GNU/Linux, type\n" "\"mformat a:\", or \"fdformat /dev/fd0\" followed by \"mkfs.vfat\n" "/dev/fd0\"." msgstr "" "Ja nüüd ongi paigaldamine selja taga ning Teie GNU/Linuxi süsteem valmis " "tööks.\n" "Selleks tuleb vaid klõpsata \"%s\" ning arvuti teeb taaskäivituse. Ärge\n" "unustage eemaldamast paigaldus-andmekandjat (CD või diskett). Seejärel\n" "võite valida, kas käivitada GNU/Linux või Windows (kui Teie arvutis on mitu\n" "süsteemi).\n" "\n" "Nupp \"%s\" pakub veel kaks võimalust:\n" "\n" " * \"%s\": loob paigaldusdisketi, mis sooritab kogu\n" "paigaldamise ilma kasutajata, paigaldamine ise on samasugune nagu äsja\n" "seljataha jäänu.\n" "\n" " Selle valiku korral ilmub veel kaks erinevat võimalust:\n" "\n" " * \"%s\". See on osaliselt automaatne, sest kõvaketta jagamisel\n" "(aga ka ainult seal) on võimalik sekkuda.\n" "\n" " * \"%s\". Täisautomaatne paigaldus: kõvaketas kirjutatakse täielikult\n" "uuesti, kõik varasemad andmed kustutatakse.\n" "\n" " See võimalus võib olla kasulik, kui paigaldamine on kavas ette võtta " "paljudel\n" "ühesugustel masinatel. Lähemalt vaadake meie veebileheküljel\n" "automaatpaigalduse sektsiooni.\n" "\n" " * \"%s\"(*): salvestab paigaldamise käigus valitud pakettide\n" "nimekirja. Kui nüüd võtate ette uue paigalduse, asetage diskett seadmesse " "ning\n" "käivitage paigaldamine klahvile [F1] vajutades abiekraani vahendusel, andes " "käsu\n" ">>linux defcfg=\"floppy\"<< ja vajutades seejärel klahvi [Enter].\n" "\n" "(*) Teil läheb vaja FAT-vorminduses disketti. Sellise loomiseks GNU/Linuxi\n" "keskkonnas andke käsureal korraldus \"mformat a:\" või \"fdformat /dev/fd0" "\"\n" "ning seejärel \"mkfs.vfat /dev/fd0\"." #: ../help.pm:412 #, c-format msgid "Generate auto-install floppy" msgstr "Loo kiirpaigaldusdiskett" #: ../help.pm:405 #, c-format msgid "Replay" msgstr "Kordamine" #: ../help.pm:405 #, c-format msgid "Automated" msgstr "Automaatne" #: ../help.pm:405 #, c-format msgid "Save packages selection" msgstr "Paketivaliku salvestamine" #: ../help.pm:408 #, fuzzy, c-format msgid "" "If you chose to reuse some legacy GNU/Linux partitions, you may wish to\n" "reformat some of them and erase any data they contain. To do so, please\n" "select those partitions as well.\n" "\n" "Please note that it's not necessary to reformat all pre-existing\n" "partitions. You must reformat the partitions containing the operating\n" "system (such as \"/\", \"/usr\" or \"/var\") but you do not have to " "reformat\n" "partitions containing data that you wish to keep (typically \"/home\").\n" "\n" "Please be careful when selecting partitions. After the formatting is\n" "completed, all data on the selected partitions will be deleted and you\n" "will not be able to recover it.\n" "\n" "Click on \"%s\" when you're ready to format the partitions.\n" "\n" "Click on \"%s\" if you want to choose another partition for your new\n" "Mageia operating system installation.\n" "\n" "Click on \"%s\" if you wish to select partitions which will be checked for\n" "bad blocks on the disk." msgstr "" "Kõik värskelt loodud partitsioonid tuleb enne kasutamist vormindada\n" "ehk sinna tuleb luua failisüsteemid.\n" "\n" "Samuti võib vormindada varem olemas olnud partitsioonid, kui soovite\n" "seal leiduvad andmed ära kustutada.\n" "\n" "Pange tähele, et alati ei ole kõigi vanade partitsioonide vormindamine\n" "vajalik. Kindlasti tuleb vormindada partitsioonid, kus varem asus \"/\", \"/" "usr\"\n" "või \"/var\", aga kasutajate faile sisaldav \"/home\" võiks jääda alles.\n" "\n" "Olge partitsioonide valikul hoolas. Pärast vormindamist on kõik valitud\n" "partitsioonidel asunud andmed kustutatud ning neid ei ole võimalik " "taastada.\n" "\n" "Klõpsake \"%s\", kui olete vormindamiseks valmis.\n" "\n" "Klõpsake \"%s\", kui soovite valida oma uue Mageiai süsteemi\n" "paigaldamiseks mõne muu partitsiooni.\n" "\n" "Klõpsake \"%s\", kui soovite valida partitsioone, millel kontrollitaks\n" "vigaste plokkide olemasolu." #: ../help.pm:437 #, fuzzy, c-format msgid "" "By the time you install Mageia, it's likely that some packages will\n" "have been updated since the initial release. Bugs may have been fixed,\n" "security issues resolved. To allow you to benefit from these updates,\n" "you're now able to download them from the Internet. Check \"%s\" if you\n" "have a working Internet connection, or \"%s\" if you prefer to install\n" "updated packages later.\n" "\n" "Choosing \"%s\" will display a list of web locations from which updates can\n" "be retrieved. You should choose one near to you. A package-selection tree\n" "will appear: review the selection, and press \"%s\" to retrieve and install\n" "the selected package(s), or \"%s\" to abort." msgstr "" "On tõenäoline, et praegu, kui Te paigaldate Mageiait, on mõned\n" "paketid jõudnud pärast väljalaset juba uuenduskuuri üle elada. Mõnes on ära\n" "parandatud paar väiksemat viga, mõnes turvaprobleemid. Et võiksite neist\n" "uuendustest tulu lõigata, on Teil nüüd võimalik need Internetist alla " "laadida.\n" "Klõpsake \"%s\", kui Teie internetiühendus töötab, või \"%s\", kui " "eelistate\n" "pakette uuendada millalgi hiljem.\n" "\n" "Kui valite \"%s\", näidatakse Teile nimekirja kohtadega, kust uuendusi " "tõmmata\n" "saab. Valige endale lähim paik. Seejärel ilmub paketivaliku puu. Vaadake " "see\n" "üle ning klõpsake nupule \"%s\", kui soovite valitud paketi(d) alla laadida " "ja\n" "paigaldada, või \"%s\", kui Te ei soovi seda teha." #: ../help.pm:450 #, fuzzy, c-format msgid "" "At this point, DrakX will allow you to choose the security level you desire\n" "for your machine. As a rule of thumb, the security level should be set\n" "higher if the machine is to contain crucial data, or if it's to be directly\n" "exposed to the Internet. The trade-off that a higher security level is\n" "generally obtained at the expense of ease of use.\n" "\n" "If you do not know what to choose, keep the default option. You'll be able\n" "to change it later with the draksec tool, which is part of Mageia\n" "Control Center.\n" "\n" "Fill the \"%s\" field with the e-mail address of the person responsible for\n" "security. Security messages will be sent to that address." msgstr "" "Nüüd on aeg valida masinale sobiv turvatase. Rusikareeglina peaks\n" "turvatase olema seda kõrgem, mida ligipääsule avatum arvuti on ja mida " "rohkem\n" "leidub selles olulise tähtsusega andmeid. Samas muudab kõrgem turvatase\n" "enamasti kasutamise mõnevõrra keerukamaks.\n" "\n" "Kui Te ei tea, mida valida, jätke kehtima vaikimisi pakutud valik. Hiljem\n" "saate turvataset muuta Mageiai juhtimiskeskuses abivahendiga " "Draksec.\n" "\n" "Väli \"%s\" on mõeldud süsteemi turvalisuse eest vastutava kasutaja\n" "teavitamiseks. Turvalisusega seotud teated saadetakse sellele aadressile." #: ../help.pm:461 #, c-format msgid "Security Administrator" msgstr "Turvahaldur" #: ../help.pm:464 #, fuzzy, c-format msgid "" "At this point, you need to choose which partition(s) will be used for the\n" "installation of your Mageia system. If partitions have already been\n" "defined, either from a previous installation of GNU/Linux or by another\n" "partitioning tool, you can use existing partitions. Otherwise, hard drive\n" "partitions must be defined.\n" "\n" "To create partitions, you must first select a hard drive. You can select\n" "the disk for partitioning by clicking on ``hda'' for the first IDE drive,\n" "``hdb'' for the second, ``sda'' for the first SCSI drive and so on.\n" "\n" "To partition the selected hard drive, you can use these options:\n" "\n" " * \"%s\": this option deletes all partitions on the selected hard drive\n" "\n" " * \"%s\": this option enables you to automatically create ext3 and swap\n" "partitions in the free space of your hard drive\n" "\n" "\"%s\": gives access to additional features:\n" "\n" " * \"%s\": saves the partition table to a floppy. Useful for later\n" "partition-table recovery if necessary. It is strongly recommended that you\n" "perform this step.\n" "\n" " * \"%s\": allows you to restore a previously saved partition table from a\n" "floppy disk.\n" "\n" " * \"%s\": if your partition table is damaged, you can try to recover it\n" "using this option. Please be careful and remember that it does not always\n" "work.\n" "\n" " * \"%s\": discards all changes and reloads the partition table that was\n" "originally on the hard drive.\n" "\n" " * \"%s\": un-checking this option will force users to manually mount and\n" "unmount removable media such as floppies and CD-ROMs.\n" "\n" " * \"%s\": use this option if you wish to use a wizard to partition your\n" "hard drive. This is recommended if you do not have a good understanding of\n" "partitioning.\n" "\n" " * \"%s\": use this option to cancel your changes.\n" "\n" " * \"%s\": allows additional actions on partitions (type, options, format)\n" "and gives more information about the hard drive.\n" "\n" " * \"%s\": when you are finished partitioning your hard drive, this will\n" "save your changes back to disk.\n" "\n" "When defining the size of a partition, you can finely set the partition\n" "size by using the Arrow keys of your keyboard.\n" "\n" "Note: you can reach any option using the keyboard. Navigate through the\n" "partitions using [Tab] and the [Up/Down] arrows.\n" "\n" "When a partition is selected, you can use:\n" "\n" " * Ctrl-c to create a new partition (when an empty partition is selected)\n" "\n" " * Ctrl-d to delete a partition\n" "\n" " * Ctrl-m to set the mount point\n" "\n" "To get information about the different filesystem types available, please\n" "read the ext2FS chapter from the ``Reference Manual''.\n" "\n" "If you are installing on a PPC machine, you will want to create a small HFS\n" "``bootstrap'' partition of at least 1MB which will be used by the yaboot\n" "bootloader. If you opt to make the partition a bit larger, say 50MB, you\n" "may find it a useful place to store a spare kernel and ramdisk images for\n" "emergency boot situations." msgstr "" "Nüüd peate valima partitsiooni(d), kuhu soovite Mageiai paigaldada.\n" "Kui need on juba olemas kas GNU/Linuxi varasema paigalduse või mõne muu\n" "kettajagamisvahendi tegevuse tulemusena, võite kasutada olemasolevaid\n" "partitsioone. Vastasel juhul tuleb need luua.\n" "\n" "Partitsioon on loogiliselt eraldatud kõvaketta piirkond, mille suurust\n" "ei ole võimalik hiljem, töötavas süsteemis enam muuta. Samuti hävivad\n" "partitsiooni kustutamisel kõik selles leiduvad andmed.\n" "\n" "Kõvaketta jagamise lihtsustamiseks on loodud nõustaja, mille soovitused\n" "on harilikult mõistlikud.\n" "\n" "Partitsioonide loomiseks valige esmalt kõvaketas. \"hda\" tähendab siin " "esimest\n" "IDE-ketast, \"hdb\" teist IDE-ketast, \"sda\" esimest SCSI-ketast ja nii " "edasi.\n" "\n" "Valitud ketta jagamiseks on järgmised võimalused:\n" "\n" " * \"%s\": kustutatakse kõik olemasolevad partitsioonid\n" "sellel kettal.\n" "\n" " * \"%s\": sel juhul tekitatakse Linuxile vajalikud\n" "partitsioonid kõvaketta vabale osale automaatselt.\n" "\n" "\"%s\" pakub mõned lisavõimalused:\n" " * \"%s\": salvestab partitsioonitabeli disketile.\n" "Sellest on kasu hilisemal partitsioonitabeli taastamisel, kui seda vaja\n" "peaks olema. Igal juhul on äärmiselt soovitav see samm ette võtta.\n" "\n" " * \"%s\": võimaldab taastada disketilt varem\n" "salvestatud partitsioonitabeli.\n" "\n" " * \"%s\": kui partitsioonitabel on vigastatud, võib\n" "proovida seda parandada. Palun ärge selle peale siiski liiga palju lootke.\n" "\n" " * \"%s\": kui soovite tühistada kõik enda tehtud muutused ja alustada algse " "partitsioonitabeliga.\n" "\n" " * \"%s\": selle võimaluse\n" "tühistamine sunnib kasutajaid käsitsi haakima ja lahutama eemaldatavaid\n" "andmekandjaid, st diskette ja CD-sid.\n" "\n" " * \"%s\": kui soovite uue partitsioonitabeli loomisel samm-sammulist\n" "juhatust. See on soovitatav, kui Te ei ole varem midagi sellist teinud.\n" "\n" " * \"%s\": selle võimalusega saab tühistada kõik tehtud muudatused.\n" "\n" " * \"%s\": võimaldab partitsioonidega ette\n" "võtta lisaoperatsioone (tüüp, võtmed, vorming) ning pakub rohkem infot.\n" "\n" " * \"%s\": kui olete kõvaketta jagamise lõpetanud, saate sellele nupule\n" "klõpsates tehtud muudatused salvestada.\n" "\n" "Partitsiooni suurust määrates saate seda täpselt paika panna klaviatuuril\n" "asuvaid nooleklahve kasutades.\n" "\n" "Märkus: igale võimalusele pääseb ligi ka klaviatuuri abil. Partitsioonidel\n" "saab liikuda klahvidega [Tab] ning üles-alla nooleklahvidega.\n" "\n" "Partitsiooni valimisel saab ette võtta järgmisi toiminguid:\n" "\n" " * Ctrl+C uue partitsiooni loomine (kui valitud on tühi partitsioon).\n" "\n" " * Ctrl+D partitsiooni kustutamine.\n" "\n" " * Ctrl+M haakepunkti määramine.\n" "\n" "Lähemat infot erinevate failisüsteemitüüpide kohta leiab \"Süvateadmiste\n" "käsiraamatu\" (\"Reference Manual\") peatükist \"Linuxi failisüsteem\".\n" "\n" "Kui paigaldamine toimub PPC-masinas, tuleks luua vähemalt 1MB suurune\n" "väike HFS \"bootstrap\"-partitsioon, mida kasutab alglaadur yaboot. Kui Te\n" "aga teete selle partitsiooni natukene suuremaks (näiteks nii umbes 50MB),\n" "on see päris hea koht, kuhu hädaolukorraks paigutada tagavarakernel\n" "ja ramdisk-laadepildid." #: ../help.pm:526 #, c-format msgid "Save partition table" msgstr "Partitsioonitabeli salvestamine" #: ../help.pm:526 #, c-format msgid "Restore partition table" msgstr "Partitsioonitabeli taastamine" #: ../help.pm:526 #, c-format msgid "Rescue partition table" msgstr "Partitsioonitabeli päästmine" #: ../help.pm:526 #, c-format msgid "Removable media auto-mounting" msgstr "Eemaldatava andmekandja automaatne haakimine" #: ../help.pm:526 #, c-format msgid "Wizard" msgstr "Nõustaja" #: ../help.pm:526 #, c-format msgid "Undo" msgstr "Tagasi" #: ../help.pm:526 #, c-format msgid "Toggle between normal/expert mode" msgstr "Tava- ja ekspertrežiimi lülitamine" #: ../help.pm:536 #, fuzzy, c-format msgid "" "More than one Microsoft partition has been detected on your hard drive.\n" "Please choose the one which you want to resize in order to install your new\n" "Mageia operating system.\n" "\n" "Each partition is listed as follows: \"Linux name\", \"Windows name\"\n" "\"Capacity\".\n" "\n" "\"Linux name\" is structured: \"hard drive type\", \"hard drive number\",\n" "\"partition number\" (for example, \"hda1\").\n" "\n" "\"Hard drive type\" is \"hd\" if your hard dive is an IDE hard drive and\n" "\"sd\" if it is a SCSI hard drive.\n" "\n" "\"Hard drive number\" is always a letter after \"hd\" or \"sd\". With IDE\n" "hard drives:\n" "\n" " * \"a\" means \"master hard drive on the primary IDE controller\";\n" "\n" " * \"b\" means \"slave hard drive on the primary IDE controller\";\n" "\n" " * \"c\" means \"master hard drive on the secondary IDE controller\";\n" "\n" " * \"d\" means \"slave hard drive on the secondary IDE controller\".\n" "\n" "With SCSI hard drives, an \"a\" means \"lowest SCSI ID\", a \"b\" means\n" "\"second lowest SCSI ID\", etc.\n" "\n" "\"Windows name\" is the letter of your hard drive under Windows (the first\n" "disk or partition is called \"C:\")." msgstr "" "Teie arvuti kõvakettal on rohkem kui üks Microsoft Windowsi partitsioon.\n" "Palun valige välja see, mille suurust soovite Mageiai jaoks muuta.\n" "\n" "Teie abistamiseks on igal partitsioonil näidatud \"Nimi Linuxis\", \"Nimi " "Windowsis\" ja \"Mahutavus\".\n" "\n" "\"Nimi Linuxis\" koosneb kõvakettatüübist, selle numbrist ja partitsiooni\n" "numbrist (näiteks \"hda1\").\n" "\n" "Kõvaketta tüüp on \"hd\", kui on tegemist IDE-kettaga, ja \"sd\", kui on\n" "tegemist SCSI-kettaga.\n" "\n" "Kõvaketta number on alati täht \"hd\" või \"sd\" järel. IDE-ketastel:\n" "\n" " * \"a\" - esmase IDE kontrolleri ülem,\n" "\n" " * \"b\" - esmase IDE kontrolleri allutatu,\n" "\n" " * \"c\" - teisese IDE kontrolleri ülem,\n" "\n" " * \"d\" - teisese IDE kontrolleri allutatu.\n" "\n" "SCSI-ketaste puhul on \"a\" esimene, \"b\" teine ja nii edasi.\n" "\n" "\n" "\"Nimi Windowsis\" on täht, millega Microsoft Windows vastavat seadet\n" "tähistab (esimene ketas või partitsioon kannab nime \"C:\")." #: ../help.pm:567 #, c-format msgid "" "\"%s\": check the current country selection. If you're not in this country,\n" "click on the \"%s\" button and choose another. If your country is not in " "the\n" "list shown, click on the \"%s\" button to get the complete country list." msgstr "" "\"%s\": võimaldab kontrollida praegust riigi valikut. Kui see ei ole riik,\n" "kus Te viibite, klõpsake nupule \"%s\" ja valige mõni muu riik. Kui\n" "Teie riiki ei ole ilmuvas nimekirjas, klõpsake nupule \"%s\", mis avab\n" "riikide täisnimekirja." #: ../help.pm:572 #, fuzzy, c-format msgid "" "This step is activated only if an existing GNU/Linux partition has been\n" "found on your machine.\n" "\n" "DrakX now needs to know if you want to perform a new installation or an\n" "upgrade of an existing Mageia system:\n" "\n" " * \"%s\". For the most part, this completely wipes out the old system.\n" "However, depending on your partitioning scheme, you can prevent some of\n" "your existing data (notably \"home\" directories) from being over-written.\n" "If you wish to change how your hard drives are partitioned, or to change\n" "the filesystem, you should use this option.\n" "\n" " * \"%s\". This installation class allows you to update the packages\n" "currently installed on your Mageia system. Your current partitioning\n" "scheme and user data will not be altered. Most of the other configuration\n" "steps remain available and are similar to a standard installation.\n" "\n" "Using the ``Upgrade'' option should work fine on Mageia systems\n" "running version \"8.1\" or later. Performing an upgrade on versions prior\n" "to Mageia version \"8.1\" is not recommended." msgstr "" "Seda sammu on vaja ainult siis, kui masinas leiti varasem\n" "GNU/Linuxi partitsioon.\n" "\n" "DrakX soovib nüüd teada, kas tahate paigaldada uue süsteemi või uuendada\n" "olemasolevat Mageiai süsteemi:\n" "\n" " * \"%s\": üldiselt pühib see vana süsteemi täielikult minema. Kui\n" "soovite muuta praeguseid partitsioone või failisüsteemi, siis võiks seda " "võimalust\n" "kasutada. Sõltuvalt kettajagamise viisist on võimalik ka mõningaid andmeid\n" "ülekirjutamise eest päästa.\n" "\n" " * \"%s\": see paigaldamisviis võimaldab uuendada praegu olemasolevasse\n" "Mageiai süsteemi paigaldatud pakette. Kettajagamisskeemi ega " "kasutajate\n" "andmeid ei muudeta. Enamik seadistussamme on kasutatavad sarnaselt " "tavapärasele\n" "paigaldamisele.\n" "\n" "Võimalus \"Uuendus\" peaks toimima edukalt Mageiai süsteemides\n" "alates versioonist 8.1. Uuenduse proovimist varasemate versioonide peal\n" "me siiski ei soovita." #: ../help.pm:594 #, c-format msgid "" "Depending on the language you chose (), DrakX will automatically select a\n" "particular type of keyboard configuration. Check that the selection suits\n" "you or choose another keyboard layout.\n" "\n" "Also, you may not have a keyboard which corresponds exactly to your\n" "language: for example, if you are an English-speaking Swiss native, you may\n" "have a Swiss keyboard. Or if you speak English and are located in Quebec,\n" "you may find yourself in the same situation where your native language and\n" "country-set keyboard do not match. In either case, this installation step\n" "will allow you to select an appropriate keyboard from a list.\n" "\n" "Click on the \"%s\" button to be shown a list of supported keyboards.\n" "\n" "If you choose a keyboard layout based on a non-Latin alphabet, the next\n" "dialog will allow you to choose the key binding which will switch the\n" "keyboard between the Latin and non-Latin layouts." msgstr "" "Tavaliselt valib DrakX klaviatuuri Teie eest juba ära (sõltuvalt valitud\n" "keelest). Kuid see võib tekitada olukorra, kus Teil ikkagi pole just see\n" "klaviatuur, mida soovite: kui olete näiteks eesti keelt kõnelev\n" "hispaanlane, võite siiski soovida hispaania asetusega klaviatuuri. Teine " "kohe\n" "pähe tulev juhtum on läti keele kõneleja Eestis. Mõlemal juhul on\n" "mõtet naasta paigaldamise selle sammu juurde ja valida nimekirjast vajalik\n" "klaviatuur.\n" "\n" "Klõpsake nupul \"%s\", mis näitab kõiki toetatud klaviatuure.\n" "\n" "Kui valite mitte-ladina tähestikuga klaviatuuri, palutakse Teil järgmises\n" "dialoogis valida klahv või klahvikombinatsioon, mis vahetab ladina ja\n" "mitte-ladina asetusega klaviatuuri." #: ../help.pm:612 #, fuzzy, c-format msgid "" "The first step is to choose your preferred language.\n" "\n" "Your choice of preferred language will affect the installer, the\n" "documentation, and the system in general. First select the region you're\n" "located in, then the language you speak.\n" "\n" "Clicking on the \"%s\" button will allow you to select other languages to\n" "be installed on your workstation, thereby installing the language-specific\n" "files for system documentation and applications. For example, if Spanish\n" "users are to use your machine, select English as the default language in\n" "the tree view and \"%s\" in the Advanced section.\n" "\n" "About UTF-8 (unicode) support: Unicode is a new character encoding meant to\n" "cover all existing languages. However full support for it in GNU/Linux is\n" "still under development. For that reason, Mageia's use of UTF-8 will\n" "depend on the user's choices:\n" "\n" " * If you choose a language with a strong legacy encoding (latin1\n" "languages, Russian, Japanese, Chinese, Korean, Thai, Greek, Turkish, most\n" "iso-8859-2 languages), the legacy encoding will be used by default;\n" "\n" " * Other languages will use unicode by default;\n" "\n" " * If two or more languages are required, and those languages are not using\n" "the same encoding, then unicode will be used for the whole system;\n" "\n" " * Finally, unicode can also be forced for use throughout the system at a\n" "user's request by selecting the \"%s\" option independently of which\n" "languages were been chosen.\n" "\n" "Note that you're not limited to choosing a single additional language. You\n" "may choose several, or even install them all by selecting the \"%s\" box.\n" "Selecting support for a language means translations, fonts, spell checkers,\n" "etc. will also be installed for that language.\n" "\n" "To switch between the various languages installed on your system, you can\n" "launch the \"localedrake\" command as \"root\" to change the language used\n" "by the entire system. Running the command as a regular user will only\n" "change the language settings for that particular user." msgstr "" "Esimene samm on vajaliku keele valik. Siin saate valida keele,\n" "mida kasutada paigaldamisel ja hilisemas töös. Valige esmalt riik,\n" "kus asute, ning seejärel vajalik keel.\n" "\n" "Klõpsates nupul \"%s\", võite valida muid keeli, mida Teie tööjaamale\n" "paigaldada. Teiste keelte valikul paigaldatakse vastava keele rakenduste\n" "ja dokumentatsiooni failid. Kui Teie masinaga töötab näiteks kasutajaid\n" "Hispaaniast, valige puuvaates põhikeeleks eesti keel ning sektsioonis\n" "\"Muud\" märkige ära \"%s\".\n" "\n" "Mõni sõna UTF-8 (unicode) toetuse kohta. Unicode on uus kodeering, mis\n" "peaks hõlmama kõiki keeli. Selle täielik toetus ei ole GNU/Linuxis\n" "siiski veel täielikult teostatud. Seetõttu lähtub Mageia selle\n" "kasutamisel või mittekasutamisel järgmistest asjaoludest:\n" "\n" " * Kui valite keele, mis üldreeglina kasutab muud kodeeringut (latin1 \n" "keeled, vene, jaapani, hiina, korea, tai, kreeka, türgi keel, enamik\n" "ISO-8859-2 keeli), kasutatakse vaikimisi vastavat kodeeringut;\n" "\n" " * Muude keelte puhul võetakse vaikimisi kasutusele Unicode;\n" "\n" " * Kui valite mitu keelt, mis ei kasuta ühesugust kodeeringut,\n" "tarvitatakse vaikimisi Unicode'i;\n" " * Ja lõpuks: kui kasutaja seda soovib, võimaldab valik \"%s\"\n" "sõltumata valitud keelest kasutada kogu süsteemis Unicode'i.\n" "\n" "Te võite igal juhul valida soovi korral ka mitu keelt, märkides ära\n" "kasti \"%s\" Täiendavate keelte valimine tähendab, et süsteemi\n" "paigaldatakse ka neile keeltele vajalikud fondid, õigekirja\n" "kontrollijad, rakenduste ja dokumentatsiooni tõlked jms.\n" "\n" "Ühelt keelelt teisele lülitumiseks võite administraatorina anda käsu\n" "\"/usr/sbin/localedrake\", mis võimaldab muuta kogu süsteemi keelt,\n" "või tavakasutajana muuta ainult enda kohta käivat keeleseadistust." #: ../help.pm:650 #, c-format msgid "Espanol" msgstr "Hispaania" #: ../help.pm:643 #, c-format msgid "Use Unicode by default" msgstr "Vaikimisi Unicode kasutamine" #: ../help.pm:646 #, c-format msgid "" "Usually, DrakX has no problems detecting the number of buttons on your\n" "mouse. If it does, it assumes you have a two-button mouse and will\n" "configure it for third-button emulation. The third-button mouse button of a\n" "two-button mouse can be obtained by simultaneously clicking the left and\n" "right mouse buttons. DrakX will automatically know whether your mouse uses\n" "a PS/2, serial or USB interface.\n" "\n" "If you have a 3-button mouse without a wheel, you can choose a \"%s\"\n" "mouse. DrakX will then configure your mouse so that you can simulate the\n" "wheel with it: to do so, press the middle button and move your mouse\n" "pointer up and down.\n" "\n" "If for some reason you wish to specify a different type of mouse, select it\n" "from the list provided.\n" "\n" "You can select the \"%s\" entry to chose a ``generic'' mouse type which\n" "will work with nearly all mice.\n" "\n" "If you choose a mouse other than the default one, a test screen will be\n" "displayed. Use the buttons and wheel to verify that the settings are\n" "correct and that the mouse is working correctly. If the mouse is not\n" "working well, press the space bar or [Return] key to cancel the test and\n" "you will be returned to the mouse list.\n" "\n" "Occasionally wheel mice are not detected automatically, so you will need to\n" "select your mouse from a list. Be sure to select the one corresponding to\n" "the port that your mouse is attached to. After selecting a mouse and\n" "pressing the \"%s\" button, a mouse image will be displayed on-screen.\n" "Scroll the mouse wheel to ensure that it is activating correctly. As you\n" "scroll your mouse wheel, you will see the on-screen scroll wheel moving.\n" "Test the buttons and check that the mouse pointer moves on-screen as you\n" "move your mouse about." msgstr "" "Tavaliselt tuvastab DrakX hõlpsasti, mitme nupuga hiirt Te kasutate. Kui\n" "see välja ei tule, eeldatakse, et Teil on kahe nupuga hiir, ning " "kasutatakse\n" "kolmanda nupu emuleerimist. Kahenupulisel hiirel saab kolmandat nuppu\n" "\"klõpsata\" üheaegselt vasakut ja paremat nuppu alla vajutades. DrakX " "tuvastab\n" "automaatselt, kas tegemist on PS/2, jadapordi või USB-hiirega.\n" "\n" "Kui Teil on kolme nupuga, aga ilma rattata hiir, võite valida tüübiks\n" "\"%s\". DrakX seadistab seejärel hiire nii, et saate matkida hiireratast.\n" "Selleks klõpsake keskmist nuppu ja liigutage hiirt üles või alla.\n" "\n" "Kui soovite muuta hiiretüüpi, valige pakutud nimekirjast sobiv tüüp.\n" "\n" "Te võite alati valida võimaluse \"%s\", mis peaks toimima peaaegu igasuguse\n" "hiire korral.\n" "Kui valite mõne muu hiiretüübi kui vaikimisi määratu, palutakse Teil seda\n" "testida. Kasutage nuppe ja ratast kontrollimaks, et valik oli õige. Kui\n" "hiir ei käitu korralikult, vajutage tühikuklahvi või klahvi [Return], mis " "viib\n" "Teid tagasi dialoogi ja lubab uuesti valida.\n" "\n" "Vahel ei õnnestu rattaga hiirt automaatselt tuvastada. Siis tuleb see " "nimekirjast\n" "käsitsi valida. Kontrollige, et valite õigesse porti ühendatud hiiretüübi. " "Kui\n" "klõpsate nupule \"%s\", näidatakse hiire kujutist. Siis tuleb Teil " "liigutada\n" "hiireratast, et see korrektselt aktiveerida. Seejärel testige, kas kõik " "nupud\n" "ja liigutused toimivad korralikult." #: ../help.pm:684 #, c-format msgid "with Wheel emulation" msgstr "Ratta emuleerimisega" #: ../help.pm:684 #, c-format msgid "Universal | Any PS/2 & USB mice" msgstr "Universaalne | Suvaline PS/2 ja USB hiir" #: ../help.pm:687 #, c-format msgid "" "Please select the correct port. For example, the \"COM1\" port under\n" "Windows is named \"ttyS0\" under GNU/Linux." msgstr "" "Palun valige õige port. Näiteks MS Windowsi \"COM1\" kannab\n" "GNU/Linuxis nime \"ttyS0\"." #: ../help.pm:684 #, c-format msgid "" "A boot loader is a little program which is started by the computer at boot\n" "time. It's responsible for starting up the whole system. Normally, the boot\n" "loader installation is totally automated. DrakX will analyze the disk boot\n" "sector and act according to what it finds there:\n" "\n" " * if a Windows boot sector is found, it will replace it with a GRUB/LILO\n" "boot sector. This way you'll be able to load either GNU/Linux or any other\n" "OS installed on your machine.\n" "\n" " * if a GRUB or LILO boot sector is found, it'll replace it with a new one.\n" "\n" "If DrakX can not determine where to place the boot sector, it'll ask you\n" "where it should place it. Generally, the \"%s\" is the safest place.\n" "Choosing \"%s\" will not install any boot loader. Use this option only if " "you\n" "know what you're doing." msgstr "" "Alglaadur on väike programm, mille arvuti käivitab alglaadimise ajal.\n" "Tavaliselt tuvastatakse see täiesti automaatselt.\n" "DrakX uurib ketta alglaadimissektorit ja talitab vastavalt sellele,\n" "mida ta sealt leiab:\n" "\n" " * kui leitakse Windowsi alglaadimissektor, asendatatakse see grub/LiLo\n" "alglaadimissektoriga. Nii võite laadida kas GNU/Linuxi või mõne muu OS-i.\n" "\n" " * kui leitakse grub-i või LiLo alglaadimissektor, asendatakse see uuega.\n" "\n" "Kui DrakX ei suuda asjast aru saada, küsitakse Teie käest, kuhu alglaadur\n" "paigutada. Üldiselt on \"%s\" kindlaim valik. Kui valida \"%s\", ei\n" "paigaldata alglaadurit üldse. Aga seda kasutage küll ainult siis, kui\n" "VÄGA TÄPSELT teate, mida teete!" #: ../help.pm:745 #, fuzzy, c-format msgid "" "Now, it's time to select a printing system for your computer. Other\n" "operating systems may offer you one, but Mageia offers two. Each of\n" "the printing systems is best suited to particular types of configuration.\n" "\n" " * \"%s\" -- which is an acronym for ``print, do not queue'', is the choice\n" "if you have a direct connection to your printer, you want to be able to\n" "panic out of printer jams, and you do not have networked printers. (\"%s\"\n" "will handle only very simple network cases and is somewhat slow when used\n" "within networks.) It's recommended that you use \"pdq\" if this is your\n" "first experience with GNU/Linux.\n" "\n" " * \"%s\" stands for `` Common Unix Printing System'' and is an excellent\n" "choice for printing to your local printer or to one halfway around the\n" "planet. It's simple to configure and can act as a server or a client for\n" "the ancient \"lpd\" printing system, so it's compatible with older\n" "operating systems which may still need print services. While quite\n" "powerful, the basic setup is almost as easy as \"pdq\". If you need to\n" "emulate a \"lpd\" server, make sure you turn on the \"cups-lpd\" daemon.\n" "\"%s\" includes graphical front-ends for printing or choosing printer\n" "options and for managing the printer.\n" "\n" "If you make a choice now, and later find that you do not like your printing\n" "system you may change it by running PrinterDrake from the Mageia\n" "Control Center and clicking on the \"%s\" button." msgstr "" "Siin saate valida oma arvuti trükkimissüsteemi. Teised " "operatsioonisüsteemid\n" "võivad Teile pakkuda vaid üht süsteemi, kuid Mageiai puhul saate\n" "valida tervelt kahe seast.\n" "\n" " * \"%s\" - mis tähendab \"trüki kohe\" (\"print, do not queue\") - tuleks " "valida siis,\n" "kui Teil on printeriga otseühendus, Te ei soovi näha mingeid järjekordi ja " "Teil\n" "ei ole võrgus asuvaid printereid. Võrkude puhul on \"%s\" mõnevõrra aeglane " "ja\n" "tal võib esineda tegutsemisraskusi. Kui see on Teie esimene retk GNU/Linuxi\n" "maailma, valige \"pdq\".\n" "\n" " * \"%s\" - \"tavaline UNIXi trükkimissüsteem\" (\"Common Unix Printing\n" "System\") - on hiilgav valik trükkimiseks Teie kohalikus printeris või ka " "mõnel teisel pool maakera asuvas\n" "printeris. See on lihtne süsteem, mis võib olla nii kliendiks kui serveriks " "iidsele\n" "trükkimissüsteemile \"lpd\". See on ka ühilduv varasemate süsteemidega.\n" "suudab teha palju asju, kuid põhitegutsemine on sama lihtne kui \"pdq\" " "puhul.\n" "Kui Teil on vajadus emuleerida \"lpd\"-serverit, tuleb sisse lülitada\n" "\"cups-lpd\"-deemon. \"%s\" pakub ka mitut graafilist kasutajaliidest\n" "trükkimiseks või printeri seadistamiseks.\n" "\n" "Kui leiate hiljem, et siinkohal langetatud valik polnud vahest kõige parem,\n" "siis saate seda muuta Mageiai juhtimiskeskuses PrinterDrake abil,\n" "klõpsates seal nupule \"%s\"." #: ../help.pm:768 #, c-format msgid "pdq" msgstr "pdq" #: ../help.pm:724 #, c-format msgid "CUPS" msgstr "CUPS" #: ../help.pm:724 #, c-format msgid "Expert" msgstr "Ekspertrežiim" #: ../help.pm:771 #, c-format msgid "" "DrakX will first detect any IDE devices present in your computer. It will\n" "also scan for one or more PCI SCSI cards on your system. If a SCSI card is\n" "found, DrakX will automatically install the appropriate driver.\n" "\n" "Because hardware detection is not foolproof, DrakX may fail in detecting\n" "your hard drives. If so, you'll have to specify your hardware by hand.\n" "\n" "If you had to manually specify your PCI SCSI adapter, DrakX will ask if you\n" "want to configure options for it. You should allow DrakX to probe the\n" "hardware for the card-specific options which are needed to initialize the\n" "adapter. Most of the time, DrakX will get through this step without any\n" "issues.\n" "\n" "If DrakX is not able to probe for the options to automatically determine\n" "which parameters need to be passed to the hardware, you'll need to manually\n" "configure the driver." msgstr "" "Esmalt otsib DrakX üles kõik Teie arvuti IDE-seadmed, püüdes samal ajal\n" "tuvastada ka PCI siini SCSI-liideseid. Kui viimaseid leitakse ja vastav(ad)\n" "draiver(id) on teada, siis laetakse ja paigaldatakse kõik vajalik " "automaatselt.\n" "\n" "Riistvara tuvastamine ei pruugi alati siiski õnnestuda ja kui see nii " "peaks \n" "minema, palub DrakX Teil teatada, kas masinas on mõni PCI SCSI-liides.\n" "\n" "Kui peate oma adapteri käsitsi määrama, küsib DrakX, kas soovite määrata\n" "ka selle parameetrid. Siin oleks mõtet lasta tegutseda DrakX'il, mis " "proovib\n" "järele liidese spetsiifilised omadused, mida see initsialiseerimiseks " "vajab.\n" "Tavaliselt õnnestub see edukalt.\n" "\n" "Kui automaatne parameetrite otsimine ei tööta, tuleb liides käsitsi " "seadistada.\n" "Selleks tutvuge palun lähemalt oma SCSI liidese dokumentatsiooniga\n" "või küsige abi riistvara müüjalt." #: ../help.pm:789 #, c-format msgid "" "\"%s\": if a sound card is detected on your system, it'll be displayed\n" "here. If you notice the sound card is not the one actually present on your\n" "system, you can click on the button and choose a different driver." msgstr "" "\"%s\": kui süsteemis leiti helikaart, näidatakse seda siin.\n" "Kui märkate, et näidatav helikaart ei ole mitte see, mis süsteemis\n" "Teie teada tegelikult on, klõpsake nuppu ja valige uus draiver." #: ../help.pm:794 #, fuzzy, c-format msgid "" "As a review, DrakX will present a summary of information it has gathered\n" "about your system. Depending on the hardware installed on your machine, you\n" "may have some or all of the following entries. Each entry is made up of the\n" "hardware item to be configured, followed by a quick summary of the current\n" "configuration. Click on the corresponding \"%s\" button to make the change.\n" "\n" " * \"%s\": check the current keyboard map configuration and change it if\n" "necessary.\n" "\n" " * \"%s\": check the current country selection. If you're not in this\n" "country, click on the \"%s\" button and choose another. If your country\n" "is not in the list shown, click on the \"%s\" button to get the complete\n" "country list.\n" "\n" " * \"%s\": by default, DrakX deduces your time zone based on the country\n" "you have chosen. You can click on the \"%s\" button here if this is not\n" "correct.\n" "\n" " * \"%s\": verify the current mouse configuration and click on the button\n" "to change it if necessary.\n" "\n" " * \"%s\": if a sound card is detected on your system, it'll be displayed\n" "here. If you notice the sound card is not the one actually present on your\n" "system, you can click on the button and choose a different driver.\n" "\n" " * \"%s\": if you have a TV card, this is where information about its\n" "configuration will be displayed. If you have a TV card and it is not\n" "detected, click on \"%s\" to try to configure it manually.\n" "\n" " * \"%s\": you can click on \"%s\" to change the parameters associated with\n" "the card if you feel the configuration is wrong.\n" "\n" " * \"%s\": by default, DrakX configures your graphical interface in\n" "\"800x600\" or \"1024x768\" resolution. If that does not suit you, click on\n" "\"%s\" to reconfigure your graphical interface.\n" "\n" " * \"%s\": if you wish to configure your Internet or local network access,\n" "you can do so now. Refer to the printed documentation or use the\n" "Mageia Control Center after the installation has finished to benefit\n" "from full in-line help.\n" "\n" " * \"%s\": allows to configure HTTP and FTP proxy addresses if the machine\n" "you're installing on is to be located behind a proxy server.\n" "\n" " * \"%s\": this entry allows you to redefine the security level as set in a\n" "previous step ().\n" "\n" " * \"%s\": if you plan to connect your machine to the Internet, it's a good\n" "idea to protect yourself from intrusions by setting up a firewall. Consult\n" "the corresponding section of the ``Starter Guide'' for details about\n" "firewall settings.\n" "\n" " * \"%s\": if you wish to change your bootloader configuration, click this\n" "button. This should be reserved to advanced users. Refer to the printed\n" "documentation or the in-line help about bootloader configuration in the\n" "Mageia Control Center.\n" "\n" " * \"%s\": through this entry you can fine tune which services will be run\n" "on your machine. If you plan to use this machine as a server it's a good\n" "idea to review this setup." msgstr "" "Siin näidatakse mitmeid Teie süsteemi puudutavaid parameetreid. Sõltuvalt\n" "riistvarast võite siin näha kõiki või osa järgmistest kirjetest. Iga kirje\n" "juures on ära toodud elemendid, mida on võimalik seadistada, ning Teie " "masinas\n" "praegu kehtiv seadistus. Selle muutmiseks klõpsake nupule \"%s\".\n" "\n" " * \"%s\": võimaldab kontrollida klaviatuuritabeli seadistusi\n" "ja neid vajaduse korral muuta.\n" "\n" " * \"%s\": võimaldab kontrollida asukohariigi valikut. Kui Te ei asu\n" "vaikimisi määratud riigis, klõpsake nupule \"%s\" ja valige uus\n" "riik. Kui Teie riiki ei ole ilmuvas nimekirjas, klõpsake nupule\n" "\"%s\", mis avab riikide täisnimekirja.\n" "\n" " * \"%s\": DrakX tuletab ajavööndi valitud riigi põhjal. Kui see ei peaks\n" "Teile sobima, klõpsake nupule \"%s\".\n" "\n" " * \"%s\": võimaldab kontrollida hiire seadistusi ja neid vajadusel muuta.\n" "\n" " * \"%s\": kui süsteemis leiti helikaart, näidatakse seda.\n" "Kui märkate, et siintoodud helikaart pole see, mis tegelikult on\n" "süsteemi paigaldatud, klõpsake nupule ja valige sobiv draiver.\n" "\n" " * \"%s\": kui süsteemis leiti TV-kaart, näidatakse seda.\n" "Kui Teil on TV-kaart, aga seda ei leitud, klõpsake nupule \"%s\"\n" "ning püüdke see käsitsi määrata.\n" "\n" " * \"%s\": nupule \"%s\" klõpsates saab muuta kaardiga seotud\n" "parameetreid, kui arvate, et need pole korrektsed.\n" "\n" " * \"%s\": vaikimisi määrab DrakX Teie graafilise liidese\n" "ekraanilahutuseks \"800x600\" või \"1024x768\". Kui see Teile ei sobi,\n" "klõpsake nupule \"%s\" ja valige mõni muu võimalus.\n" "\n" " * \"%s\": Kui soovite kohe seadistada juurdepääsu Internetti või\n" "kohtvõrku, saate seda teha nupule klõpsates. Täpsemalt kõnelevad\n" "võrgu seadistustest distributsiooniga kaasas olevad trükised või\n" "Mageiai juhtimiskeskuse abimaterjalid.\n" " * \"%s\": siin saab määrata HTTP ja FTP puhverserveri aadressid,\n" "kui Teie masin asub puhverserveri taga.\n" "\n" " * \"%s\": see võimaldab muuta eelmisel sammul paika pandud turvataset.\n" "\n" " * \"%s\": kui kavatsete oma süsteemi Internetti ühendada, kuluks\n" "ära enda kaitsmine rünnakute eest tulemüüriga. Vaadake\n" "üksikasju, kuidas tulemüüri seadistada, \"Põhiteadmiste käsiraamatu\" " "vastavast peatükist.\n" "\n" " * \"%s\": kui soovite muuta alglaaduri seadistusi, klõpsake\n" "sellele nupule. See on mõeldud siiski vaid kogenud kasutajatele.\n" "Täpsemat infot leiab käsiraamatust või Mageiai juhtimiskeskusest.\n" "\n" " * \"%s\": saate täpselt kontrollida, millised teenused Teie\n" "süsteemis töötavad. Kui kavatsete kasutada oma masinat serverina, kuluks\n" "ära seadistused üle vaadata." #: ../help.pm:809 #, c-format msgid "TV card" msgstr "TV-kaart" #: ../help.pm:809 #, c-format msgid "ISDN card" msgstr "ISDN kaart" #: ../help.pm:858 #, c-format msgid "Graphical Interface" msgstr "Graafiline kasutajaliides" #: ../help.pm:861 #, fuzzy, c-format msgid "" "Choose the hard drive you want to erase in order to install your new\n" "Mageia partition. Be careful, all data on this drive will be lost\n" "and will not be recoverable!" msgstr "" "Valige kõvaketas, mida soovite puhastada oma uue Mageiai\n" "paigaldamiseks. Ettevaatust, kõik sellel leiduvad andmed hävitatakse\n" "ja neid ei saa enam taastada." #: ../help.pm:866 #, c-format msgid "" "Click on \"%s\" if you want to delete all data and partitions present on\n" "this hard drive. Be careful, after clicking on \"%s\", you will not be able\n" "to recover any data and partitions present on this hard drive, including\n" "any Windows data.\n" "\n" "Click on \"%s\" to quit this operation without losing data and partitions\n" "present on this hard drive." msgstr "" "Valige \"%s\", kui soovite kustutada kõik sellel kettal asuvad\n" "partitsioonid. Ettevaatust, pärast \"%s\" klõpsamist ei ole enam\n" "võimalik sellelt kettalt andmeid taastada.\n" "\n" "Loobumiseks valige \"%s\", mis katkestab tegevuse ilma andmeid\n" "ja käesoleval kõvakettal olevaid partitsioone kustutamata." #: ../help.pm:872 #, c-format msgid "Next ->" msgstr "Järgmine ->" #: ../help.pm:872 #, c-format msgid "<- Previous" msgstr "<- Eelmine" #~ msgid "" #~ "\"%s\": clicking on the \"%s\" button will open the printer " #~ "configuration\n" #~ "wizard. Consult the corresponding chapter of the ``Starter Guide'' for " #~ "more\n" #~ "information on how to set up a new printer. The interface presented in " #~ "our\n" #~ "manual is similar to the one used during installation." #~ msgstr "" #~ "\"%s\": klõps nupul \"%s\" avab printeri seadistamise nõustaja.\n" #~ "Uurige lähemalt \"Põhiteadmiste käsiraamatu\" (\"Starter Guide\")\n" #~ "vastavast peatükist, kuidas uut printerit häälestada.\n" #~ "Siin näidatav sarnaneb sellele, mida võisite näha paigaldamise ajal." #~ msgid "" #~ "This is the most crucial decision point for the security of your GNU/" #~ "Linux\n" #~ "system: you must enter the \"root\" password. \"Root\" is the system\n" #~ "administrator and is the only user authorized to make updates, add " #~ "users,\n" #~ "change the overall system configuration, and so on. In short, \"root\" " #~ "can\n" #~ "do everything! That's why you must choose a password which is difficult " #~ "to\n" #~ "guess: DrakX will tell you if the password you chose is too simple. As " #~ "you\n" #~ "can see, you're not forced to enter a password, but we strongly advise\n" #~ "against this. GNU/Linux is just as prone to operator error as any other\n" #~ "operating system. Since \"root\" can overcome all limitations and\n" #~ "unintentionally erase all data on partitions by carelessly accessing the\n" #~ "partitions themselves, it is important that it be difficult to become\n" #~ "\"root\".\n" #~ "\n" #~ "The password should be a mixture of alphanumeric characters and at least " #~ "8\n" #~ "characters long. Never write down the \"root\" password -- it makes it " #~ "far\n" #~ "too easy to compromise your system.\n" #~ "\n" #~ "One caveat: do not make the password too long or too complicated because " #~ "you\n" #~ "must be able to remember it!\n" #~ "\n" #~ "The password will not be displayed on screen as you type it. To reduce " #~ "the\n" #~ "chance of a blind typing error you'll need to enter the password twice. " #~ "If\n" #~ "you do happen to make the same typing error twice, you'll have to use " #~ "this\n" #~ "``incorrect'' password the first time you'll try to connect as \"root\".\n" #~ "\n" #~ "If you want an authentication server to control access to your computer,\n" #~ "click on the \"%s\" button.\n" #~ "\n" #~ "If your network uses either LDAP, NIS, or PDC Windows Domain " #~ "authentication\n" #~ "services, select the appropriate one for \"%s\". If you do not know " #~ "which\n" #~ "one to use, you should ask your network administrator.\n" #~ "\n" #~ "If you happen to have problems with remembering passwords, or if your\n" #~ "computer will never be connected to the Internet and you absolutely " #~ "trust\n" #~ "everybody who uses your computer, you can choose to have \"%s\"." #~ msgstr "" #~ "Nüüd on kätte jõudnud kõige olulisem hetk Teie arvuti turvalisuse " #~ "tagamisel:\n" #~ "Teil tuleb määrata administraatori (\"root\") parool. Administraator " #~ "haldab kogu\n" #~ "süsteemi ja ainult temal on õigus seda uuendada, kasutajaid lisada, "