summaryrefslogtreecommitdiffstats
path: root/perl_checker.src/tree.ml
blob: f866e14ed50188bcf9d35f11b5535a3fbb8328ec (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
open Types
open Common
open Printf
open Config_file
open Parser_helper

type special_export = Re_export_all | Fake_export_all

type exports = { 
    export_ok : (context * string) list ;
    export_auto : (context * string) list ;
    export_tags : (string * (context * string) list) list ;
    special_export : special_export option ;
  }

type uses = (string * ((context * string) list option * pos)) list

type prototype = {
    proto_nb_min : int ;
    proto_nb_max : int option ;
  }

type per_package = {
    file_name : string ;
    package_name : string ; has_package_name : bool ;
    vars_declared : (context * string, pos * bool ref * prototype option) Hashtbl.t ;
    imported : ((context * string) * (string * bool ref * prototype option)) list option ref ;
    exports : exports ;
    uses : uses ;
    required_packages : (string * pos) list ;
    body : fromparser list ;
    isa : (string * pos) list option ;
    lines_starts : int list ;
    build_time : int ;
    from_cache : bool ;
    from_basedir : bool ;
  }

let anonymous_package_count = ref 0
let empty_exports = { export_ok = []; export_auto = []; export_tags = []; special_export = None }
let use_lib = ref (readlines (Unix.open_process_in "perl -le 'print foreach @INC'"))

let ignore_package pkg = 
  if !Flags.verbose then print_endline_flush ("ignoring 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 s2context s = 
  match s.[0] with
  | '$' -> I_scalar, skip_n_char 1 s
  | '%' -> I_hash  , skip_n_char 1 s
  | '@' -> I_array , skip_n_char 1 s
  | '&' -> I_func  , skip_n_char 1 s
  | '*' -> I_star  , skip_n_char 1 s
  | _ -> I_raw, s



let get_current_package t =
  match t with
  | Package(Ident _ as ident) :: body ->
      let rec bundled_packages packages current_package found_body = function
	| [] -> (Some current_package, List.rev found_body) :: packages
	| Package(Ident _ as ident) :: body ->
	    let packages = (Some current_package, List.rev found_body) :: packages in
	    bundled_packages packages (string_of_Ident ident) [] body
	| instr :: body ->
	    bundled_packages packages current_package (instr :: found_body) body
      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.current_file) ;
      [ None, t ]

let from_qw_raw = function
  | Call_op("qw", [ Raw_string(s, pos)], _) -> 
      List.map (fun symbol -> symbol, pos) (words s)
  | String(_, pos) ->
      warn_with_pos pos "not recognised yet" ;
      []
  | Raw_string(s, pos) ->
      [ s, pos ]
  | _ -> internal_error "from_qw_raw"

let from_qw e =
  List.map (fun (s, pos) -> 
    let context, s' = s2context s in
    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
      | _ -> context 
    in context, s'
  ) (from_qw_raw e)

let get_exported t =
  List.fold_left (fun exports e ->
    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" ;
	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" ;
	{ exports with export_auto = from_qw v }

    | Perl_checker_comment("RE-EXPORT-ALL", _) -> { exports with special_export = Some Re_export_all }
    | Perl_checker_comment("EXPORT-ALL",    _) -> { exports with special_export = Some Fake_export_all }

    | 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" ;
	(match v with
	| Call(Deref(I_func, Ident(None, "map", _)), 
	       [ Anonymous_sub(_, Block [List [Deref(I_array, Deref(I_scalar, Ident (None, "_", _)))]], _);
		 Call(Deref(I_func, Ident(None, "values", _)), [ Deref(I_hash, Ident(None, "EXPORT_TAGS", _))])]) ->
		   { exports with export_ok = collect snd exports.export_tags }
	| _ -> { exports with export_ok = from_qw v })

    | List [ Call_op("=", [ Deref(I_hash, Ident(None, "EXPORT_TAGS", _)); v ], pos)]
    | List [ Call_op("=", [ My_our("our", [(I_hash, "EXPORT_TAGS")], _);  v ], pos)] ->
	(try
	  let export_tags =
	    match v with
	    | List [ List l ] ->
		List.map (function
		  | Raw_string(tag, _), Ref(I_array, List [List [v]]) ->
		      let para =
			match v with
			| Deref(I_array, Ident(None, "EXPORT_OK", _)) -> exports.export_ok
			| _ -> from_qw v
		      in
		      ":" ^ tag, para
		  | _ -> raise Not_found
	        ) (group_by_2 l)
	    | _ -> raise Not_found
	  in
	  if exports.export_tags <> [] then warn_with_pos pos "weird, %EXPORT_TAGS set twice" ;
	  { exports with export_tags = export_tags }
	with _ ->
	  warn_with_pos pos "unrecognised %EXPORT_TAGS" ;
	  exports)

      (* $EXPORT_TAGS{all} = [ map { @$_ } values %EXPORT_TAGS ]; *)
    | List [Call_op("=", [
		    Deref_with(I_hash, I_scalar, Ident(None, "EXPORT_TAGS", _), Raw_string("all", _));
		    Ref(I_array,
			List[List[
			     Call(Deref(I_func, Ident(None, "map", _)),
				  [Anonymous_sub(_, Block [List [Deref(I_array, Deref(I_scalar, Ident(None, "_", _)))]], _);
				   Call(Deref(I_func, Ident(None, "values", _)), [Deref(I_hash, Ident(None, "EXPORT_TAGS", _))])])
			   ]])
		  ], _)] ->
		    { exports with export_tags = (":all", collect snd exports.export_tags) :: exports.export_tags }

    | List (My_our _ :: _) ->
	let _,_ = e,e in
	exports
    | _ -> exports
  ) empty_exports t

let uses_external_package = function
  | "vars" | "MDK::Common::Globals" | "Exporter" | "diagnostics" | "strict" | "lib" | "POSIX" | "Gtk" | "Storable"
  | "Config" | "Socket" | "IO::Socket" | "DynaLoader" | "Data::Dumper" | "Time::localtime" | "Expect" -> true
  | _ -> false

let get_uses t =
  List.fold_left (fun uses e ->
    match e with
    | Use(Ident(None, "lib", _), [libs]) ->
	use_lib := List.map snd (from_qw libs) @ !use_lib ;
	uses
    | Use(Ident _ as pkg, _) when uses_external_package (string_of_Ident pkg) -> uses
    | Use(Ident(_, _, pos) as ident, l) ->
	let package = string_of_Ident ident in
	let para = if l = [] then None else Some(from_qw (List.hd l)) in
	(package, (para, pos)) :: uses
    | _ -> uses
  ) [] t

let get_isa t =
  List.fold_left (fun (isa, exporter) e ->
    match e with
    | List [ Call_op("=", [ Deref(I_array, Ident(None, "ISA", pos)) ; classes ], _) ]
    | List [ Call_op("=", [ My_our("our", [ I_array, "ISA" ], pos) ; classes ], _) ] ->
	if isa <> None || exporter <> None then die_with_pos pos "@ISA set twice";
	let special, l = List.partition (fun (s, _) -> s = "DynaLoader" || s = "Exporter") (from_qw_raw classes) in
	let exporter = if List.mem_assoc "Exporter" special then Some pos else None in
	let isa = if l = [] && special <> [] then None else Some l in
	isa, exporter
    | _ -> isa, exporter
  ) (None, None) t

let read_xs_extension_from_c global_vars_declared package pos =
  try
    let cfile = Filename.chop_extension package.file_name ^ ".c" in
    let prefix = "newXS(\"" ^ package.package_name ^ "::" in
    ignore (fold_lines (fun in_bootstrap s ->
      if in_bootstrap then
	(try
	  let offset = strstr s prefix + String.length prefix in
	  let end_ = String.index_from s offset '"' in
	  let ident = String.sub s offset (end_ - offset) in
	  match split_name_or_fq_name ident with
	  | None, ident -> Hashtbl.replace package.vars_declared (I_func, ident) (pos, ref false, None)
	  | Some fq, ident -> 
	      let fq = package.package_name ^ "::" ^ fq in
	      Hashtbl.replace global_vars_declared (I_func, fq, ident) (pos, None)
	 with Not_found -> ());
      in_bootstrap || str_contains s "XS_VERSION_BOOTCHECK"
    ) false (open_in cfile));
    true
  with Invalid_argument _ | Sys_error _ -> false

let findfile dirs f = List.find (fun dir -> Sys.file_exists (dir ^ "/" ^ f)) dirs

let read_xs_extension_from_so global_vars_declared package pos =
  try
    let splitted = split_at2 ':'':' package.package_name in
    let rel_file = String.concat "/" ("auto" :: splitted @ [ last splitted ]) ^ ".so" in
    let so = (findfile !use_lib rel_file) ^ "/" ^ rel_file in
    let channel = Unix.open_process_in (Printf.sprintf "nm --defined-only -D \"%s\"" so) in
    fold_lines (fun () s ->
      let s = skip_n_char 11 s in
      if str_begins_with s "XS_" then
	let s = skip_n_char 3 s in
	let len = String.length s in
	let rec find_package_name accu i =
	  try
	    let i' = String.index_from s i '_' in
	    let accu = String.sub s i (i'-i) :: accu in
	    if i' + 1 < len && s.[i'+1] = '_' then
	      find_package_name accu (i' + 2)
	    else
	      List.rev accu, skip_n_char (i'+1) s
	  with Not_found -> List.rev accu, skip_n_char i s
	in
	let fq, name = find_package_name [] 0 in
	Hashtbl.replace global_vars_declared (I_func, String.concat "::" fq, name) (pos, None)
    ) () channel;
    let _ = Unix.close_process_in channel in
    true
  with Not_found -> false

let has_proto perl_proto body = 
  match perl_proto with
  | Some "" -> Some([], raw_pos2pos bpos, [body])
  | _ -> 
      match body with
      | Block [] ->
	  Some([ I_array, "_empty" ], raw_pos2pos bpos, [])
      | Block (List [Call_op ("=", [My_our ("my", mys, mys_pos); Deref(I_array, Ident(None, "_", _))], _pos)] :: body) ->
	  Some(mys, mys_pos, body)
      | _ -> None

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"
    | _ -> ());
    let is_optional (_, s) = String.length s > 2 && (s.[0] = 'o' || s.[0] = 'b') && s.[1] = '_' 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";
    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)

let get_vars_declaration global_vars_declared package = 
  List.iter (function
    | Sub_declaration(Ident(None, name, pos), perl_proto, body, _) ->
	Hashtbl.replace package.vars_declared (I_func, name) (pos, ref false, get_proto perl_proto body)
    | Sub_declaration(Ident(Some fq, name, pos), perl_proto, body, _) ->
	Hashtbl.replace global_vars_declared (I_func, fq, name) (pos, get_proto perl_proto body)

    | List [ Call_op("=", [My_our("our", ours, pos); _], _) ]
    | List [ Call_op("=", [My_our("local", ([ I_scalar, "_" ] as ours), pos); _], _) ]
    | List [ My_our("our", ours, pos) ]
    | My_our("our", ours, pos) ->
	List.iter (fun (context, name) -> Hashtbl.replace package.vars_declared (context, name) (pos, ref false, None)) ours

    | Use(Ident(Some "MDK::Common", "Globals", pos), [ String _ ; ours ])
    | Use(Ident(None, "vars", pos), [ours]) -> 
	List.iter (fun (context, name) -> Hashtbl.replace package.vars_declared (context, name) (pos, ref false, None)) (from_qw ours)
    | Use(Ident(None, "vars", pos), _) -> 
	die_with_pos pos "usage: use vars qw($var func)"

    | 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)"
	else
	  if not (read_xs_extension_from_c global_vars_declared package pos) then 
	    if not (read_xs_extension_from_so global_vars_declared package pos) then
	      ignore_package pkg
    | _ -> ()
  ) package.body

let rec fold_tree f env e = 
 match f env e with
  | Some env -> env
  | None ->
  match e with
  | Anonymous_sub(_, e', _)
  | Ref(_, e')
  | Deref(_, e')
    -> fold_tree f env e'

  | Diamond(e')
    -> fold_tree_option f env e'

  | String(l, _)
    -> List.fold_left (fun env (_, e) -> fold_tree f env e) env l

  | Sub_declaration(e1, _, e2, _)
  | Deref_with(_, _, e1, e2)
    -> 
      let env = fold_tree f env e1 in
      let env = fold_tree f env e2 in
      env

  | Use(_, l)
  | List l
  | Block l
  | Call_op(_, l, _)
    -> List.fold_left (fold_tree f) env l

  | Call(e', l)
    -> 
      let env = fold_tree f env e' in
      List.fold_left (fold_tree f) env l

  | Method_call(e1, e2, l)
    ->
      let env = fold_tree f env e1 in
      let env = fold_tree f env e2 in
      List.fold_left (fold_tree f) env l

  | _ -> env

and fold_tree_option f env = function
  | None -> env
  | Some e -> fold_tree f env e


let get_global_info_from_package from_basedir build_time t =
  let current_packages = get_current_package t in
  List.map (fun (current_package, t) ->
    let exports = get_exported t in
    let exporting_something() = exports.export_ok <> [] || exports.export_auto <> [] || exports.export_tags <> [] || exports.special_export = Some Re_export_all in

    let package_name =
      match current_package with
      | None -> 
	  if exporting_something() then
	    die_with_pos (!Info.current_file, 0, 0) "file with no package name wants to export!"
	  else
	    (incr anonymous_package_count ; sprintf "anonymous%d" !anonymous_package_count)
      | Some name -> name
    in
    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"
    | Some pos ->
	if not (exporting_something()) then warn_with_pos 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
    let required_packages = List.fold_left (fold_tree (fun l -> 
      function
	| Perl_checker_comment(s, pos) when str_begins_with s "require " ->
	    Some((skip_n_char 8 s, pos) :: l)
	| Call(Deref(I_func, Ident (None, "require", pos)), [Ident _ as pkg]) ->
	    let package = string_of_Ident pkg in
	    if uses_external_package package then None else Some((package, pos) :: l)
	| Call(Deref(I_func, Ident (None, "require", pos)), [Raw_string(pkg, _)])
	    when not (String.contains pkg '/') && Filename.check_suffix pkg ".pm" ->
	    let package = Filename.chop_suffix pkg ".pm" in
	    if uses_external_package package then None else Some((package, pos) :: l)
	| _ -> None)
      ) required_packages t in
    { 
      file_name = !Info.current_file ; 
      package_name = package_name;
      has_package_name = current_package <> None ;
      exports = exports ;
      imported = ref None ;
      vars_declared = Hashtbl.create 16 ;
      uses = uses ;
      required_packages = required_packages ;
      body = t ;
      isa = isa ;
      lines_starts = !Info.current_file_lines_starts ;
      build_time = build_time ;
      from_cache = false ;
      from_basedir = from_basedir ;
    }
  ) current_packages
baren " "Mirrors zu erhalten" #: any.pm:195 #, c-format msgid "Choose a mirror from which to get the packages" msgstr "Bitte wählen Sie einen Mirror, von dem Sie die Pakete holen wollen." #: any.pm:225 #, c-format msgid "NFS setup" msgstr "NFS-Einrichtungsetup" #: any.pm:226 #, c-format msgid "Please enter the hostname and directory of your NFS media" msgstr "Bitte geben Sie den Rechnernamen und das Verzeichnis ihres NFS-Mediums ein" #: any.pm:230 #, c-format msgid "Hostname missing" msgstr "Hostname fehlt" #: any.pm:231 #, c-format msgid "Directory must begin with \"/\"" msgstr "Verzeichnis muss mit \"/\" beginnen" #: any.pm:235 #, c-format msgid "Hostname of the NFS mount ?" msgstr "Rechnername der NFS-Einbindung?" #: any.pm:236 #, c-format msgid "Directory" msgstr "Verzeichnis" #: any.pm:258 #, c-format msgid "Supplementary" msgstr "Ergänzend" #: any.pm:293 #, c-format msgid "" "Can't find a package list file on this mirror. Make sure the location is " "correct." msgstr "Kann die Datei hdlist nicht auf diesem Spiegel finden" #: any.pm:328 #, c-format msgid "Looking at packages already installed..." msgstr "Suche nach bereits installierten Paketen ..." #: any.pm:335 #, c-format msgid "Removing packages prior to upgrade..." msgstr "Entferne Pakete vor der Aktualisierung..." #: any.pm:377 #, c-format msgid "Finding packages to upgrade..." msgstr "Finde die zu aktualisierenden Pakete ..." #. -PO: keep the double empty lines between sections, this is formatted a la LaTeX #: any.pm:564 #, c-format msgid "" "You have selected the following server(s): %s\n" "\n" "\n" "These servers are activated by default. They do not have any known security\n" "issues, but some new ones could be found. In that case, you must make sure\n" "to upgrade as soon as possible.\n" "\n" "\n" "Do you really want to install these servers?\n" msgstr "" "Sie haben die folgenden Server ausgewählt: %s\n" "\n" "\n" "Diese Server werden standardmäßig aktiviert. Sie haben keine bekannten\n" "Sicherheitsprobleme, jedoch könnten einige neue entdeckt werden. Stellen\n" "Sie deshalb sicher, dass Sie diese Pakete so zeitig wie möglich " "aktualisieren.\n" "\n" "\n" "Wollen Sie diese Server wirklich installieren?\n" #. -PO: keep the double empty lines between sections, this is formatted a la LaTeX #: any.pm:587 #, c-format msgid "" "The following packages will be removed to allow upgrading your system: %s\n" "\n" "\n" "Do you really want to remove these packages?\n" msgstr "" "Folgende Pakete werden entfernt, um das Aktualisieren Ihres Rechners zu " "ermöglichen: %s\n" "\n" "\n" "Wollen Sie diese Pakete wirklich entfernen?\n" #: any.pm:801 #, c-format msgid "Error reading file %s" msgstr "Fehler beim Lesen der Datei %s" #: any.pm:1008 #, c-format msgid "The following disk(s) were renamed:" msgstr "Die folgenden Datenträger wurden umbenannt:" #: any.pm:1010 #, c-format msgid "%s (previously named as %s)" msgstr "%s (vorher als %s bezeichnet)" #: any.pm:1067 #, c-format msgid "HTTP" msgstr "HTTP" #: any.pm:1067 #, c-format msgid "FTP" msgstr "FTP" #: any.pm:1067 #, c-format msgid "NFS" msgstr "NFS" #: any.pm:1086 steps_interactive.pm:972 #, c-format msgid "Network" msgstr "Netzwerk" #: any.pm:1090 #, c-format msgid "Please choose a media" msgstr "Bitte wählen Sie ein Medium" #: any.pm:1106 #, c-format msgid "File already exists. Overwrite it?" msgstr "Die Datei existiert bereits. Überschreiben?" #: any.pm:1110 #, c-format msgid "Permission denied" msgstr "Erlaubnis verweigert" #: any.pm:1158 #, c-format msgid "Bad NFS name" msgstr "Falscher NFS-Name" #: any.pm:1179 #, c-format msgid "Bad media %s" msgstr "Mediumfehler %s" #: any.pm:1222 #, c-format msgid "Can not make screenshots before partitioning" msgstr "Vor der Partitionierung kann ich keine Screenshots machen." #: any.pm:1230 #, c-format msgid "Screenshots will be available after install in %s" msgstr "Die Screenshots liegen nach der Installation unter „%s“" #: gtk.pm:126 #, c-format msgid "Installation" msgstr "Installation" #: gtk.pm:130 share/meta-task/compssUsers.pl:42 #, c-format msgid "Configuration" msgstr "Konfiguration" #: install2.pm:168 #, c-format msgid "You must also format %s" msgstr "Sie müssen auch %s formatieren." #: interactive.pm:16 #, c-format msgid "" "Some hardware on your computer needs ``proprietary'' drivers to work.\n" "You can find some information about them at: %s" msgstr "" "Einige Hardware-Komponenten Ihres Rechners benötigen „proprietäre“\n" "Treiber. Weitere Infos hierzu finden Sie unter: %s" #: interactive.pm:22 #, c-format msgid "Bringing up the network" msgstr "Netzwerkverbindung herstellen" #: interactive.pm:27 #, c-format msgid "Bringing down the network" msgstr "Netzwerkverbindung trennen" #: media.pm:703 media.pm:714 #, c-format msgid "Downloading file %s..." msgstr "Lade Datei %s herunter..." #: media.pm:806 #, c-format msgid "Copying some packages on disks for future use" msgstr "Pakete auf die Festplatte speichern für die spätere Verwendung" #: media.pm:859 #, c-format msgid "Copying in progress" msgstr "Dateien werden kopiert" #: pkgs.pm:29 #, c-format msgid "must have" msgstr "unbedingt notwendig" #: pkgs.pm:30 #, c-format msgid "important" msgstr "wichtig" #: pkgs.pm:31 #, c-format msgid "very nice" msgstr "sehr angenehm" #: pkgs.pm:32 #, c-format msgid "nice" msgstr "angenehm" #: pkgs.pm:33 #, c-format msgid "maybe" msgstr "eventuell" #: pkgs.pm:253 #, c-format msgid "" "Some packages requested by %s cannot be installed:\n" "%s" msgstr "" "Einige der Ausgewählten Programme von %s können nicht installiert werden:\n" "%s" #: share/meta-task/compssUsers.pl:11 #, c-format msgid "Workstation" msgstr "Arbeitsplatzrechner" #: share/meta-task/compssUsers.pl:13 #, c-format msgid "Office Workstation" msgstr "Büro-Arbeitsplatz" #: share/meta-task/compssUsers.pl:15 #, c-format msgid "" "Office programs: wordprocessors (OpenOffice.org Writer, Kword), spreadsheets " "(OpenOffice.org Calc, Kspread), PDF viewers, etc" msgstr "" "Office-Programme: Textverarbeitung (Openoffice.org Writer, KWord), " "Tabellenkalkulation (OpenOffice.org Calc, KSpread), PDF-Betrachter, usw." #: share/meta-task/compssUsers.pl:16 #, c-format msgid "" "Office programs: wordprocessors (kword, abiword), spreadsheets (kspread, " "gnumeric), pdf viewers, etc" msgstr "" "Office-Programme: Textverarbeitung (KWord, Abiword), Tabellenkalkulation " "(KSpread, Gnumeric), PDF-Betrachter, usw." #: share/meta-task/compssUsers.pl:21 #, c-format msgid "Game station" msgstr "Spiele-Station" #: share/meta-task/compssUsers.pl:22 #, c-format msgid "Amusement programs: arcade, boards, strategy, etc" msgstr "Spiele: Arcade-, Brett-, Strategiespiele, usw." #: share/meta-task/compssUsers.pl:25 #, c-format msgid "Multimedia station" msgstr "Multimedia-Station" #: share/meta-task/compssUsers.pl:26 #, c-format msgid "Sound and video playing/editing programs" msgstr "Programme, um Sound und Video abzuspielen und zu bearbeiten" #: share/meta-task/compssUsers.pl:31 #, c-format msgid "Internet station" msgstr "Internet-Station" #: share/meta-task/compssUsers.pl:32 #, c-format msgid "" "Set of tools to read and send mail and news (mutt, tin..) and to browse the " "Web" msgstr "" "Programme um E-Mails und News zu lesen und zu versenden (pine, mutt, tin..) " "und um im Internet zu surfen" #: share/meta-task/compssUsers.pl:37 #, c-format msgid "Network Computer (client)" msgstr "Netzwerk-Computer (Client)" #: share/meta-task/compssUsers.pl:38 #, c-format msgid "Clients for different protocols including ssh" msgstr "Clients für verschiedene Protokolle, u.a. SSH" #: share/meta-task/compssUsers.pl:43 #, c-format msgid "Tools to ease the configuration of your computer" msgstr "Werkzeuge, die die Konfiguration Ihres Computers erleichtern" #: share/meta-task/compssUsers.pl:47 #, c-format msgid "Console Tools" msgstr "Konsolen-Werkzeuge" #: share/meta-task/compssUsers.pl:48 #, c-format msgid "Editors, shells, file tools, terminals" msgstr "Editoren, Shells, Dateiwerkzeuge, Konsolen" #: share/meta-task/compssUsers.pl:52 share/meta-task/compssUsers.pl:153 #: share/meta-task/compssUsers.pl:155 #, c-format msgid "Development" msgstr "Entwicklung" #: share/meta-task/compssUsers.pl:53 share/meta-task/compssUsers.pl:156 #, c-format msgid "C and C++ development libraries, programs and include files" msgstr "C und C++ Entwicklungsbibliotheken, Programme und Include-Dateien" #: share/meta-task/compssUsers.pl:56 share/meta-task/compssUsers.pl:160 #, c-format msgid "Documentation" msgstr "Dokumentation" #: share/meta-task/compssUsers.pl:57 share/meta-task/compssUsers.pl:161 #, c-format msgid "Books and Howto's on Linux and Free Software" msgstr "Bücher und HOWTOs zu GNU/Linux und Freier Software" #: share/meta-task/compssUsers.pl:61 share/meta-task/compssUsers.pl:164 #, c-format msgid "LSB" msgstr "LSB" #: share/meta-task/compssUsers.pl:62 share/meta-task/compssUsers.pl:165 #, c-format msgid "Linux Standard Base. Third party applications support" msgstr "Linux-Standard-Base. Drittanbieterunterstützung" #: share/meta-task/compssUsers.pl:71 #, c-format msgid "Web Server" msgstr "Webserver" #: share/meta-task/compssUsers.pl:72 #, c-format msgid "Apache" msgstr "Apache" #: share/meta-task/compssUsers.pl:75 #, c-format msgid "Groupware" msgstr "Groupware" #: share/meta-task/compssUsers.pl:76 #, c-format msgid "Kolab Server" msgstr "Kolab-Server" #: share/meta-task/compssUsers.pl:79 share/meta-task/compssUsers.pl:120 #, c-format msgid "Firewall/Router" msgstr "Firewall / Router" #: share/meta-task/compssUsers.pl:80 share/meta-task/compssUsers.pl:121 #, c-format msgid "Internet gateway" msgstr "Internet-Gateway" #: share/meta-task/compssUsers.pl:83 #, c-format msgid "Mail/News" msgstr "E-Mail/News" #: share/meta-task/compssUsers.pl:84 #, c-format msgid "Postfix mail server, Inn news server" msgstr "Postfix Mail-Server, Inn News-Server" #: share/meta-task/compssUsers.pl:87 #, c-format msgid "Directory Server" msgstr "Verzeichnisdienst" #: share/meta-task/compssUsers.pl:91 #, c-format msgid "FTP Server" msgstr "FTP-Server" #: share/meta-task/compssUsers.pl:92 #, c-format msgid "ProFTPd" msgstr "ProFTPd" #: share/meta-task/compssUsers.pl:95 #, c-format msgid "DNS/NIS" msgstr "DNS/NIS" #: share/meta-task/compssUsers.pl:96 #, c-format msgid "Domain Name and Network Information Server" msgstr "Domänennamen- und Netzwerk-Informations-Server" #: share/meta-task/compssUsers.pl:99 #, c-format msgid "File and Printer Sharing Server" msgstr "Datei- und Druckerserver" #: share/meta-task/compssUsers.pl:100 #, c-format msgid "NFS Server, Samba server" msgstr "NFS-Server, Samba Server" #: share/meta-task/compssUsers.pl:103 share/meta-task/compssUsers.pl:116 #, c-format msgid "Database" msgstr "Datenbank" #: share/meta-task/compssUsers.pl:104 #, c-format msgid "PostgreSQL and MySQL Database Server" msgstr "PostgreSQL und MySQL-Datenbankserver" #: share/meta-task/compssUsers.pl:108 #, c-format msgid "Web/FTP" msgstr "Web/FTP" #: share/meta-task/compssUsers.pl:109 #, c-format msgid "Apache, Pro-ftpd" msgstr "Apache, Pro-ftpd" #: share/meta-task/compssUsers.pl:112 #, c-format msgid "Mail" msgstr "Email" #: share/meta-task/compssUsers.pl:113 #, c-format msgid "Postfix mail server" msgstr "Postfix Mail-Server" #: share/meta-task/compssUsers.pl:117 #, c-format msgid "PostgreSQL or MySQL database server" msgstr "PostgreSQL oder MySQL-Datenbankserver" #: share/meta-task/compssUsers.pl:124 #, c-format msgid "Network Computer server" msgstr "Netzwerkrechner-Server" #: share/meta-task/compssUsers.pl:125 #, c-format msgid "NFS server, SMB server, Proxy server, ssh server" msgstr "NFS-Server, SMB-Server, Proxy-Server, SSH-Server" #: share/meta-task/compssUsers.pl:131 #, c-format msgid "Graphical Environment" msgstr "Grafische Arbeitsoberfläche" #: share/meta-task/compssUsers.pl:133 #, c-format msgid "KDE Workstation" msgstr "KDE-Arbeitsplatz" #: share/meta-task/compssUsers.pl:134 #, c-format msgid "" "The K Desktop Environment, the basic graphical environment with a collection " "of accompanying tools" msgstr "" "Die K-Desktop-Umgebung, die Standard-Arbeitsfläche mit einer Sammlung " "zugehöriger Programme" #: share/meta-task/compssUsers.pl:138 #, c-format msgid "GNOME Workstation" msgstr "Gnome-Arbeitsplatz" #: share/meta-task/compssUsers.pl:139 #, c-format msgid "" "A graphical environment with user-friendly set of applications and desktop " "tools" msgstr "Eine grafische Umgebung mit anwenderfreundlichen Anwendungen und Werkzeugen" #: share/meta-task/compssUsers.pl:142 #, c-format msgid "IceWm Desktop" msgstr "IceWm-Desktop" #: share/meta-task/compssUsers.pl:146 #, c-format msgid "Other Graphical Desktops" msgstr "Andere grafische Arbeitsflächen" #: share/meta-task/compssUsers.pl:147 #, c-format msgid "Window Maker, Enlightenment, Fvwm, etc" msgstr "Window Maker, Enlightenment, Fvwm, usw." #: share/meta-task/compssUsers.pl:170 #, c-format msgid "Utilities" msgstr "Werkzeuge" #: share/meta-task/compssUsers.pl:172 share/meta-task/compssUsers.pl:173 #, c-format msgid "SSH Server" msgstr "SSH-Server" #: share/meta-task/compssUsers.pl:177 #, c-format msgid "Webmin" msgstr "Webmin" #: share/meta-task/compssUsers.pl:178 #, c-format msgid "Webmin Remote Configuration Server" msgstr "Webmin Fernkonfigurationsserver" #: share/meta-task/compssUsers.pl:182 #, c-format msgid "Network Utilities/Monitoring" msgstr "Netzwerkwerkzeuge/-überwachung" #: share/meta-task/compssUsers.pl:183 #, c-format msgid "Monitoring tools, processes accounting, tcpdump, nmap, ..." msgstr "Überwachungswerkzeuge, Prozessverwaltung, tcpdump, nmap, ..." #: share/meta-task/compssUsers.pl:187 #, c-format msgid "Mandriva Wizards" msgstr "Mandriva-Assistenten" #: share/meta-task/compssUsers.pl:188 #, c-format msgid "Wizards to configure server" msgstr "Assistenten zur Servereinrichtung" #: steps.pm:85 #, c-format msgid "" "An error occurred, but I do not know how to handle it nicely.\n" "Continue at your own risk." msgstr "" "Es trat ein Fehler auf. Ich weiß jedoch nicht, wie ich damit sinnvoll \n" "umgehen soll. Sie können fortfahren, jedoch auf eigenes Risiko!" #: steps.pm:437 #, c-format msgid "" "Some important packages did not get installed properly.\n" "Either your cdrom drive or your cdrom is defective.\n" "Check the cdrom on an installed computer using \"rpm -qpl media/main/*.rpm" "\"\n" msgstr "" "Einige wichtige Pakete wurden nicht richtig installiert. \n" "Entweder ist Ihr CD-ROM-Laufwerk oder Ihre CD-ROM defekt. \n" "Testen Sie die CD-ROM auf einem Linux-Rechner mittels „rpm -qpl \n" "media/main/*.rpm“\n" #: steps_auto_install.pm:71 steps_stdio.pm:27 #, c-format msgid "Entering step `%s'\n" msgstr "Beginn von Schritt „%s\n" #: steps_curses.pm:22 #, c-format msgid "Mandriva Linux Installation %s" msgstr "Mandriva Linux-Installation %s" #: steps_curses.pm:32 #, c-format msgid "<Tab>/<Alt-Tab> between elements" msgstr "<Tab>/<Alt-Tab> zwischen den Elementen" #: steps_gtk.pm:84 #, c-format msgid "Xorg server is slow to start. Please wait..." msgstr "Xorg Server braucht lange zum Starten. Bitte warten Sie..." #: steps_gtk.pm:194 #, c-format msgid "" "Your system is low on resources. You may have some problem installing\n" "Mandriva Linux. If that occurs, you can try a text install instead. For " "this,\n" "press `F1' when booting on CDROM, then enter `text'." msgstr "" "Ihr Rechner hat nicht genug Ressourcen. Vermutlich werden bei der \n" "Installation Probleme auftreten. In diesem Fall sollten Sie eine \n" "Text-Installation versuchen. Drücken Sie dafür <F1> während dem \n" "Installationsstart und geben Sie „text“ an der Eingabeaufforderung \n" "ein." #: steps_gtk.pm:228 #, c-format msgid "Install Mandriva KDE Desktop" msgstr "Installation des Mandriva KDE Desktop" #: steps_gtk.pm:229 #, c-format msgid "Install Mandriva GNOME Desktop" msgstr "Installation des Mandriva GNOME Desktop" #: steps_gtk.pm:230 #, c-format msgid "Custom install" msgstr "Benutzer Installation" #: steps_gtk.pm:253 #, c-format msgid "Here's a preview of the '%s' desktop." msgstr "Hier sehen Sie eine Vorschau des '%s' Desktops" #: steps_gtk.pm:275 #, c-format msgid "Click on images in order to see a bigger preview" msgstr "Klicken Sie auf die Bilder, um größere Vorschauen zu erhalten" #: steps_gtk.pm:287 steps_interactive.pm:618 steps_list.pm:30 #, c-format msgid "Package Group Selection" msgstr "Auswahl der Paketgruppen" #: steps_gtk.pm:308 steps_interactive.pm:635 #, c-format msgid "Individual package selection" msgstr "Individuelle Paketauswahl" #: steps_gtk.pm:330 steps_interactive.pm:561 #, c-format msgid "Total size: %d / %d MB" msgstr "Gesamtgröße: %d / %d MB" #: steps_gtk.pm:375 #, c-format msgid "Bad package" msgstr "Ungültiges Paket" #: steps_gtk.pm:377 #, c-format msgid "Version: " msgstr "Version: " #: steps_gtk.pm:378 #, c-format msgid "Size: " msgstr "Größe: " #: steps_gtk.pm:378 #, c-format msgid "%d KB\n" msgstr "%d KB\n" #: steps_gtk.pm:379 #, c-format msgid "Importance: " msgstr "Wichtigkeit: " #: steps_gtk.pm:413 #, c-format msgid "You can not select/unselect this package" msgstr "Sie können dieses Paket nicht auswählen/abwählen." #: steps_gtk.pm:417 #, c-format msgid "due to missing %s" msgstr "%s fehlt" #: steps_gtk.pm:418 #, c-format msgid "due to unsatisfied %s" msgstr "Aufgrund unerfüllter %s" #: steps_gtk.pm:419 #, c-format msgid "trying to promote %s" msgstr "Versuche %s voranzutreiben" #: steps_gtk.pm:420 #, c-format msgid "in order to keep %s" msgstr "um %s beizubehalten" #: steps_gtk.pm:425 #, c-format msgid "" "You can not select this package as there is not enough space left to install " "it" msgstr "" "Sie können dieses Paket nicht auswählen, da Sie nicht genug Plattenplatz " "haben." #: steps_gtk.pm:428 #, c-format msgid "The following packages are going to be installed" msgstr "Die folgenden Pakete werden installiert" #: steps_gtk.pm:429 #, c-format msgid "The following packages are going to be removed" msgstr "Die folgenden Pakete werden entfernt" #: steps_gtk.pm:454 #, c-format msgid "This is a mandatory package, it can not be unselected" msgstr "Dieses Paket ist existenziell, sie können es nicht abwählen!" #: steps_gtk.pm:456 #, c-format msgid "You can not unselect this package. It is already installed" msgstr "" "Sie können dieses Paket nicht aus der Auswahl entfernen. \n" "Es ist bereits installiert!" #: steps_gtk.pm:458 #, c-format msgid "You can not unselect this package. It must be upgraded" msgstr "" "Sie können dieses Paket nicht aus der Auswahl entfernen. \n" "Es muss aktualisiert werden!" #: steps_gtk.pm:462 #, c-format msgid "Show automatically selected packages" msgstr "Automatisch markierte Pakete anzeigen" #: steps_gtk.pm:464 #, c-format msgid "Install" msgstr "Installation" #: steps_gtk.pm:467 #, c-format msgid "Load/Save selection" msgstr "Auswahl laden/speichern" #: steps_gtk.pm:468 #, c-format msgid "Updating package selection" msgstr "Erneuere Paket Auswahl" #: steps_gtk.pm:473 #, c-format msgid "Minimal install" msgstr "Minimal-Installation" #: steps_gtk.pm:487 #, c-format msgid "Software Management" msgstr "Software verwalten" #: steps_gtk.pm:487 steps_interactive.pm:447 #, c-format msgid "Choose the packages you want to install" msgstr "Zu installierende Pakete auswählen" #: steps_gtk.pm:504 steps_interactive.pm:649 steps_list.pm:32 #, c-format msgid "Installing" msgstr "Installation" #: steps_gtk.pm:530 #, c-format msgid "No details" msgstr "Keine Details" #: steps_gtk.pm:545 #, c-format msgid "Time remaining " msgstr "Verbleibende Zeit " #: steps_gtk.pm:546 #, c-format msgid "(estimating...)" msgstr "(Schätzen...)" #: steps_gtk.pm:573 #, c-format msgid "%d package" msgid_plural "%d packages" msgstr[0] "%d Paket" msgstr[1] "%d Pakete" #: steps_gtk.pm:619 steps_interactive.pm:837 steps_list.pm:43 #, c-format msgid "Summary" msgstr "Zusammenfassung" #: steps_gtk.pm:636 #, c-format msgid "Configure" msgstr "Konfigurieren" #: steps_gtk.pm:653 steps_interactive.pm:833 steps_interactive.pm:984 #, c-format msgid "not configured" msgstr "Nicht eingerichtet" #: steps_gtk.pm:694 #, fuzzy, c-format msgid "Media Selection" msgstr "Auswahl der Paketgruppen" #: steps_gtk.pm:704 steps_interactive.pm:335 #, c-format msgid "" "The following installation media have been found.\n" "If you want to skip some of them, you can unselect them now." msgstr "" "Die folgenden Installationsmedien wurden gefunden.\n" "Wählen Sie die Medien ab, die Sie überspringen wollen." #: steps_gtk.pm:700 steps_interactive.pm:337 #, c-format msgid "" "You have the option to copy the contents of the CDs onto the hard drive " "before installation.\n" "It will then continue from the hard drive and the packages will remain " "available once the system is fully installed." msgstr "" "Sie haben die Möglichkeit, den Inhalt der CDs vor der Installation auf " "Festplatte zu kopieren. Die Installation wird dann von Festplatte " "fortgeführt und die Softwarepakete bleiben verfügbar, nachdem das System " "fertig installiert ist." #: steps_gtk.pm:702 steps_interactive.pm:339 #, c-format msgid "Copy whole CDs" msgstr "Kopiere die CDs" #: steps_interactive.pm:38 #, c-format msgid "An error occurred" msgstr "Ein Fehler ist aufgetreten" #: steps_interactive.pm:98 #, c-format msgid "Here is the full list of available keyboards" msgstr "Komplette Liste aller Tastaturlayouts" #: steps_interactive.pm:102 #, c-format msgid "Please choose your keyboard layout." msgstr "Bitte wählen Sie Ihren Tastaturtyp." #: steps_interactive.pm:135 #, c-format msgid "Install/Upgrade" msgstr "Installation/Aktualisierung" #: steps_interactive.pm:134 #, c-format msgid "Is this an install or an upgrade?" msgstr "Handelt es sich um eine Installation oder eine Aktualisierung?" #: steps_interactive.pm:138 #, c-format msgid "" "_: This is a noun:\n" "Install" msgstr "Installation" #: steps_interactive.pm:140 #, c-format msgid "Upgrade %s" msgstr "Aktualisiere %s" #: steps_interactive.pm:144 #, c-format msgid "Upgrade from a 32bit to a 64bit distribution is not supported" msgstr "Upgrade von einem 32bit System auf ein 64bit System wird nicht unterstützt" #: steps_interactive.pm:148 #, c-format msgid "Upgrade from a 64bit to a 32bit distribution is not supported" msgstr "Upgrade von einem 64bit System auf ein 32bit System wird nicht unterstützt" #: steps_interactive.pm:167 #, c-format msgid "Encryption key for %s" msgstr "Schlüssel für %s" #: steps_interactive.pm:199 #, c-format msgid "Cancel installation, reboot system" msgstr "Installation abbrechen, das System neustarten" #: steps_interactive.pm:200 #, c-format msgid "New Installation" msgstr "Neuinstallation" #: steps_interactive.pm:201 #, c-format msgid "Upgrade previous installation (not recommended)" msgstr "Vorhergehende Installation aktualisieren (nicht empfohlen)" #: steps_interactive.pm:205 #, c-format msgid "" "Installer has detected that your installed Mandriva Linux system could not\n" "safely be upgraded to %s.\n" "\n" "New installation replacing your previous one is recommended.\n" "\n" "Warning : you should backup all your personal data before choosing \"New\n" "Installation\"." msgstr "" "Der Installer hat festgestellt, dass Ihr Mandriva Linux System nicht\n" "sicher zu %s aktualisiert werden kann.\n" "\n" "Eine Neuinstallation, die Ihre bisherige ersetzt, wird empfohlen.\n" "\n" "Warnung: Sie sollten all Ihre persönlichen Daten sichern, bevor Sie \"Neu\n Installation\" wählen." #: steps_interactive.pm:247 #, c-format msgid "IDE" msgstr "IDE" #: steps_interactive.pm:247 #, c-format msgid "Configuring IDE" msgstr "IDE konfigurieren" #: steps_interactive.pm:284 #, c-format msgid "" "No free space for 1MB bootstrap! Install will continue, but to boot your " "system, you'll need to create the bootstrap partition in DiskDrake" msgstr "" "Sie haben keinen Platz für die 1 MB große Start-Partition vorgesehen! Die " "Installation wird fortgesetzt, Sie müssen jedoch eine Start-Partition mit " "DiskDrake erstellen." #: steps_interactive.pm:289 #, c-format msgid "" "You'll need to create a PPC PReP Boot bootstrap! Install will continue, but " "to boot your system, you'll need to create the bootstrap partition in " "DiskDrake" msgstr "" "Sie müssen einen PPC PReP Boot Lader erzeugen! Die Installation wird " "fortgesetzt, Sie müssen jedoch eine Start-Partition mit DiskDrake erstellen." #: steps_interactive.pm:381 #, c-format msgid "" "Change your Cd-Rom!\n" "Please insert the Cd-Rom labelled \"%s\" in your drive and press Ok when " "done.\n" "If you do not have it, press Cancel to avoid installation from this Cd-Rom." msgstr "" "Bitte wechseln Sie die CD!\n" "Bitte legen Sie die CD-ROM „%s“ in Ihr Laufwerk. Drücken Sie dann auf „OK“.\n" "Falls Sie sie nicht vorliegen haben, drücken Sie auf „Abbrechen“." #: steps_interactive.pm:403 #, c-format msgid "Looking for available packages..." msgstr "Suche nach vorhandenen Paketen..." #: steps_interactive.pm:411 #, c-format msgid "" "Your system does not have enough space left for installation or upgrade (%" "dMB > %dMB)" msgstr "" "Das System hat für die Installation oder das Update nicht genug freien " "Speicher (%dMB > %dMB)" #: steps_interactive.pm:459 #, c-format msgid "" "Please choose load or save package selection.\n" "The format is the same as auto_install generated files." msgstr "" "Bitte wählen Sie, ob die Paketauswahl geladen oder\n" "gespeichert werden soll. Es handelt sich um das gleiche\n" "Format, wie die unter „auto_install“ erzeugten Disketten." #: steps_interactive.pm:461 #, c-format msgid "Load" msgstr "Last" #: steps_interactive.pm:461 #, c-format msgid "Save" msgstr "Speichern" #: steps_interactive.pm:469 #, c-format msgid "Bad file" msgstr "Datei fehlerhaft" #: steps_interactive.pm:485 #, c-format msgid "KDE" msgstr "KDE" #: steps_interactive.pm:486 #, c-format msgid "GNOME" msgstr "GNOME" #: steps_interactive.pm:489 #, fuzzy, c-format msgid "Desktop Selection" msgstr "Auswahl der Paketgruppen" #: steps_interactive.pm:490 #, c-format msgid "You can choose your workstation desktop profile:" msgstr "Sie haben die Wahl zwischen verschiedenen Desktopprofilen:" #: steps_interactive.pm:575 #, c-format msgid "Selected size is larger than available space" msgstr "Gewünschte Größe übersteigt den verfügbaren Platz" #: steps_interactive.pm:590 #, c-format msgid "Type of install" msgstr "Installationstyp" #: steps_interactive.pm:591 #, c-format msgid "" "You have not selected any group of packages.\n" "Please choose the minimal installation you want:" msgstr "" "Sie haben keine Paketgruppe ausgewählt.\n" "Bitte wählen Sie die minimale Installation, die Sie wünschen." #: steps_interactive.pm:594 #, c-format msgid "With X" msgstr "Mit X" #: steps_interactive.pm:595 #, c-format msgid "With basic documentation (recommended!)" msgstr "Mit minimaler Dokumentation (Empfohlen)" #: steps_interactive.pm:596 #, c-format msgid "Truly minimal install (especially no urpmi)" msgstr "Extrem minimale Installation (ohne „urpmi“)" #: steps_interactive.pm:650 #, c-format msgid "Preparing installation" msgstr "Bereite Installation vor" #: steps_interactive.pm:658 #, c-format msgid "Installing package %s" msgstr "Installiere Paket %s" #: steps_interactive.pm:682 #, c-format msgid "There was an error ordering packages:" msgstr "Bei der Anforderung folgender Pakete trat ein Fehler auf:" #: steps_interactive.pm:682 #, c-format msgid "Go on anyway?" msgstr "Wollen Sie trotzdem fortfahren?" #: steps_interactive.pm:686 #, c-format msgid "Retry" msgstr "Wiederholen" #: steps_interactive.pm:687 #, c-format msgid "Skip this package" msgstr "Dieses Paket überspringen" #: steps_interactive.pm:688 #, c-format msgid "Skip all packages from medium \"%s\"" msgstr "Überspringe alle Pakete von dem Medium \"%s\""