coinst-1.9.3/ 0000755 0001750 0001750 00000000000 12657630652 011775 5 ustar mehdi mehdi coinst-1.9.3/solver.mli 0000644 0001750 0001750 00000003210 12657630652 014006 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module type S = sig
type reason
end
module type SOLVER = sig
type state
type reason
type var = int
type lit
val lit_of_var : var -> bool -> lit
val initialize_problem :
?print_var:(Format.formatter -> int -> unit) -> int -> state
val propagate : state -> unit
val protect : state -> unit
val reset : state -> unit
type value = True | False | Unknown
val assignment : state -> value array
val add_rule : state -> lit array -> reason list -> unit
val associate_vars : state -> lit -> var list -> unit
val solve : state -> var -> bool
val solve_lst : state -> var list -> bool
val solve_neg_list : state -> var list -> var list -> bool
val collect_reasons : state -> var -> reason list
val collect_reasons_lst : state -> var list -> reason list
end
module F (X : S) : SOLVER with type reason = X.reason
coinst-1.9.3/common.mli 0000644 0001750 0001750 00000002027 12657630652 013771 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
type st
val start_parsing : bool -> in_channel -> st
val parsing_tick : st -> unit
val stop_parsing : st -> unit
type st'
val start_generate : bool -> int -> st'
val generate_next : st' -> unit
val stop_generate : st' -> unit
coinst-1.9.3/update_data.ml 0000644 0001750 0001750 00000012743 12657630652 014611 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2012 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
(*
- incremental update using Packages.diff?
*)
let src = ref "http://http.debian.net/debian/dists/"
let hint_src = "https://release.debian.org/britney/hints/"
let britney_src = "https://release.debian.org/britney/data-b2/"
let britney_files =
[("Dates", `Testing, "Dates");
("Urgency", `Testing, "Urgency");
("testing_BugsV", `Testing, "BugsV");
("unstable_BugsV", `Unstable, "BugsV")]
let sects = ["main"; "contrib"; "non-free"]
let ext = "gz"
let decompress_tool = "zcat"
(****)
let download dst url =
let tmp = dst ^ ".tmp" in
begin try Sys.remove tmp with Sys_error _ -> () end;
let cmd =
if Sys.file_exists dst then
Format.sprintf
"curl -L -f -z %s --create-dirs -o %s %s 2>/dev/null" dst tmp url
else
Format.sprintf "curl -L -f --create-dirs -o %s %s 2>/dev/null" tmp url
in
Format.eprintf "Fetching %s...@." url;
(*
Format.printf "> %s@." cmd;
*)
if Sys.command cmd = 0 && Sys.file_exists tmp then
ignore (Sys.rename tmp dst)
let rec make_directories f =
let f = Filename.dirname f in
if not (Sys.file_exists f) then begin
try
Unix.mkdir f (0o755)
with Unix.Unix_error (Unix.ENOENT, _, _) ->
make_directories f;
Unix.mkdir f (0o755)
end
let par_iter f l =
let l = List.map (fun s -> (s, Task.spawn (fun () -> ()))) l in
Task.iter l (fun (x, st) -> f st x) (fun () -> ());
List.iter (fun (_, st) -> Task.kill st) l
(****)
let uncompress cache_dir target_dir suite arch_tmp arch_dst =
let srcs =
List.map
(fun sect ->
Filename.concat cache_dir (Format.sprintf "%s/%s" sect arch_tmp))
sects
@
List.map
(fun sect ->
Filename.concat cache_dir
(Format.sprintf "%s/debian-installer/%s" sect arch_tmp))
sects
in
let dst = Filename.concat target_dir arch_dst in
let should_update =
try
let t = (Unix.stat dst).Unix.st_mtime in
List.exists
(fun src ->
try
(Unix.stat src).Unix.st_mtime > t
with Unix.Unix_error (Unix.ENOENT, _, _) ->
false)
srcs
with Unix.Unix_error (Unix.ENOENT, _, _) ->
true
in
if should_update then begin
make_directories dst;
let tmp = dst ^ ".tmp" in
let cmd = decompress_tool ^ " " ^ String.concat " " srcs ^ " > " ^ tmp in
Format.eprintf "> %s@." cmd;
ignore (Sys.command cmd);
ignore (Sys.rename tmp dst)
end
let update_suite suite archs target_dir =
if !src = "" || !src.[String.length !src - 1] <> '/' then src := !src ^ "/";
let cache_dir = Filename.concat target_dir ".coinst_cache" in
List.iter
(fun (arch_tmp, arch_dst) ->
List.iter
(fun sect ->
let file1 = Format.sprintf "%s/%s" sect arch_tmp in
let url = Format.sprintf "%s%s/%s" !src suite file1 in
let dst = Filename.concat cache_dir file1 in
download dst url;
let file2 =
Format.sprintf "%s/debian-installer/%s" sect arch_tmp in
let url = Format.sprintf "%s%s/%s" !src suite file2 in
let dst = Filename.concat cache_dir file2 in
download dst url)
sects;
uncompress cache_dir target_dir suite arch_tmp arch_dst)
((Format.sprintf "source/Sources.%s" ext, "Sources") ::
List.map
(fun s -> (Format.sprintf "binary-%s/Packages.%s" s ext,
Format.sprintf "Packages_%s" s))
archs)
let update_suites suites archs =
let f =
Task.funct
(fun _ (suite, archs, target_dir) -> update_suite suite archs target_dir)
in
par_iter (fun st (suite, dir) -> f st (suite, archs, dir))
suites
(****)
let update_britney_files testing_dir unstable_dir =
let f =
Task.funct
(fun _ (src_file, suite, dst_file) ->
let dir =
match suite with
`Testing -> testing_dir
| `Unstable -> unstable_dir
in
let url = Format.sprintf "%s%s" britney_src src_file in
let dst = Filename.concat dir dst_file in
make_directories dst;
ignore (download dst url))
in
par_iter f britney_files
(****)
let update_hints hint_dir hint_files =
let f =
Task.funct
(fun _ file ->
let url = Format.sprintf "%s%s" hint_src file in
let dst = Filename.concat hint_dir file in
ignore (download dst url))
in
par_iter f hint_files
(****)
let f testing_dir unstable_dir archs hint_dir hint_files =
if Sys.command "curl -L -V > /dev/null" <> 0 then begin
Format.eprintf "Could not execute 'curl' command.@.";
exit 1
end;
update_suites [("testing", testing_dir); ("unstable", unstable_dir)] archs;
update_britney_files testing_dir unstable_dir;
update_hints hint_dir hint_files
coinst-1.9.3/BUGS.txt 0000644 0001750 0001750 00000001255 12657630652 013301 0 ustar mehdi mehdi Comigrate
=========
* on "break" architectures, we need to remove binary packages without
corresponding source packages from the Heidi output
(or do we have the right semantics for these architectures?)
===> we should just not check co-installability on break_arch ???
(but not true for smooth upgrade...)
* Issue with --equivocal (not the same choices made in both cases...)
We should probably start by checking just installability, and then
refine with co-installability.
Fatal error: exception Assert_failure("transition.ml", 2517, 2)
Called from file "transition.ml", line 2538, characters 4-70
Called from file "transition.ml", line 2706, characters 2-6
coinst-1.9.3/README.md 0000644 0001750 0001750 00000001034 12657630652 013252 0 ustar mehdi mehdi coinst
======
Collection of tools to find issues in package repositories and help manage Debian package integration.
- `coinst` creates a graph that show all conflicts between packages while being orders of magnitude smaller than the whole graph of dependency and conflicts;
- `coinst-upgrades` finds set of packages that could be installed together in a previous version of a Debian repository and cannot be installed any longer;
- `comigrate` is a tool designed to help manage the migration of packages from Debian unstable to testing.
coinst-1.9.3/transition.ml 0000644 0001750 0001750 00000377502 12657630652 014537 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
(*
- incremental (re)computations (of repositories, flattened repositories, ...)
- repeat the remove commands from the input to the hint ouput?
- cache reverse dependencies: then, either we have a lot of work to do and
we can afford to compute them, or we can get them rapidly
- better report issues preventing migration:
=> show source package version numbers
=> example: empathy
- improve '--migrate option': multiple files, bin_nmus
- could the 'migrate' option automatically generate removal hints?
(seems difficult, as there can be many possible choices...)
- parse more options from britney config file
- make Deb_lib more abstract...
- SVG graphs: use CSS styles
- revise hints: check hint parsing; block binary packages
EXPLANATIONS
==> summaries; in particular, show packages that only wait for age,
for bugs
LATER
==> user interaction
- interactive mode
==> performance
- for migration, is it possible to focus on a small part of
the repositories?
- urgency information is huge; can we reduce it?
(filter, depending on source informations...)
- reducing size with installability:
===> flatten a superposition of testing and sid
===> needs to be very conservative!!
packages with no deps after flattening do not need deps before that
===> robustness
- find_coinst_constraints: check whether we have a larger set
of unconstrained packages and automatically recompute the set
of packages to consider in that case
*)
(**** Configuration settings ****)
let archs =
ref ["i386"; "amd64"; "arm64"; "armel"; "armhf"; "mips"; "mipsel";
"powerpc"; "ppc64el"; "s390x"]
let smooth_updates = ref ["libs"; "oldlibs"]
let dir = ref ""
let options = Hashtbl.create 17
let get_option key def =
try
match Hashtbl.find options key with
[s] -> s
| _ -> assert false
with Not_found ->
def
let testing () = get_option "TESTING" (Filename.concat !dir "testing")
let unstable () = get_option "UNSTABLE" (Filename.concat !dir "unstable")
let bug_url n = "http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=" ^ n
let pts_url nm = Format.sprintf "http://packages.qa.debian.org/%s" nm
let build_log_url nm arch =
Format.sprintf
"https://buildd.debian.org/status/logs.php?arch=%s&pkg=%s" arch nm
let cache_dir =
let cache_home = try Sys.getenv "XDG_CACHE_HOME" with Not_found -> "" in
let base_dir =
if cache_home = "" then
Filename.concat (Sys.getenv "HOME") ".cache"
else
cache_home
in
Filename.concat base_dir "coinst"
let urgency_delay u =
match u with
"low" -> 10
| "medium" -> 5
| "high" -> 2
| "critical" -> 0
| "emergency" -> 0
| _ -> assert false
let default_urgency = urgency_delay "medium"
let update_data = ref false
let hint_file = ref ""
let heidi_file = ref ""
let excuse_file = ref ""
let explain_dir = ref ""
let offset = ref 0
let all_hints = ref false
let to_migrate = ref None
let to_remove = ref []
let check_coinstallability = ref true
let equivocal = ref false
let svg = ref false
let broken_sets = Upgrade_common.empty_break_set ()
let popcon_file = ref ""
(**** Debug options ****)
let debug = Debug.make "normal" "Set normal debug output level." []
let verbose =
Debug.make "explain" "Explain why packages are not propagated." ["normal"]
let debug_time = Debug.make "time" "Print execution times" []
let debug_reduction =
Debug.make "reduction" "Debug repository size reduction" ["normal"]
let debug_coinst =
Debug.make "coinst" "Debug co-installability issue analyse" ["normal"]
let debug_outcome =
Debug.make "outcome" "Print the possible changes" ["normal"]
let debug_hints =
Debug.make "hints" "Output suggested hints to standard output" ["normal"]
let debug_migration =
Debug.make "migration" "Debug migration option" ["normal"]
let debug_gc =
Debug.make "gc" "Output gc stats" []
let debug_remove = Debug.make "remove" "Debug removal hints" ["normal"]
let debug_choice =
Debug.make "choice" "Warn about arbitrary choices performed by the solver"
["normal"]
(**** Useful modules from Util ****)
module StringSet = Util.StringSet
module IntSet = Util.IntSet
module Timer = Util.Timer
module ListTbl = Util.ListTbl
module StringTbl = Util.StringTbl
module IntTbl = Util.IntTbl
module BitVect = Util.BitVect
module Union_find = Util.Union_find
let (>>) v f = f v
(*XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX*)
let _ =
Printexc.record_backtrace true;
Gc.set { (Gc.get ())
with Gc.space_overhead = 200; max_overhead = 1000000;
major_heap_increment = 5 * 1024 * 1024 }
module M = Deb_lib
(**** Parsing of input files ****)
let whitespaces = Str.regexp "[ \t]+"
let comma = Str.regexp ","
let slash = Str.regexp "/"
let now = truncate ((Unix.time () /. 3600. -. 15.) /. 24.)
let read_package_info file f =
let h = M.PkgTbl.create 32768 in
if not (Sys.file_exists file) then
Util.print_warning (Format.sprintf "file '%s' not found." file)
else begin
let ch = open_in file in
begin try
while true do
let l = input_line ch in
match Str.split whitespaces l with
[name; version; info] ->
let version = Deb_lib.parse_version version in
if M.name_exists name then
M.PkgTbl.add h (M.id_of_name name) (version, f info)
| [] ->
()
| _ ->
assert false
done;
with End_of_file -> () end;
close_in ch
end;
h
let read_dates src_uid file =
let cache = Filename.concat cache_dir "Dates" in
fst (Cache.cached [file] cache ("version 2\n" ^ src_uid)
(fun () -> read_package_info file int_of_string))
let read_urgencies src_uid file =
let cache = Filename.concat cache_dir "Urgencies" in
fst (Cache.cached [file] cache ("version 2\n" ^ src_uid)
(fun () -> read_package_info file urgency_delay))
let read_bugs file =
let h = StringTbl.create 4096 in
if not (Sys.file_exists file) then
Util.print_warning (Format.sprintf "file '%s' not found." file)
else begin
let ch = open_in file in
begin try
while true do
let l = input_line ch in
match Str.split whitespaces l with
[name; bugs] ->
StringTbl.add h name
(List.fold_right StringSet.add
(Str.split comma bugs) StringSet.empty)
| _ ->
assert false
done;
with End_of_file -> () end;
close_in ch
end;
h
type hint =
{ h_block : string StringTbl.t;
h_block_udeb : string M.PkgTbl.t;
mutable h_block_all : string option;
h_unblock : Deb_lib.version M.PkgTbl.t;
h_unblock_udeb : Deb_lib.version M.PkgTbl.t;
h_urgent : Deb_lib.version M.PkgTbl.t;
h_remove : Deb_lib.version M.PkgTbl.t;
h_age_days : (Deb_lib.version option * int) M.PkgTbl.t }
let debug_read_hints = Debug.make "read_hints" "Show input hints." ["normal"]
let process_unblock_request h l =
List.iter
(fun p ->
match Str.split slash p with
[nm; v] when M.name_exists nm ->
let nm = M.id_of_name nm in
let v = Deb_lib.parse_version v in
begin try
let v' = M.PkgTbl.find h nm in
if Deb_lib.compare_version v' v < 0 then raise Not_found
with Not_found ->
M.PkgTbl.replace h nm v
end
| _ ->
())
l
exception Ignored_hint
let hint_files () =
let hint_re = Str.regexp "^HINTS_\\(.*\\)$" in
Hashtbl.fold
(fun key _ l ->
if Str.string_match hint_re key 0 then
String.lowercase (Str.matched_group 1 key) :: l
else
l)
options []
>> List.sort compare
let read_hints dir =
let hints =
{ h_block = StringTbl.create 16;
h_block_udeb = M.PkgTbl.create 16;
h_block_all = None;
h_unblock = M.PkgTbl.create 16;
h_unblock_udeb = M.PkgTbl.create 16;
h_urgent = M.PkgTbl.create 16;
h_remove = M.PkgTbl.create 16;
h_age_days = M.PkgTbl.create 16 }
in
if debug_read_hints () then
Format.eprintf "Reading hints:@.";
let files =
List.filter
(fun who ->
Sys.file_exists (Filename.concat dir who)
||
(Format.eprintf "Warning: hint file '%s' does not exists.@." who;
false))
(hint_files ())
in
List.iter
(fun who ->
let ch = open_in (Filename.concat dir who) in
begin try
while true do
let l = input_line ch in
let l = Str.split whitespaces l in
try
let add tbl nm v =
if M.name_exists nm then
M.PkgTbl.replace tbl (M.id_of_name nm) v
in
begin match l with
| "block" :: l ->
List.iter
(fun p -> StringTbl.replace hints.h_block p who) l
| "block-udeb" :: l ->
List.iter
(fun p -> add hints.h_block_udeb p who) l
| "block-all" :: l ->
if List.mem "source" l then hints.h_block_all <- Some who
| "unblock" :: l ->
process_unblock_request hints.h_unblock l
| "unblock-udeb" :: l ->
process_unblock_request hints.h_unblock_udeb l
| "urgent" :: l ->
List.iter
(fun p ->
match Str.split slash p with
[nm; v] -> add hints.h_urgent
nm (Deb_lib.parse_version v)
| _ -> ())
l
| "remove" :: l ->
List.iter
(fun p ->
match Str.split slash p with
[nm; v] -> add hints.h_remove
nm (Deb_lib.parse_version v)
| _ -> ())
l
| "age-days" :: n :: l ->
let n = int_of_string n in
List.iter
(fun p ->
match Str.split slash p with
[nm; v] ->
let v =
if v = "-" then None else
Some (Deb_lib.parse_version v)
in
add hints.h_age_days nm (v, n)
| _ ->
())
l
| "finished" :: _ ->
raise End_of_file
| [] ->
raise Ignored_hint
| s :: _ when s.[0] = '#' ->
raise Ignored_hint
| _ ->
if debug_read_hints () then
Format.eprintf "> (ignored) %s@." (String.concat " " l);
raise Ignored_hint
end;
if debug_read_hints () then
Format.eprintf "> %s@." (String.concat " " l)
with Ignored_hint ->
()
done
with End_of_file -> () end;
close_in ch
)
files;
hints
let read_extra_info src_uid =
let dates = read_dates src_uid (Filename.concat (testing ()) "Dates") in
let urgencies =
read_urgencies src_uid (Filename.concat (testing ()) "Urgency") in
let hints = read_hints (Filename.concat (unstable ()) "Hints") in
(dates, urgencies, hints)
let read_bugs () =
let testing_bugs = read_bugs (Filename.concat (testing ()) "BugsV") in
let unstable_bugs = read_bugs (Filename.concat (unstable ()) "BugsV") in
(testing_bugs, unstable_bugs)
(**** Conversion from dot to svg ****)
let send_to_dot_process (oc, _) s = output_string oc s; flush oc
let send_to_dot_process = Task.funct send_to_dot_process
let shutdown_dot_process (oc, pid) () =
close_out oc; ignore (Unix.waitpid [] pid)
let shutdown_dot_process = Task.funct shutdown_dot_process
let create_dot_process () =
let (out_read, out_write) = Unix.pipe () in
flush_all ();
let helper =
Task.spawn
(fun () ->
Unix.close out_read;
let (in_read, in_write) = Unix.pipe () in
match Unix.fork () with
0 ->
Unix.close in_write;
Unix.dup2 in_read Unix.stdin; Unix.dup2 out_write Unix.stdout;
Unix.close in_read; Unix.close out_write;
Unix.execv "/bin/sh" [| "/bin/sh"; "-c"; "dot" |]
| pid ->
Unix.close in_read;
(Unix.out_channel_of_descr in_write, pid))
in
Unix.close out_write;
(helper, Unix.in_channel_of_descr out_read)
let dot_process = lazy (create_dot_process ())
let dot_to_svg s =
let (t, ic) = Lazy.force dot_process in
let send = send_to_dot_process t s in
let (_, g) = Dot_graph.of_channel ic in
ignore (Task.wait send);
let (bbox, scene) = Dot_render.f g in
let l = Scene.get scene in
let b = Buffer.create 200 in
Scene_svg.format (Format.formatter_of_buffer b) (bbox, l);
Buffer.contents b
(**** Parsing of Debian control files ****)
module Repository = Upgrade_common.Repository
open Repository
let bin_package_file suite arch =
Filename.concat suite (Format.sprintf "Packages_%s" arch)
let src_package_file suite = Filename.concat suite "Sources"
let load_bin_packages suite arch =
let file = bin_package_file suite arch in
let dist = M.new_pool () in
assert (not (Sys.is_directory file));
let ch = File.open_in file in
M.parse_packages dist [] ch;
close_in ch;
M.only_latest dist
let load_src_packages suite =
let file = src_package_file suite in
let dist = M.new_src_pool () in
assert (not (Sys.is_directory file));
let ch = File.open_in file in
M.parse_src_packages dist ch;
close_in ch;
M.src_only_latest dist
let has_bin_packages arch =
Sys.file_exists (bin_package_file (testing ()) arch)
let filter_architectures () =
if !dir <> "" then begin
archs := List.filter has_bin_packages !archs;
if !archs = [] then begin
Format.eprintf "No binary package control file found.@.";
exit 1
end
end
(**** Possible reasons for a package not to be upgraded ****)
type reason =
| Unchanged
(* Source *)
| Blocked of (string * string)
| Too_young of int * int
| Binary_not_added | Binary_not_removed
| No_binary
(* Both *)
| More_bugs of StringSet.t
(* Binaries *)
| Conflict of IntSet.t * IntSet.t * Upgrade_common.problem
| Not_yet_built of string * M.version * M.version * bool
| Source_not_propagated
| Atomic
module L = Layout
let (&) = L.(&)
let print_pkg_ref (nm, t, u) =
match t, u with
true, true -> L.code (L.s nm)
| true, false -> L.code (L.s nm) & L.s " (testing)"
| false, true -> L.code (L.s nm) & L.s " (sid)"
| false, false -> assert false
let print_cstr r =
match r with
Upgrade_common.R_depends (pkg, dep, pkgs) ->
print_pkg_ref pkg & L.s " depends on " &
L.code (L.format M.print_package_dependency [dep]) &
L.s " {" & L.seq ", " print_pkg_ref pkgs & L.s "}"
| Upgrade_common.R_conflict (pkg, confl, pkg') ->
print_pkg_ref pkg & L.s " conflicts with " &
L.code
(L.format M.print_package_dependency (List.map (fun c -> [c]) confl)) &
L.s " {" & print_pkg_ref pkg' & L.s "}"
let print_explanation problem =
let conflict_graph () =
let b = Buffer.create 200 in
Upgrade_common.output_conflict_graph (Format.formatter_of_buffer b)
problem;
dot_to_svg (Buffer.contents b)
in
let expl = problem.Upgrade_common.p_explain in
L.ul ~prefix:" - " (L.list (fun r -> L.li (print_cstr r)) expl) &
(if !svg then L.raw_html conflict_graph else L.emp)
let print_binaries conj print_binary s =
let l =
IntSet.elements s
>> List.map print_binary
>> List.sort (Util.compare_pair compare compare)
>> List.map snd
in
match l with
[] -> L.emp
| [p] -> p
| [p; q] -> p & L.s " " & L.s conj & L.s " " & q
| _ -> L.seq ", " (fun x -> x)
(l
>> List.rev
>> (fun l ->
match l with
[] | [_] -> l
| p :: (_ :: _ as r) -> (L.s conj & L.s " " & p) :: r)
>> List.rev)
let print_reason capitalize print_binary print_source lits reason =
let c = if capitalize then String.capitalize else String.uncapitalize in
match reason with
Unchanged ->
L.s (c "No update")
| Blocked (kind, who) ->
L.s (c "Left unchanged due to ") & L.s kind &
L.s " request by " & L.s who & L.s "."
| Too_young (cur_ag, req_ag) ->
L.s (c "Only ") & L.i cur_ag & L.s " days old; must be " & L.i req_ag &
L.s " days old to go in."
| More_bugs s ->
L.s (c "Has new bugs: ") &
L.seq ", " (fun s -> L.anchor (bug_url s) (L.s "#" & L.s s))
(StringSet.elements s) &
L.s "."
| Conflict (s, s', problem) ->
begin match IntSet.cardinal s with
0 ->
L.s (c "A dependency would not be satisfied")
| 1 ->
L.s (c "Needs migration of binary package ") &
snd (print_binary false (IntSet.choose s))
| _ ->
L.s (c "Needs migration of one of the binary packages ") &
print_binaries "or" (print_binary false) s
end
&
begin
if IntSet.cardinal s' > 1 || not (IntSet.mem lits.(0) s') then begin
if IntSet.cardinal s' = 1 then begin
L.s " (would break package " &
snd (print_binary false (IntSet.choose s')) & L.s ")"
end else begin
L.s " (would break co-installability of packages " &
print_binaries "and" (print_binary false) s' & L.s ")"
end
end else
L.emp
end
&
L.s ":" & L.div ~clss:"problem" (print_explanation problem)
| Not_yet_built (src, v1, v2, outdated) ->
(if outdated then
L.s (c "Not yet rebuilt (source ")
else
L.s (c "Obsolete (source "))
&
L.s src & L.s " version " & L.format M.print_version v1 &
L.s " rather than " & L.format M.print_version v2 & L.s ")."
| Source_not_propagated ->
L.s (c "Source package ") & print_source lits.(1) &
L.s " cannot migrate."
| Atomic ->
L.s (c "Binary package ") & snd (print_binary false lits.(1)) &
L.s " cannot migrate."
| Binary_not_added ->
L.s (c "Binary package ") & snd (print_binary true lits.(1)) &
L.s " cannot migrate."
| Binary_not_removed ->
L.s (c "Binary package ") & snd (print_binary true lits.(1)) &
L.s " cannot be removed."
| No_binary ->
L.s (c "No associated binary package.")
let print_reason' get_name_arch lits reason =
let print_binary verbose id =
let (nm, arch) = get_name_arch id in
(nm, if verbose then L.s nm & L.s "/" & L.s arch else L.s nm)
in
let print_source id = let (nm, _) = get_name_arch id in L.s nm in
print_reason false print_binary print_source lits reason
(**** Constraint solver ****)
module HornSolver = Horn.F (struct type t = reason type reason = t end)
(**** Caching of non-coinstallability issues ****)
let learnt_rules = ref []
let learn_rule r neg s problem =
learnt_rules := (r, neg, s, problem) :: !learnt_rules
let coinst_rules = ref []
let switch_to_installability solver =
assert !check_coinstallability;
List.iter (fun r -> HornSolver.retract_rule solver r) !coinst_rules;
check_coinstallability := false
let ambiguous_rules = ref []
let discard_ambiguous_rules solver =
List.iter (fun r -> HornSolver.retract_rule solver r) !ambiguous_rules;
ambiguous_rules := []
let broken_arch_all_packages = ref StringSet.empty
let learn_broken_arch_all_packages s =
broken_arch_all_packages := StringSet.union !broken_arch_all_packages s
let load_rules solver uids =
let cache = Filename.concat cache_dir "Rules" in
let uids = String.concat "\n" uids in
let ((rules, broken_packages), _) =
Cache.cached [] cache ("version 8\n" ^ uids)
(fun () -> ([], StringSet.empty))
in
List.iter
(fun (r, neg, s, problem) ->
let n = IntSet.cardinal s in
if
(!check_coinstallability || n = 1)
&&
not (Upgrade_common.is_ignored_set broken_sets
problem.Upgrade_common.p_issue)
then begin
let r = HornSolver.add_rule solver r (Conflict (neg, s, problem)) in
if n > 1 then coinst_rules := r :: !coinst_rules
end)
rules;
learnt_rules := List.rev rules;
broken_arch_all_packages := broken_packages
let save_rules uids =
let cache = Filename.concat cache_dir "Rules" in
let uids = String.concat "\n" uids in
ignore (Cache.cached ~force:true [] cache ("version 8\n" ^ uids)
(fun () -> (List.rev !learnt_rules, !broken_arch_all_packages)))
(**** Global state for per-architecture processes ****)
type st =
{ arch : string;
testing : M.pool; unstable : M.pool;
testing_srcs : M.s_pool; unstable_srcs : M.s_pool;
unstable_bugs : StringSet.t StringTbl.t;
testing_bugs : StringSet.t StringTbl.t;
mutable outdated_binaries : M.p list;
first_bin_id : int;
id_of_bin : HornSolver.var M.PkgDenseTbl.t;
bin_of_id : M.package_name array;
id_of_source : HornSolver.var M.PkgDenseTbl.t;
mutable upgrade_state :
(Upgrade_common.state * Upgrade_common.state) option;
uid : string;
mutable break_arch_all : bool;
broken_sets : Upgrade_common.ignored_sets }
(**** Misc. useful functions ****)
let source_version src nm =
try
Some (M.find_source_by_name src nm).M.s_version
with Not_found ->
None
let same_source_version t u nm =
match source_version t nm, source_version u nm with
None, None -> true
| Some v, Some v' -> M.compare_version v v' = 0
| _ -> false
let no_new_source t u nm =
match source_version t nm, source_version u nm with
None, None -> true
| Some v, Some v' -> M.compare_version v v' >= 0
| _ -> false
let bin_version dist nm =
match M.find_packages_by_name dist nm with
p :: _ -> Some p.M.version
| [] -> None
let same_bin_version t u nm =
match bin_version t nm, bin_version u nm with
None, None -> true
| Some v, Some v' -> M.compare_version v v' = 0
| _ -> false
let no_new_bin t u nm =
match bin_version t nm, bin_version u nm with
None, None -> true
| Some v, Some v' -> M.compare_version v v' >= 0
| _ -> false
let allow_smooth_updates p =
List.mem "ALL" !smooth_updates || List.mem p.M.section !smooth_updates
let compute_ages dates urgencies hints nm uv tv =
let d =
try
let (v, d) = M.PkgTbl.find dates nm in
if M.compare_version uv v = 0 then d else now
with Not_found ->
now
in
let u =
if
try
M.compare_version uv (M.PkgTbl.find hints.h_urgent nm) = 0
with Not_found ->
false
then
0
else
try
let (v, d) = M.PkgTbl.find hints.h_age_days nm in
if
match v with
Some v -> M.compare_version v uv <> 0
| None -> false
then
raise Not_found;
d
with Not_found ->
let l =
List.filter
(fun (v', d) ->
(match tv with
Some v -> M.compare_version v v' < 0
| None -> true)
&&
M.compare_version v' uv <= 0)
(M.PkgTbl.find_all urgencies nm)
in
let u =
match l with
[] -> default_urgency
| (_, u) :: rem -> List.fold_left (fun u (_, u') -> min u u') u rem
in
match tv with
None -> max u default_urgency
| Some _ -> u
in
(now + !offset - d, u)
(**** Writing of an excuse file ****)
let rec interesting_reason solver (lits, reason) =
match reason with
Unchanged ->
false
| Binary_not_added | Binary_not_removed ->
List.exists (interesting_reason solver)
(HornSolver.direct_reasons solver lits.(1))
| Source_not_propagated ->
false
| Atomic ->
false
| _ ->
true
let binary_names st (offset, l) =
List.map
(fun id ->
let nm = st.bin_of_id.(id - offset) in
let p =
match M.find_packages_by_name st.unstable nm with
p :: _ -> p
| [] -> match M.find_packages_by_name st.testing nm with
p :: _ -> p
| [] -> List.find (fun p -> p.M.package = nm)
st.outdated_binaries
in
(* For faux packages, the source name is not available in the
driving processus, so we have to translate here. *)
(id, M.name_of_id nm, M.name_of_id (fst p.M.source)))
l
let binary_names = Task.funct binary_names
let output_reasons
l dates urgencies hints solver source_of_id id_offsets filename t u =
let reason_t = Timer.start () in
let blocked_source = Hashtbl.create 1024 in
let sources = ref [] in
let binaries = ref IntSet.empty in
Array.iteri
(fun id nm ->
let reasons = HornSolver.direct_reasons solver id in
if List.exists (interesting_reason solver) reasons then begin
sources := (M.name_of_id nm, nm, (id, reasons)) :: !sources;
Hashtbl.add blocked_source (M.name_of_id nm) ();
List.iter
(fun (lits, reason) ->
match reason with
Binary_not_added | Binary_not_removed ->
let id = lits.(1) in
binaries := IntSet.add id !binaries;
List.iter
(fun (lits, reason) ->
match reason with
Conflict (s, s', _) ->
binaries :=
IntSet.union (IntSet.union s s') !binaries
| _ ->
())
(HornSolver.direct_reasons solver id)
| _ ->
())
reasons
end)
source_of_id;
let name_of_binary = IntTbl.create 1024 in
Task.iteri l
(fun (arch, st) ->
let (first, offset, len) = StringTbl.find id_offsets arch in
let pos = first + offset in
let l =
IntSet.elements
(IntSet.filter (fun id -> id >= pos && id < pos + len) !binaries)
in
(arch, binary_names st (pos, l)))
(fun arch l ->
List.iter
(fun (id, nm, src) ->
IntTbl.add name_of_binary id (nm, arch, src))
l);
let print_binary _ id =
let (nm, arch, source_name) = IntTbl.find name_of_binary id in
let txt =
if nm = source_name then
L.code (L.s nm)
else
(L.code (L.s nm) & L.s " (from " & L.code (L.s source_name) & L.s ")")
in
if not (Hashtbl.mem blocked_source source_name) then (nm, txt) else
(nm, L.anchor ("#" ^ source_name) txt)
in
let print_source id = assert false in
let lst =
L.dl (L.list
(fun (source_name, nm, (id, reasons)) ->
let about_bin (_, r) =
match r with
Binary_not_added | Binary_not_removed -> true
| _ -> false
in
let src_reasons =
begin try
let p = M.find_source_by_name u nm in
if same_source_version t u nm then L.emp else
let (cur_ag, req_ag) =
compute_ages dates urgencies hints
nm p.M.s_version (source_version t nm)
in
if cur_ag < req_ag then L.emp else
L.li (L.s "Package is " & L.i cur_ag &
L.s " days old (needed " & L.i req_ag & L.s " days).")
with Not_found ->
L.emp
end
&
L.list
(fun r ->
if interesting_reason solver r && not (about_bin r) then
L.li (print_reason true print_binary print_source
(fst r) (snd r))
else
L.emp)
reasons
in
let binaries =
reasons
>> List.filter
(fun r -> interesting_reason solver r && about_bin r)
>> List.map (fun (lits, r) -> (lits.(1), r))
>> List.sort (Util.compare_pair compare compare)
>> Util.group compare
>> List.map
(fun (id, l) ->
let (name, arch, _) = IntTbl.find name_of_binary id in
let is_removal =
List.for_all (fun r -> r = Binary_not_removed) l in
(name, (arch, (id, is_removal))))
>> List.sort
(Util.compare_pair compare (Util.compare_pair compare compare))
in
let not_yet_built =
binaries
>>
List.filter
(fun (_, (_, (id, _))) ->
List.exists
(fun (_, r) ->
match r with Not_yet_built _ -> true | _ -> false)
(HornSolver.direct_reasons solver id))
>> List.map (fun (name, (arch, _)) -> (name, arch))
>> List.sort (Util.compare_pair compare compare)
>> Util.group compare
>> List.map (fun (name, l) -> (l, name))
>> List.sort (Util.compare_pair (Util.compare_list compare) compare)
>> Util.group (Util.compare_list compare)
in
let build_reasons =
L.list
(fun (al, bl) ->
L.li (L.s (if List.length bl = 1 then "Binary package "
else "Binary packages ") &
L.seq ", " (fun nm -> L.code (L.s nm)) bl &
L.s " not yet rebuilt on " &
L.seq ", "
(fun arch ->
L.anchor (build_log_url source_name arch)
(L.s arch)) al &
L.s "."))
not_yet_built
in
let with_new_bugs =
Util.group compare
(List.flatten
(List.map
(fun (nm, (_, (id, _))) ->
List.flatten
(List.map
(fun (_, reason) ->
match reason with
More_bugs s -> [(nm, s)]
| _ -> [])
(HornSolver.direct_reasons solver id)))
binaries))
in
let bug_reasons =
L.list
(fun (nm', s) ->
let s = List.hd s in (* Same bugs on all archs. *)
if nm' <> source_name then
L.li (L.s "Binary package " & L.code (L.s nm') &
L.s " has new bugs: " &
L.seq ", "
(fun s -> L.anchor (bug_url s) (L.s "#" & L.s s))
(StringSet.elements s) &
L.s ".")
else
L.emp)
with_new_bugs
in
let compare_conflict r r' =
match r, r' with
Conflict (s1, s1', p1), Conflict (s2, s2', p2) ->
compare p1.Upgrade_common.p_explain p2.Upgrade_common.p_explain
| _ ->
assert false
in
let compare_reason =
Util.compare_pair (fun x y -> 0) compare_conflict in
let binaries =
binaries >> Util.group compare >>
List.map
(fun (nm, l) ->
l >>
List.map
(fun (arch, (id, is_removal)) ->
(HornSolver.direct_reasons solver id
>>
List.filter
(fun r ->
interesting_reason solver r &&
match snd r with
Not_yet_built _ | More_bugs _ -> false
| Conflict _ -> true
| _ -> assert false)
>>
List.sort compare_reason,
(arch, is_removal))) >>
List.sort (Util.compare_pair
(Util.compare_list compare_reason) compare) >>
Util.group (Util.compare_list compare_reason) >>
List.map (fun (archs, l) -> (nm, (archs, l)))) >>
List.flatten
in
let bin_reasons =
L.list
(fun (nm, (reasons, archs_and_removals)) ->
if reasons = [] then L.emp else
let is_removal = List.for_all snd archs_and_removals in
let archs = List.map fst archs_and_removals in
let reasons =
L.list
(fun (lits, r) ->
L.li (print_reason true print_binary print_source
lits r))
reasons
in
L.li (L.s "Binary package " & L.code (L.s nm) &
L.s " cannot " &
L.s (if is_removal then "be removed" else "migrate") &
L.s " (" & L.seq ", " L.s archs & L.s "):" &
L.ul reasons))
binaries
in
let version dist nm =
try
let p = M.find_source_by_name dist nm in
L.format M.print_version p.M.s_version
with Not_found ->
L.s "-"
in
let versions nm =
if
List.exists (fun (_, r) -> r = Unchanged)
(HornSolver.direct_reasons solver id)
then
version t nm
else
(version t nm & L.s " to " & version u nm)
in
L.dli ~id:source_name
(L.anchor (pts_url source_name) (L.code (L.s source_name)) &
L.s " (" & versions nm & L.s ")")
(L.ul (src_reasons & build_reasons & bug_reasons & bin_reasons)))
(List.sort (fun (nm1, _, _) (nm2, _, _) -> compare nm1 nm2) !sources))
in
let ch = if filename = "-" then stdout else open_out filename in
L.print (new L.html_printer ch "Explanations") lst;
if filename <> "-" then close_out ch;
if debug_time () then
Format.eprintf "Writing excuse file: %f@." (Timer.stop reason_t)
(**** Per arch. information on which packages are not propagated ****)
let extract_unchanged_bin solver id_offsets arch unch =
let (first, offset, len) = StringTbl.find id_offsets arch in
BitVect.sub unch (first + offset) len
let is_unchanged st unch nm =
BitVect.test unch (M.PkgDenseTbl.find st.id_of_bin nm - st.first_bin_id)
(**** Prepare repositories before looking for (co-)installability issues ****)
let compute_reverse_dependencies st d id_tbl =
let rdeps = Array.make (Array.length st.bin_of_id) [] in
let add_rdep src_id dep =
List.iter
(fun cstr ->
List.iter
(fun q ->
let target_id =
PTbl.get id_tbl (Package.of_index q.M.num) in
let i = target_id - st.first_bin_id in
rdeps.(i) <- src_id :: rdeps.(i))
(M.find_provided_packages d (fst cstr)))
dep
in
M.iter_packages d
(fun p ->
let src_id = PTbl.get id_tbl (Package.of_index p.M.num) in
List.iter (fun d -> add_rdep src_id d) p.M.depends;
List.iter (fun d -> add_rdep src_id d) p.M.pre_depends);
rdeps
let compute_reverse_dependencies st d id_tbl =
let rdep_t = Timer.start () in
let rdeps = compute_reverse_dependencies st d id_tbl in
(*
let cache = Filename.concat cache_dir ("Rev_" ^ st.arch) in
let (rdeps, _) =
Cache.cached [] cache ("version 1\n" ^ st.uid)
(fun () -> compute_reverse_dependencies st d id_tbl)
in
*)
if debug_time () then
Format.eprintf " Reversing dependencies: %f@." (Timer.stop rdep_t);
rdeps
let reduce_for_installability st unchanged =
(* We only keep:
1) packages that have changed,
2) packages that depend on these changed packages
(if arch:all packages are allowed to break, we omit them here),
3) as well as all the packages they depend on.
*)
let t = st.testing in
let u = st.unstable in
let d = M.new_pool () in
M.merge d (fun _ -> true) t;
M.merge d (fun _ -> true) u;
let id_tbl = PTbl.create d 0 in
M.iter_packages d
(fun p ->
PTbl.set id_tbl
(Package.of_index p.M.num)
(M.PkgDenseTbl.find st.id_of_bin p.M.package));
let rdeps = compute_reverse_dependencies st d id_tbl in
let predecessors = M.PkgDenseTbl.create () in
let rec add_preds nm =
if not (M.PkgDenseTbl.mem predecessors nm) then begin
M.PkgDenseTbl.add predecessors nm ();
let id = M.PkgDenseTbl.find st.id_of_bin nm in
List.iter (fun id -> add_preds st.bin_of_id.(id - st.first_bin_id))
rdeps.(id - st.first_bin_id)
end
in
Array.iter
(fun nm -> if not (is_unchanged st unchanged nm) then add_preds nm)
st.bin_of_id;
let pkgs = M.PkgDenseTbl.create () in
let rec add_package nm =
if not (M.PkgDenseTbl.mem pkgs nm) then begin
M.PkgDenseTbl.add pkgs nm ();
List.iter follow_deps (M.find_packages_by_name d nm);
end
and follow_deps p =
follow_deps_2 p.M.depends; follow_deps_2 p.M.pre_depends
and follow_deps_2 deps =
List.iter
(fun l ->
List.iter
(fun (nm, _) ->
List.iter
(fun q -> add_package q.M.package)
(M.find_provided_packages d nm))
l)
deps
in
let arch_all_package_2 d nm =
match M.find_packages_by_name d nm with
[] -> true
| [p] -> p.M.architecture = "all"
| l -> assert false
in
let arch_all_package nm =
arch_all_package_2 t nm && arch_all_package_2 u nm in
M.PkgDenseTbl.iteri
(fun nm _ ->
if not (st.break_arch_all && arch_all_package nm) then add_package nm)
predecessors;
pkgs
let compute_conflicts t u =
let conflicts = ListTbl.create 101 in
let add_conflicts dist p confls =
List.iter
(fun l ->
List.iter
(fun cstr ->
List.iter
(fun q ->
ListTbl.add conflicts p.M.package q.M.package;
ListTbl.add conflicts q.M.package p.M.package)
(M.resolve_package_dep_raw dist cstr))
l)
confls
in
let compute_package_conflicts d1 d2 =
M.iter_packages d1
(fun p ->
add_conflicts d2 p p.M.conflicts;
add_conflicts d2 p p.M.breaks)
in
compute_package_conflicts t t; compute_package_conflicts t u;
compute_package_conflicts u t; compute_package_conflicts u u;
conflicts
let reduce_for_coinstallability st unchanged =
let t = st.testing in
let u = st.unstable in
let conflicts = compute_conflicts t u in
let changed_packages = M.PkgDenseTbl.create () in
let consider_package p =
let nm = p.M.package in
if not (is_unchanged st unchanged nm) then
M.PkgDenseTbl.replace changed_packages nm ()
in
M.iter_packages t consider_package;
M.iter_packages u consider_package;
let pkgs = M.PkgDenseTbl.create () in
let rec add_package p =
if not (M.PkgDenseTbl.mem pkgs p) then begin
M.PkgDenseTbl.add pkgs p ();
List.iter add_package (ListTbl.find conflicts p);
List.iter follow_deps (M.find_packages_by_name t p);
List.iter follow_deps (M.find_packages_by_name u p)
end
and follow_deps p =
follow_deps_2 t p; follow_deps_2 u p
and follow_deps_2 d p =
follow_deps_3 d p.M.depends; follow_deps_3 d p.M.pre_depends
and follow_deps_3 d deps =
List.iter
(fun l ->
List.iter
(fun (nm, _) ->
List.iter
(fun q -> add_package q.M.package)
(M.find_provided_packages d nm))
l)
deps
in
(* Changed packages should be kept. *)
M.PkgDenseTbl.iteri (fun p _ -> add_package p) changed_packages;
(* Packages unchanged but with stronger dependencies, or that may
depend on a package for which we ignore some co-installability
issues, should be kept as well. *)
let break_candidates = Upgrade_common.ignored_set_domain st.broken_sets in
let stronger_deps l =
(* Check whether there is a package that satisfied the dependency,
that might not satisfy the dependency anymore. *)
List.exists
(fun d ->
List.exists
(fun cstr ->
List.exists
(fun p ->
(* If the package is left unchanged, the dependency
will remain satisfied *)
(M.PkgDenseTbl.mem changed_packages p.M.package &&
(* Otherwise, we check whether a replacement exists,
that still satisfies the dependency *)
List.for_all
(fun cstr' ->
List.for_all
(fun p' -> p.M.package <> p'.M.package)
(M.resolve_package_dep_raw u cstr'))
d))
(M.resolve_package_dep_raw t cstr)
||
(* Also include packages that depend on a break candidate;
we have checked that the dependency over packages in t
is included in the dependency over packages in u, hence
we only have to look in u *)
(not (M.PkgSet.is_empty break_candidates)
&&
List.exists
(fun p -> M.PkgSet.mem p.M.package break_candidates)
(M.resolve_package_dep_raw u cstr)))
d)
l
in
(* Changed packages are already all in [pkgs], thus we only have to
look in testing. *)
M.iter_packages t
(fun p ->
if not (M.PkgDenseTbl.mem pkgs p.M.package) then
if stronger_deps p.M.depends || stronger_deps p.M.pre_depends then
add_package p.M.package);
pkgs
let prepare_repository st unchanged check_coinstallability =
let t = st.testing in
let u = st.unstable in
let red_t = Timer.start () in
let pkgs =
if check_coinstallability then
reduce_for_coinstallability st unchanged
else
reduce_for_installability st unchanged
in
let n = ref 0 in
let m = ref 0 in
let filter p =
incr m;
let nm = p.M.package in
let keep = M.PkgDenseTbl.mem pkgs nm in
if keep then incr n;
keep
in
let t' = M.new_pool () in
M.merge t' filter t;
let u' = M.new_pool () in
M.merge u' filter u;
if debug_reduction () then Format.eprintf "==> %d/%d@." !n !m;
if debug_time () then
Format.eprintf " Reducing repository sizes: %f@." (Timer.stop red_t);
st.upgrade_state <-
Some (Upgrade_common.prepare_analyze t', Upgrade_common.prepare_analyze u')
let rec get_upgrade_state st unchanged check_coinstallability =
match st.upgrade_state with
Some state -> state
| None -> prepare_repository st unchanged check_coinstallability;
get_upgrade_state st unchanged check_coinstallability
let clear_upgrade_state_local st = st.upgrade_state <- None
let clear_upgrade_state =
Task.funct (fun st () -> clear_upgrade_state_local st)
let clear_upgrade_states l =
Task.iter l (fun (arch, st) -> clear_upgrade_state st ()) (fun () -> ())
let initialize_broken_sets_local st s =
if st.break_arch_all then
StringSet.iter
(fun nm -> Upgrade_common.allow_broken_sets st.broken_sets nm) s
let initialize_broken_sets = Task.funct initialize_broken_sets_local
let initialize_broken_sets l s =
Task.iter l (fun (arch, st) -> initialize_broken_sets st s) (fun () -> ())
(**** Loading ****)
let compute_bin_ids first_id t u =
let id = ref first_id in
let id_of_bin = M.PkgDenseTbl.create (-1) in
let bin_of_id = ref [] in
let insert nm =
M.PkgDenseTbl.add id_of_bin nm !id; bin_of_id := nm :: !bin_of_id; incr id
in
M.iter_packages_by_name t (fun nm _ -> insert nm);
M.iter_packages_by_name u
(fun nm _ -> if not (M.PkgDenseTbl.mem id_of_bin nm) then insert nm);
let bin_of_id = Array.of_list (List.rev !bin_of_id) in
(id_of_bin, bin_of_id)
let compute_source_ids t u =
let id = ref 0 in
let id_of_source = M.PkgDenseTbl.create 16384 in
let source_of_id = ref [] in
let insert nm =
M.PkgDenseTbl.add id_of_source nm !id; source_of_id := nm :: !source_of_id;
incr id
in
M.iter_sources (fun s -> insert s.M.s_name) t;
M.iter_sources
(fun {M.s_name = nm} ->
if not (M.PkgDenseTbl.mem id_of_source nm) then insert nm)
u;
let source_of_id = Array.of_list (List.rev !source_of_id) in
(id_of_source, source_of_id)
let share_packages (t, u) =
let unchanged dist p =
match M.find_packages_by_name dist p.M.package with
[] -> false
| [q] -> M.compare_version p.M.version q.M.version = 0
| _ -> assert false
in
let common = M.new_pool () in
M.merge common (fun p -> unchanged u p) t;
let t' = M.copy common in
M.merge t' (fun p -> not (unchanged u p)) t;
let u' = common in
M.merge u' (fun p -> not (unchanged t p)) u;
assert (M.pool_size t' = M.pool_size t && M.pool_size u' = M.pool_size u);
(t', u')
let load_arch arch
testing_srcs testing_bugs unstable_srcs unstable_bugs
id_of_source first_id () =
let files =
[bin_package_file (testing ()) arch;
bin_package_file (unstable ()) arch]
in
let cache = bin_package_file cache_dir arch in
let ((dict, (t, u)), uid) =
Cache.cached files cache "version 3"
~is_valid:(fun (dict, _) -> M.valid_directory dict)
(fun () ->
let packages =
share_packages
(load_bin_packages (testing ()) arch,
load_bin_packages (unstable ()) arch)
in
(M.current_dict (), packages))
in
M.set_dict dict;
let (id_of_bin, bin_of_id) = compute_bin_ids first_id t u in
{ arch = arch;
testing = t;
testing_srcs = testing_srcs; testing_bugs = testing_bugs;
unstable = u;
unstable_srcs = unstable_srcs; unstable_bugs = unstable_bugs;
outdated_binaries = [];
first_bin_id = first_id; id_of_bin = id_of_bin; bin_of_id = bin_of_id;
id_of_source = id_of_source;
upgrade_state = None; uid = uid;
break_arch_all = false; (* dummy value *)
broken_sets = Upgrade_common.copy_ignored_sets broken_sets }
let load_all_files () =
let load_t = Timer.start () in
let (testing_bugs, unstable_bugs) = read_bugs () in
let files =
[src_package_file (testing ()); src_package_file (unstable ())] in
let cache = Filename.concat cache_dir "Sources" in
let ((dict, t, u), src_uid) =
Cache.cached files cache "version 4" (fun () ->
(M.current_dict (),
load_src_packages (testing ()), load_src_packages (unstable ())))
in
M.set_dict dict;
let (id_of_source, source_of_id) = compute_source_ids t u in
if debug_time () then
Format.eprintf " Loading shared data: %f@." (Timer.stop load_t);
let l =
List.map
(fun arch ->
(arch,
Task.spawn
(load_arch arch t testing_bugs u unstable_bugs
id_of_source (Array.length source_of_id))))
!archs
in
let (dates, urgencies, hints) = read_extra_info src_uid in
if debug_time () then Format.eprintf "Loading: %f@." (Timer.stop load_t);
(dates, urgencies, hints, t, u, testing_bugs, unstable_bugs, l,
id_of_source, source_of_id, src_uid)
(**** Deferred constraints ****)
let retract_deferred_constraints solver constraints =
List.iter
(fun (_, l) ->
List.iter (fun (id, _) -> HornSolver.retract_assumptions solver id) l)
constraints
let perform_deferred
solver ?(before=fun _ _ -> true) ?(after=fun _ _ -> ()) (kind, lst) =
if before (lst <> []) kind then begin
List.iter (fun (id, reason) -> HornSolver.assume solver id reason) lst;
after (lst <> []) kind
end
let assert_deferred_constraints solver ?before ?after constraints =
List.iter (fun lst -> perform_deferred solver ?before ?after lst) constraints
(**** Constraint computation ****)
type cstr =
Assume of HornSolver.var * reason
| Implies of HornSolver.var * HornSolver.var * reason
| All_or_none of HornSolver.var list * reason
let compute_hints () = debug_hints () || !hint_file <> ""
let string_uid s =
s >> Digest.string >> Digest.to_hex >> fun s -> String.sub s 0 16
let should_remove t u nm v =
match source_version t nm with
Some v' ->
M.compare_version v v' = 0
| None ->
match source_version u nm with
Some v' ->
M.compare_version v v' = 0
| None ->
false
let remove_sources central remove_hints t u =
let l = ref [] in
M.PkgTbl.iter
(fun nm v ->
if should_remove t u nm v && M.has_source u nm then begin
if central && debug_remove () then
Format.eprintf "Trying to remove source package %s@."
(M.name_of_id nm);
M.remove_source u nm;
l := nm :: !l
end)
remove_hints;
(!l,
!l >> List.sort compare
>> fun l -> Marshal.to_string l [] >> string_uid)
let arch_constraints
st (produce_excuses, fucked_arch, break_arch,
break_arch_all, remove_hints) =
st.break_arch_all <- break_arch_all;
let t = st.testing_srcs in
let u = st.unstable_srcs in
let t' = st.testing in
let u' = st.unstable in
let removed_pkgs = ref [] in
M.iter_packages u'
(fun p ->
let (nm, _) = p.M.source in
try
let v = M.PkgTbl.find remove_hints nm in
if should_remove t u nm v then begin
if debug_remove () then
Format.eprintf
"Trying to remove binary package %s/%s (source: %s)@."
(M.name_of_id p.M.package) st.arch (M.name_of_id nm);
removed_pkgs := p :: !removed_pkgs
end
with Not_found ->
());
List.iter (fun p -> M.remove_package u' p) !removed_pkgs;
(* We have forked before the sources are removed on the master;
so we have to remove them as well here. *)
ignore (remove_sources false remove_hints t u);
let fake_srcs = ref [] in
(* Source packages missing in testing (with name) *)
let added_srcs = ref [] in
(* Source packages temporarily added in testing or sid *)
let extra_srcs = ref [] in
(* Source packages missing in both testing and sid *)
let is_fake = M.PkgTbl.create 17 in
let sources_with_binaries = ref [] in
let source_has_binaries = M.PkgTbl.create 8192 in
let l = ref [] in
let assume id reason = l := Assume (id, reason) :: !l in
let implies id1 id2 reason = l := Implies (id1, id2, reason):: !l
in
let all_or_none pkgl reason = l :=
All_or_none (Util.sort_and_uniq compare pkgl, reason) :: !l in
let get_bugs src bugs p =
try StringTbl.find bugs p with Not_found -> StringSet.empty
in
let no_new_bugs is_new p =
let p = M.name_of_id p in
if is_new then
StringSet.is_empty (get_bugs u st.unstable_bugs p)
else
StringSet.subset
(get_bugs u st.unstable_bugs p)
(get_bugs t st.testing_bugs p)
in
let new_bugs is_new p =
let p = M.name_of_id p in
if is_new then
get_bugs u st.unstable_bugs p
else
StringSet.diff
(get_bugs u st.unstable_bugs p)
(get_bugs t st.testing_bugs p)
in
let bin_nmus = ListTbl.create 101 in
let source_id p = M.PkgDenseTbl.find st.id_of_source (fst p.M.source) in
let bin_id p = M.PkgDenseTbl.find st.id_of_bin p.M.package in
let bin_id_count = Array.length st.bin_of_id in
let last_id = ref (st.first_bin_id + bin_id_count) in
M.iter_packages u'
(fun p ->
let id = bin_id p in
let (nm, v) = p.M.source in
(* Package without source *)
if not (M.has_source u nm) then begin
M.add_source u
{ M.s_name = nm; s_version = v; s_section = "";
s_binary = []; s_extra_source = false };
added_srcs := (u, nm) :: !added_srcs;
if not (M.has_source t nm) then begin
extra_srcs := M.name_of_id nm :: !extra_srcs;
M.PkgTbl.add is_fake nm ();
if not (M.PkgDenseTbl.mem st.id_of_source nm) then begin
M.PkgDenseTbl.add st.id_of_source nm !last_id;
incr last_id
end
end;
assume (source_id p) Unchanged
end;
let v' = (M.find_source_by_name u nm).M.s_version in
let source_changed = not (same_source_version t u nm) in
(* Do not add a binary package if its source is not
the most up to date source file. *)
let outdated = M.compare_version v v' <> 0 in
if outdated then begin
st.outdated_binaries <- p :: st.outdated_binaries;
let still_built =
List.memq p.M.package (M.find_source_by_name u nm).M.s_binary in
assume id (Not_yet_built (M.name_of_id nm, v, v', still_built))
end else begin
if not (M.PkgTbl.mem source_has_binaries nm) then begin
sources_with_binaries := nm :: !sources_with_binaries;
M.PkgTbl.add source_has_binaries nm ()
end;
(* We only propagate binary packages with a larger version.
Faux packages are not propagated. *)
if no_new_bin t' u' p.M.package || M.PkgTbl.mem is_fake nm then
assume id Unchanged
else begin
(* Do not upgrade a package if it has new bugs *)
let is_new = bin_version t' p.M.package = None in
if not (no_new_bugs is_new p.M.package) then
assume id (More_bugs (new_bugs is_new p.M.package));
if source_changed then
(* We cannot add a binary package without also adding
its source. *)
implies (source_id p) id Source_not_propagated
else
ListTbl.add bin_nmus nm id
end
end;
(* If a source is propagated, all its binaries should
be propagated as well *)
if
(source_changed || produce_excuses)
&&
not (outdated && fucked_arch)
&&
not (not outdated && break_arch)
then
implies id (source_id p)
(if outdated then Binary_not_removed else Binary_not_added));
(* Remove not up to date binaries from sid. The idea is that removing
the 'Not_yet_build' constraint then makes it possible to test whether
these packages can be removed without breaking anything. To allow smooth
updates, libraries in sid are rather replaced by their counterpart in
testing. This way, the 'Binary_not_propagated' constraint just above
can always be satisfied when the 'Not_yet_build' constraint is removed. *)
let is_outdated = M.PkgTbl.create 400 in
List.iter
(fun p ->
M.PkgTbl.add is_outdated p.M.package ();
if
allow_smooth_updates p &&
M.has_package_of_name t' p.M.package
then
M.replace_package u' p
(List.hd (M.find_packages_by_name t' p.M.package))
else
M.remove_package u' p)
st.outdated_binaries;
M.iter_packages t'
(fun p ->
let id = bin_id p in
let (nm, v) = p.M.source in
(* Faux packages *)
if not (M.has_source t nm) then begin
M.add_source t
{ M.s_name = nm; s_version = v; s_section = "";
s_binary = []; s_extra_source = false };
added_srcs := (t, nm) :: !added_srcs;
fake_srcs := (M.name_of_id nm, v) :: !fake_srcs;
M.PkgTbl.replace is_fake nm ();
if not (M.PkgDenseTbl.mem st.id_of_source nm) then begin
extra_srcs := M.name_of_id nm :: !extra_srcs;
M.PkgDenseTbl.add st.id_of_source nm !last_id;
incr last_id;
end;
assume (source_id p) Unchanged
end;
let v' = (M.find_source_by_name t nm).M.s_version in
let source_changed =
not (same_source_version t u nm) in
(* We only propagate binary packages with a larger version.
Faux packages are not propagated. Outdated packages are
never consider to be unchanged, so that we can test smooth
upgrades. *)
if
not (M.PkgTbl.mem is_outdated p.M.package)
&&
(no_new_bin t' u' p.M.package || M.PkgTbl.mem is_fake nm)
then
assume id Unchanged
else begin
let taken_over =
match M.find_packages_by_name u' p.M.package with
p :: _ -> nm <> fst (p.M.source)
| [] -> false
in
(* Binary packages without source of the same version can
be removed freely when not needed anymore (these are
binaries left for smooth update). *)
(* They can be updated freely when the source package changes *)
if M.compare_version v v' <> 0 || taken_over then
()
(* We cannot remove a binary without removing its source *)
else if source_changed then
implies (source_id p) id Source_not_propagated
else
(* We can update binaries when the source is unchanged (Bin NMUs),
but only atomically. *)
ListTbl.add bin_nmus nm id
end;
(* We cannot remove or upgrade a source package if a
corresponding binary package still exists.
We relax this constraint for libraries when upgrading
a source package. *)
(* We only generate a constraint when the source has changed
(or to link the source package to the binary package when
producing excuses). Indeed, otherwise, the constraint
is redundant. *)
if
(source_changed || produce_excuses)
&&
not (allow_smooth_updates p && M.has_source u nm)
&&
not break_arch
then
implies id (source_id p) Binary_not_removed);
(* All binaries packages from a same source are propagated
atomically on any given architecture. *)
ListTbl.iter
(fun _ pkgs -> all_or_none pkgs Atomic) bin_nmus;
(* Clear temporarily added packages (needed when using a
single processor). *)
List.iter (fun (d, nm) -> M.remove_source d nm) !added_srcs;
(* Also leaves id_of_source unchanged. *)
List.iter
(fun nm -> M.PkgDenseTbl.remove st.id_of_source (M.id_of_name nm))
!extra_srcs;
(List.rev !l, st.uid, !sources_with_binaries, List.rev !extra_srcs,
!fake_srcs, bin_id_count, Array.map M.name_of_id st.bin_of_id)
let arch_constraints = Task.funct arch_constraints
let initial_constraints
(dates, urgencies, hints, t, u,
testing_bugs, unstable_bugs, l, id_of_source, source_of_id, src_uid) =
let init_t = Timer.start () in
List.iter
(fun p ->
let l = Str.split slash p in
try
match l with
[nm; v] when M.name_exists nm ->
let nm = M.id_of_name nm in
M.PkgTbl.replace hints.h_remove nm
(Deb_lib.parse_version v)
| [nm] when M.name_exists nm ->
let nm = M.id_of_name nm in
M.PkgTbl.replace hints.h_remove nm
(try
(M.find_source_by_name t nm).M.s_version
with Not_found ->
(M.find_source_by_name u nm).M.s_version)
| _ ->
raise Not_found
with Not_found ->
Format.eprintf "No source package %s.@." (List.hd l);
exit 1)
!to_remove;
let (removed_srcs, rem_uid) = remove_sources true hints.h_remove t u in
let name_of_id =
ref [("source", 0,
Array.length source_of_id, Array.map M.name_of_id source_of_id)] in
let get_name_arch id =
let (arch, start, len, tbl) =
List.find
(fun (arch, start, len, tbl) ->
id >= start && id < start + len)
!name_of_id
in
(tbl.(id - start), arch)
in
let print_package f id =
let (name, arch) = get_name_arch id in
if arch = "source" then
Format.fprintf f "%s" name
else
Format.fprintf f "%s/%s" name arch
in
let signal_assign r reason =
if reason <> Unchanged && verbose () then begin
let id = r.(0) in
let (nm, arch) = get_name_arch id in
L.print (new L.format_printer Format.err_formatter)
(L.s "Skipping " & L.i id & L.s " - " &
L.s nm & L.s "/" & L.s arch & L.s ": " &
print_reason' get_name_arch r reason)
end
in
let solver =
HornSolver.initialize ~signal_assign (Array.length source_of_id) in
HornSolver.set_var_printer solver print_package;
let get_bugs src bugs p =
try StringTbl.find bugs p with Not_found -> StringSet.empty
in
let no_new_bugs is_new p =
if is_new then
StringSet.is_empty (get_bugs u unstable_bugs p)
else
StringSet.subset (get_bugs u unstable_bugs p) (get_bugs t testing_bugs p)
in
let new_bugs is_new p =
if is_new then
get_bugs u unstable_bugs p
else
StringSet.diff (get_bugs u unstable_bugs p) (get_bugs t testing_bugs p)
in
let is_unblocked h nm v =
try M.compare_version (M.PkgTbl.find h nm) v = 0 with Not_found -> false
in
let is_blocked source_name nm v =
((hints.h_block_all <> None || StringTbl.mem hints.h_block source_name) &&
not (is_unblocked hints.h_unblock nm v))
||
(M.PkgTbl.mem hints.h_block_udeb nm &&
not (is_unblocked hints.h_unblock_udeb nm v))
in
let blocked_reason source_name nm v =
if
StringTbl.mem hints.h_block source_name &&
not (is_unblocked hints.h_unblock nm v)
then
("block", StringTbl.find hints.h_block source_name)
else if
M.PkgTbl.mem hints.h_block_udeb nm &&
not (is_unblocked hints.h_unblock_udeb nm v)
then
("block-udeb", M.PkgTbl.find hints.h_block_udeb nm)
else
match hints.h_block_all with
None ->
assert false
| Some who ->
assert (not (is_unblocked hints.h_unblock nm v));
("block", who)
in
let block_constraints = ref [] in
let age_constraints = ref [] in
let bug_constraints = ref [] in
let outdated_constraints = ref [] in
let obsolete_constraints = ref [] in
let produce_excuses = !excuse_file <> "" || !explain_dir <> "" in
let implies id1 id2 reason =
ignore (HornSolver.add_rule solver [|id2; id1|] reason) in
let assume_deferred lst id reason =
if produce_excuses then
lst := (id, reason) :: !lst
else
HornSolver.assume solver id reason
in
let deferred_constraints () =
[(`Bugs, !bug_constraints); (`Outdated, !outdated_constraints);
(`Obsolete, !obsolete_constraints);
(`Age, !age_constraints); (`Blocked, !block_constraints)]
in
let all_or_none ids reason =
match ids with
[] ->
()
| id :: rem ->
List.iter
(fun id' -> implies id id' reason; implies id' id reason) rem
in
let arch_results =
List.map
(fun (arch, t) ->
let fucked_arch =
List.mem arch
(try Hashtbl.find options "FUCKED_ARCHES" with Not_found -> [])
in
let break_arch =
List.mem arch
(try Hashtbl.find options "BREAK_ARCHES" with Not_found -> [])
in
let break_arch_all =
not (List.mem arch
(try
Hashtbl.find options "NOBREAKALL_ARCHES"
with Not_found -> []))
in
(arch,
arch_constraints t
(produce_excuses, fucked_arch, break_arch, break_arch_all,
hints.h_remove)))
l
in
M.iter_sources
(fun s ->
let nm = s.M.s_name in
let v = s.M.s_version in
let id = M.PkgDenseTbl.find id_of_source nm in
(* We only propagate source packages with a larger version *)
if no_new_source t u nm then
ignore (HornSolver.add_rule solver [|id|] Unchanged)
else begin
(* Do not propagate a source package requested to be blocked *)
let source_name = M.name_of_id nm in
if is_blocked source_name nm v then
assume_deferred block_constraints id
(Blocked (blocked_reason source_name nm v));
(* Do not propagate a source package if not old enough *)
let v' = source_version t nm in
let (cur_ag, req_ag) = compute_ages dates urgencies hints nm v v' in
if cur_ag < req_ag then
assume_deferred age_constraints id (Too_young (cur_ag, req_ag));
(* Do not propagate a source package if it has new bugs *)
let is_new = v' = None in
if
not (no_new_bugs is_new source_name &&
no_new_bugs is_new ("src:" ^ source_name))
then
assume_deferred bug_constraints id
(More_bugs (StringSet.union
(new_bugs is_new source_name)
(new_bugs is_new ("src:" ^ source_name))))
end)
u;
M.iter_sources
(fun s ->
let nm = s.M.s_name in
if not (M.has_source u nm) then
try
let who = StringTbl.find hints.h_block ("-" ^ M.name_of_id nm) in
let id =
try
M.PkgDenseTbl.find id_of_source nm
with Not_found ->
assert false
in
assume_deferred block_constraints id (Blocked ("blocked", who))
with Not_found ->
())
t;
List.iter
(fun nm ->
if not (M.has_source t nm) then begin
(* We cannot migrate a package that exists neither in testing
nor in unstable. *)
let id = M.PkgDenseTbl.find id_of_source nm in
ignore (HornSolver.add_rule solver [|id|] Unchanged)
end)
removed_srcs;
let source_has_binaries = M.PkgTbl.create 8192 in
let is_extra = M.PkgTbl.create 17 in
let first_bin_id = Array.length source_of_id in
let id_offset = ref 0 in
let id_offsets = StringTbl.create 17 in
let smooth_uid =
string_uid (String.concat " " (List.sort compare !smooth_updates)) in
let uids =
smooth_uid ::
rem_uid ::
src_uid ::
List.map
(fun (arch, r) ->
let (constraints, uid, sources_with_binaries,
extra_srcs, fake_srcs, bin_id_count, bin_of_id) =
Task.wait r in
(*XXXXX Use ids? *)
List.iter
(fun nm ->
if not (M.PkgTbl.mem source_has_binaries nm) then
M.PkgTbl.add source_has_binaries nm ())
sources_with_binaries;
let last_bin_id = first_bin_id + bin_id_count in
let last_id = ref (last_bin_id + !id_offset) in
let id_of_fake = IntTbl.create 101 in
let offset id =
if id < first_bin_id then
id
else if id < last_bin_id then
id + !id_offset
else
IntTbl.find id_of_fake id
in
StringTbl.add id_offsets arch (first_bin_id, !id_offset, bin_id_count);
name_of_id :=
(arch, first_bin_id + !id_offset, bin_id_count, bin_of_id) ::
!name_of_id;
let cur_id = ref last_bin_id in
let extra_lst = ref [] in
List.iter
(fun nm ->
let nm = M.add_name nm in
if not (M.PkgTbl.mem is_extra nm) then begin
extra_lst := nm :: !extra_lst;
M.PkgTbl.add is_extra nm !last_id;
M.PkgDenseTbl.add id_of_source nm !last_id;
incr last_id;
end;
IntTbl.add id_of_fake !cur_id (M.PkgTbl.find is_extra nm);
incr cur_id)
extra_srcs;
if !extra_lst <> [] then begin
let start = last_bin_id + !id_offset in
let tbl =
Array.map M.name_of_id (Array.of_list (List.rev !extra_lst)) in
assert (Array.length tbl = !last_id - start);
name_of_id :=
("source", start, !last_id - start, tbl) :: !name_of_id
end;
List.iter
(fun (nm, v) ->
let nm = M.id_of_name nm in
if not (M.has_source t nm) then
M.add_source t
{ M.s_name = nm; s_version = v; s_section = "faux";
s_binary = []; s_extra_source = false })
fake_srcs;
HornSolver.extend solver !last_id;
List.iter
(fun c ->
match c with
Assume (id, reason) ->
begin match reason with
Unchanged ->
ignore (HornSolver.add_rule solver [|offset id|] reason)
| Too_young _ ->
assume_deferred age_constraints (offset id) reason
| More_bugs _ ->
assume_deferred bug_constraints (offset id) reason
| Not_yet_built (_, _, _, true) ->
assume_deferred outdated_constraints (offset id) reason
| Not_yet_built (_, _, _, false) ->
assume_deferred obsolete_constraints (offset id) reason
| Blocked _ | Binary_not_added | Binary_not_removed
| No_binary | Conflict _ | Source_not_propagated | Atomic ->
assert false
end
| Implies (id1, id2, reason) ->
implies (offset id1) (offset id2) reason
| All_or_none (ids, reason) ->
all_or_none (List.map offset ids) reason)
constraints;
id_offset := !last_id - first_bin_id;
uid)
arch_results
in
M.iter_sources
(fun {M.s_name = nm} ->
if not (M.PkgTbl.mem source_has_binaries nm) then
ignore
(HornSolver.add_rule solver
[|M.PkgDenseTbl.find id_of_source nm|] No_binary))
u;
if !explain_dir = "" then load_rules solver uids;
initialize_broken_sets l !broken_arch_all_packages;
if debug_time () then
Format.eprintf "Initial constraints: %f@." (Timer.stop init_t);
(uids, solver, deferred_constraints (), id_offsets, get_name_arch)
(**** Dealing with arch:all packages ****)
let is_arch_all st unchanged nm =
let nm = M.id_of_name nm in
let is_arch_all dist =
match M.find_packages_by_name dist nm with
[p] -> p.M.architecture = "all"
| _ -> assert false
in
if is_unchanged st unchanged nm then
is_arch_all st.testing
else
is_arch_all st.unstable
let ignore_arch_all_issues st unchanged problems =
if st.break_arch_all then
List.partition
(fun p ->
not (StringSet.exists
(fun nm -> is_arch_all st unchanged nm)
p.Upgrade_common.p_issue))
problems
else
(problems, [])
let involved_arch_all_packages st unchanged problems =
List.fold_left
(fun s p ->
StringSet.union s
(StringSet.filter
(fun nm -> is_arch_all st unchanged nm) p.Upgrade_common.p_issue))
StringSet.empty problems
(**** Find constraints due to co-installability issues ****)
let rec find_coinst_constraints
st unchanged check_coinstallability broken_arch_all_packages =
Gc.set { (Gc.get ()) with Gc.space_overhead = 80 };
if debug_gc () then begin
Gc.full_major (); Gc.print_stat stderr; flush stderr
end;
let arch = st.arch in
let (t', u') = get_upgrade_state st unchanged check_coinstallability in
if debug_coinst () then
Format.eprintf "==================== %s@." arch;
let step_t = Timer.start () in
let problems =
if check_coinstallability then
Upgrade_common.find_problematic_packages
~check_new_packages:true st.broken_sets t' u'
(fun nm -> is_unchanged st unchanged nm)
else
Upgrade_common.find_non_inst_packages st.break_arch_all
st.broken_sets t' u' (fun nm -> is_unchanged st unchanged nm)
in
let t = Timer.start () in
let (problems, arch_all_issues) =
ignore_arch_all_issues st unchanged problems in
let is_singleton pos =
StringSet.cardinal pos = 1
||
let source nm =
match M.find_packages_by_name st.testing (M.id_of_name nm) with
[p] when not (allow_smooth_updates p) -> Some p.M.source
| _ -> None
in
let eq s1 s2 =
match s1, s2 with
Some (nm1, v1), Some (nm2, v2) ->
nm1 = nm2 && M.compare_version v1 v2 = 0
| _ ->
false
in
let src = source (StringSet.choose pos) in
StringSet.for_all (fun nm -> eq (source nm) src) pos
in
let has_singletons =
List.exists
(fun p -> is_singleton p.Upgrade_common.p_clause.Upgrade_common.pos)
problems
in
let changes = ref [] in
List.iter
(fun ({Upgrade_common.p_clause = {Upgrade_common.pos = pos; neg = neg};
p_issue = s } as problem) ->
let singleton = is_singleton pos in
if singleton || not has_singletons then begin
(*
let arch_all dist p = match M.find_packages_by_name dist p with [] -> true | [p] -> p.M.architecture = "all" | _ -> assert false in
StringSet.iter
(fun nm -> if arch_all st.testing nm && arch_all st.unstable nm then Format.eprintf "IGN %s/%s@." nm arch) s;
*)
let to_ids s =
StringSet.fold
(fun nm s ->
IntSet.add
(M.PkgDenseTbl.find st.id_of_bin (M.id_of_name nm)) s)
s IntSet.empty
in
let neg = to_ids neg in
let s' = to_ids s in
let id =
M.PkgDenseTbl.find
st.id_of_bin (M.id_of_name (StringSet.choose pos)) in
let r = Array.of_list (id :: IntSet.elements neg) in
if not singleton && debug_choice () then begin
Format.eprintf "Warning: cannot migrate all of";
StringSet.iter (fun s -> Format.eprintf " %s" s) pos;
Format.eprintf ". Not migrating %s.@." (StringSet.choose pos)
end;
let can_learn = singleton in
changes := (r, neg, s', problem, can_learn) :: !changes
end)
problems;
if debug_time () then begin
Format.eprintf " New constraints: %f@." (Timer.stop t);
Format.eprintf "Step duration: %f@." (Timer.stop step_t)
end;
if !changes = [] && arch_all_issues <> [] then begin
let s = involved_arch_all_packages st unchanged arch_all_issues in
if debug_coinst () then begin
Format.eprintf "Ignoring arch:all packages:";
StringSet.iter (fun nm -> Format.eprintf " %s" nm) s;
Format.eprintf "@."
end;
initialize_broken_sets_local st s;
clear_upgrade_state_local st;
find_coinst_constraints st unchanged check_coinstallability
(StringSet.union broken_arch_all_packages s)
end else
(List.rev !changes, broken_arch_all_packages)
let find_coinst_constraints =
Task.funct (fun st (unchanged, check_coinstallability) ->
find_coinst_constraints st unchanged check_coinstallability
StringSet.empty)
let find_all_coinst_constraints solver id_offsets l =
let t = Timer.start () in
let a = Array.of_list l in
let c = Array.length a in
let running = Array.make c false in
let changed = Array.make c true in
let n = ref 0 in
let max_proc = Task.get_processor_count () in
let scheduler = Task.scheduler () in
let rec start c i0 i =
if running.(i) || not changed.(i) then begin
let i = (i + 1) mod c in
if i <> i0 then start c i0 i
end else begin
changed.(i) <- false;
running.(i) <- true;
incr n;
let (arch, st) = a.(i) in
Task.async scheduler
(find_coinst_constraints st
(extract_unchanged_bin
solver id_offsets arch (HornSolver.assignment solver),
!check_coinstallability))
(fun changes -> stop c i changes);
if !n < max_proc then begin
start c 0 0
end
end
and stop c i (changes, broken_arch_all_packages) =
learn_broken_arch_all_packages broken_arch_all_packages;
if changes <> [] then begin
Array.fill changed 0 c true;
let (_, offset, _) = StringTbl.find id_offsets (fst a.(i)) in
List.iter
(fun (r, neg, s, problem, can_learn) ->
let r = Array.map (fun id -> id + offset) r in
let offset_set ids =
IntSet.fold (fun id s -> IntSet.add (id + offset) s)
ids IntSet.empty
in
let neg = offset_set neg in
let s = offset_set s in
let r' =
HornSolver.add_rule solver r (Conflict (neg, s, problem)) in
if IntSet.cardinal s > 1 then coinst_rules := r' :: !coinst_rules;
if can_learn then
learn_rule r neg s problem
else
ambiguous_rules := r' :: !ambiguous_rules)
changes
end;
running.(i) <- false;
decr n;
start c i i
in
(*
start 1 0 0;
Task.run scheduler;
*)
start c 0 0;
Task.run scheduler;
if debug_time () then
Format.eprintf "Solving constraints: %f@." (Timer.stop t)
(**** Output all changes (for debugging) ****)
let output_arch_changes st unchanged =
let arch = st.arch in
let t' = st.testing in
let u' = st.unstable in
M.iter_packages t'
(fun p ->
let nm = p.M.package in
let v = p.M.version in
if not (is_unchanged st unchanged nm) then
match bin_version u' nm with
Some v' ->
Format.eprintf
"Upgrade binary package %s/%s from %a to %a@."
(M.name_of_id nm) arch M.print_version v M.print_version v'
| None ->
Format.eprintf "Remove binary package %s/%s@."
(M.name_of_id nm) arch);
M.iter_packages u'
(fun p ->
let nm = p.M.package in
if not (is_unchanged st unchanged nm) then
if not (M.has_package_of_name t' nm) then
Format.eprintf "Adding binary package %s/%s@."
(M.name_of_id nm) arch)
let output_arch_changes = Task.funct output_arch_changes
let output_outcome solver id_of_source id_offsets t u l unchanged =
let is_unchanged src =
BitVect.test unchanged (M.PkgDenseTbl.find id_of_source src) in
M.iter_sources
(fun s ->
let nm = s.M.s_name in
if not (is_unchanged nm) then
try
let s' = M.find_source_by_name u nm in
Format.eprintf "Upgrade source package %s from %a to %a@."
(M.name_of_id nm)
M.print_version s.M.s_version M.print_version s'.M.s_version
with Not_found ->
Format.eprintf "Remove source package %s@." (M.name_of_id nm))
t;
M.iter_sources
(fun {M.s_name = nm} ->
if not (M.has_source t nm || is_unchanged nm) then
Format.eprintf "Adding source package %s@." (M.name_of_id nm))
u;
List.iter
(fun (arch, st) ->
Task.wait (output_arch_changes st
(extract_unchanged_bin solver id_offsets arch unchanged)))
l
(**** Hint output ****)
let cluster_packages st (unchanged, clusters, check_coinstallability) =
let clusters =
List.map (fun (lst, id) -> (lst, (id, Union_find.elt id))) clusters
in
let merge (_, e1) (_, e2) = Union_find.merge e1 e2 min in
let (t, u) = get_upgrade_state st unchanged check_coinstallability in
Upgrade_common.find_clusters t u
(fun nm -> is_unchanged st unchanged nm) clusters merge;
List.map (fun (_, (id, elt)) -> (id, Union_find.get elt)) clusters
let cluster_packages = Task.funct cluster_packages
type 'a easy_hint =
{ mutable h_names : 'a list;
mutable h_pkgs : (string * string) list;
mutable h_live : bool;
h_id : int }
let generate_small_hints solver id_offsets l buckets subset_opt =
let to_consider = ref [] in
let buckets_by_id = Hashtbl.create 17 in
let n = ref 0 in
ListTbl.iter
(fun (src, arch) lst ->
let info =
{ h_names = [((src, arch), List.for_all snd lst)];
h_pkgs = List.map fst lst; h_live = true; h_id = !n }
in
let elt = Union_find.elt info in
Hashtbl.add buckets_by_id !n elt;
incr n;
to_consider := (info, elt) :: !to_consider)
buckets;
let merge elt elt' =
Union_find.merge elt elt'
(fun info info' ->
assert (info.h_live);
assert (info'.h_live);
info.h_names <- info'.h_names @ info.h_names;
info.h_pkgs <- info'.h_pkgs @ info.h_pkgs;
info'.h_live <- false;
info)
in
(* When the source of a package changes, the package may occur in
two different clusters. We merge these clusters. *)
let package_cluster = Hashtbl.create 101 in
List.iter
(fun (info, elt) ->
List.iter
(fun p ->
try
merge (Hashtbl.find package_cluster p) elt
with Not_found ->
Hashtbl.add package_cluster p elt)
info.h_pkgs)
!to_consider;
let to_consider = List.filter (fun (info, _) -> info.h_live) !to_consider in
Task.iter l
(fun (arch, st) ->
let unchanged =
extract_unchanged_bin
solver id_offsets arch (HornSolver.assignment solver)
in
let clusters = ref [] in
List.iter
(fun (info, elt) ->
let l =
List.filter (fun (_, arch') -> arch = arch') info.h_pkgs in
if l <> [] then
clusters :=
(List.map (fun (nm, _) -> nm) l, (Union_find.get elt).h_id)
:: !clusters)
to_consider;
cluster_packages st (unchanged, !clusters, !check_coinstallability))
(fun lst ->
List.iter
(fun (id, id') ->
merge (Hashtbl.find buckets_by_id id)
(Hashtbl.find buckets_by_id id'))
lst);
let compare_elt = Util.compare_pair compare compare in
to_consider
>> List.map fst
>> List.filter (fun info -> info.h_live)
>> List.map
(fun info ->
info.h_names
>> List.filter (fun (_, hide) -> not hide)
>> List.map fst
>> List.sort compare_elt)
>> List.filter (fun l -> l <> [])
>> List.sort (Util.compare_list compare_elt)
>> List.stable_sort (fun l l' -> compare (List.length l) (List.length l'))
let collect_changes st (unchanged, subset, src_unchanged) =
let changes = ref [] in
let u' = st.unstable in
let t' = st.testing in
M.iter_packages u'
(fun p ->
let nm = p.M.package in
if not (is_unchanged st unchanged nm) then begin
let (src, v) = p.M.source in
changes :=
(M.name_of_id src, M.name_of_id nm,
is_unchanged st subset nm) :: !changes
end);
let src_is_unchanged src =
BitVect.test src_unchanged (M.PkgDenseTbl.find st.id_of_source src) in
M.iter_packages t'
(fun p ->
let nm = p.M.package in
if
not (is_unchanged st unchanged nm)
&&
(* Do not include a binary package twice,
except when it source is different in testing and sid,
and migrates in testing *)
not (match M.find_packages_by_name u' nm with
p' :: _ -> fst (p'.M.source) = fst (p.M.source)
||
src_is_unchanged (fst p.M.source)
| [] -> false)
then begin
let (src, v) = p.M.source in
let smooth_update =
M.compare_version v
(M.find_source_by_name st.testing_srcs src).M.s_version <> 0
in
let src =
if smooth_update then begin
let b = Buffer.create 20 in
Format.bprintf b "-%s/%s/%a%!"
(M.name_of_id nm) st.arch M.print_version v;
Buffer.contents b
end else
M.name_of_id src
in
changes :=
(src, M.name_of_id nm, is_unchanged st subset nm) :: !changes
end);
List.rev !changes
let collect_changes = Task.funct collect_changes
let generate_hints ?formatter
solver id_of_source id_offsets t u l extra_lines pkg_opt subset_opt =
let hint_t = Timer.start () in
let unchanged = HornSolver.assignment solver in
let subset = match subset_opt with Some s -> s | None -> unchanged in
let changes = ListTbl.create 101 in
Task.iteri l
(fun (arch, st) ->
(arch,
collect_changes st
(extract_unchanged_bin solver id_offsets arch unchanged,
extract_unchanged_bin solver id_offsets arch subset,
unchanged)))
(fun arch lst ->
List.iter
(fun (src, nm, hide) -> ListTbl.add changes src ((nm, arch), hide))
lst);
let buckets = ListTbl.create 101 in
let is_unchanged src =
BitVect.test unchanged (M.PkgDenseTbl.find id_of_source (M.id_of_name src))
in
ListTbl.iter
(fun src l ->
if src.[0] <> '-' && not (is_unchanged src) then
List.iter
(fun info -> ListTbl.add buckets (src, "source") info)
l
else
List.iter
(fun (((_, arch), _) as info) ->
ListTbl.add buckets (src, arch) info)
l)
changes;
let hints =
generate_small_hints solver id_offsets l buckets subset_opt in
if debug_time () then
Format.eprintf "Generating hints: %f@." (Timer.stop hint_t);
let is_smooth_update src = src.[0] = '-' in
let print_pkg f src arch =
(* We are removing a binary package subject to smooth update. *)
if is_smooth_update src then Format.fprintf f " %s" src else
try
let vers =
(M.find_source_by_name u (M.id_of_name src)).M.s_version in
if arch = "source" then begin
(* We are propagating a source package. *)
Format.fprintf f " %s/%a" src M.print_version vers
end else begin
(* We are changing some binaries. *)
Format.fprintf f " %s/%s/%a" src arch M.print_version vers
end
with Not_found ->
(* We are removing a source package. *)
if arch = "source" then
let vers =
(M.find_source_by_name t (M.id_of_name src)).M.s_version in
Format.fprintf f " -%s/%a" src M.print_version vers
in
let print_hint f l =
let should_show =
(!all_hints || List.length l > 1 || subset_opt <> None)
&&
match pkg_opt with
Some pkg -> List.mem_assoc pkg l
| None -> true
in
if should_show then begin
let (su, gen) =
List.partition (fun (src, arch) -> is_smooth_update src) l in
if List.length gen > 1 || !all_hints then begin
Format.fprintf f "easy";
List.iter (fun (src, arch) -> print_pkg f src arch) gen;
Format.fprintf f "@.";
if debug_hints () && su <> [] then begin
Format.fprintf f "# ";
List.iter (fun (src, arch) -> print_pkg f src arch) su;
Format.fprintf f "@."
end
end else if debug_hints () then begin
Format.fprintf f "#easy";
List.iter (fun (src, arch) -> print_pkg f src arch) su;
Format.fprintf f "@."
end
end
in
let print_hints f =
List.iter (fun l -> Format.fprintf f "%s@." l) extra_lines;
List.iter (fun names -> print_hint f names) hints
in
if debug_hints () || (!hint_file = "-" && formatter = None) then
print_hints Format.std_formatter;
match formatter with
Some f ->
print_hints f
| None ->
if !hint_file <> "" && !hint_file <> "-" then begin
let ch = open_out !hint_file in
print_hints (Format.formatter_of_out_channel ch);
close_out ch
end
(**** Heidi file output ****)
let heidi_buffer = Buffer.create 80
let heidi_line lines nm vers arch sect =
Buffer.add_string heidi_buffer nm;
Buffer.add_char heidi_buffer ' ';
Buffer.add_string heidi_buffer (M.string_of_version vers);
Buffer.add_char heidi_buffer ' ';
Buffer.add_string heidi_buffer arch;
Buffer.add_char heidi_buffer ' ';
Buffer.add_string heidi_buffer sect;
Buffer.add_char heidi_buffer '\n';
(*
Format.bprintf heidi_buffer "%s %a %s %s@."
nm M.print_version vers arch sect;
*)
lines := Buffer.contents heidi_buffer :: !lines;
Buffer.clear heidi_buffer
let heidi_arch st unchanged =
let lines = ref [] in
let t = st.testing in
let u = st.unstable in
let sources_with_binaries = ref [] in
let source_has_binaries = M.PkgTbl.create 8192 in
let register_source p =
let (nm, _) = p.M.source in
if not (M.PkgTbl.mem source_has_binaries nm) then begin
sources_with_binaries := nm :: !sources_with_binaries;
M.PkgTbl.add source_has_binaries nm ()
end
in
let source_version_match p =
(* When architectures are marked as "fucked", their binary version
may be lower than the corresponding source version. This does not
make sense for arch:all packages which must have the same version
on all architectures. *)
p.M.architecture <> "all" ||
let (src, v) = p.M.source in
match source_version st.testing_srcs src with
None -> false
| Some v' -> M.compare_version v v' = 0
in
M.iter_packages t
(fun p ->
let nm = p.M.package in
let sect = if p.M.section = "" then "faux" else p.M.section in
if is_unchanged st unchanged nm && source_version_match p then begin
register_source p;
heidi_line lines (M.name_of_id nm) p.M.version p.M.architecture sect
end);
M.iter_packages u
(fun p ->
let nm = p.M.package in
let sect = if p.M.section = "" then "faux" else p.M.section in
if
not (is_unchanged st unchanged nm) && source_version_match p
then begin
register_source p;
heidi_line lines (M.name_of_id nm) p.M.version p.M.architecture sect
end);
(String.concat "" (List.sort (fun l l' -> compare l l') !lines),
!sources_with_binaries)
let heidi_arch = Task.funct heidi_arch
let print_heidi solver id_of_source id_offsets l t u =
let ch = if !heidi_file = "-" then stdout else open_out !heidi_file in
let heidi_t = Timer.start () in
let source_has_binaries = M.PkgTbl.create 8192 in
Task.iter_ordered
(List.sort (fun (arch, _) (arch', _) -> compare arch arch') l)
(fun (arch, st) ->
heidi_arch st (extract_unchanged_bin
solver id_offsets arch (HornSolver.assignment solver)))
(fun (lines, sources_with_binaries) ->
output_string ch lines;
List.iter
(fun nm ->
if not (M.PkgTbl.mem source_has_binaries nm) then
M.PkgTbl.add source_has_binaries nm ())
sources_with_binaries);
let unchanged = HornSolver.assignment solver in
let is_unchanged src =
BitVect.test unchanged (M.PkgDenseTbl.find id_of_source src) in
let source_sect nm s =
if s.M.s_section = "" then "unknown" else s.M.s_section in
let lines = ref [] in
M.iter_sources
(fun s ->
let nm = s.M.s_name in
let sect = source_sect nm s in
if is_unchanged nm && M.PkgTbl.mem source_has_binaries nm then
heidi_line lines (M.name_of_id nm) s.M.s_version "source" sect)
t;
M.iter_sources
(fun s ->
let nm = s.M.s_name in
let sect = source_sect nm s in
if not (is_unchanged nm) && M.PkgTbl.mem source_has_binaries nm then
heidi_line lines (M.name_of_id nm) s.M.s_version "source" sect)
u;
List.iter (output_string ch) (List.sort compare !lines);
if !heidi_file <> "-" then close_out ch;
if debug_time () then
Format.eprintf "Writing Heidi file: %f@." (Timer.stop heidi_t)
(**** Migration analyze ****)
let rec collect_reasons solver get_name_arch print_package id =
match HornSolver.reason solver id with
None ->
let l = HornSolver.assumptions solver id in
L.s "Package " & L.format print_package id & L.s ": " &
print_reason' get_name_arch [|id|] (List.hd (List.rev l))
| Some (l, r) ->
let cur =
L.s "Package " & L.format print_package id & L.s ": " &
print_reason' get_name_arch l r
in
let len = Array.length l in
let rem sep =
L.list
(fun id ->
sep (collect_reasons solver get_name_arch print_package id))
(Array.to_list (Array.sub l 1 (len - 1)))
in
if len <= 2 then
(cur & rem (fun x -> L.p & x))
else
(cur & L.ul (rem L.li))
let rec collect_assumptions solver id =
match HornSolver.reason solver id with
None ->
IntSet.singleton id
| Some (l, _) ->
let s = ref IntSet.empty in
for i = 1 to Array.length l - 1 do
s := IntSet.union (collect_assumptions solver l.(i)) !s
done;
!s
let analyze_migration
?formatter uids solver id_of_source id_offsets t u l get_name_arch nm =
let id = M.PkgDenseTbl.find id_of_source (M.id_of_name nm) in
(* Name already checked *)
if debug_migration () then
Format.eprintf "%s (%d) : %b@."
nm id (BitVect.test (HornSolver.assignment solver) id);
let lst = ref [] in
let print_package f id =
let (name, arch) = get_name_arch id in
if arch = "source" then
Format.fprintf f "%s" name
else
Format.fprintf f "%s/%s" name arch
in
let output_hints () =
let source_bugs = StringTbl.create 17 in
List.iter
(fun (p, reason) ->
match reason with
More_bugs s ->
let (src, arch) = get_name_arch p in
if arch = "source" then StringTbl.add source_bugs src s
| _ ->
())
!lst;
let lst =
let b = Buffer.create 80 in
let to_b = Format.formatter_of_buffer b in
List.map
(fun (p, reason) ->
Buffer.clear b;
begin match reason with
Not_yet_built (nm, _, _, outdated) ->
if outdated then
Format.fprintf to_b "# remove outdated binary package %a"
print_package p
else
Format.fprintf to_b "# remove obsolete binary package %a"
print_package p
| Blocked (kind, _) ->
let (src, _) = get_name_arch p in
let vers =
(M.find_source_by_name u (M.id_of_name src)).M.s_version
in
Format.fprintf to_b "un%s %s/%a" kind src M.print_version vers
| Too_young (cur_ag, _) ->
let (src, _) = get_name_arch p in
let vers =
(M.find_source_by_name u (M.id_of_name src)).M.s_version
in
Format.fprintf to_b "age-days %d %s/%a"
cur_ag src M.print_version vers
| More_bugs s ->
let print_bugs =
Util.print_list (fun f s -> Format.fprintf f "#%s" s) ", "
in
let (nm, arch) = get_name_arch p in
if arch = "source" then begin
let vers =
(M.find_source_by_name u (M.id_of_name nm)).M.s_version
in
Format.fprintf to_b "# source package %s/%a: fix "
nm M.print_version vers;
if StringSet.cardinal s = 1 then
Format.fprintf to_b "bug %a"
print_bugs (StringSet.elements s)
else
Format.fprintf to_b "bugs %a"
print_bugs (StringSet.elements s)
end else begin
let s =
try
StringSet.diff s (StringTbl.find source_bugs nm)
with Not_found ->
StringTbl.add source_bugs nm s;
s
in
if not (StringSet.is_empty s) then begin
Format.fprintf to_b "# binary package %s: fix bugs %a"
nm print_bugs (StringSet.elements s)
end
end
| Conflict _ | Atomic | Source_not_propagated | No_binary
| Binary_not_added | Binary_not_removed | Unchanged ->
assert false
end;
Format.pp_print_flush to_b ();
Buffer.contents b)
(List.rev !lst)
in
let lst = List.filter (fun s -> s <> "") lst in
if !hint_file = "" then hint_file := "-";
generate_hints ?formatter
solver id_of_source id_offsets t u l lst (Some nm) None
in
let rec migrate () =
if BitVect.test (HornSolver.assignment solver) id then begin
let s = collect_assumptions solver id in
if IntSet.is_empty s then begin
L.print (new L.format_printer Format.std_formatter)
(L.s "Package " & L.s nm & L.s " cannot migrate:" & L.p &
L.ul ~prefix:" "
(L.li (collect_reasons solver get_name_arch print_package id)))
end else begin
if debug_migration () then
L.print (new L.format_printer Format.err_formatter)
(collect_reasons solver get_name_arch print_package id);
let p = IntSet.choose s in
let ass = HornSolver.assumptions solver p in
lst := List.rev_append (List.map (fun reason -> (p, reason)) ass) !lst;
if debug_migration () then begin
L.print (new L.format_printer Format.err_formatter)
(L.s "Need the following:" &
L.ul
(L.list
(fun r ->
L.li (L.format print_package p & L.s ": " &
print_reason' get_name_arch [|p|] r))
ass))
end;
HornSolver.retract_assumptions solver p;
migrate ()
end
end else begin
(* We need to check whether there are additional constraints to
consider. First clear the state: we may have removed some
constraints, so we may have to consider a larger set of
packages. *)
clear_upgrade_states l;
find_all_coinst_constraints solver id_offsets l;
if BitVect.test (HornSolver.assignment solver) id then
migrate ()
else begin
if formatter = None then begin
if !lst = [] then
Format.printf "The package %s can already migrate.@." nm
else
Format.printf "Successful:@."
end;
output_hints ()
end
end
in
migrate ();
save_rules uids
(**** Detailed explanations ****)
let package_changed solver id =
let reasons = HornSolver.direct_reasons solver id in
not (List.exists (fun (_, r) -> r = Unchanged) reasons)
let source_is_interesting solver id =
package_changed solver id
||
List.exists
(fun (lits, reason) ->
match reason with
| Binary_not_added | Binary_not_removed ->
package_changed solver lits.(1)
| _ ->
false)
(HornSolver.direct_reasons solver id)
(*
Levels
======
0 - yellow: co-installability issues only
1 - green: age/blocked issue; will eventually migrate
2 - orange: obsolete packages and bugs
3 - red: would make packages non-installable
*)
let footer () =
L.footer (L.s "Page generated by " &
L.anchor "http://coinst.irill.org/comigrate" (L.s "comigrate") &
L.s (" on " ^ Util.date () ^ "."))
let report_future_issues =
Task.funct
(fun st (unchanged, output, interesting_source) ->
let dist = M.new_pool () in
let is_preserved nm = is_unchanged st unchanged nm in
M.merge dist (fun p -> not (is_preserved p.M.package)) st.unstable;
M.merge dist (fun p -> is_preserved p.M.package) st.testing;
let format_package i =
let p = M.find_package_by_num dist (Package.index i) in
let nm = L.s (M.name_of_id p.M.package) in
let src = M.name_of_id (fst p.M.source) in
if Hashtbl.mem interesting_source src then
L.anchor ("p/" ^ src ^ ".html") nm
else
nm
in
let issues =
Upgrade.compute
?popcon_file:(if !popcon_file = "" then None else Some !popcon_file)
st.broken_sets st.testing dist format_package in
let d = Upgrade.explanations issues in
let ch = open_out output in
L.print (new L.html_printer ch ~stylesheet:"style.css" "Future issues")
(L.heading (L.s ("Possible future issues (on " ^ st.arch ^ ")")) &
(if Upgrade.has_issues issues then d else L.s "No issue found.") &
footer ());
close_out ch)
let generate_explanations
uids dates urgencies hints solver id_of_source source_of_id id_offsets
t u l get_name_arch deferred_constraints =
Util.make_directories (Filename.concat !explain_dir "foo");
svg := true; all_hints := true;
ignore (Lazy.force dot_process);
find_all_coinst_constraints solver id_offsets l;
let red = BitVect.copy (HornSolver.assignment solver) in
let obsolete = ref None in
let orange = ref None in
assert_deferred_constraints solver
~before:(fun _ k ->
if k = `Obsolete then
obsolete :=
Some (BitVect.copy (HornSolver.assignment solver));
if k = `Age then
orange := Some (BitVect.copy (HornSolver.assignment solver));
true)
~after:(fun p _ ->
if p then begin
discard_ambiguous_rules solver;
find_all_coinst_constraints solver id_offsets l
end)
deferred_constraints;
let obsolete = match !obsolete with Some a -> a | None -> assert false in
let orange = match !orange with Some a -> a | None -> assert false in
let green = HornSolver.assignment solver in
let hint_suggestions = Hashtbl.create 128 in
let count = ref 0 in
Array.iteri (fun id nm -> if not (BitVect.test red id) then incr count)
source_of_id;
let n = ref 0 in
let t0 = Unix.gettimeofday () in
Util.enable_messages true;
Array.iteri
(fun id nm ->
if not (BitVect.test red id && BitVect.test green id) then begin
incr n;
let p = float !n /. float !count in
let t1 = Unix.gettimeofday () in
Util.set_msg
(Format.sprintf "Generating hints: %s %.0f%% eta %.0fs"
(Util.progress_bar p) (p *. 100.)
((1. -. p) *. (t1 -. t0) /. p));
let b = Buffer.create 128 in
analyze_migration ~formatter:(Format.formatter_of_buffer b)
uids solver id_of_source id_offsets t u l get_name_arch
(M.name_of_id nm);
Hashtbl.add hint_suggestions id (Buffer.contents b);
retract_deferred_constraints solver deferred_constraints;
assert_deferred_constraints solver deferred_constraints
end)
source_of_id;
Util.set_msg "";
Util.enable_messages false;
let planned_migrations =
match
try Hashtbl.find options "NOBREAKALL_ARCHES" with Not_found -> []
with
arch :: _ when List.mem_assoc arch l ->
retract_deferred_constraints solver deferred_constraints;
assert_deferred_constraints solver
~before:(fun _ k -> k <> `Age && k <> `Blocked)
deferred_constraints;
find_all_coinst_constraints solver id_offsets l;
Some (arch, BitVect.copy (HornSolver.assignment solver))
| _ ->
None
in
check_coinstallability := true;
clear_upgrade_states l;
retract_deferred_constraints solver deferred_constraints;
find_all_coinst_constraints solver id_offsets l;
assert_deferred_constraints solver
~after:(fun p _ ->
if p then begin
discard_ambiguous_rules solver;
find_all_coinst_constraints solver id_offsets l
end)
deferred_constraints;
let level id =
if BitVect.test red id then 3 else
if BitVect.test orange id then 2 else
if BitVect.test green id then 1 else
0
in
let level_class l =
match l with
3 -> "unsat"
| 2 -> "issues"
| 1 -> "age"
| _ -> "coinst"
in
let interesting_source = Hashtbl.create 1024 in
let sources = ref [] in
let binaries = ref IntSet.empty in
Array.iteri
(fun id nm ->
let reasons = HornSolver.direct_reasons solver id in
if source_is_interesting solver id then begin
sources := (M.name_of_id nm, nm, id, reasons) :: !sources;
Hashtbl.add interesting_source (M.name_of_id nm) ();
List.iter
(fun (lits, reason) ->
match reason with
Binary_not_added | Binary_not_removed ->
let id = lits.(1) in
binaries := IntSet.add id !binaries;
List.iter
(fun (lits, reason) ->
match reason with
Conflict (s, s', _) ->
binaries :=
IntSet.union (IntSet.union s s') !binaries
| _ ->
())
(HornSolver.direct_reasons solver id)
| _ ->
())
reasons
end)
source_of_id;
begin match planned_migrations with
Some (arch, assignment) ->
Task.wait
(report_future_issues (List.assoc arch l)
(extract_unchanged_bin solver id_offsets arch assignment,
Filename.concat !explain_dir "future_issues.html",
interesting_source))
| None ->
()
end;
let name_of_binary = IntTbl.create 1024 in
Task.iteri l
(fun (arch, st) ->
let (first, offset, len) = StringTbl.find id_offsets arch in
let pos = first + offset in
let l =
IntSet.elements
(IntSet.filter (fun id -> id >= pos && id < pos + len) !binaries)
in
(arch, binary_names st (pos, l)))
(fun arch l ->
List.iter
(fun (id, nm, src) ->
IntTbl.add name_of_binary id (nm, arch, src))
l);
let print_source nm = L.anchor (nm ^ ".html") (L.code (L.s nm)) in
let print_binary _ id =
let (nm, arch, source_name) = IntTbl.find name_of_binary id in
let txt =
if nm = source_name then
L.code (L.s nm)
else
(L.code (L.s nm) & L.s " (from " & L.code (L.s source_name) & L.s ")")
in
if not (Hashtbl.mem interesting_source source_name) then (nm, txt) else
(nm, L.anchor (source_name ^ ".html") txt)
in
let package_list = open_out (Filename.concat !explain_dir "packages.js") in
Printf.fprintf package_list "set_package_list([";
List.iter
(fun (source_name, nm, id, reasons) ->
let binaries = ref StringSet.empty in
List.iter
(fun (lits, reason) ->
match reason with
Binary_not_added | Binary_not_removed ->
let id = lits.(1) in
let (nm, arch, source) = IntTbl.find name_of_binary id in
binaries := StringSet.add nm !binaries
| _ ->
())
reasons;
Printf.fprintf package_list "[\"%s\"" source_name;
StringSet.iter
(fun nm -> Printf.fprintf package_list ",\"%s\"" nm)
(StringSet.remove source_name !binaries);
Printf.fprintf package_list "],";
let about_bin (_, r) =
match r with
Binary_not_added | Binary_not_removed -> true
| _ -> false
in
let src_reasons =
begin try
let p = M.find_source_by_name u nm in
if same_source_version t u nm then L.emp else
let (cur_ag, req_ag) =
compute_ages dates urgencies hints
nm p.M.s_version (source_version t nm)
in
if cur_ag < req_ag then L.emp else
L.dt (L.s "The package is " & L.i cur_ag &
L.s " days old (needed " & L.i req_ag & L.s " days).")
with Not_found ->
L.emp
end
&
L.list
(fun (_, r) ->
match r with
| Blocked (kind, who) ->
L.dt
(L.span ~clss:"blocked"
(L.s "Left unchanged due to " & L.s kind &
L.s " request") &
L.s " by " & L.s who & L.s ".")
| Too_young (cur_ag, req_ag) ->
L.dt
(L.span ~clss:"age"
(L.s "Only " & L.i cur_ag & L.s " days old") &
L.s "; must be " & L.i req_ag & L.s " days old to go in.")
| More_bugs s ->
L.dt
(L.span ~clss:"bugs" (L.s "The package has new bugs") &
L.s ": " &
L.seq ", "
(fun s -> L.anchor (bug_url s) (L.s "#" & L.s s))
(StringSet.elements s) &
L.s ".")
| _ ->
L.emp)
reasons
in
let binaries =
reasons
>> List.filter
(fun r -> interesting_reason solver r && about_bin r)
>> List.map (fun (lits, r) -> (lits.(1), r))
>> List.sort (Util.compare_pair compare compare)
>> Util.group compare
>> List.map
(fun (id, l) ->
let (name, arch, _) = IntTbl.find name_of_binary id in
let is_removal =
List.for_all (fun r -> r = Binary_not_removed) l in
(name, (arch, (id, is_removal))))
>> List.sort
(Util.compare_pair compare (Util.compare_pair compare compare))
in
let involved_archs =
List.fold_left
(fun archs (_, (arch, _)) -> StringSet.add arch archs)
StringSet.empty binaries
in
let binnmu_message =
if List.exists (fun (_, r) -> r = Unchanged) reasons then begin
L.s "BinNMUs on " &
L.seq ", " L.s (StringSet.elements involved_archs) &
L.s "."
end else
L.emp
in
let not_yet_built outdated =
binaries
>>
List.filter
(fun (_, (_, (id, _))) ->
List.exists
(fun (_, r) ->
match r with
Not_yet_built (_, _, _, outdated') ->
outdated = outdated'
| _ ->
false)
(HornSolver.direct_reasons solver id))
>> List.map (fun (name, (arch, _)) -> (name, arch))
>> List.sort (Util.compare_pair compare compare)
>> Util.group compare
>> List.map (fun (name, l) -> (l, name))
>> List.sort (Util.compare_pair (Util.compare_list compare) compare)
>> Util.group (Util.compare_list compare)
in
let build_reasons outdated =
L.list
(fun (al, bl) ->
let heading =
match outdated, List.length bl with
false, 1 -> "A binary package is obsolete"
| false, _ -> "Some binary packages are obsolete"
| true, 1 -> "A binary package has not yet been rebuilt"
| true, _ -> "Some binary packages have not yet been rebuilt"
in
L.dt ~clss:"collapsible"
(L.span ~clss:(if outdated then "outdated" else "obsolete")
(L.s heading) &
L.s " on " &
L.seq ", "
(fun arch ->
L.anchor (build_log_url source_name arch)
(L.s arch)) al &
L.s ".") &
L.dd (L.seq ", " (fun nm -> L.code (L.s nm)) bl & L.s "."))
(not_yet_built outdated)
in
let with_new_bugs =
Util.group compare
(List.flatten
(List.map
(fun (nm, (_, (id, _))) ->
List.flatten
(List.map
(fun (_, reason) ->
match reason with
More_bugs s -> [(nm, s)]
| _ -> [])
(HornSolver.direct_reasons solver id)))
binaries))
in
let bug_reasons =
L.list
(fun (nm', s) ->
let s = List.hd s in (* Same bugs on all archs. *)
if nm' <> source_name then
L.dt (L.span ~clss:"bugs"
(L.s "Binary package " & L.code (L.s nm') &
L.s " has new bugs") &
L.s ": " &
L.seq ", "
(fun s -> L.anchor (bug_url s) (L.s "#" & L.s s))
(StringSet.elements s) &
L.s ".")
else
L.emp)
with_new_bugs
in
let compare_conflicts (_, _, p1) (_, _, p2) =
compare p1.Upgrade_common.p_explain p2.Upgrade_common.p_explain
in
let binaries =
binaries >>
List.map
(fun (nm, (arch, (id, is_removal))) ->
HornSolver.direct_reasons solver id >>
List.map
(fun (_, r) ->
match r with
Conflict (s, s', problem) ->
let srcs =
IntSet.fold
(fun id' srcs ->
let (_, _, source) =
IntTbl.find name_of_binary id' in
StringSet.add source srcs)
s StringSet.empty
in
[(srcs, (s, s', problem))]
| _ ->
[]) >>
List.flatten >>
List.sort (Util.compare_pair StringSet.compare
(fun _ _ -> 0)) >>
Util.group StringSet.compare >>
List.map
(fun (srcs, reasons) ->
(srcs, (nm, (reasons, (arch, is_removal)))))) >>
List.flatten >>
List.sort (Util.compare_pair StringSet.compare
(fun _ _ -> 0)) >>
Util.group StringSet.compare >>
List.map
(fun (srcs, l) ->
(srcs,
l >>
List.sort
(Util.compare_pair compare
(Util.compare_pair
(Util.compare_list compare_conflicts)
(Util.compare_pair compare (fun _ _ -> 0)))) >>
Util.group compare >>
List.map
(fun (nm, l) ->
l >>
Util.group (Util.compare_list compare_conflicts) >>
List.map (fun (reasons, l) -> (nm, l, reasons))) >>
List.flatten))
in
let bin_reasons =
let format_reason collapsible (s, s', problem) =
let lvl =
if IntSet.cardinal s' > 1 then 0 else
IntSet.fold (fun id l -> min l (level id)) s 3
in
L.dt ?clss:(if collapsible then Some "collapsible" else None)
(begin match IntSet.cardinal s with
0 -> L.emp
| 1 -> L.span ~clss:(level_class lvl)
(L.s "Needs migration of binary package " &
snd (print_binary false (IntSet.choose s))) &
L.s ". "
| _ -> L.span ~clss:(level_class lvl)
(L.s "Needs migration of one of the binary packages " &
print_binaries "or" (print_binary false) s) &
L.s ". "
end
&
L.s "Would " &
(if IntSet.cardinal s > 0 then L.s "otherwise " else L.emp)
&
L.s "break " &
if IntSet.cardinal s' = 1 then begin
L.s "package " &
snd (print_binary false (IntSet.choose s')) & L.s "."
end else begin
L.s "co-installability of packages " &
print_binaries "and" (print_binary false) s' & L.s "."
end)
&
L.dd (L.div ~clss:"problem" (print_explanation problem))
in
L.list
(fun (srcs, l) ->
let lvl =
List.fold_left
(fun l (_, _, reasons) ->
max l
(List.fold_left
(fun l (s, s', _) ->
max l (if IntSet.cardinal s' > 1 then 0 else
IntSet.fold
(fun id l -> min l (level id)) s 3))
0 reasons))
0 l
in
L.dt ~clss:"collapsible"
(match StringSet.elements srcs with
[] ->
L.span ~clss:(level_class lvl)
(L.s "Some dependencies would become unsatisfiable") &
L.s "."
| [nm] ->
L.span ~clss:(level_class lvl)
(L.s "Needs migration of source package " &
print_source nm) &
L.s "."
| srcs ->
L.span ~clss:(level_class lvl)
(L.s "Needs migration of one of the source packages " &
L.seq ", " print_source srcs) &
L.s ".")
&
L.dd (L.dl ~clss:"explanation"
(L.list
(fun (nm, archs_and_removals, reasons) ->
let is_removal =
List.for_all snd archs_and_removals in
let archs = List.map fst archs_and_removals in
let level =
List.fold_left
(fun l (s, s', _) ->
max l (if IntSet.cardinal s' > 1 then 0 else
IntSet.fold
(fun id l -> min l (level id)) s 3))
0 reasons
in
let reasons =
L.list (format_reason (List.length reasons > 1))
reasons in
L.dt ?clss:(if List.length l = 1 then None else
Some "collapsible")
(L.span ~clss:(level_class level)
(if is_removal then
L.s "Out of date binary package " &
L.code (L.s nm) &
L.s " cannot be removed"
else
L.s "Binary package " & L.code (L.s nm) &
L.s " cannot migrate" &
(if StringSet.is_empty srcs then L.emp else
L.s " in isolation"))
&
(if
List.length archs > 4 &&
List.sort compare archs =
StringSet.elements involved_archs
then
L.s " (on any architecture)."
else
L.s
" (on " & L.seq ", " L.s archs & L.s ").")) &
L.dd (L.dl ~clss:"explanation" reasons))
l)))
binaries
in
let versions nm =
let version dist nm =
try
let p = M.find_source_by_name dist nm in
L.format M.print_version p.M.s_version
with Not_found ->
L.s "-"
in
if
List.exists (fun (_, r) -> r = Unchanged)
(HornSolver.direct_reasons solver id)
then
(L.s "version " & version t nm)
else
(L.s "from " & version t nm & L.s " to " & version u nm)
in
let file =
Filename.concat (Filename.concat !explain_dir "p")
(source_name ^ ".html") in
Util.make_directories file;
let ch = open_out file in
L.print (new L.html_printer ch ~stylesheet:"../style.css"
~scripts:["../jquery.js"; "../script.js"]
("Source package " ^ source_name))
(L.heading
(L.s "Source package " &
L.anchor (pts_url source_name) (L.s source_name) &
L.s " (" & versions nm & L.s ")")
&
binnmu_message &
L.dl ~clss:"explanation"
(src_reasons & build_reasons false & build_reasons true &
bug_reasons & bin_reasons)
&
(try
let hints = Hashtbl.find hint_suggestions id in
L.section
(L.heading (L.s "Suggested hints") & L.pre (L.s hints))
with Not_found ->
L.emp)
&
footer ());
close_out ch)
!sources;
Printf.fprintf package_list "]);";
close_out package_list;
let ready = ref [] in
Array.iteri
(fun id nm ->
if not (BitVect.test green id) then ready := M.name_of_id nm :: !ready)
source_of_id;
let ch = open_out (Filename.concat !explain_dir "ready.html") in
L.print (new L.html_printer ch "")
(L.section ~clss:"ready"
(L.heading
(L.s ("Packages ready to migrate (as of " ^ Util.date () ^ ")"))
&
L.ul
(L.list
(fun nm ->
L.li (L.anchor ("p/" ^ nm ^ ".html") (L.code (L.s nm))))
(List.sort compare !ready))));
close_out ch;
let lst = ref [] in
Array.iteri
(fun id nm ->
if
BitVect.test orange id &&
not (BitVect.test obsolete id)
then
lst := M.name_of_id nm :: !lst)
source_of_id;
let ch = open_out (Filename.concat !explain_dir "obsolete.html") in
L.print (new L.html_printer ch "")
(L.section ~clss:"obsolete"
(L.heading
(L.s ("Packages blocked by obsolete binaries (as of " ^
Util.date () ^ ")"))
&
L.ul
(L.list
(fun nm ->
L.li (L.anchor ("p/" ^ nm ^ ".html") (L.code (L.s nm))))
(List.sort compare !lst))));
close_out ch
(**** Main part of the program ****)
let print_equivocal_packages uids solver id_of_source id_offsets t u l =
assert !check_coinstallability;
find_all_coinst_constraints solver id_offsets l;
let coinst_unchanged = BitVect.copy (HornSolver.assignment solver) in
switch_to_installability solver;
clear_upgrade_states l;
find_all_coinst_constraints solver id_offsets l;
save_rules uids;
let inst_unchanged = HornSolver.assignment solver in
assert (BitVect.implies inst_unchanged coinst_unchanged);
let equivocal_pkgs =
BitVect.(lor) (BitVect.lnot coinst_unchanged) inst_unchanged in
if debug_outcome () then
output_outcome solver id_of_source id_offsets t u l equivocal_pkgs;
if !hint_file = "" then hint_file := "-";
generate_hints solver id_of_source id_offsets t u l
["# equivocal packages:"] None (Some equivocal_pkgs)
let f () =
Util.enable_messages false;
filter_architectures ();
let (dates, urgencies, hints, t, u, testing_bugs, unstable_bugs, l,
id_of_source, source_of_id, src_uid) as info =
load_all_files () in
if !equivocal then check_coinstallability := true;
if !explain_dir <> "" then check_coinstallability := false;
begin match !to_migrate with
Some p ->
if not (M.PkgDenseTbl.mem id_of_source (M.add_name p)) then begin
Format.eprintf "Unknown package %s@." p;
exit 1
end
| None ->
()
end;
let (uids, solver, deferred_constraints, id_offsets, get_name_arch) =
initial_constraints info in
if !equivocal then
print_equivocal_packages uids solver id_of_source id_offsets t u l
else if !explain_dir <> "" then
generate_explanations
uids dates urgencies hints solver id_of_source source_of_id id_offsets
t u l get_name_arch deferred_constraints
else begin match !to_migrate with
Some p ->
analyze_migration
uids solver id_of_source id_offsets t u l get_name_arch p
| None ->
find_all_coinst_constraints solver id_offsets l;
assert_deferred_constraints solver
~after:(fun p _ ->
if p then begin
discard_ambiguous_rules solver;
find_all_coinst_constraints solver id_offsets l
end)
deferred_constraints;
save_rules uids;
if debug_outcome () then
output_outcome solver id_of_source id_offsets t u l
(HornSolver.assignment solver);
if compute_hints () then
generate_hints solver id_of_source id_offsets t u l [] None None;
if !heidi_file <> "" then
print_heidi solver id_of_source id_offsets l t u;
if !excuse_file <> "" then
output_reasons l dates urgencies hints
solver source_of_id id_offsets !excuse_file t u
end;
List.iter (fun (_, t) -> Task.kill t) l
(**** Parsing of configuration settings ****)
let read_conf f =
let ch = open_in f in
begin try
while true do
let l = input_line ch in
let l = Str.split whitespaces l in
match l with
[] -> ()
| s :: _ when s.[0] = '#' -> ()
| k :: "=" :: l -> Hashtbl.replace options k l
| _ -> assert false
done
with End_of_file -> () end;
close_in ch;
archs := (try Hashtbl.find options "ARCHITECTURES" with Not_found -> !archs);
smooth_updates :=
(try
Hashtbl.find options "SMOOTH_UPDATES"
with Not_found ->
!smooth_updates)
let comma_re = Str.regexp "[ \t]*,[ \t]*"
let _ =
let spec =
Arg.align
["--update",
Arg.Unit (fun () -> update_data := true),
" Update data";
"--input",
Arg.String (fun d -> dir := d),
"DIR Select directory containing britney data";
"--arches",
Arg.String (fun a -> archs := Str.split comma_re (Util.trim a)),
"LST Comma-separated list of arches to consider (default to all)";
"--hints",
Arg.String (fun f -> hint_file := f),
"FILE Output hints to FILE";
"--all-hints",
Arg.Unit (fun () -> all_hints := true),
" Show all hints (including single package ones)";
"--heidi",
Arg.String (fun f -> heidi_file := f),
"FILE Output Heidi results to FILE";
"--excuses",
Arg.String (fun f -> excuse_file := f),
"FILE Output excuses to FILE";
"--explain",
Arg.String (fun d -> explain_dir := d),
"DIR Output detailed explanations to DIR";
"--svg",
Arg.Unit (fun () -> svg := true),
" Include conflict graphs (in SVG) in excuse output";
"--migrate",
Arg.String (fun p -> to_migrate := Some p),
"PKG Explain what it takes to migrate PKG";
"--equivocal",
Arg.Unit (fun () -> equivocal := true),
" List packages whose behavior depends on the migration policy";
"--offset",
Arg.Int (fun n -> offset := n),
"N Move N days into the future";
"--inst",
Arg.Unit (fun () -> check_coinstallability := false),
" Check for single package installability only";
"--remove",
Arg.String (fun p -> to_remove := p :: !to_remove),
"PKG Attempt to remove the source package PKG";
"--break",
Arg.String (Upgrade_common.allow_broken_sets broken_sets),
"SETS Allows sets of packages to be broken by the migration";
"-c",
Arg.String read_conf,
"FILE Read britney config FILE";
"--config",
Arg.String read_conf,
"FILE Read britney config FILE";
"--no-cache",
Arg.Unit (fun () -> Cache.set_disabled true),
" Disable on-disk caching";
"--proc",
Arg.Int Task.set_processor_count,
"N Provide number of processors (use 1 to disable concurrency)";
"--debug",
Arg.String Debug.set,
"NAME Activate debug option NAME";
"--popcon",
Arg.String (fun s -> popcon_file := s),
"FILE Use popcon data from FILE";
"--source",
Arg.String (fun s -> Update_data.src := s),
"URL Uses URL as a source for package information";
"--control-files",
Arg.Unit (fun () -> ()),
" Currently ignored";
"-v",
Arg.Unit (fun () -> ()),
" Currently ignored"]
in
let msg =
"Usage: " ^ Sys.argv.(0) ^ " OPTIONS\n\
Computes which packages can migrate from sid to testing.\n\
Takes as input either a britney data directory (option --input)\n\
or a britney config file (option -c).\n\
\n\
Options:"
in
Arg.parse spec (fun p -> ()) msg;
if
!dir = "" &&
not (Hashtbl.mem options "TESTING" && Hashtbl.mem options "UNSTABLE")
then begin
Arg.usage spec msg;
Format.eprintf
"@.Please use '--input' or '-c' option to indicate \
the location of britney data.@.";
exit 1
end;
let opts =
[!to_migrate <> None, "--migrate";
!excuse_file <> "", "--excuse";
!explain_dir <> "", "--explain";
!equivocal, "--equivocal";
!update_data, "--update"]
in
begin match List.filter (fun (b, _) -> b) opts with
(_, o1) :: (_, o2) :: _ ->
Format.eprintf "Incompatible options %s and %s.@." o1 o2;
exit 1
| _ ->
()
end;
if
!heidi_file = "" && !hint_file = "" && !excuse_file = "" &&
!explain_dir = "" && !to_migrate = None && not !equivocal && not !update_data
then begin
heidi_file := get_option "HEIDI_OUTPUT" !heidi_file;
if !heidi_file = "" && not (debug_hints () || debug_outcome ()) then
Format.eprintf "Warning: no output option has been provided.@.";
end;
if !heidi_file <> "" then Util.make_directories !heidi_file;
if !update_data then begin
Update_data.f
(testing ()) (unstable ()) !archs
(Filename.concat (unstable ()) "Hints") (hint_files ())
end else
f ()
coinst-1.9.3/repository.ml 0000644 0001750 0001750 00000017717 12657630652 014563 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module type S = sig
type pool
module Package : sig
type t
val compare : t -> t -> int
val print : pool -> Format.formatter -> t -> unit
val print_name : pool -> Format.formatter -> t -> unit
val index : t -> int
val of_index : int -> t
val of_index_list : int list -> t list
end
module PSet : Set.S with type elt = Package.t
module PMap : Map.S with type key = Package.t
val pset_indices : PSet.t -> Util.IntSet.t
module PTbl : sig
type 'a t
val create : pool -> 'a -> 'a t
val init : pool -> (Package.t -> 'a) -> 'a t
val get : 'a t -> Package.t -> 'a
val set : 'a t -> Package.t -> 'a -> unit
val iteri : (Package.t -> 'a -> unit) -> 'a t -> unit
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (Package.t -> 'a -> 'b) -> 'a t -> 'b t
val copy : 'a t -> 'a t
end
module type DISJ = sig
type t
val print : ?compact:bool -> pool -> Format.formatter -> t -> unit
val implies : t -> t -> bool
val equiv : t -> t -> bool
val lit : Package.t -> t
val lit_disj : Package.t list -> t
val _false : t
val disj : t -> t -> t
end
module Disj : sig
include DISJ
val iter : t -> (Package.t -> unit) -> unit
val fold : (Package.t -> 'a -> 'a) -> t -> 'a -> 'a
val cut : t -> Package.t -> t -> t
val for_all : (Package.t -> bool) -> t -> bool
val exists : (Package.t -> bool) -> t -> bool
val filter : (Package.t -> bool) -> t -> t
val compare : t -> t -> int
val implies1 : Package.t -> t -> bool
val to_lit : t -> Package.t option
val to_lits : t -> PSet.t
val of_lits : PSet.t -> t
val diff : t -> t -> t
val disj1 : Package.t -> t -> t
val cardinal : t -> int
module Set : Set.S with type elt = t
end
module Formula : sig
include DISJ
val _true : t
val conj : t -> t -> t
val conjl : t list -> t
val implies1 : t -> Disj.t -> bool
val iter : t -> (Disj.t -> unit) -> unit
val of_disj : Disj.t -> t
val fold : (Disj.t -> 'a -> 'a) -> t -> 'a -> 'a
val filter : (Disj.t -> bool) -> t -> t
val exists : (Disj.t -> bool) -> t -> bool
val normalize : t -> t
end
type dependencies = Formula.t PTbl.t
module Conflict : sig
type t
val create : pool -> t
val check : t -> Package.t -> Package.t -> bool
val add : t -> Package.t -> Package.t -> unit
val remove : t -> Package.t -> Package.t -> unit
val iter : t -> (Package.t -> Package.t -> unit) -> unit
val copy : t -> t
val has : t -> Package.t -> bool
val of_package : t -> Package.t -> PSet.t
val iter_on_packages : t -> (Package.t -> PSet.t -> unit) -> unit
val exists : t -> (Package.t -> bool) -> Package.t -> bool
val for_all : t -> (Package.t -> bool) -> Package.t -> bool
end
end
module F (M : Api.S) = struct
type pool = M.pool
module Package = struct
type t = int
let compare (x : int) y = compare x y
let print = M.print_pack
let print_name = M.print_pack_name
let index p = p
let of_index p = p
let of_index_list p = p
end
module PSet = Util.IntSet
let print_set ch pr sep l = Util.print_list ch pr sep (PSet.elements l)
let pset_of_lst l = List.fold_left (fun s x -> PSet.add x s) PSet.empty l
let pset_map f s = pset_of_lst (List.map f (PSet.elements s))
let pset_indices s = s
module PMap = Map.Make (Package)
module PTbl = struct
type 'a t = 'a array
let create pool v = Array.make (M.pool_size pool) v
let init pool f =
Array.init (M.pool_size pool) (fun i -> f (Package.of_index i))
let get a i = a.(Package.index i)
let set a i v = a.(Package.index i) <- v
let iteri f a = Array.iteri (fun i v -> f (Package.of_index i) v) a
let map = Array.map
let mapi f a = Array.mapi (fun i v -> f (Package.of_index i) v) a
let copy = Array.copy
end
module type DISJ = sig
type t
val print : ?compact:bool -> pool -> Format.formatter -> t -> unit
val implies : t -> t -> bool
val equiv : t -> t -> bool
val lit : Package.t -> t
val lit_disj : Package.t list -> t
val _false : t
val disj : t -> t -> t
end
module Disj = struct
type t = PSet.t
let print ?(compact=false) pool ch l =
if PSet.is_empty l then
Format.fprintf ch "MISSING"
else
print_set
(if compact then Package.print_name pool else Package.print pool)
" | " ch l
let implies = PSet.subset
let equiv = PSet.equal
let lit = PSet.singleton
let lit_disj l = List.fold_right PSet.add l PSet.empty
let _false = PSet.empty
let disj = PSet.union
let iter s f = PSet.iter f s
let cut d p d' = assert (PSet.mem p d); PSet.union (PSet.remove p d) d'
let fold = PSet.fold
let for_all = PSet.for_all
let exists = PSet.exists
let implies1 = PSet.mem
let to_lit l = if PSet.cardinal l = 1 then Some (PSet.choose l) else None
let to_lits l = l
let of_lits l = l
let filter = PSet.filter
let normalize d = pset_map (fun i -> i) d
let compare = PSet.compare
let diff = PSet.diff
let cardinal = PSet.cardinal
let disj1 = PSet.add
module Set = Set.Make (struct type t = PSet.t let compare = compare end)
end
module Formula = struct
type t = Disj.t list
let print ?compact pool ch d =
Util.print_list (Disj.print ?compact pool) ", " ch d
let of_disj d = [d]
let lit p = of_disj (Disj.lit p)
let lit_disj l = of_disj (Disj.lit_disj l)
let implies1 l1 y = List.exists (fun x -> Disj.implies x y) l1
let implies l1 l2 =
List.for_all (fun y -> implies1 l1 y) l2
let equiv l1 l2 =
List.for_all (fun y -> List.exists (fun x -> Disj.equiv x y) l1) l2 &&
List.for_all (fun y -> List.exists (fun x -> Disj.equiv x y) l2) l1
let _true = []
let conj1 l x =
if implies1 l x then l else
x :: List.filter (fun y -> not (Disj.implies x y)) l
let conj l1 l2 = List.fold_left conj1 l1 l2
let conjl l = List.fold_left conj _true l
let _false = of_disj (Disj._false)
let disj l1 l2 =
List.fold_left
(fun l x -> List.fold_left (fun l y -> conj1 l (Disj.disj x y)) l l2)
_true l1
let iter l f = List.iter f l
let fold f l = List.fold_right f l
let filter = List.filter
let exists = List.exists
let normalize f =
let f = List.map Disj.normalize f in
let f = List.sort PSet.compare f in
f
end
type dependencies = Formula.t PTbl.t
module Conflict = struct
type t = PSet.t PTbl.t
let create pool = PTbl.create pool PSet.empty
let has c p1 = not (PSet.is_empty (PTbl.get c p1))
let check c p1 p2 = PSet.mem p1 (PTbl.get c p2)
let add c p1 p2 =
PTbl.set c p1 (PSet.add p2 (PTbl.get c p1));
PTbl.set c p2 (PSet.add p1 (PTbl.get c p2))
let remove c p1 p2 =
PTbl.set c p1 (PSet.remove p2 (PTbl.get c p1));
PTbl.set c p2 (PSet.remove p1 (PTbl.get c p2))
let iter c f =
PTbl.iteri (fun i s -> PSet.iter (fun j -> if i < j then f i j) s) c
let iter_on_packages c f = PTbl.iteri f c
let of_package = PTbl.get
let copy = PTbl.copy
let exists c f p = PSet.exists f (PTbl.get c p)
let for_all c f p = PSet.for_all f (PTbl.get c p)
end
end
coinst-1.9.3/conflicts.ml 0000644 0001750 0001750 00000011354 12657630652 014317 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
(*
Data Reduction and Exact Algorithms for Clique Cover
Jens Gramm, Jiong Guo, Falk Huffner, and Rolf Niedermeier
XXX This implementation should be made more robust: at the moment, if we fail
to decompose the conflicts into obvious maximal cliques, we do not try to find
any other clique...
*)
module F (R : Repository.S) = struct
open R
module Quotient = Quotient.F(R)
module Pair (X : Set.OrderedType) (Y : Set.OrderedType) =
struct
type t = X.t * Y.t
let compare (x, y) (x', y') =
let c = X.compare x x' in if c = 0 then Y.compare y y' else c
end
module PPairMap = Map.Make (Pair (Package) (Package))
let print_clique quotient s =
Format.eprintf "Clique:";
PSet.iter
(fun p -> Format.eprintf " %a" (Quotient.print_class quotient) p) s;
Format.eprintf "@."
let f quotient confl =
let l = ref [] in
let common = ref PPairMap.empty in
Conflict.iter confl
(fun p q ->
let c =
PSet.inter
(Conflict.of_package confl p)
(Conflict.of_package confl q)
in
let n = ref 0 in
Conflict.iter confl
(fun p' q' -> if PSet.mem p' c && PSet.mem q' c then incr n);
assert (p < q);
common := PPairMap.add (p, q) (c, PSet.cardinal c, !n) !common);
let covered = Conflict.create (Quotient.pool quotient) in
let removed = PTbl.create (Quotient.pool quotient) false in
let changed = ref false in
while
changed := false;
(*
prerr_endline "AAAAA";
*)
PPairMap.iter
(fun (p, q) (c, i, n) ->
let m = (i * (i - 1)) / 2 in
if m = n && not (Conflict.check covered p q) then begin
(*
Format.eprintf "Rule 2: %a # %a : %d -- %d / %d %b@."
(Quotient.print_class quotient) p (Quotient.print_class quotient) q
i m n (m = n);
*)
let c = PSet.add p (PSet.add q c) in
(*
print_clique quotient c;
*)
l := c :: !l;
changed := true;
PSet.iter
(fun p ->
PSet.iter
(fun q ->
if p < q then begin
Conflict.add covered p q;
common := PPairMap.remove (p, q) !common
end)
c)
c;
PSet.iter
(fun p ->
let neigh = Conflict.of_package confl p in
if
not (PTbl.get removed p) &&
PSet.for_all (fun q -> Conflict.check covered p q) neigh
then begin
PTbl.set removed p true;
Conflict.iter confl
(fun p' q' ->
if PSet.mem p' neigh && PSet.mem q' neigh then begin
(*
Format.eprintf "%a => %a %a@."
(Quotient.print_class quotient) p (Quotient.print_class quotient) p' (Quotient.print_class quotient) q';
*)
try
let (d, i, n) = PPairMap.find (p', q') !common in
(*
Format.eprintf "-@.";
*)
assert (PSet.mem p d);
let d = PSet.remove p d in
let n = n - PSet.cardinal (PSet.inter neigh d) in
(*
Format.eprintf "%d@." i;
*)
assert (n >= 0);
if i = 0 then
common := PPairMap.remove (p', q') !common
else
common :=
PPairMap.add (p', q')
(d, i - 1, n) !common
with Not_found ->
()
end)
end)
c
end)
!common;
!changed
do () done;
PPairMap.iter
(fun (p, q) (c, i, n) ->
let m = (i * (i - 1)) / 2 in
Format.eprintf "Remaining edge: %a # %a : %d -- %d / %d %b@."
(Quotient.print_class quotient) p (Quotient.print_class quotient) q
i m n (m = n);
l := PSet.add p (PSet.singleton q) :: !l)
!common;
!l
end
coinst-1.9.3/layout.ml 0000644 0001750 0001750 00000030336 12657630652 013651 0 ustar mehdi mehdi
class type printer = object
method start_doc : unit -> unit
method end_doc : unit -> unit
method text : string -> unit
method start_code : unit -> unit
method end_code : unit -> unit
method change_p : unit -> unit
method start_ul : string -> unit
method li : unit -> unit
method end_ul : unit -> unit
method start_a : string -> unit
method end_a : unit -> unit
method start_dl : ?clss:string -> unit -> unit
method dt : ?clss:string -> string option -> unit
method dd : unit -> unit
method end_dl : unit -> unit
method start_div : ?clss:string -> unit -> unit
method end_div : unit -> unit
method start_span : ?clss:string -> unit -> unit
method end_span : unit -> unit
method start_pre : ?clss:string -> unit -> unit
method end_pre : unit -> unit
method start_heading : unit -> unit
method end_heading : unit -> unit
method start_section : ?clss:string -> unit -> unit
method end_section : unit -> unit
method start_footer : unit -> unit
method end_footer : unit -> unit
method raw_html : (unit -> string) -> unit
end
type +'a t = printer -> unit
let (&) f1 f2 p = f1 p; f2 p
let emp p = ()
(****)
type +'a flow
type +'a phras
type 'a phrasing = 'a phras flow
let s s p = p#text s
let i i p = p#text (string_of_int i)
let rec seq sep f l p =
match l with
[] -> ()
| [v] -> f v p
| v :: r -> f v p; s sep p; seq sep f r p
let rec seq2 sep sep' f l p =
match l with
[] -> ()
| [v] -> f v p
| [v; v'] -> f v p; s sep' p; f v' p
| v :: r -> f v p; s sep p; seq2 sep sep' f r p
let buf = Buffer.create 16
let formatter = Format.formatter_of_buffer buf
let format f v p =
Buffer.clear buf; f formatter v; Format.pp_print_flush formatter ();
p#text (Buffer.contents buf)
let code contents p = p#start_code (); contents p; p#end_code ()
type in_anchor
type outside_anchor
let anchor link contents p = p#start_a link; contents p; p#end_a ()
let p pr = pr#change_p ()
let div ?clss contents p = p#start_div ?clss (); contents p; p#end_div ()
let span ?clss contents p = p#start_span ?clss (); contents p; p#end_span ()
let pre ?clss contents p = p#start_pre ?clss (); contents p; p#end_pre ()
let heading contents p = p#start_heading (); contents p; p#end_heading ()
let section ?clss contents p =
p#start_section ?clss (); contents p; p#end_section ()
let footer contents p = p#start_footer (); contents p; p#end_footer ()
let raw_html f pr = pr#raw_html f
(****)
type +'a lst
let rec list f l p = List.iter (fun v -> f v p) l
type u
let ul ?(prefix="* ") lst p = p#start_ul prefix; lst p; p#end_ul ()
let li contents p = p#li (); contents p
type d
let dl ?clss lst p = p#start_dl ?clss (); lst p; p#end_dl ()
let dli ?id key desc (p : #printer) = p#dt id; key p; p#dd (); desc p
let dt ?clss key p = p#dt ?clss None; key p
let dd desc p = p#dd (); desc p
(****)
let print p doc = p#start_doc (); doc p; p#end_doc ()
let html_escape s =
let s = Bytes.of_string s in
let l = Bytes.length s in
let n = ref 0 in
for i = 0 to l - 1 do
match Bytes.unsafe_get s i with
'<' | '>' -> n := !n + 3
| '&' -> n := !n + 4
| '\'' -> n := !n + 5
| _ -> ()
done;
if !n = 0 then Bytes.to_string s else
let s' = Bytes.create (l + !n) in
n := 0;
for i = 0 to l - 1 do
match Bytes.unsafe_get s i with
'<' ->
Bytes.unsafe_set s' !n '&'; incr n;
Bytes.unsafe_set s' !n 'l'; incr n;
Bytes.unsafe_set s' !n 't'; incr n;
Bytes.unsafe_set s' !n ';'; incr n
| '>' ->
Bytes.unsafe_set s' !n '&'; incr n;
Bytes.unsafe_set s' !n 'g'; incr n;
Bytes.unsafe_set s' !n 't'; incr n;
Bytes.unsafe_set s' !n ';'; incr n
| '&' ->
Bytes.unsafe_set s' !n '&'; incr n;
Bytes.unsafe_set s' !n 'a'; incr n;
Bytes.unsafe_set s' !n 'm'; incr n;
Bytes.unsafe_set s' !n 'p'; incr n;
Bytes.unsafe_set s' !n ';'; incr n
| '\'' ->
Bytes.unsafe_set s' !n '&'; incr n;
Bytes.unsafe_set s' !n 'a'; incr n;
Bytes.unsafe_set s' !n 'p'; incr n;
Bytes.unsafe_set s' !n 'o'; incr n;
Bytes.unsafe_set s' !n 's'; incr n;
Bytes.unsafe_set s' !n ';'; incr n
| c ->
Bytes.unsafe_set s' !n c; incr n
done;
Bytes.to_string s'
class html_printer ch ?stylesheet ?(style="") ?(scripts=[]) title : printer =
object (self)
val mutable in_p = false
val mutable need_break = false
val mutable at_list_start = None
method private break () = if need_break then output_char ch '\n'
method start_doc () =
output_string ch
"\n\n
";
output_string ch (html_escape title);
output_string ch "\n";
begin match stylesheet with
Some url ->
output_string ch "\n";
| None ->
()
end;
if style <> "" then begin
output_string ch "\n"
end;
List.iter
(fun url ->
output_string ch "\n")
scripts
method end_doc () = ()
method text s =
if not in_p then begin
self#break (); output_string ch "
"; in_p <- true
end;
output_string ch (html_escape s); need_break <- true
method change_p () = in_p <- false
method start_ul _ = at_list_start <- Some ""
method li () =
begin match at_list_start with
Some clss ->
self#break (); output_string ch "
()
| Some clss -> output_string ch (" class='" ^ clss ^ "'")
end;
begin match id with
None -> ()
| Some id -> output_string ch (" id='" ^ id ^ "'")
end;
output_string ch ">";
in_p <- true
method dd () =
begin match at_list_start with
Some clss ->
self#break (); output_string ch "
"; need_break <- true; in_p <- false
method start_span ?clss () =
if not in_p then begin
self#break (); output_string ch "
"; in_p <- true
end;
begin match clss with
Some clss -> output_string ch ("")
| None -> output_string ch ""
end
method end_span () = output_string ch "";
method start_pre ?clss () =
if not in_p then begin
self#break (); output_string ch "
"; in_p <- true
end;
begin match clss with
Some clss -> output_string ch ("
"; need_break <- true; in_p <- false
method start_section ?clss () =
self#break ();
begin match clss with
Some clss ->
output_string ch ("")
| None ->
output_string ch ""
end;
need_break <- true; in_p <- false
method end_section () =
self#break (); output_string ch "";
need_break <- true; in_p <- false
method start_footer () =
self#break ();
output_string ch "";
need_break <- true; in_p <- false
method raw_html f =
if not in_p then begin
self#break (); output_string ch "
"; in_p <- true
end;
output_string ch (f ());
need_break <- true
end
let space = Str.regexp " "
(*XXX recognize non-breaking spaces and replace them with spaces (?) *)
(*Unicode bullets? • *)
class format_printer f : printer = object
val mutable at_flow_start = true
val mutable in_p = false
val mutable at_list_start = false
val mutable ul_prefixes = []
method start_doc () =
Format.fprintf f "@[";
at_flow_start <- true; in_p <- false; ul_prefixes <- []
method end_doc () =
if in_p then Format.fprintf f "@]";
Format.fprintf f "@]@."
method text s =
if not in_p then begin
if not at_flow_start then Format.fprintf f "@ ";
Format.fprintf f "@[";
end;
at_flow_start <- false; in_p <- true;
List.iter
(fun e ->
match e with
Str.Delim _ -> Format.fprintf f "@ "
| Str.Text s -> Format.fprintf f "%s" s)
(Str.full_split space s)
method change_p () =
if in_p then Format.fprintf f "@]";
in_p <- false
method start_ul prefix =
ul_prefixes <- prefix :: ul_prefixes;
if in_p then Format.fprintf f "@]";
at_list_start <- true; in_p <- false
method li () =
if at_list_start then begin
if not at_flow_start then Format.fprintf f "@ ";
Format.fprintf f "@[";
end else begin
if in_p then Format.fprintf f "@]";
Format.fprintf f "@]@ "
end;
Format.fprintf f "@[%s" (List.hd ul_prefixes);
in_p <- false; at_list_start <- false; at_flow_start <- true
method end_ul () =
ul_prefixes <- List.tl ul_prefixes;
if not at_list_start then begin
if in_p then Format.fprintf f "@]";
Format.fprintf f "@]@]";
at_flow_start <- false
end;
at_list_start <- false; in_p <- false
method start_a l = ()
method end_a l = ()
method start_code l = ()
method end_code l = ()
method start_dl ?clss () = at_list_start <- true; assert false
method dt ?clss id =
if at_list_start then begin
Format.fprintf f "@["; at_list_start <- false
end else
Format.fprintf f "@]@]@ ";
Format.fprintf f "@[* @["
method dd () = Format.fprintf f "@]@ @["
method end_dl () =
if not at_list_start then Format.fprintf f "@]"
method start_div ?clss () = ()
method end_div () = ()
method start_span ?clss () = ()
method end_span () = ()
method start_pre ?clss () = ()
method end_pre () = ()
method start_heading () = ()
method end_heading () = ()
method start_section ?clss () = ()
method end_section () = ()
method start_footer () = ()
method end_footer () = ()
method raw_html f = ()
end
coinst-1.9.3/graph.ml 0000644 0001750 0001750 00000016525 12657630652 013441 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module F (R : Repository.S) = struct
open R
module Quotient = Quotient.F(R)
module Conflicts = Conflicts.F (R)
let output
?options
?package_weight
?package_emph
?(edge_color = fun _ _ _ -> Some "blue") ?(grayscale =false)
file ?(mark_all = false) ?(mark_reversed = false) ?(roots = [])
quotient deps confl =
let package_weight =
match package_weight with
Some f -> f
| None -> fun p -> float (Quotient.class_size quotient p)
in
let package_emph =
match package_emph with
Some f -> f
| None -> fun p -> false
in
let confl_style = if grayscale then ",style=dashed" else ",color=red" in
let confl_clique_style =
if grayscale then "" else ",color=red,fontcolor=red" in
let dep_style col = if grayscale then "" else Format.sprintf "color=%s" col in
let disj_dep_style col =
if grayscale then "" else Format.sprintf "fontcolor=%s,color=%s" col col in
(* Mark the packages to be included in the graph *)
let marks = Hashtbl.create 101 in
let marked i = Hashtbl.mem marks i in
let has_dependencies p =
let dep = PTbl.get deps p in
not (Formula.implies Formula._true dep ||
Formula.implies (Formula.lit p) dep)
in
let rec mark p =
if not (marked p) then begin
Hashtbl.add marks p ();
PSet.iter mark (Conflict.of_package confl p)
end
in
if mark_all then
Quotient.iter (fun p -> Hashtbl.add marks p ()) quotient
else if roots = [] then begin
Quotient.iter
(fun p ->
if has_dependencies p then begin
mark p;
Formula.iter (PTbl.get deps p) (fun d -> Disj.iter d mark)
end)
quotient;
if mark_reversed then begin
let m = Hashtbl.copy marks in
Hashtbl.clear marks;
Quotient.iter
(fun p -> if not (Hashtbl.mem m p) then Hashtbl.add marks p ())
quotient
end
end else (*XXX Find the right algorithm...
Work on transitive closure of dependencies
Mark all conflicts; marks all packages at the other side of
these conflicts and all the alternative in the dependency.
Proceed recursively...
Backward mode:
mark source package and all edges but the one considered
A package is not relevant if installing it or not has no
impact on the considered package
*)
List.iter mark roots;
let dep_targets = ref PSet.empty in
Quotient.iter
(fun p ->
Formula.iter (PTbl.get deps p)
(fun d ->
Disj.iter d
(fun q ->
if p <> q then dep_targets := PSet.add q !dep_targets)))
quotient;
let ch = open_out file in
let f = Format.formatter_of_out_channel ch in
Format.fprintf f "digraph G {@.";
begin match options with
None ->
Format.fprintf f "rankdir=LR;@.";
Format.fprintf f "ratio=1.4;@.margin=5;@.ranksep=3;@."
| Some l ->
List.iter (fun s -> Format.fprintf f "%s@." s) l
end;
Format.fprintf f "node [style=rounded];@.";
let confl_n = ref 0 in
Conflict.iter confl
(fun p q ->
if not (marked p) then begin
assert (not (marked q));
Conflict.remove confl p q
end);
let l = Conflicts.f quotient confl in
List.iter
(fun cset ->
match PSet.elements cset with
[i; j] ->
if
PSet.mem j !dep_targets && not (PSet.mem i !dep_targets)
then
Format.fprintf f "%d -> %d [dir=none%s];@."
(Package.index j) (Package.index i) confl_style
else
Format.fprintf f "%d -> %d [dir=none%s];@."
(Package.index i) (Package.index j) confl_style
| l ->
incr confl_n;
let n = !confl_n in
Format.fprintf f
"confl%d [label=\"#\",shape=circle%s];@."
n confl_clique_style;
List.iter
(fun i ->
Format.fprintf f
"%d -> confl%d [dir=none%s];@."
(Package.index i) n confl_style)
l)
l;
let dep_tbl = Hashtbl.create 101 in
let dep_n = ref 0 in
let add_dep i dep d =
let s = Disj.to_lits d in
match edge_color i dep d with
None ->
()
| Some col ->
match PSet.cardinal s with
0 ->
incr dep_n;
let n = !dep_n in
Format.fprintf f
"dep%d \
[label=\"MISSING DEP\",shape=box,fontcolor=red,%s];@."
n (dep_style col);
Format.fprintf f "%d -> dep%d [%s];@."
(Package.index i) n (dep_style col)
| 1 ->
if PSet.choose s <> i then
Format.fprintf f "%d -> %d [minlen=2, weight=2, %s];@."
(Package.index i) (Package.index (PSet.choose s))
(dep_style col)
| _ ->
let n =
try
Hashtbl.find dep_tbl s
with Not_found ->
incr dep_n;
let n = !dep_n in
Hashtbl.add dep_tbl s n;
(*
Format.fprintf f "dep%d [label=\"DEP\",shape=box,color=%s];@."
n col;
*)
Format.fprintf f "dep%d [label=\"∨\",shape=circle,%s];@."
n (disj_dep_style col);
(*
Format.fprintf f "dep%d [label=\"or\",shape=circle,%s];@."
n (disj_dep_style col);
*)
PSet.iter
(fun j ->
Format.fprintf f "dep%d -> %d [%s];@."
n (Package.index j) (dep_style col))
s;
n
in
Format.fprintf f "%d -> dep%d [dir=none,%s];@."
(Package.index i) n (dep_style col)
in
Quotient.iter
(fun i ->
let dep = PTbl.get deps i in
if marked i then begin
let n = package_weight i in
let em = package_emph i in
let w = (min 1. (log n /. log 1000.)) in
let color =
if grayscale then
let c = 255 - truncate (w *. 255.9) in
Format.sprintf "#%02x%02x%02x" c c c
else
Format.sprintf "0.0,%f,1.0" w
in
Format.fprintf f
"%d [label=\"%a\",style=\"filled\",\
fillcolor=\"%s\"%s];@."
(Package.index i) (Quotient.print_class quotient) i
color
(if em then ",penwidth=1.7" else "");
Formula.iter dep (fun s -> add_dep i dep s)
end)
quotient;
Format.fprintf f "}@.";
close_out ch
end
coinst-1.9.3/rpm_lib.ml 0000644 0001750 0001750 00000104623 12657630652 013761 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
(*
References
----------
http://rpm.org/
rpm sources
*)
(*
XXXX Validator (check that the fields all have the right type)
XXXX Check results
XXXX Print generated rules
XXXX Share more code with deb.ml
*)
let rec match_prefix_rec p d i l =
i = l || (d.[i] = p.[i] && match_prefix_rec p d (i + 1) l)
let match_prefix p d =
let l = String.length p in
String.length d >= l && match_prefix_rec p d 0 l
(* Mandriva has a patch that makes rpm ignore conflict on some
documentation files *)
let doc_dirs =
["/usr/share/man/"; "/usr/share/gtk-doc/html/"; "/usr/share/gnome/html/"]
let keep_directory d =
not (List.exists (fun p -> match_prefix p d) doc_dirs)
type typ =
NULL | CHAR | INT8 | INT16 | INT32 | INT64
| STRING | BIN | STRING_ARRAY | I18NSTRING
| UNKOWNTYPE of int
let intern_typ i =
match i with
0 -> NULL | 1 -> CHAR | 2 -> INT8 | 3 -> INT16 | 4 -> INT32
| 5 -> INT64 | 6 -> STRING | 7 -> BIN | 8 -> STRING_ARRAY | 9 -> I18NSTRING
| _ -> Util.print_warning (Format.sprintf "unknown type %d" i);
UNKOWNTYPE i
let substring ch l =
let s = Bytes.create l in
really_input ch s 0 l;
s
let int ch =
let s = substring ch 4 in
Char.code (Bytes.get s 0) lsl 24 + Char.code (Bytes.get s 1) lsl 16 +
Char.code (Bytes.get s 2) lsl 8 + Char.code (Bytes.get s 3)
let sstring store pos =
let len = ref 0 in
while store.[pos + !len] <> '\000' do incr len done;
String.sub store pos !len
let rec sstring_array_rec store pos count =
if count = 0 then [] else
let s = sstring store pos in
s :: sstring_array_rec store (pos + String.length s + 1) (count - 1)
let sstring_array store pos count =
Array.of_list (sstring_array_rec store pos count)
let rec sarray_rec l f store pos count =
if count = 0 then [] else
let s = f store pos in
s :: sarray_rec l f store (pos + l) (count - 1)
let sarray l f store pos count = Array.of_list (sarray_rec l f store pos count)
let sint32 s pos =
Char.code s.[pos] lsl 24 + Char.code s.[pos + 1] lsl 16 +
Char.code s.[pos + 2] lsl 8 + Char.code s.[pos + 3]
let sint32_array = sarray 4 sint32
let sint16 s pos = Char.code s.[pos] lsl 8 + Char.code s.[pos + 1]
let sint16_array = sarray 2 sint16
(****)
let get_package_list' h n =
try
Hashtbl.find h n
with Not_found ->
let r = ref [] in
Hashtbl.add h n r;
r
let add_to_package_list h n p =
let l = get_package_list' h n in
l := p :: !l
let get_package_list h n = try !(Hashtbl.find h n) with Not_found -> []
(****)
let pr_typ ch t =
Format.fprintf ch "%s"
(match t with
NULL -> "NULL" | CHAR -> "CHAR" | INT8 -> "INT8" | INT16 -> "INT16"
| INT32 -> "INT32" | INT64 -> "INT64" | STRING -> "STRING" | BIN -> "BIN"
| STRING_ARRAY -> "STRING_ARRAY" | I18NSTRING -> "I18NSTRING"
| UNKOWNTYPE i -> "UNKOWNTYPE(" ^ string_of_int i ^ ")")
let tags =
[( 63, (BIN, "HEADERIMMUTABLE", false));
( 100, (STRING_ARRAY, "HEADERI18NTABLE", false));
( 257, (INT32, "SIGSIZE", false));
( 261, (BIN, "SIGMD5", false));
( 262, (BIN, "SIGGPG", false));
( 266, (STRING_ARRAY, "PUBKEYS", false));
( 267, (BIN, "DSAHEADER", false));
( 269, (STRING, "SHA1HEADER", false));
(1000, (STRING, "NAME", true)); (* ! *)
(1001, (STRING, "VERSION", true)); (* ! *)
(1002, (STRING, "RELEASE", true)); (* ! *)
(1003, (INT32, "EPOCH", true)); (* ! *)
(1004, (I18NSTRING, "SUMMARY", false));
(1005, (I18NSTRING, "DESCRIPTION", false));
(1006, (INT32, "BUILDTIME", false));
(1007, (STRING, "BUILDHOST", false));
(1009, (INT32, "SIZE", false));
(1010, (STRING, "DISTRIBUTION", false));
(1011, (STRING, "VENDOR", false));
(1012, (BIN, "GIF", false));
(1013, (BIN, "XPM", false));
(1014, (STRING, "LICENSE", false));
(1015, (STRING, "PACKAGER", false));
(1016, (I18NSTRING, "GROUP", false));
(1020, (STRING, "URL", false));
(1021, (STRING, "OS", false));
(1022, (STRING, "ARCH", false));
(1023, (STRING, "PREIN", false));
(1024, (STRING, "POSTIN", false));
(1025, (STRING, "PREUN", false));
(1026, (STRING, "POSTUN", false));
(1028, (INT32, "FILESIZES", false));
(1030, (INT16, "FILEMODES", true)); (* ! *)
(1033, (INT16, "FILERDEVS", false));
(1034, (INT32, "FILEMTIMES", false));
(1035, (STRING_ARRAY, "FILEMD5S", true)); (* ! *)
(1036, (STRING_ARRAY, "FILELINKTOS", true)); (* ! *)
(1037, (INT32, "FILEFLAGS", true)); (* ! *)
(1039, (STRING_ARRAY, "FILEUSERNAME", false));
(1040, (STRING_ARRAY, "FILEGROUPNAME", false));
(1044, (STRING, "SOURCERPM", false));
(1045, (INT32, "FILEVERIFYFLAGS", false));
(1046, (INT32, "ARCHIVESIZE", false));
(1047, (STRING_ARRAY, "PROVIDENAME", true)); (* ! *)
(1048, (INT32, "REQUIREFLAGS", true)); (* ! *)
(1049, (STRING_ARRAY, "REQUIRENAME", true)); (* ! *)
(1050, (STRING_ARRAY, "REQUIREVERSION", true)); (* ! *)
(1053, (INT32, "CONFLICTFLAGS", true)); (* ! *)
(1054, (STRING_ARRAY, "CONFLICTNAME", true)); (* ! *)
(1055, (STRING_ARRAY, "CONFLICTVERSION", true)); (* ! *)
(1064, (STRING, "RPMVERSION", false));
(1065, (STRING_ARRAY, "TRIGGERSCRIPTS", false));
(1066, (STRING_ARRAY, "TRIGGERNAME", false));
(1067, (STRING_ARRAY, "TRIGGERVERSION", false));
(1068, (INT32, "TRIGGERFLAGS", false));
(1069, (INT32, "TRIGGERINDEX", false));
(1079, (STRING, "VERIFYSCRIPT", false));
(1080, (INT32, "CHANGELOGTIME", false));
(1081, (STRING_ARRAY, "CHANGELOGNAME", false));
(1082, (STRING_ARRAY, "CHANGELOGTEXT", false));
(1085, (STRING, "PREINPROG", false));
(1086, (STRING, "POSTINPROG", false));
(1087, (STRING, "PREUNPROG", false));
(* (1087, (STRING_ARRAY, "PREUNPROG", false));*)
(1088, (STRING, "POSTUNPROG", false));
(1090, (STRING_ARRAY, "OBSOLETENAME", false));
(1091, (STRING, "VERIFYSCRIPTPROG", false));
(1092, (STRING_ARRAY, "TRIGGERSCRIPTPROG", false));
(1094, (STRING, "COOKIE", false));
(1095, (INT32, "FILEDEVICES", false));
(1096, (INT32, "FILEINODES", false));
(1097, (STRING_ARRAY, "FILELANGS", false));
(1098, (STRING_ARRAY, "PREFIXES", false)); (* ? *)
(1112, (INT32, "PROVIDEFLAGS", true)); (* ! *)
(1113, (STRING_ARRAY, "PROVIDEVERSION", true)); (* ! *)
(1114, (INT32, "OBSOLETEFLAGS", false));
(1115, (STRING_ARRAY, "OBSOLETEVERSION", false));
(1116, (INT32, "DIRINDEXES", true)); (* ! *)
(1117, (STRING_ARRAY, "BASENAMES", true)); (* ! *)
(1118, (STRING_ARRAY, "DIRNAMES", true)); (* ! *)
(1122, (STRING, "OPTFLAGS", false));
(1123, (STRING, "DISTURL", false));
(1124, (STRING, "PAYLOADFORMAT", false));
(1125, (STRING, "PAYLOADCOMPRESSOR", false));
(1126, (STRING, "PAYLOADFLAGS", false));
(1131, (STRING, "RHNPLATFORM", false));
(1132, (STRING, "PLATFORM", false));
(1140, (INT32, "FILECOLORS", false)); (* ? *)
(* 1 = elf32, 2 = elf64, 0 = other *)
(1141, (INT32, "FILECLASS", false));
(1142, (STRING_ARRAY, "CLASSDICT", false));
(1143, (INT32, "FILEDEPENDSX", false)); (* ? *)
(1144, (INT32, "FILEDEPENDSN", false)); (* ? *)
(1145, (INT32, "DEPENDSDICT", false)); (* ? *)
(1146, (BIN, "SOURCEPKGID", false));
(1152, (STRING, "POSTTRANS", false));
(1154, (STRING, "POSTTRANSPROG", false));
(1155, (STRING, "DISTTAG", false));
(1156, (STRING_ARRAY, "SUGGESTSNAME", false));
(1157, (STRING_ARRAY, "SUGGESTSVERSION", false));
(1158, (INT32, "SUGGESTSFLAGS", false));
(1177, (INT32, "FILEDIGESTALGOS", false));
(1199, (INT32, "RPMLIBVERSION", false));
(1200, (INT32, "RPMLIBTIMESTAMP", false));
(1201, (INT32, "RPMLIBVENDOR", false));
(1218, (STRING, "DISTEPOCH", true));
(5012, (STRING, "BUGURL", false));
(1000000, (STRING, "FILENAME", false));
(1000001, (INT32, "FILESIZE", false));
(1000005, (STRING, "MD5", false));
(1000010, (STRING, "DIRECTORY", false))]
let tag_name tag typ =
try
List.assoc tag tags
with Not_found ->
Util.print_warning (Format.sprintf "unknown tag %d" tag);
(typ, Format.sprintf "UNKNOWN(%d)" tag, true)
let pr_tag ch tag =
let (_, nm, _) = tag_name tag BIN (* Dummy type*) in
Format.fprintf ch "%s" nm
let pr_field_contents ch (store, (_, typ, pos, count)) =
match typ with
STRING ->
Format.fprintf ch "\"%s\"" (String.escaped (sstring store pos))
| STRING_ARRAY ->
Array.iter (fun s -> Format.fprintf ch "\"%s\" " (String.escaped s))
(sstring_array store pos count)
| INT32 ->
Array.iter
(fun i -> Format.fprintf ch "0x%x " i) (sint32_array store pos count)
| INT16 ->
Array.iter
(fun i -> Format.fprintf ch "0x%x " i) (sint16_array store pos count)
| _ ->
Format.fprintf ch "(not shown)"
let show_all = ref false
let pr_field ch ((store, (tag, typ, pos, count)) as field) =
let (typ', nm, shown) = tag_name tag typ in
if typ <> typ' then
Util.print_warning (Format.sprintf "wrong type for tag %s" nm);
if shown || !show_all then begin
Format.fprintf ch "%s %a 0x%x %d" nm pr_typ typ pos count;
Format.fprintf ch " %a@." pr_field_contents field
end
let pr_fields store entry =
for i = 0 to Array.length entry - 1 do
let (tag, typ, pos, count) as field = entry.(i) in
Format.printf "%a" pr_field (store, field)
done;
Format.printf "@."
(****)
let _NAME = 1000
let _VERSION = 1001
let _RELEASE = 1002
let _EPOCH = 1003
let _FILEMODES = 1030
let _FILEMD5S = 1035
let _FILELINKTOS = 1036
let _FILEFLAGS = 1037
let _PROVIDENAME = 1047
let _REQUIREFLAGS = 1048
let _REQUIRENAME = 1049
let _REQUIREVERSION = 1050
let _CONFLICTFLAGS = 1053
let _CONFLICTNAME = 1054
let _CONFLICTVERSION = 1055
let _OBSOLETENAME = 1090
let _PROVIDEFLAGS = 1112
let _PROVIDEVERSION = 1113
let _OBSOLETEFLAGS = 1114
let _OBSOLETENVERSION = 1115
let _DIRINDEXES = 1116
let _BASENAMES = 1117
let _DIRNAMES = 1118
let _DISTEPOCH = 1218
let etag entry i =
if i >= Array.length entry then max_int else
let (tag, _, _, _) = entry.(i) in tag
let rec move_to entry i tag =
if etag entry i >= tag then i else move_to entry (i + 1) tag
exception Skip
let check_entry tag typ tag' typ' =
if tag <> tag' then begin
let b = Buffer.create 80 in
Format.bprintf b "Expected tag %a but actual tag is %a@?"
pr_tag tag pr_tag tag';
Util.print_warning (Buffer.contents b);
raise Skip
end;
if typ <> typ' then begin
let b = Buffer.create 80 in
Format.bprintf b "Entry %a has expected type %a but actual typ is %a@?"
pr_tag tag pr_typ typ pr_typ typ';
Util.fail (Buffer.contents b)
end
let estring store entry i tag =
let (tag', typ, pos, count) = entry.(i) in
check_entry tag STRING tag' typ;
if count <> 1 then begin
let b = Buffer.create 80 in
Format.bprintf b "Entry %a has type STRING with count %d > 1@?"
pr_tag tag count;
Util.fail (Buffer.contents b)
end;
sstring store pos
let estring_array store entry i tag =
let (tag', typ, pos, count) = entry.(i) in
check_entry tag STRING_ARRAY tag' typ;
sstring_array store pos count
let eint32 store entry i tag =
let (tag', typ, pos, count) = entry.(i) in
check_entry tag INT32 tag' typ;
if count <> 1 then begin
let b = Buffer.create 80 in
Format.bprintf b "Expecting a single INT32 for entry %a but got %d@?"
pr_tag tag count;
Util.fail (Buffer.contents b)
end;
sint32 store pos
let eint32_array store entry i tag =
let (tag', typ, pos, count) = entry.(i) in
check_entry tag INT32 tag' typ;
sint32_array store pos count
let eint16_array store entry i tag =
let (tag', typ, pos, count) = entry.(i) in
check_entry tag INT16 tag' typ;
sint16_array store pos count
(****)
type file_info =
Dir | Char | Block | Link of string | Sock | Pipe | Reg of string
let intern_file filemodes filemd5s filelinktos i =
let mode = filemodes.(i) in
match mode land 0o170000 with
0o40000 -> Dir
| 0o20000 -> Char
| 0o60000 -> Block
| 0o120000 -> Link (filelinktos.(i))
| 0o140000 -> Sock
| 0o10000 -> Pipe
| 0o100000 -> Reg (String.sub filemd5s.(i) 0 32)
| _ -> Util.fail (Format.sprintf "unknown mode %o" mode)
let pr_info ch i =
match i with
Dir ->
Format.fprintf ch "DIR"
| Char ->
Format.fprintf ch "CHAR"
| Block ->
Format.fprintf ch "BLOCK"
| Link l ->
Format.fprintf ch "LINK(%s)" l
| Sock ->
Format.fprintf ch "SOCK"
| Pipe ->
Format.fprintf ch "PIPE"
| Reg s ->
Format.fprintf ch "REG(%s)" s
(****)
type rel = SE | E | EQ | L | SL | ALL
let pr_rel ch rel =
Format.fprintf ch "%s"
(match rel with
SE -> "<<"
| E -> "<="
| EQ -> "="
| L -> ">="
| SL -> ">>"
| ALL -> "ALL")
let intern_flags f =
match f land 15 with
0 -> ALL
| 2 -> SE
| 10 -> E
| 8 -> EQ
| 12 -> L
| 4 -> SL
| _ -> Util.fail (Format.sprintf "Wrong flag %d" (f land 15))
(* RPMSENSE_RPMLIB | RPMSENSE_MISSINGOK *)
let requires_to_skip_bitmask = (1 lsl 24) lor (1 lsl 19)
(* Dependencies on rpmlib and "suggests" dependencies are skipped *)
let skipped_dep name flags i =
flags.(i) land requires_to_skip_bitmask <> 0 ||
let nm = name.(i) in
(String.length nm > 8 &&
nm.[0] = 'r' && nm.[1] = 'p' && nm.[2] = 'm' && nm.[3] = 'l' &&
nm.[4] = 'i' && nm.[5] = 'b' && nm.[6] = '(')
type vers = int option * string * string option * string option
type pack_ref = string * rel * vers option
type p =
{ num : int;
name : string; version : string; release : string;
epoch : int option; distepoch : string option;
provide : pack_ref list;
require : pack_ref list;
conflict : pack_ref list }
type pool =
{ mutable size : int;
files : (string * string, (file_info * p) list ref) Hashtbl.t;
provides : (string, (rel * vers option * p) list ref) Hashtbl.t;
mutable packages : p list;
packages_by_num : (int, p) Hashtbl.t;
packages_by_name : (string, p list ref) Hashtbl.t;
}
let new_pool () =
{ size = 0;
files = Hashtbl.create 300000;
provides = Hashtbl.create 10000;
packages = [];
packages_by_num = Hashtbl.create 1000;
packages_by_name = Hashtbl.create 1000 }
let add_file p f v =
let l =
try Hashtbl.find p.files f with Not_found ->
let l = ref [] in Hashtbl.add p.files f l; l
in
l := v :: !l
let add_provide pool p (nm, rel, vers) =
let l =
try Hashtbl.find pool.provides nm with Not_found ->
let l = ref [] in Hashtbl.add pool.provides nm l; l
in
l := (rel, vers, p) :: !l
(****)
let pr_version ch (epoch, version, release, distepoch) =
begin match epoch with
None -> ()
| Some e -> Format.fprintf ch "%d:" e
end;
Format.fprintf ch "%s" version;
begin match release with
Some r -> Format.fprintf ch "-%s" r
| None -> ()
end;
begin match distepoch with
Some e -> Format.fprintf ch ":%s" e
| None -> ()
end
let is_lower c = c >= 'a' && c <= 'z'
let is_upper c = c >= 'A' && c <= 'Z'
let is_digit c = c >= '0' && c <= '9'
let is_alpha c = is_lower c || is_upper c
let is_alnum c = is_alpha c || is_digit c
let check_version s = s <> "" && not (is_alnum s.[String.length s - 1])
(* _evr_tuple_match, rpmevr.c *)
let version_re_1 =
Str.regexp
"^\\(\\([0-9]*\\):\\)?\\([^:]+\\)\\(-\\([^:-]+\\)\\)\\(:\\([^:-]+\\)\\)?$"
let version_re_2 =
Str.regexp
"^\\(\\([0-9]*\\):\\)?\\([^:-]+\\)\\(-\\([^:-]+\\)\\)?\\(:\\([^:-]+\\)\\)?$"
let parse_version s =
if s = "" then
None
else if not (Str.string_match version_re_1 s 0 ||
Str.string_match version_re_2 s 0) then begin
Util.print_warning (Format.sprintf "bad version '%s'" s);
raise Skip
end else begin
let epoch =
try
let s = Str.matched_group 2 s in
Some (if s = "" then 0 else int_of_string s)
with Not_found ->
None
in
let version = Str.matched_group 3 s in
let release = try Some (Str.matched_group 5 s) with Not_found -> None in
let distepoch = try Some (Str.matched_group 7 s) with Not_found -> None in
if
check_version s ||
match release with Some r -> check_version r | _ -> false
then begin
let b = Buffer.create 80 in
Format.bprintf b
"version '%a' not ending with an alphanumeric character@?"
pr_version (epoch, version, release, distepoch);
Util.print_warning (Buffer.contents b)
end;
Some (epoch, version, release, distepoch)
end
let rec split_vers_rec s p l =
let q = ref p in
while !q < l && not (is_alnum s.[!q]) do incr q done;
if !q = l then begin
if p = !q then [] else [`Other]
end else begin
let p = !q in
if is_digit s.[p] then begin
let q = ref p in
while !q < l && s.[!q] = '0' do incr q done;
let p = !q in
while !q < l && is_digit s.[!q] do incr q done;
`Num (String.sub s p (!q - p)) :: split_vers_rec s !q l
end else (* if is_alpha s.[p] then*) begin
let q = ref (p + 1) in
while !q < l && is_alpha s.[!q] do incr q done;
`Alpha (String.sub s p (!q - p)) :: split_vers_rec s !q l
end
end
let split_vers s = split_vers_rec s 0 (String.length s)
let rec compare_vers_rec l1 l2 =
match l1, l2 with
`Alpha s1 :: r1, `Alpha s2 :: r2 ->
let c = compare s1 s2 in
if c <> 0 then c else
compare_vers_rec r1 r2
| `Num n1 :: r1, `Num n2 :: r2 ->
let c = compare (String.length n1) (String.length n2) in
if c <> 0 then c else
let c = compare n1 n2 in
if c <> 0 then c else
compare_vers_rec r1 r2
| `Num _ :: _, `Alpha _ :: _
| `Num _ :: _, `Other :: _ ->
1
| `Alpha _ :: _, `Num _ :: _
| `Alpha _ :: _, `Other :: _ ->
-1
| `Other :: _, `Alpha _ :: _
| `Other :: _, `Num _ :: _ (* Should have been 1 *)
| `Other :: _, `Other :: _ -> (* Should have been 0 *)
-1
| [], [] -> 0
| _, [] -> 1
| [], _ -> -1
(*
Not stable by extension
10 < 10a
10a.5 < 10.5
Not a total order
10. < 10, 10, < 10.
10.a < 10. 10. < 10.a (but 10.1 > 10. 10. < 10.1)
*)
(*rpmvercmp.c*)
let compare_vers s1 s2 =
if s1 = s2 then 0 else
compare_vers_rec (split_vers s1) (split_vers s2)
let promote = false
let compare_versions ver1 ver2 rel2 =
match ver1, ver2 with
Some (e1, v1, r1, d1), Some (e2, v2, r2, d2) ->
let c2 =
let c = compare_vers v1 v2 in
if c <> 0 then c else
let c =
match r1, r2, rel2 with
Some r1, Some r2, _ -> compare_vers r1 r2
| _, None, (E|EQ|L) -> 0
| None, Some r2, _ -> compare_vers "" r2
| Some r1, None, _ -> compare_vers r1 ""
| None, None, _ -> 0
in
if c <> 0 then c else
match d1, d2, rel2 with
Some d1, Some d2, _ -> compare_vers d1 d2
| _, None, (EQ|L) -> 0
| None, Some d2, _ -> compare_vers "" d2
| Some d1, None, _ -> compare_vers d1 ""
| None, None, _ -> 0
in
let c1 =
match e1, e2 with
None, None | None, Some 0 | Some 0, None ->
0
| Some e1, Some e2 ->
compare (e1 : int) e2
| None, Some _ ->
-1
| Some _, None ->
if promote then 0 else 1
in
if c1 <> 0 then c1 else c2
| _ ->
(* Checked in function validate_deps *)
assert false
(* rpmdsCompare, rpmds.c *)
let compare_pack_refs (n1, r1, v1) (n2, r2, v2) =
n1 = n2 &&
match r1, r2 with
ALL, _ | _, ALL | (SE | E), (SE | E) | (SL | L), (SL | L) -> true
| (EQ | L | SL), SE | SL, (EQ | E) -> compare_versions v1 v2 r2 < 0
| SE, (EQ | L | SL) | (EQ | E), SL -> compare_versions v1 v2 r2 > 0
| EQ, E | L, E | L, EQ -> compare_versions v1 v2 r2 <= 0
| E, EQ | E, L | EQ, L -> compare_versions v1 v2 r2 >= 0
| EQ, EQ -> compare_versions v1 v2 r2 = 0
let pr_pack_ref ch (name, rel, ver) =
Format.fprintf ch "%s" name;
match ver with
Some v -> Format.fprintf ch " (%a %a)" pr_rel rel pr_version v
| None -> ()
let pr_pack ch p =
pr_pack_ref ch
(p.name, EQ, Some (p.epoch, p.version, Some p.release, p.distepoch))
let resolve_file_dep p (nm, rel, ver) =
if nm = "" || nm.[0] <> '/' then [] else begin
let i = String.rindex nm '/' in
let d = String.sub nm 0 (i + 1) in
let f = String.sub nm (i + 1) (String.length nm - i - 1) in
let l = try !(Hashtbl.find p.files (d, f)) with Not_found -> [] in
List.map (fun (_, p) -> p) l
end
let resolve_pack_ref p ((nm, rel, ver) as rf) =
let l =
try
let l = !(Hashtbl.find p.provides nm) in
List.filter
(fun (rel, vers, p) ->
(* The order here is important: the comparison is not symmetric! *)
compare_pack_refs (nm, rel, vers) rf) l
with Not_found ->
[]
in
resolve_file_dep p rf @ List.map (fun (rel, vers, p) -> p) l
let validate_deps l =
List.iter
(fun (nm, rel, ver) ->
match rel, ver with
ALL, Some _ -> assert false
| ALL, None -> ()
| _, None -> assert false
| _, Some _ -> ())
l
let parse_deps name flags version =
let l = ref [] in
for i = Array.length name - 1 downto 0 do
if not (skipped_dep name flags i) then begin
l := (name.(i), intern_flags flags.(i), parse_version version.(i)) :: !l
end
done;
validate_deps !l;
!l
let dump_fields = ref false
let parse_header pool ignored_packages ch =
let h = substring ch 8 in
let get = Bytes.get in
if not (get h 0 = '\142' && get h 1 = '\173' && get h 2 = '\232') then
Util.fail "Bad header";
let entry_count = int ch in
let sz = int ch in
(*Format.eprintf "%d %d@." entry_count sz;*)
let entry = Array.make entry_count (0, NULL, 0, 0) in
for i = 0 to entry_count - 1 do
let tag = int ch in
let typ = intern_typ (int ch) in
let pos = int ch in
let count = int ch in
(* Format.eprintf "%d %a@." tag pr_typ typ;*)
entry.(i) <- (tag, typ, pos, count)
done;
Array.sort (fun (tag1, _, _, _) (tag2, _, _, _) -> compare tag1 tag2) entry;
let store = substring ch sz in
let store = Bytes.to_string store in
try
let i = move_to entry 0 _NAME in
let name = estring store entry i _NAME in
let version = estring store entry (i + 1) _VERSION in
let release = estring store entry (i + 2) _RELEASE in
assert (version <> ""); assert (release <> "");
let epoch =
if etag entry (i + 3) <> _EPOCH then None else
Some (eint32 store entry (i + 3) _EPOCH)
in
Util.set_warning_location
(match epoch with
None ->
Format.sprintf "in package %s = %s-%s" name version release
| Some e ->
Format.sprintf "in package %s = %d:%s-%s" name e version release);
if !dump_fields then pr_fields store entry;
let i = move_to entry i _FILEMODES in
let file_info = etag entry i = _FILEMODES in
let filemodes =
if file_info then eint16_array store entry i _FILEMODES else [||] in
let i = move_to entry i _FILEMD5S in
let filemd5s =
if file_info then estring_array store entry i _FILEMD5S else [||] in
let filelinktos =
if file_info then estring_array store entry (i + 1) _FILELINKTOS else [||]
in
let fileflags =
if file_info then eint32_array store entry (i + 2) _FILEFLAGS else [||]
in
let i = move_to entry i _PROVIDENAME in
let has_provides = etag entry i = _PROVIDENAME in
let providename =
if has_provides then estring_array store entry i _PROVIDENAME else [||]
in
let i = move_to entry i _REQUIREFLAGS in
let requireflags = eint32_array store entry i _REQUIREFLAGS in
let requirename = estring_array store entry (i + 1) _REQUIRENAME in
let requireversion = estring_array store entry (i + 2) _REQUIREVERSION in
let i = move_to entry i _CONFLICTFLAGS in
let has_confl = etag entry i = _CONFLICTFLAGS in
let conflictflags =
if has_confl then eint32_array store entry i _CONFLICTFLAGS else [||] in
let conflictname =
if has_confl then estring_array store entry (i + 1) _CONFLICTNAME else [||]
in
let conflictversion =
if has_confl then estring_array store entry (i + 2) _CONFLICTVERSION
else [||]
in
let i = move_to entry i _PROVIDEFLAGS in
let provideflags =
if has_provides then eint32_array store entry i _PROVIDEFLAGS else [||]
in
let provideversion =
if has_provides then estring_array store entry (i + 1) _PROVIDEVERSION
else [||]
in
let i = move_to entry i _DIRINDEXES in
let non_empty = etag entry i = _DIRINDEXES in
let dirindexes =
if non_empty then eint32_array store entry i _DIRINDEXES else [||] in
let basenames =
if non_empty then estring_array store entry (i + 1) _BASENAMES else [||] in
let dirnames =
if non_empty then estring_array store entry (i + 2) _DIRNAMES else [||] in
let i = move_to entry i _DISTEPOCH in
let distepoch =
if etag entry i <> _DISTEPOCH then None else
Some (estring store entry i _DISTEPOCH)
in
if List.mem name ignored_packages then raise Skip;
let p =
{ num = pool.size;
name = name; version = version; release = release;
epoch = epoch; distepoch = distepoch;
provide = parse_deps providename provideflags provideversion;
require = parse_deps requirename requireflags requireversion;
conflict = parse_deps conflictname conflictflags conflictversion }
in
pool.packages <- p :: pool.packages;
Hashtbl.add pool.packages_by_num pool.size p;
add_to_package_list pool.packages_by_name p.name p;
List.iter (fun pr -> add_provide pool p pr) p.provide;
pool.size <- pool.size + 1;
if file_info then begin
Array.iteri
(fun i f ->
let d = dirnames.(dirindexes.(i)) in
let is_ghost = fileflags.(i) land 0x40 <> 0 in
if not is_ghost && keep_directory d then
add_file pool (d, f)
(intern_file filemodes filemd5s filelinktos i, p))
basenames
end else
Array.iteri
(fun i f ->
let d = dirnames.(dirindexes.(i)) in
add_file pool (d, f) (Dir (* Dummy value *), p))
basenames;
Util.reset_warning_location ()
with Skip ->
Util.reset_warning_location ()
let parse_packages pool ignored_packages ch =
let st = Common.start_parsing (not !dump_fields) ch in
begin try while true do
parse_header pool ignored_packages ch;
Common.parsing_tick st
done with End_of_file -> () end;
Common.stop_parsing st
(****)
let package_re = Str.regexp "^\\([^ (]+\\) *( *\\([<=>]+\\) *\\([^ )]+\\) *)$"
let parse_package_dependency pool s =
if not (Str.string_match package_re s 0) then
failwith (Format.sprintf "Bad package name '%s'" s);
let name = Str.matched_group 1 s in
let (rel, ver) =
try
let rel =
match Str.matched_group 2 s with
"<<" -> SE
| "<=" | "<" -> E
| "=" -> EQ
| ">=" | ">" -> L
| ">>" -> SL
| s -> failwith (Format.sprintf "Bad relation '%s'" s)
in
(rel, parse_version (Str.matched_group 3 s))
with Not_found ->
(ALL, None)
in
let l = resolve_pack_ref pool (name, rel, ver) in
List.map (fun p -> p.num) l
let parse_package_name pool s =
List.map (fun p -> p.num) (get_package_list pool.packages_by_name s)
(****)
type conflict_reason =
R_File of string * string
| R_Explicit of pack_ref
type reason =
R_conflict of p * p * conflict_reason
| R_depends of p * pack_ref
let print_pack p ch n =
let p = Hashtbl.find p.packages_by_num n in
Format.fprintf ch "%a" pr_pack p
let print_pack_name p ch n =
let p = Hashtbl.find p.packages_by_num n in
Format.fprintf ch "%s" p.name
module Solver = Solver.F (struct type t = reason type reason = t end)
let print_rules = ref false
let add_conflict st p1 p2 reason =
let p = Solver.lit_of_var p1.num false in
let p' = Solver.lit_of_var p2.num false in
Solver.add_rule st [|p; p'|] [R_conflict (p1, p2, reason)]
let add_depend st n l r =
let l = List.map (fun p -> p.num) l in
Solver.add_rule st
(Array.of_list
(Solver.lit_of_var n.num false ::
List.map (fun n' -> Solver.lit_of_var n' true) l))
[R_depends (n, r)];
match l with
[] | [_] -> ()
| _ -> Solver.associate_vars st (Solver.lit_of_var n.num true) l
let add_dependencies pool pr p dep kind =
(*
if !print_rules then begin
Format.printf "%d -> any-of (" n;
List.iter (fun c -> Format.printf " %d" c) l;
Format.printf ")@."
end;
*)
List.iter
(fun r ->
let l = resolve_pack_ref pool r in
match kind with
`Require ->
add_depend pr p l r
| `Conflict ->
List.iter (fun p' -> add_conflict pr p p' (R_Explicit r)) l)
dep
let generate_rules pool =
let st = Common.start_generate (not !print_rules) pool.size in
let pr = Solver.initialize_problem ~print_var:(print_pack pool) pool.size in
(* File conflicts *)
let h = Hashtbl.create 127 in
Hashtbl.iter
(fun (d, f) {contents = l} ->
match l with
[] | [_] -> ()
| (inf, _) :: _ ->
if not (List.for_all (fun (inf', _) -> inf = inf') l) then begin
let a = Array.of_list l in
let len = Array.length a in
for i = 0 to len - 1 do
for j = i + 1 to len - 1 do
let (info1, p1) = a.(i) in
let (info2, p2) = a.(j) in
let pair = (min p1.num p2.num, max p1.num p2.num) in
if
info1 <> info2 && not (Hashtbl.mem h pair)
then begin
Hashtbl.add h pair ();
if !print_rules then begin
Format.printf "conflict between %a and %a on file %s%s (%a vs %a).@."
pr_pack p1 pr_pack p2 d f pr_info info1 pr_info info2
end;
add_conflict pr p1 p2 (R_File (d, f))
end
done
done
end)
pool.files;
List.iter
(fun p ->
Common.generate_next st;
add_dependencies pool pr p p.require `Require;
add_dependencies pool pr p p.conflict `Conflict)
pool.packages;
Common.stop_generate st;
Solver.propagate pr;
pr
(****)
let rec print_package_list_rec ch l =
match l with
[] -> Format.fprintf ch "NOT AVAILABLE"
| [x] -> pr_pack ch x
| x :: r -> Format.fprintf ch "%a, %a" pr_pack x print_package_list_rec r
let print_package_list ch l =
Format.fprintf ch "{%a}" print_package_list_rec l
let show_reasons pool l =
if l <> [] then begin
Format.printf "The following constraints cannot be satisfied:@.";
List.iter
(fun r ->
match r with
R_conflict (n1, n2, R_Explicit rf) ->
Format.printf " %a conflicts with %a {%a}@."
pr_pack n1 pr_pack_ref rf pr_pack n2
| R_conflict (n1, n2, R_File (d, f)) ->
Format.printf " %a conflicts with %a on file %s%s@."
pr_pack n1 pr_pack n2 d f
| R_depends (n, r) ->
Format.printf " %a depends on %a %a@."
pr_pack n pr_pack_ref r
print_package_list (resolve_pack_ref pool r))
l
end
let conflicts_in_reasons rl = List.fold_left (fun cl -> function R_conflict (i,j,r) -> (min i.num j.num, max i.num j.num)::cl | _ -> cl) [] rl
(****)
let compute_conflicts pool =
let conflict_pairs = Hashtbl.create 1000 in
let conflicts = Hashtbl.create 1000 in
let add_conflict p1 p2 =
let pair = (min p1.num p2.num, max p1.num p2.num) in
if not (Hashtbl.mem conflict_pairs pair) then begin
Hashtbl.add conflict_pairs pair ();
add_to_package_list conflicts p1.num p2.num;
add_to_package_list conflicts p2.num p1.num
end
in
List.iter
(fun p ->
List.iter
(fun r ->
let l = resolve_pack_ref pool r in
List.iter (fun p' -> add_conflict p p') l)
p.conflict)
pool.packages;
let conflict_pairs' = Hashtbl.copy conflict_pairs in
let has_conflict p1 p2 =
let pair = (min p1.num p2.num, max p1.num p2.num) in
Hashtbl.mem conflict_pairs' pair
in
(* File conflicts *)
Hashtbl.iter
(fun (d, f) {contents = l} ->
match l with
[] | [_] -> ()
| (inf, _) :: _ ->
if not (List.for_all (fun (inf', _) -> inf = inf') l) then begin
let a = Array.of_list l in
let len = Array.length a in
for i = 0 to len - 1 do
for j = i + 1 to len - 1 do
let (info1, p1) = a.(i) in
let (info2, p2) = a.(j) in
if not (has_conflict p1 p2) && info1 <> info2 then begin
(*
Format.printf "conflict between %a and %a on file %s%s (%a vs %a).@."
pr_pack p1 pr_pack p2 d f pr_info info1 pr_info info2;
*)
add_conflict p1 p2
end
done
done
end)
pool.files;
Array.init pool.size (fun i -> get_package_list conflicts i)
let compute_deps dist =
Array.init dist.size (fun i ->
let p = Hashtbl.find dist.packages_by_num i in
List.map (fun r -> List.map (fun p -> p.num) (resolve_pack_ref dist r))
p.require)
(*
List.map
(fun l ->
normalize_set
(List.flatten
(List.map (fun p -> resolve_package_dep dist p) l)))
(p.depends @ p.pre_depends))
*)
(****)
let pool_size p = p.size
coinst-1.9.3/update_data.mli 0000644 0001750 0001750 00000001616 12657630652 014757 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2012 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
val src : string ref
val f : string -> string -> string list -> string -> string list -> unit
coinst-1.9.3/repository.mli 0000644 0001750 0001750 00000007215 12657630652 014724 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module type S = sig
type pool
module Package : sig
type t
val compare : t -> t -> int
val print : pool -> Format.formatter -> t -> unit
val print_name : pool -> Format.formatter -> t -> unit
val index : t -> int
val of_index : int -> t
val of_index_list : int list -> t list
end
module PSet : Set.S with type elt = Package.t
module PMap : Map.S with type key = Package.t
val pset_indices : PSet.t -> Util.IntSet.t
module PTbl : sig
type 'a t
val create : pool -> 'a -> 'a t
val init : pool -> (Package.t -> 'a) -> 'a t
val get : 'a t -> Package.t -> 'a
val set : 'a t -> Package.t -> 'a -> unit
val iteri : (Package.t -> 'a -> unit) -> 'a t -> unit
val map : ('a -> 'b) -> 'a t -> 'b t
val mapi : (Package.t -> 'a -> 'b) -> 'a t -> 'b t
val copy : 'a t -> 'a t
end
module type DISJ = sig
type t
val print : ?compact:bool -> pool -> Format.formatter -> t -> unit
val implies : t -> t -> bool
val equiv : t -> t -> bool
val lit : Package.t -> t
val lit_disj : Package.t list -> t
val _false : t
val disj : t -> t -> t
end
module Disj : sig
include DISJ
val iter : t -> (Package.t -> unit) -> unit
val fold : (Package.t -> 'a -> 'a) -> t -> 'a -> 'a
val cut : t -> Package.t -> t -> t
val for_all : (Package.t -> bool) -> t -> bool
val exists : (Package.t -> bool) -> t -> bool
val filter : (Package.t -> bool) -> t -> t
val compare : t -> t -> int
val implies1 : Package.t -> t -> bool
val to_lit : t -> Package.t option
val to_lits : t -> PSet.t
val of_lits : PSet.t -> t
val diff : t -> t -> t
val disj1 : Package.t -> t -> t
val cardinal : t -> int
module Set : Set.S with type elt = t
end
module Formula : sig
include DISJ
val _true : t
val conj : t -> t -> t
val conjl : t list -> t
val implies1 : t -> Disj.t -> bool
val iter : t -> (Disj.t -> unit) -> unit
val of_disj : Disj.t -> t
val fold : (Disj.t -> 'a -> 'a) -> t -> 'a -> 'a
val filter : (Disj.t -> bool) -> t -> t
val exists : (Disj.t -> bool) -> t -> bool
val normalize : t -> t
end
type dependencies = Formula.t PTbl.t
module Conflict : sig
type t
val create : pool -> t
val check : t -> Package.t -> Package.t -> bool (*XXX rename in [mem]*)
val add : t -> Package.t -> Package.t -> unit
val remove : t -> Package.t -> Package.t -> unit
val iter : t -> (Package.t -> Package.t -> unit) -> unit
val copy : t -> t
val has : t -> Package.t -> bool
val of_package : t -> Package.t -> PSet.t
val iter_on_packages : t -> (Package.t -> PSet.t -> unit) -> unit
val exists : t -> (Package.t -> bool) -> Package.t -> bool
val for_all : t -> (Package.t -> bool) -> Package.t -> bool
end
end
module F : functor (M : Api.S) -> S with type pool = M.pool
coinst-1.9.3/quotient.ml 0000644 0001750 0001750 00000013346 12657630652 014206 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module S (R : Repository.S) = struct
module type S = sig
open R
type t
val perform : pool -> ?packages:PSet.t -> Formula.t PTbl.t -> t
val trivial : pool -> t
val subset : pool -> PSet.t -> t
val from_partition : pool -> PSet.t -> Package.t list list -> t
val formula : t -> Formula.t -> Formula.t
val dependencies : t -> dependencies -> dependencies
val conflicts : t -> Conflict.t -> Conflict.t
val package_set : t -> PSet.t -> PSet.t
val iter : (Package.t -> unit) -> t -> unit
val print : t -> dependencies -> unit
val print_class : t -> Format.formatter -> Package.t -> unit
val clss : t -> Package.t -> PSet.t
val class_size : t -> Package.t -> int
val pool : t -> pool
end
end
module F (R : Repository.S) = struct
open R
type t =
{ pool : pool;
count : int;
repr_tbl : Package.t PTbl.t;
repr_map : PSet.t PMap.t }
let trivial pool =
let count = ref 0 in
let repr_map = ref PMap.empty in
let repr_tbl =
PTbl.init pool
(fun p ->
incr count; repr_map := PMap.add p (PSet.singleton p) !repr_map; p)
in
{ pool = pool; count = !count; repr_tbl = repr_tbl; repr_map = !repr_map }
let subset pool s =
let count = ref 0 in
let repr_map = ref PMap.empty in
let repr_tbl =
PTbl.init pool
(fun p ->
if PSet.mem p s then begin
incr count; repr_map := PMap.add p (PSet.singleton p) !repr_map
end;
p)
in
{ pool = pool; count = !count; repr_tbl = repr_tbl; repr_map = !repr_map }
let from_partition pool pkgs partition =
let repr_tbl = PTbl.create pool (Package.of_index (-1)) in
let repr_map = ref PMap.empty in
List.iter
(fun l ->
let s = List.fold_left (fun s p -> PSet.add p s) PSet.empty l in
let s' = PSet.filter (fun p -> PSet.mem p pkgs) s in
if not (PSet.is_empty s') then begin
let p = PSet.choose s' in
repr_map := PMap.add p s !repr_map;
PSet.iter (fun q -> PTbl.set repr_tbl q p) s
end)
partition;
{ pool = pool; count = List.length partition;
repr_tbl = repr_tbl; repr_map = !repr_map }
let perform pool ?packages deps =
let classes_by_dep = Hashtbl.create 17 in
let class_count = ref 0 in
let add_package p f =
let f = Formula.normalize f in
let s =
try
Hashtbl.find classes_by_dep f
with Not_found ->
incr class_count;
let s = ref PSet.empty in
Hashtbl.add classes_by_dep f s;
s
in
s := PSet.add p !s
in
begin match packages with
None -> PTbl.iteri add_package deps
| Some s -> PSet.iter (fun p -> add_package p (PTbl.get deps p)) s
end;
(* Compute good representatives *)
let repr_tbl = PTbl.create pool (Package.of_index (-1)) in
let repr_map = ref PMap.empty in
Hashtbl.iter
(fun f {contents = s} ->
let s' =
Formula.fold (fun d s -> PSet.union (Disj.to_lits d) s)
f PSet.empty
in
let s' = PSet.inter s s' in
let p = try PSet.choose s' with Not_found -> PSet.choose s in
repr_map := PMap.add p s !repr_map;
PSet.iter (fun q -> PTbl.set repr_tbl q p) s)
classes_by_dep;
{pool = pool; count = !class_count;
repr_map = !repr_map; repr_tbl = repr_tbl}
let print_class quotient ch p =
let n = PSet.cardinal (PMap.find p quotient.repr_map) in
if n = 1 then
Format.fprintf ch "%a" (Package.print quotient.pool) p
else
Format.fprintf ch "%a (x %d)" (Package.print quotient.pool) p n
let print quotient deps =
(* Output equivalence classes *)
Util.title (Format.sprintf "EQUIVALENCE CLASSES (%d)" quotient.count);
PMap.iter
(fun p s ->
(* Skip the class of always installable packages *)
if not (Formula.implies Formula._true (PTbl.get deps p)) then begin
Format.printf "%a:" (print_class quotient) p;
PSet.iter
(fun q -> Format.printf " %a" (Package.print quotient.pool) q) s;
Format.printf "@."
end)
quotient.repr_map;
Format.printf "@."
let repr quotient p = PTbl.get quotient.repr_tbl p
let formula quotient f =
Formula.fold
(fun d f ->
Formula.conj
(Disj.fold
(fun p d -> Formula.disj (Formula.lit (repr quotient p)) d)
d Formula._false)
f)
f Formula._true
let dependencies quotient deps =
let class_deps = PTbl.create quotient.pool Formula._false in
PMap.iter
(fun p _ -> PTbl.set class_deps p (formula quotient (PTbl.get deps p)))
quotient.repr_map;
class_deps
let conflicts quotient confl =
let c = Conflict.create quotient.pool in
Conflict.iter confl
(fun p1 p2 -> Conflict.add c (repr quotient p1) (repr quotient p2));
c
let package_set quotient s =
PSet.fold (fun p s -> PSet.add (repr quotient p) s) s PSet.empty
let clss quotient p = PMap.find p quotient.repr_map
let class_size quotient p = PSet.cardinal (clss quotient p)
let iter f quotient = PMap.iter (fun p _ -> f p) quotient.repr_map
let pool q = q.pool
end
coinst-1.9.3/debug.mli 0000644 0001750 0001750 00000001606 12657630652 013571 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
val make : string -> string -> string list -> (unit -> bool)
val set : string -> unit
coinst-1.9.3/upgrade.mli 0000644 0001750 0001750 00000000673 12657630652 014135 0 ustar mehdi mehdi
type t
val compute :
Upgrade_common.ignored_sets -> ?popcon_file:string ->
Deb_lib.pool -> Deb_lib.pool ->
(Upgrade_common.Repository.Package.t ->
Layout.outside_anchor Layout.phrasing Layout.t) ->
t
val f :
Upgrade_common.ignored_sets -> ?popcon_file:string ->
Deb_lib.pool -> Deb_lib.pool -> string -> unit
val read_data : string -> Deb_lib.pool
val explanations : t -> _ Layout.flow Layout.t
val has_issues : t -> bool
coinst-1.9.3/cache.ml 0000644 0001750 0001750 00000005547 12657630652 013405 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let make_uid () =
let magic1 = 0xcab4ea850533f24dL in
let magic2 = 0xb517d4f5440b7995L in
Format.sprintf "%016Lx"
(Int64.logxor
(Int64.mul magic1 (Int64.of_float (1e6 *. Unix.gettimeofday ())))
(Int64.mul magic2 (Int64.of_int (Unix.getpid ()))))
let cache_disabled = ref false
let set_disabled b = cache_disabled := b
let recompute cache magic f ch =
begin match ch with Some ch -> close_in ch | None -> () end;
let res = f () in
let uid = make_uid () in
if not !cache_disabled then begin
let tmp = cache ^ ".tmp" in
Util.make_directories tmp;
let ch = open_out tmp in
output_string ch magic;
output_string ch uid;
Marshal.to_channel ch res [];
close_out ch;
Sys.rename tmp cache
end;
(res, uid)
let cached ?(force=false) files cache magic ?(is_valid=fun _ -> true) f =
let magic =
Format.sprintf
"This cache file can be safely removed at any time.\n%s\n%s\n\n"
magic (String.concat "\n" files)
in
let ch = try Some (open_in cache) with Sys_error _ -> None in
let should_compute =
!cache_disabled || force ||
match ch with
None ->
true
| Some ch ->
(try
let cache_time =
(Unix.fstat (Unix.descr_of_in_channel ch)).Unix.st_mtime in
List.exists
(fun file -> (Unix.stat file).Unix.st_mtime > cache_time)
files
with Unix.Unix_error (Unix.ENOENT, _, _) ->
true)
||
(try
let l = String.length magic in
let s = Bytes.create l in
really_input ch s 0 l;
(Bytes.to_string s) <> magic
with End_of_file ->
true)
in
if should_compute then
recompute cache magic f ch
else begin
match ch with
Some ch ->
let uid = Bytes.create 16 in
really_input ch uid 0 16;
let res = Marshal.from_channel ch in
close_in ch;
if is_valid res then
(res, Bytes.to_string uid)
else
recompute cache magic f None
| None ->
assert false
end
coinst-1.9.3/coinst.ml 0000644 0001750 0001750 00000122715 12657630652 013636 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
(*
./check_coinstall -ignore daemontools-run /var/lib/apt/lists/ftp.fr.debian.org_debian_dists_testing_main_binary-amd64_Packages -ignore liboss-salsa-asound2 -ignore libgd2-noxpm -ignore libqt4-phonon -ignore libjack-jackd2-0 -ignore libjpeg8-dev -ignore libhdf4-dev -ignore libgl1-mesa-swx11
*)
let mark_all = ref false
let mark_reversed = ref false
let grayscale = ref false
let explain = ref false
let roots = ref []
let stats = ref false
let graph = ref "graph.dot"
let conflict_file = ref None
let conflict_pairs_only = ref false
type output_type = Graph | Json
let output_type = ref Graph
(****)
let insert tbl x v =
let l =
try Hashtbl.find tbl x with Not_found ->
let l = ref [] in Hashtbl.add tbl x l; l
in
l := v :: !l
let get tbl x = try !(Hashtbl.find tbl x) with Not_found -> []
(****)
module F (M : Api.S) = struct
module Repository = Repository.F(M)
open Repository
module Quotient = Quotient.F (Repository)
module Graph = Graph.F (Repository)
module Json = Coinst_json.F (Repository)
(****)
let get_output_f () =
match !output_type with
| Graph -> Graph.output
| Json -> Json.output
let simplify_formula confl f =
Formula.filter
(fun d ->
Disj.for_all
(fun p ->
Conflict.exists confl (fun q -> not (Disj.implies1 q d)) p) d)
f
let filter_conflicts confl p f =
Formula.fold
(fun d nf ->
Formula.conj nf
(Formula.of_disj
(Disj.filter
(fun q ->
not (PSet.exists (fun r -> Formula.implies1 f (Disj.lit r))
(Conflict.of_package confl q)))
d)))
f Formula._true
let rec flatten_deps tbl dist deps conflicts visited l =
Formula.fold
(fun d (l, r) ->
let (l', r') =
Disj.fold
(fun i (l, r) ->
let (l', r') = flatten_dep tbl dist deps conflicts visited i in
(Formula.disj l' l, PSet.union r r')) d (Formula._false, r)
in
(Formula.conj l' l, r'))
l (Formula._true, PSet.empty)
and flatten_dep tbl dist deps conflicts visited i =
try
(Hashtbl.find tbl i, PSet.empty)
with Not_found ->
let res =
if List.mem i visited then
(Formula._true, PSet.singleton i)
else begin
let (l, r) =
flatten_deps tbl dist deps conflicts (i :: visited) (PTbl.get deps i)
in
let l = simplify_formula conflicts l in
(*???
let l = filter_conflicts conflicts i l in
*)
let r = PSet.remove i r in
if Conflict.has conflicts i then
(Formula.conj (Formula.lit i) l, r)
else
(l, r)
end
in
(* Only cache the result if it is unconditionally true *)
if PSet.is_empty (snd res) then Hashtbl.add tbl i (fst res);
res
let flatten_dependencies dist deps confl =
let tbl = Hashtbl.create 17 in
PTbl.init dist (fun p -> fst (flatten_dep tbl dist deps confl [] p))
(****)
let focus pool deps confl =
(*
- Map: i |-> (p, d)
-
*)
let large = false in
if !roots <> [] then begin
let i = ref (-1) in
let pieces = Hashtbl.create 101 in
let piece_conflicts = PTbl.create pool [] in
let package_pieces = PTbl.create pool [] in
let tbl_add tbl p v = PTbl.set tbl p (v :: PTbl.get tbl p) in
PTbl.iteri
(fun p f ->
Formula.iter f
(fun d ->
incr i;
Disj.iter d
(fun q -> tbl_add piece_conflicts q !i);
tbl_add package_pieces p !i;
Hashtbl.add pieces !i (p, d)))
deps;
let roots =
List.fold_left
(fun s nm ->
List.fold_left (fun s p -> PSet.add (Package.of_index p) s)
s (M.parse_package_name pool nm))
PSet.empty !roots
in
Format.eprintf "ROOTS: %d@." (PSet.cardinal roots);
let dp = deps in
let new_deps = PTbl.create pool Formula._true in
let new_confl = Conflict.create pool in
let visited = ref PSet.empty in
let packages = ref PSet.empty in
let rec add_conflict p =
Format.eprintf "ADD confl: %a@." (Package.print pool) p;
if not (PSet.mem p !visited) then begin
visited := PSet.add p !visited;
packages := PSet.add p !packages;
PTbl.set new_deps p
(Formula.conj (PTbl.get new_deps p) (Formula.lit p));
PSet.iter
(fun q ->
Format.eprintf "ADD confl: %a %a@." (Package.print pool) p (Package.print pool) q;
Conflict.add new_confl p q;
let l = PTbl.get piece_conflicts q in
packages := PSet.add q !packages;
List.iter (fun i -> add_piece (Some q) i) l)
(Conflict.of_package confl p)
end
and add_piece q i =
if large then begin
let (p, d) = Hashtbl.find pieces i in
let l = PTbl.get package_pieces p in
List.iter (fun i -> add_piece_2 q i) l
end else
add_piece_2 q i
and add_piece_2 q i =
let (p, d) = Hashtbl.find pieces i in
Format.eprintf "ADD piece: %a => %a@." (Package.print pool) p (Disj.print pool) d;
if
(*
true
*)
PSet.mem p roots ||
(*FIX: or any equivalent package... *)
not (Disj.exists (fun r -> PSet.mem r roots) d
||
(*FIX: or any equivalent package... *)
(Some p <> q &&
PSet.exists (fun r -> Conflict.check confl r p) roots)
)
then begin
packages := PSet.add p !packages;
PTbl.set new_deps p
(Formula.conj (PTbl.get new_deps p) (Formula.of_disj d));
Disj.iter d (fun r -> if Some r <> q then add_conflict r)
end
and add_dep p =
packages := PSet.add p !packages;
let l = PTbl.get package_pieces p in
List.iter
(fun i -> add_piece None i)
l
in
PSet.iter
(fun p ->
Format.eprintf "ADD root: %a ==> %a@." (Package.print pool) p (Formula.print pool) (PTbl.get dp p);
add_dep p;
(*
PSet.iter add_dep (Conflict.of_package confl p)
*)
)
roots;
Conflict.iter confl
(fun p q ->
if
PSet.mem p !packages &&
Formula.implies (PTbl.get new_deps p) (Formula.lit p) &&
PSet.mem q !packages &&
Formula.implies (PTbl.get new_deps q) (Formula.lit q)
then begin
Conflict.add new_confl p q;
end);
(*
*)
(Some !packages, new_deps, new_confl)
end else
(None, deps, confl)
(****)
(*
If a set of packages are not co-installable, then there is a minimal
set of dependencies and conflicts that make them incompatible. We
enumerate (an overapproximation) of all these minimal sets.
We define inductively *forced* dependencies and packages:
- a dependency d is forced when all packages p in d but at most one
are forced;
- a package p is forced when all dependencies d' such that there
exists a package p' in d' such that p conflicts wih p', either
d' is forced, or p in d'.
In a minimal set, if we have dependencies d, d' and packages p, p'
such that p in d, p' in d', p conflicts with p' and d' is forced,
then there are no other dependencies such that p'' in d'' and p''
conflicts with p.
In a minimal set, if we have dependencies d, d' and packages p, p'
such that p in d, p' in d', p conflicts with p' and p is forced,
then
1) d' is forced
2) p not in d'
3) there is no other dependency in a similar situation with respect
to p
4) p' is not forced (so all other packages in d' are forced)
XXX
*)
let debug_problems =
Debug.make "coinst_prob"
"Debug enumeration of possible co-installability issues" []
(*let _ = Debug.set "coinst_prob"*)
let debug = false
module IntSet = Util.IntSet
module ListTbl = Util.ListTbl
module PSetSet = Set.Make (PSet)
module PSetMap = Map.Make (PSet)
type st =
{ dist : M.pool; deps : Formula.t PTbl.t; confl : Conflict.t;
pieces : (int, Package.t * Disj.t) Hashtbl.t;
pieces_in_confl : (Package.t, int) ListTbl.t;
set : PSet.t; forced_deps : (int, Package.t option) Hashtbl.t;
forced_packages : PSet.t;
installed : IntSet.t; not_installed : IntSet.t;
check : PSet.t -> bool }
let print_prob st =
let space = String.make (2 * IntSet.cardinal st.installed) ' ' in
Format.eprintf "-------------------@.";
IntSet.iter
(fun i ->
let (p, d) = Hashtbl.find st.pieces i in
Format.eprintf "%s| %a => %a@." space
(Package.print_name st.dist) p
(Disj.print st.dist) d)
st.installed
let rec add_piece st i cont =
assert (not (IntSet.mem i st.installed || IntSet.mem i st.not_installed));
let (p, d) = Hashtbl.find st.pieces i in
(*
if debug(*_problems ()*) then
*)
(*
Format.printf "Considering %a => %a@."
(Package.print_name st.dist) p (Disj.print st.dist) d;
*)
if
(* We do not add a dependency if it is implied by, or implies, a
dependency currently under consideration. *)
not (IntSet.exists
(fun i' ->
let (_, d') = Hashtbl.find st.pieces i' in
Disj.implies d d' || Disj.implies d' d)
st.installed)
&&
(* When adding a package in st.set, we check that d is not implied
by any of the dependencies of a package already in st.set *)
(PSet.mem p st.set ||
not (PSet.exists
(fun p -> Formula.implies1 (PTbl.get st.deps p) d)
st.set))
&&
(* If we are adding a package, we check whether the set is still
co-installable *)
(PSet.mem p st.set || st.check (PSet.add p st.set))
then begin
if debug(*_problems ()*) then
Format.printf "Adding %a => %a@."
(Package.print_name st.dist) p (Disj.print st.dist) d;
let st =
{st with
set = PSet.add p st.set;
(*
forced =
(match Disj.to_lit d with
Some q -> PSet.union (Conflict.of_package st.confl q) st.forced
| None -> st.forced);
*)
installed = IntSet.add i st.installed}
in
(*
Format.eprintf "-";
IntSet.iter (fun i -> Format.eprintf " %d" i) st.installed;
Format.eprintf "@.";
*)
if debug(*_problems ()*) then print_prob st;
if false then print_prob st;
(* Make sure that there is at least one piece in conflict for all
dependencies, then consider all possible additions *)
Disj.fold
(fun p cont st ->
if
PSet.exists (fun q -> PSet.mem q st.forced_packages)
(Conflict.of_package st.confl p)
then
cont st
else
let st =
PSet.fold
(fun q st ->
List.fold_right
(fun j st ->
match
try
Hashtbl.find st.forced_deps j
with Not_found ->
None
with
Some q' when q' = q ->
let (_, d') = Hashtbl.find st.pieces j in
if Disj.implies1 p d' then st else
do_add_piece st q j cont
| _ ->
st)
(ListTbl.find st.pieces_in_confl q) st)
(Conflict.of_package st.confl p) st
in
PSet.fold
(fun q cont ->
List.fold_right
(fun j cont st ->
if Hashtbl.mem st.forced_deps j then
cont st
else
maybe_add_piece st j cont)
(ListTbl.find st.pieces_in_confl q) cont)
(Conflict.of_package st.confl p) cont st)
d
cont
st
end else
if debug(*_problems ()*) then
Format.printf "Could not add %a => %a@."
(Package.print_name st.dist) p (Disj.print st.dist) d;
and do_add_piece st q i cont =
if IntSet.mem i st.installed then begin
st
end else if not (IntSet.mem i st.not_installed) then begin
add_piece {st with forced_packages = PSet.add q st.forced_packages} i cont;
st(* {st with not_installed = IntSet.add i st.not_installed}*)
end else
st
and maybe_add_piece st i cont =
if
not (IntSet.mem i st.installed || IntSet.mem i st.not_installed)
then begin
add_piece st i cont;
cont {st with not_installed = IntSet.add i st.not_installed}
end else
cont st
let forced_deps confl pieces pieces_in_confl =
let forced = Hashtbl.create 101 in
while
let changed = ref false in
Hashtbl.iter
(fun i (p, d) ->
if not (Hashtbl.mem forced i) then begin
let forced_package q =
PSet.for_all
(fun q' ->
List.for_all
(fun i' ->
Hashtbl.mem forced i' ||
let (p', d') = Hashtbl.find pieces i' in
Disj.implies1 q d')
(ListTbl.find pieces_in_confl q'))
(Conflict.of_package confl q)
in
let floating_packages =
Disj.filter (fun q -> not (forced_package q)) d in
if Disj.implies floating_packages Disj._false then begin
Hashtbl.add forced i None; changed := true
end else
match Disj.to_lit floating_packages with
Some p -> Hashtbl.add forced i (Some p); changed := true
| None -> ()
end)
pieces;
!changed
do () done;
forced
(*
Hashtbl.iter
(fun i (p, d) ->
if not (Hashtbl.mem forced i) then begin
Format.eprintf "> %a => %a@."
(Package.print_name dist) p
(Disj.print dist) d;
Disj.iter d (fun q ->
PSet.iter
(fun q' ->
try
let i' =
List.find
(fun i' ->
not (Hashtbl.mem forced i' ||
let (p', d') = Hashtbl.find pieces i' in
Disj.implies1 q d'))
(ListTbl.find pieces_in_confl q')
in
let (p, d) = Hashtbl.find pieces i' in
Format.eprintf "(%a => %a)@."
(Package.print_name dist) p
(Disj.print dist) d
with Not_found -> ())
(Conflict.of_package confl q))
end)
pieces;
let deps = PTbl.create (Quotient.pool quotient) Formula._true in
Hashtbl.iter
(fun i (p, d) ->
if not (Hashtbl.mem forced i) then
PTbl.set deps p (Formula.conj (PTbl.get deps p) (Formula.of_disj d)))
pieces;
Graph.output "/tmp/floating.dot" ~mark_all:false
~grayscale:(!grayscale)
quotient deps confl
*)
let find_problems quotient deps confl check =
let dist = Quotient.pool quotient in
let pieces = Hashtbl.create 101 in
let last_piece = ref (-1) in
let pieces_in_confl = ListTbl.create 101 in
Quotient.iter
(fun p ->
let f = PTbl.get deps p in
Formula.iter f
(fun d ->
incr last_piece;
let i = !last_piece in
Hashtbl.add pieces i (p, d);
Disj.iter d (fun p -> ListTbl.add pieces_in_confl p i)))
quotient;
let forced = forced_deps confl pieces pieces_in_confl in
let st =
{ dist = dist; deps = deps; confl = confl;
pieces = pieces; pieces_in_confl = pieces_in_confl;
set = PSet.empty; forced_packages = PSet.empty;
forced_deps = forced; check = check;
installed = IntSet.empty; not_installed = IntSet.empty }
in
let st = ref st in
for i = 0 to !last_piece do
add_piece !st i (fun _ -> ());
if None = try Hashtbl.find forced i with Not_found -> None then begin
st := {!st with not_installed = IntSet.add i (!st).not_installed}
end
done
let enumerate_non_coinstallable_sets quotient deps confl st =
let dist = Quotient.pool quotient in
let results = ref PSetSet.empty in
let add_result s =
if not (PSetSet.mem s !results) then begin
if debug_problems () then begin
Format.eprintf "==>";
PSet.iter
(fun p -> Format.eprintf " %a" (Package.print_name dist) p) s;
Format.eprintf "@."
end;
results := PSetSet.add s !results
end else
if debug then Format.printf "Already considered@."
in
let installable_status = ref PSetMap.empty in
let check s =
let is_installable s =
try PSetMap.find s !installable_status with Not_found ->
let res =
M.Solver.solve_lst st (List.map Package.index (PSet.elements s)) in
M.Solver.reset st;
installable_status := PSetMap.add s res !installable_status;
res
in
if is_installable s then begin
if debug then begin
Format.printf "Still co-installable:";
List.iter (fun p -> Format.printf " %a" (Package.print_name dist) p)
(PSet.elements s);
Format.printf "@.";
end;
true
end else begin
if
PSet.exists (fun p -> not (is_installable (PSet.remove p s))) s
then begin
if debug_problems () then begin
Format.eprintf "Not minimal:";
List.iter (fun p -> Format.eprintf " %a" (Package.print_name dist) p)
(PSet.elements s);
Format.eprintf "@.";
end
end else begin
add_result s
end;
false
end
in
find_problems quotient deps confl check;
!results
(****)
let read_data ignored_packages ic =
let dist = M.new_pool () in
M.parse_packages dist ignored_packages ic;
let confl = Conflict.create dist in
let c = M.compute_conflicts dist in
Array.iteri
(fun p1 l ->
List.iter
(fun p2 ->
Conflict.add confl
(Package.of_index p1) (Package.of_index p2))
l)
c;
let deps =
let d = M.compute_deps dist in
PTbl.init dist
(fun p ->
Formula.conjl
(List.map (fun l' -> Formula.lit_disj (Package.of_index_list l'))
d.(Package.index p)))
in
(dist, deps, confl)
let print_problem quotient deps confl =
let dist = Quotient.pool quotient in
Quotient.iter
(fun p ->
let f = PTbl.get deps p in
Format.eprintf "%a => %a@."
(Package.print dist) p (Formula.print dist) f)
quotient;
Conflict.iter confl
(fun p1 p2 ->
Format.eprintf "%a ## %a@."
(Package.print dist) p1 (Package.print dist) p2)
let generate_rules quotient deps confl =
let dist = Quotient.pool quotient in
let st =
M.Solver.initialize_problem
~print_var:(M.print_pack dist) (M.pool_size dist) in
Conflict.iter confl
(fun p1 p2 ->
let p1 = M.Solver.lit_of_var (Package.index p1) false in
let p2 = M.Solver.lit_of_var (Package.index p2) false in
M.Solver.add_rule st [|p1; p2|] []);
Quotient.iter
(fun p ->
let f = PTbl.get deps p in
Formula.iter f
(fun d ->
let l = Disj.to_lits d in
if not (PSet.mem p l) then begin
let l = List.map (fun p -> Package.index p) (PSet.elements l) in
M.Solver.add_rule st
(Array.of_list
(M.Solver.lit_of_var (Package.index p) false ::
List.map (fun p -> M.Solver.lit_of_var p true) l))
[];
match l with
[] | [_] ->
()
| _ ->
M.Solver.associate_vars st
(M.Solver.lit_of_var (Package.index p) true) l
end))
quotient;
st
(****)
let remove_redundant_conflicts dist deps confl =
let conj_deps p =
let f = PTbl.get deps p in
Formula.fold
(fun d s -> match Disj.to_lit d with Some p -> PSet.add p s | None -> s)
f PSet.empty
in
Conflict.iter confl
(fun p1 p2 ->
let d1 = conj_deps p1 in
let d2 = conj_deps p2 in
if
PSet.exists
(fun q1 ->
PSet.exists
(fun q2 ->
(p1 <> q1 || p2 <> q2) &&
(p1 <> q2 || p2 <> q1) &&
Conflict.check confl q1 q2)
d2)
d1
then begin
(*
Format.eprintf "%a ## %a@."
(Package.print dist) p1 (Package.print dist) p2;
*)
Conflict.remove confl p1 p2
end);
let try_remove_conflict p1 p2 =
let f1 = PTbl.get deps p1 in
let d2 = conj_deps p2 in
if
Formula.exists
(fun d1 ->
Disj.for_all
(fun q1 ->
PSet.exists
(fun q2 ->
(p1 <> q1 || p2 <> q2) &&
(p1 <> q2 || p2 <> q1) &&
Conflict.check confl q1 q2)
d2)
d1)
f1
then begin
(*
Format.eprintf "%a ## %a@."
(Package.print dist) p1 (Package.print dist) p2;
*)
Conflict.remove confl p1 p2
end
in
Conflict.iter confl try_remove_conflict;
Conflict.iter confl (fun p1 p2 -> try_remove_conflict p2 p1);
(* We may now be able to remove some dependencies *)
PTbl.map (simplify_formula confl) deps
(****)
let remove_self_conflicts dist deps confl =
let s = ref PSet.empty in
PTbl.iteri
(fun p f ->
if Formula.exists (fun d -> match Disj.to_lit d with Some q -> Conflict.check confl p q | None -> false) f then
s := PSet.add p !s)
deps;
(*
PSet.iter (fun p -> Format.eprintf "SELF CONFLICT: %a@." (Package.print dist) p) !s;
*)
PTbl.map
(fun f ->
Formula.fold
(fun d f ->
let d = Disj.filter (fun q -> not (PSet.mem q !s)) d in
Formula.conj (Formula.of_disj d) f)
f Formula._true)
deps
(****)
module DepMap = Map.Make (Disj)
module DepSet = Set.Make (Disj)
let coinstallability_kernel quotient deps confl =
let deps_of_confl = PTbl.create (Quotient.pool quotient) DepSet.empty in
let all_deps = ref DepSet.empty in
PTbl.iteri
(fun p f ->
Formula.iter f
(fun d ->
all_deps := DepSet.add d !all_deps;
Disj.iter d
(fun p ->
PTbl.set deps_of_confl p
(DepSet.add d (PTbl.get deps_of_confl p)))))
deps;
let forced_deps = ref DepSet.empty in
let updated = ref false in
let update_dep d =
if not (DepSet.mem d !forced_deps) then begin
(*
Format.eprintf "Checking %a@." (Disj.print (Quotient.pool quotient)) d;
*)
let c =
Disj.fold
(fun p n ->
if n > 1 then n else begin
if
Conflict.for_all confl
(fun p' ->
(*
DepSet.iter (fun d ->
let pool = Quotient.pool quotient in
Format.eprintf "%a # %a => %a %b@." (Package.print pool) p (Package.print pool) p' (Disj.print pool) d (DepSet.mem d !forced_deps)) (PTbl.get deps_of_confl p');
*)
Disj.implies1 p' d
||
DepSet.for_all
(fun d' ->
Disj.equiv d' d (*XXX implies?*)
||
Disj.implies1 p d'
||
DepSet.mem d' !forced_deps)
(PTbl.get deps_of_confl p')
(*
DepSet.subset (DepSet.remove d (PTbl.get deps_of_confl p')) !forced_deps
*)
)
p
then
n
else
1 + n
end)
d 0
in
Format.eprintf "Checked (%d) %a@." c (Disj.print (Quotient.pool quotient)) d;
if c <= 1 then begin
updated := true;
Format.eprintf "Forced: %a@." (Disj.print (Quotient.pool quotient)) d;
forced_deps := DepSet.add d !forced_deps
end
end
in
prerr_endline "========================================";
while
updated := false;
DepSet.iter update_dep !all_deps;
prerr_endline "========================================";
!updated
do () done;
DepSet.iter
(fun d ->
if not (DepSet.mem d !forced_deps) then
Format.eprintf "Not forced: %a@."
(Disj.print (Quotient.pool quotient)) d)
!all_deps;
let deps' = PTbl.create (Quotient.pool quotient) Formula._true in
Quotient.iter
(fun p ->
PTbl.set deps' p
(Formula.filter
(fun d -> not (DepSet.mem d !forced_deps))
(PTbl.get deps p)))
quotient;
let targets = ref PSet.empty in
DepSet.iter
(fun d ->
if not (DepSet.mem d !forced_deps) then
Disj.iter d (fun p -> targets := PSet.add p !targets))
!all_deps;
let confl' = Conflict.create (Quotient.pool quotient) in
Conflict.iter confl
(fun p p' ->
if PSet.mem p !targets || PSet.mem p' !targets then
Conflict.add confl' p p');
(deps', confl')
(****)
let array_mean a =
let c = ref 0 in
let s = ref 0 in
for i = 0 to Array.length a - 1 do
let (u, v) = a.(i) in
c := !c + u;
s := !s + u * v
done;
float !s /. float !c
let array_median a =
let c = ref 0 in
for i = 0 to Array.length a - 1 do
let (u, v) = a.(i) in
c := !c + u
done;
let i = ref 0 in
let s = ref 0 in
while !s < (!c + 1) / 2 do
let (u, v) = a.(!i) in
s := !s + u;
incr i
done;
snd a.(!i - 1)
let rec cone deps s p =
if PSet.mem p s then s else
let s = PSet.add p s in
Formula.fold (fun d s -> Disj.fold (fun q s -> cone deps s q) d s)
(PTbl.get deps p) s
let conflicts_count confl s =
let count = ref 0 in
PSet.iter (fun p -> if Conflict.has confl p then incr count) s;
!count
let output_cone f pool deps confl p s =
(*
Format.eprintf "== %a ==@." (Package.print pool) p;
*)
let quotient = Quotient.subset pool s in
let cfl = Conflict.create pool in
Conflict.iter
confl
(fun p q -> if PSet.mem p s && PSet.mem q s then Conflict.add cfl p q);
let output_f = get_output_f () in
output_f f ~mark_all:true
~package_weight:(fun p -> if Conflict.has confl p then 1000. else 1.)
~edge_color:(fun _ _ _ -> Some "blue") quotient deps cfl
let print_stats f txt quotient deps confl =
let pkgs = ref 0 in
let dps = ref 0 in
let cones = ref [] in
let confls = ref 0 in
Quotient.iter
(fun p ->
incr pkgs;
let c = cone deps PSet.empty p in
let sz = PSet.cardinal c in
let ncfl = conflicts_count confl c in
if sz <= 38 && sz > 20 && ncfl = 3 then
output_cone "/tmp/cone.dot" (Quotient.pool quotient) deps confl p c;
cones :=
(1 (*Quotient.class_size quotient p*),
sz, ncfl) ::
!cones;
Formula.iter (PTbl.get deps p) (fun d -> if not (Disj.implies1 p d) then incr dps))
quotient;
Conflict.iter confl (fun _ _ -> incr confls);
let cones = Array.of_list !cones in
Array.sort (fun (_, x, _) (_, y, _) -> compare y x) cones;
let ch = open_out (Format.sprintf "/tmp/%s.txt" f) in
let s = ref 0 in
for i = 0 to Array.length cones - 1 do
let (w, sz, ncfl) = cones.(i) in
Printf.fprintf ch "%d %d %d\n" !s sz ncfl;
s := !s + w;
if i = Array.length cones - 1 then
Printf.fprintf ch "%d %d\n" !s sz
done;
close_out ch;
let cones = Array.map (fun (w, sz, _) -> (w, sz)) cones in
Format.eprintf "%s: %d package, %d dependencies, %d conflicts; cone size: %d / %f / %d@."
txt !pkgs !dps !confls (snd cones.(0))
(array_mean cones) (array_median cones)
(****)
let f ignored_packages ic =
let (dist, deps, confl) = read_data ignored_packages ic in
if !stats then
print_stats "initial" "Initial repository"
(Quotient.trivial dist) deps confl;
let flatten_deps = flatten_dependencies dist deps confl in
(*XXX FIX: should iterate... *)
let flatten_deps = remove_self_conflicts dist flatten_deps confl in
let flatten_deps = remove_redundant_conflicts dist flatten_deps confl in
let flatten_deps = flatten_dependencies dist flatten_deps confl in
let maybe_remove fd2 p f d =
Disj.exists (fun q ->
Conflict.for_all confl (fun r ->
Formula.exists (fun d' -> Disj.implies d' d && not (Disj.implies1 q d')) (PTbl.get fd2 r)) q
(*
&& (
Format.eprintf "%a =>(%a) %a@." (Package.print dist) p (Package.print dist) q (Disj.print dist) d;
true)
*)
) d
in
let is_composition fd2 p f d =
Formula.exists (fun d' ->
not (Disj.equiv d d') && not (Disj.equiv (Disj.lit p) d') &&
(
let f =
Disj.fold (fun p f -> Formula.disj (PTbl.get fd2 p) f) d' Formula._false
in
let res1 =
Formula.exists (fun d'' -> Disj.implies d d'') f
in
(*
let res2 =
not (Formula.implies (Formula.filter (fun d' -> not (Disj.equiv d d')) f) f)
in
let res =
Disj.exists (fun q ->
Formula.exists (fun d'' ->
Disj.implies d (Disj.cut d' q d'')) (PTbl.get fd2 q)) d'
in
if res1 <> res2 then begin
Format.eprintf "??? %b %b@." res1 res2
end;
*)
(*
if res <> res1 then begin
(*
Format.eprintf "%a : %a => %a@." (Package.print dist) p
(Disj.print dist) d (Formula.print dist) f;
Disj.iter d' (fun q ->
if not (Formula.exists (fun d'' -> Disj.equiv (Disj.lit q) d'') (PTbl.get fd2 q)) then
Format.eprintf "!!! %a => %a@." (Package.print dist) q (Formula.print dist) (PTbl.get fd2 q);
Formula.iter (PTbl.get fd2 q) (fun d'' ->
if Disj.implies d (Disj.cut d' q d'')
then Format.eprintf "%a <= %a / %a / %a@." (Disj.print dist) d (Disj.print dist) d' (Package.print dist) q (Disj.print dist) d''
));
*)
Format.eprintf "!!! %b %b %b@." res res1 res2
end;
*)
res1
)
) f
in
(*
PTbl.iteri (fun p f ->
Formula.iter f (fun d -> if Conflict.exists confl (fun q -> Disj.implies1 q d) p then Format.eprintf "YYY %a ==> %a@." (Package.print dist) p (Disj.print dist) d
)) fd2;
*)
let rec remove_deps deps =
let changed = ref false in
let deps =
PTbl.mapi
(fun p f ->
Formula.filter (fun d ->
let b =
not (maybe_remove deps p f d) || is_composition deps p f d
in
if not b then changed := true;
b) f)
deps
in
if !changed then remove_deps deps else deps
in
let fd2 = remove_deps flatten_deps in
(*
PTbl.iteri
(fun p f ->
Formula.iter f (fun d ->
if maybe_remove fd2 p f d then
Format.eprintf "REM %a: %a (%a)@." (Package.print dist) p (Disj.print dist) d (Formula.print dist) f)) fd2;
*)
(*??? Need to adapt other checks... (also, conflict to uninstallable package)
let fd2 = PTbl.mapi (fun p f -> filter_conflicts confl p f) fd2 in
*)
(*
enumerate_non_coinstallable_sets dist fd2 confl
(generate_rules (Quotient.trivial dist) fd2 confl);
*)
(*XXXXX
Build equivalence classes
Focus up to equivalence
Build equivalence classes on package in focus
*)
let (domain, fd2, confl) = focus dist fd2 confl in
(* Build package equivalence classes *)
let quotient = Quotient.perform dist fd2 in
let deps = Quotient.dependencies quotient fd2 in
let confl = Quotient.conflicts quotient confl in
Quotient.print quotient deps;
(* Generate SAT problem *)
(*
let st = M.generate_rules dist in
*)
(*XXX FIX: should consider *all* packages, not just the ones we focus on*)
let st = generate_rules quotient deps confl in
(*
print_problem quotient fd2 confl;
*)
let st' = if !explain then Some (M.generate_rules dist) else None in
(*
let no_deps = PTbl.create dist Formula._true in
let all_confl = Conflict.create dist in
PSetSet.iter
(fun s ->
match PSet.elements s with
[q; q'] -> Conflict.add all_confl q q'
| [q] -> PTbl.set no_deps q Formula._false
| _ -> ())
sets;
*)
Util.title "NON-INSTALLABLE PACKAGES";
let non_inst = ref PSet.empty in
let is_installable i = not (PSet.mem i !non_inst) in
Quotient.iter
(fun p ->
let i = Package.index p in
if not (M.Solver.solve st i) then begin
Format.printf "%a@." (Quotient.print_class quotient) p;
begin match st' with
Some st' ->
PSet.iter
(fun p ->
let i = Package.index p in
ignore (M.Solver.solve st' i);
M.show_reasons dist (M.Solver.collect_reasons st' i);
M.Solver.reset st')
(Quotient.clss quotient p)
| None ->
()
end;
non_inst := PSet.add p !non_inst
end;
M.Solver.reset st)
quotient;
Format.printf "@.";
Util.title "NON-COINSTALLABLE PAIRS";
let dep_tbl = Hashtbl.create 101 in
let confl_tbl = Hashtbl.create 101 in
Quotient.iter
(fun p ->
if is_installable p then begin
let f = PTbl.get deps p in
Formula.iter f
(fun d ->
Disj.iter d
(fun q ->
if is_installable q then begin
insert dep_tbl q p;
PSet.iter
(fun r ->
if is_installable r then insert confl_tbl r p)
(Conflict.of_package confl q)
end))
end)
quotient;
let pairs = Hashtbl.create 101 in
let c = ref 0 in
let c' = ref 0 in
let c'' = ref 0 in
let conflicts = Hashtbl.create 101 in
(*
let coinstallable_pairs = ref PSetSet.empty in
*)
let non_coinstallable_pairs = ref PSetSet.empty in
Hashtbl.iter
(fun p l ->
let l' = get dep_tbl p in
List.iter
(fun p ->
let i = Package.index p in
List.iter
(fun q ->
let j = Package.index q in
let pair = (min i j, max i j) in
if i <> j && not (Hashtbl.mem pairs pair) then begin
Hashtbl.add pairs pair ();
if M.Solver.solve_lst st [i; j] then begin
((*
coinstallable_pairs :=
PSetSet.add (PSet.add i (PSet.singleton j))
!coinstallable_pairs
*))
end else begin
incr c'';
let r =
match st' with
Some st' ->
ignore (M.Solver.solve_lst st' [i; j]);
let r = M.Solver.collect_reasons_lst st' [i; j] in
M.Solver.reset st';
r
| None ->
[]
in
insert conflicts p (q, r);
insert conflicts q (p, r);
(*
*)
non_coinstallable_pairs :=
PSetSet.add (PSet.add p (PSet.singleton q))
!non_coinstallable_pairs
end;
M.Solver.reset st;
incr c'
end)
l')
!l;
c := !c + List.length !l * List.length l')
confl_tbl;
(*
if !debug then Format.eprintf "Pairs: %d - %d - %d@." !c !c' !c'';
*)
let cl = ref [] in
Hashtbl.iter
(fun i l ->
let c = ref 0 in
List.iter (fun (j, _) -> c := !c + Quotient.class_size quotient j) !l;
cl := (!c, (i, !l)) :: !cl)
conflicts;
let sort l = List.sort (fun (c, _) (c', _) -> - compare c c') l in
List.iter
(fun (c, (i, l)) ->
Format.printf "%d %a:" c (Quotient.print_class quotient) i;
let l =
sort (List.map
(fun (j, r) -> (Quotient.class_size quotient j, (j, r))) l)
in
let nf = ref false in
List.iter
(fun (c, (j, _)) ->
if !nf then Format.printf ","; nf := true;
Format.printf " %a" (Quotient.print_class quotient) j) l;
Format.printf "@.";
List.iter (fun (_, (_, r)) -> if r <> [] then M.show_reasons dist r) l)
(sort !cl);
let pw =
List.fold_left
(fun m (c, (p, _)) -> PMap.add p (max 1. (float c /. 4.)) m)
PMap.empty !cl
in
Format.printf "@.";
let sets =
if !conflict_pairs_only then
!non_coinstallable_pairs
else
enumerate_non_coinstallable_sets quotient fd2 confl st
in
if not !conflict_pairs_only then
begin
Util.title "LARGER NON-INSTALLABLE SETS";
PSetSet.iter
(fun s ->
if PSet.cardinal s > 2 then begin
let first = ref true in
PSet.iter
(fun p ->
if not !first then Format.printf " ";
Format.printf "%a" (Package.print_name dist) p;
first := false)
s;
Format.printf "@."
end)
sets;
assert (PSetSet.subset !non_coinstallable_pairs sets)
end;
(******************
let (deps, confl) = coinstallability_kernel quotient deps confl in
******************)
let comp_count = ref 0 in
let comps = Hashtbl.create 107 in
Quotient.iter
(fun p ->
let f = PTbl.get deps p in
Formula.iter f
(fun d -> if is_composition deps p (PTbl.get deps p) d then begin
incr comp_count;
Hashtbl.add comps (p, d) ()
end))
quotient;
(*
Format.eprintf "Comp count: %d@." !comp_count;
*)
let comp_count = ref 0 in
let rec remove_composition deps =
(*
prerr_endline "COMP";
*)
let changed = ref false in
Quotient.iter
(fun p ->
let found = ref false in
PTbl.set deps p
(Formula.filter
(fun d ->
!found || begin
let b = is_composition deps p (PTbl.get deps p) d in
found := b;
if !found then begin changed := true; incr comp_count end;
not b
end)
(PTbl.get deps p)))
quotient;
if !changed then remove_composition deps
in
remove_composition deps;
(*
Format.eprintf "Comp count: %d@." !comp_count;
*)
let comp_count = ref 0 in
(* let comps = Hashtbl.create 107 in*)
Quotient.iter
(fun p ->
let f = PTbl.get deps p in
Formula.iter f
(fun d -> if is_composition deps p (PTbl.get deps p) d then begin
incr comp_count;
(* Hashtbl.add comps (p, d) ()*)
end))
quotient;
(*
Format.eprintf "Comp count: %d@." !comp_count;
*)
let package_weight p = try PMap.find p pw with Not_found -> 1. in
let edge_color p f d =
(*
if (*maybe_remove deps p f d &&*) (*is_composition deps p f d*)
Hashtbl.mem comps (p, d)
then
Some "violet"
else
*)
Some "blue"
in
if !stats then
print_stats "final" "Final repository" quotient deps confl;
let output_f = get_output_f () in
output_f !graph ~mark_all:(!mark_all) ~mark_reversed:(!mark_reversed)
~grayscale:(!grayscale) ~package_weight ~edge_color
quotient deps confl;
(*
Graph.output "/tmp/conflicts.dot" ~mark_all:true
~grayscale:(!grayscale) ~package_weight ~edge_color
quotient no_deps all_confl;
*)
begin match !conflict_file with
None ->
()
| Some f ->
Json.output_non_coinstallable_sets f quotient (PSetSet.elements sets)
end
end
type kind = Cudf | Deb | Rpm | Auto
let _ =
let ignored_packages = ref [] in
let kind = ref Auto in
let files = ref [] in
Arg.parse
(Arg.align
["-cudf",
Arg.Unit (fun () -> kind := Cudf),
" Parse CUDF files";
"-rpm",
Arg.Unit (fun () -> kind := Rpm),
" Parse hdlist.cz (RPM) files";
"-deb",
Arg.Unit (fun () -> kind := Deb),
" Parse (Debian) binary package control files (default)";
"-o",
Arg.String (fun f -> graph := f),
"FILE Output graph to file FILE";
"-ignore",
Arg.String (fun p -> ignored_packages := p :: !ignored_packages),
"PACKAGE Ignore package of name PACKAGE";
(*
"-max",
Arg.Int (fun n -> max_size := n),
"N Limit to the size of non-coinstallable sets searched (default: 2)";
"-graph",
Arg.String (fun f -> graph_file := Some f),
"FILE Output coinstallability graph to file FILE";
*)
"-all",
Arg.Unit (fun () -> mark_all := true),
" Include all packages in the coinstallability graph";
"-only_simple",
Arg.Unit (fun () -> mark_reversed := true),
" Only input configurations involving only conflicts";
"-grayscale",
Arg.Unit (fun () -> grayscale := true),
" Output a grayscale graph";
"-root",
Arg.String (fun p -> roots := p :: !roots),
"PACKAGE Draw only the relevant portion of the graph around this package";
"-explain",
Arg.Unit (fun () -> explain := true),
" Explain the results";
"-stats",
Arg.Unit (fun () -> stats := true),
" Output stats regarding the input and output repositories";
"-json",
Arg.Unit (fun () -> output_type := Json),
" Output a JSON file instead of a graph";
"-conflicts",
Arg.String (fun f -> conflict_file := Some f),
"FILE Output all minimal non co-installable set of packages to FILE";
"-conflict-pairs-only",
Arg.Unit (fun () -> conflict_pairs_only := true),
" Do not try to enumerate all minimal conflict sets: compute only conflict pairs.";
(*
"-debug",
Arg.Unit (fun () -> debug := true),
" Output debugging informations";
*)
])
(fun p -> files := p :: !files)
("Usage: " ^ Sys.argv.(0) ^ " OPTIONS INPUT-FILES\n\
Analyze package coinstallability. Package information is read from\n\
the given input files. If none are provided, it is read from the\n\
standard input instead.\n\
\n\
Options:");
let ic =
if !files = [] then File.filter stdin else
File.open_in_multiple (List.rev !files)
in
let kind =
if !kind = Auto && File.has_magic ic "\142\173\232" then Rpm else !kind in
match kind with
Cudf -> let module M = F(Cudf_lib) in M.f !ignored_packages ic
| Auto | Deb -> let module M = F(Deb_lib) in M.f !ignored_packages ic
| Rpm -> let module M = F(Rpm_lib) in M.f !ignored_packages ic
coinst-1.9.3/task_stubs.c 0000644 0001750 0001750 00000000355 12657630652 014326 0 ustar mehdi mehdi #include
#include "caml/mlvalues.h"
CAMLprim value task_processor_count (value unit) {
long v;
#ifdef _SC_NPROCESSORS_ONLN
v = sysconf (_SC_NPROCESSORS_ONLN);
#else
v = 1;
#endif
return Val_long ((v<=0)?1:v);
}
coinst-1.9.3/Makefile 0000644 0001750 0001750 00000005572 12657630652 013446 0 ustar mehdi mehdi VERSION=1.9.3
COINST=coinst
UPGRADE=coinst-upgrades
TRANS=comigrate
OCAMLC=ocamlfind ocamlc
OCAMLOPT=ocamlfind ocamlopt
OCAMLDEP=ocamldep
OCAMLYACC=ocamlyacc
OCAMLLEX=ocamllex
TASK = bytearray_stubs.o bytearray.cmx task_stubs.o task.cmx
SVG=viewer/scene.cmx viewer/dot_parser.cmx viewer/dot_lexer.cmx \
viewer/dot_graph.cmx viewer/dot_render.cmx viewer/scene_svg.cmx \
viewer/dot_file.cmx
OBJS = ptset.cmx util.cmx file.cmx debug.cmx common.cmx cache.cmx layout.cmx \
solver.cmx api.cmx deb_lib.cmx rpm_lib.cmx \
repository.cmx quotient.cmx conflicts.cmx graph.cmx coinst_common.cmx
COMPFLAGS=-package unix,str,bigarray,cudf -g -I viewer -annot -bin-annot -safe-string
OPTLINKFLAGS=$(COMPFLAGS) -linkpkg
BYTELINKFLAGS=$(OPTLINKFLAGS) -dllib -lbytearray_stubs -cclib -lbytearray_stubs -dllib -ltask_stubs -cclib -ltask_stubs
OCAMLDEP=ocamlfind ocamldep
DEPFLAGS = -package js_of_ocaml,js_of_ocaml.syntax -syntax camlp4o -I viewer
all: $(COINST) $(UPGRADE) $(TRANS)
opt: all
byte: dllbytearray_stubs.so dlltask_stubs.so $(COINST).byte $(UPGRADE).byte $(TRANS).byte
dllbytearray_stubs.so: bytearray_stubs.o
ocamlmklib -o bytearray_stubs $^
dlltask_stubs.so: task_stubs.o
ocamlmklib -o task_stubs $^
$(COINST): $(OBJS) cudf_lib.cmx coinst_json.cmx coinst.cmx
$(OCAMLOPT) -o $@ $(OPTLINKFLAGS) $^ $(LINKFLAGS)
$(COINST).byte: $(OBJS:.cmx=.cmo) cudf_lib.cmo coinst_json.cmo coinst.cmo
$(OCAMLC) -o $@ $(BYTELINKFLAGS) $^ $(LINKFLAGS)
cp $@ $(COINST)
$(UPGRADE): $(OBJS) $(TASK) $(SVG) upgrade_common.cmx upgrade.cmx upgrade_main.cmx
$(OCAMLOPT) -o $@ $(OPTLINKFLAGS) $^ $(LINKFLAGS)
$(UPGRADE).byte: $(OBJS:.cmx=.cmo) $(TASK:.cmx=.cmo) $(SVG:.cmx=.cmo) upgrade_common.cmo upgrade.cmo upgrade_main.cmo
$(OCAMLC) -o $@ $(BYTELINKFLAGS) $^ $(LINKFLAGS)
cp $@ $(UPGRADE)
$(TRANS): $(OBJS) $(TASK) $(SVG) update_data.cmx upgrade_common.cmx upgrade.cmx horn.cmx transition.cmx
$(OCAMLOPT) -o $@ $(OPTLINKFLAGS) $^ $(LINKFLAGS)
$(TRANS).byte: $(OBJS:.cmx=.cmo) $(TASK:.cmx=.cmo) $(SVG:.cmx=.cmo) update_data.cmo upgrade_common.cmo upgrade.cmo horn.cmo transition.cmo
$(OCAMLC) -o $@ $(BYTELINKFLAGS) $^ $(LINKFLAGS)
cp $@ $(TRANS)
clean::
rm -f $(COINST) $(UPGRADE) $(TRANS) $(COINST).byte $(UPGRADE).byte $(TRANS).byte
#####
clean::
find . -regex ".*\\.\(cm[toix].?\|o\|annot\)" | xargs rm -f
.SUFFIXES: .cmo .cmi .cmx .ml .mli .mly .mll .idl .o .c
.ml.cmx:
$(OCAMLOPT) $(OPTCOMPFLAGS) $(COMPFLAGS) -c $<
.ml.cmo:
$(OCAMLC) $(BYTECOMPFLAGS) $(COMPFLAGS) -c $<
.mli.cmi:
$(OCAMLC) $(COMPFLAGS) -c $<
.idl.ml:
$(OCAMLIDL) $<
.mly.ml:
$(OCAMLYACC) $<
.mly.mli:
$(OCAMLYACC) $<
.mll.ml:
$(OCAMLLEX) $<
.c.o:
$(OCAMLC) -ccopt "-o $@" $(COMPFLAGS) -ccopt "$(CFLAGS)" -c $<
depend: viewer/dot_parser.ml viewer/dot_lexer.ml
ls *.ml *.mli viewer/*.ml viewer/*.mli | \
xargs $(OCAMLDEP) $(DEPFLAGS) > .depend
include .depend
####
release:
darcs dist -d coinst-$(VERSION)
coinst-1.9.3/ptset.ml 0000644 0001750 0001750 00000052021 12657630652 013466 0 ustar mehdi mehdi (**************************************************************************)
(* *)
(* Copyright (C) Jean-Christophe Filliatre *)
(* *)
(* This software is free software; you can redistribute it and/or *)
(* modify it under the terms of the GNU Library General Public *)
(* License version 2.1, with the special exception on linking *)
(* described in file LICENSE. *)
(* *)
(* This software is distributed in the hope that it will be useful, *)
(* but WITHOUT ANY WARRANTY; without even the implied warranty of *)
(* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *)
(* *)
(**************************************************************************)
(*i $Id: ptset.ml,v 1.17 2008-07-22 06:44:06 filliatr Exp $ i*)
(*s Sets of integers implemented as Patricia trees, following Chris
Okasaki and Andrew Gill's paper {\em Fast Mergeable Integer Maps}
({\tt\small http://www.cs.columbia.edu/\~{}cdo/papers.html\#ml98maps}).
Patricia trees provide faster operations than standard library's
module [Set], and especially very fast [union], [subset], [inter]
and [diff] operations. *)
(*s The idea behind Patricia trees is to build a {\em trie} on the
binary digits of the elements, and to compact the representation
by branching only one the relevant bits (i.e. the ones for which
there is at least on element in each subtree). We implement here
{\em little-endian} Patricia trees: bits are processed from
least-significant to most-significant. The trie is implemented by
the following type [t]. [Empty] stands for the empty trie, and
[Leaf k] for the singleton [k]. (Note that [k] is the actual
element.) [Branch (m,p,l,r)] represents a branching, where [p] is
the prefix (from the root of the trie) and [m] is the branching
bit (a power of 2). [l] and [r] contain the subsets for which the
branching bit is respectively 0 and 1. Invariant: the trees [l]
and [r] are not empty. *)
(*i*)
type elt = int
(*i*)
type t =
| Empty
| Leaf of int
| Branch of int * int * t * t
(*s Example: the representation of the set $\{1,4,5\}$ is
$$\mathtt{Branch~(0,~1,~Leaf~4,~Branch~(1,~4,~Leaf~1,~Leaf~5))}$$
The first branching bit is the bit 0 (and the corresponding prefix
is [0b0], not of use here), with $\{4\}$ on the left and $\{1,5\}$ on the
right. Then the right subtree branches on bit 2 (and so has a branching
value of $2^2 = 4$), with prefix [0b01 = 1]. *)
(*s Empty set and singletons. *)
let empty = Empty
let is_empty = function Empty -> true | _ -> false
let singleton k = Leaf k
(*s Testing the occurrence of a value is similar to the search in a
binary search tree, where the branching bit is used to select the
appropriate subtree. *)
let zero_bit k m = (k land m) == 0
let rec mem k = function
| Empty -> false
| Leaf j -> k == j
| Branch (_, m, l, r) -> mem k (if zero_bit k m then l else r)
let rec find k = function
| Empty -> raise Not_found
| Leaf j -> if k == j then j else raise Not_found
| Branch (_, m, l, r) -> find k (if zero_bit k m then l else r)
(*s The following operation [join] will be used in both insertion and
union. Given two non-empty trees [t0] and [t1] with longest common
prefixes [p0] and [p1] respectively, which are supposed to
disagree, it creates the union of [t0] and [t1]. For this, it
computes the first bit [m] where [p0] and [p1] disagree and create
a branching node on that bit. Depending on the value of that bit
in [p0], [t0] will be the left subtree and [t1] the right one, or
the converse. Computing the first branching bit of [p0] and [p1]
uses a nice property of twos-complement representation of integers. *)
let lowest_bit x = x land (-x)
let branching_bit p0 p1 = lowest_bit (p0 lxor p1)
let mask p m = p land (m-1)
let join (p0,t0,p1,t1) =
let m = branching_bit p0 p1 in
if zero_bit p0 m then
Branch (mask p0 m, m, t0, t1)
else
Branch (mask p0 m, m, t1, t0)
(*s Then the insertion of value [k] in set [t] is easily implemented
using [join]. Insertion in a singleton is just the identity or a
call to [join], depending on the value of [k]. When inserting in
a branching tree, we first check if the value to insert [k]
matches the prefix [p]: if not, [join] will take care of creating
the above branching; if so, we just insert [k] in the appropriate
subtree, depending of the branching bit. *)
let match_prefix k p m = (mask k m) == p
let add k t =
let rec ins = function
| Empty -> Leaf k
| Leaf j as t ->
if j == k then t else join (k, Leaf k, j, t)
| Branch (p,m,t0,t1) as t ->
if match_prefix k p m then
if zero_bit k m then
Branch (p, m, ins t0, t1)
else
Branch (p, m, t0, ins t1)
else
join (k, Leaf k, p, t)
in
ins t
let of_list =
List.fold_left (fun t e -> add e t) Empty
(*s The code to remove an element is basically similar to the code of
insertion. But since we have to maintain the invariant that both
subtrees of a [Branch] node are non-empty, we use here the
``smart constructor'' [branch] instead of [Branch]. *)
let branch = function
| (_,_,Empty,t) -> t
| (_,_,t,Empty) -> t
| (p,m,t0,t1) -> Branch (p,m,t0,t1)
let remove k t =
let rec rmv = function
| Empty -> Empty
| Leaf j as t -> if k == j then Empty else t
| Branch (p,m,t0,t1) as t ->
if match_prefix k p m then
if zero_bit k m then
branch (p, m, rmv t0, t1)
else
branch (p, m, t0, rmv t1)
else
t
in
rmv t
(*s One nice property of Patricia trees is to support a fast union
operation (and also fast subset, difference and intersection
operations). When merging two branching trees we examine the
following four cases: (1) the trees have exactly the same
prefix; (2/3) one prefix contains the other one; and (4) the
prefixes disagree. In cases (1), (2) and (3) the recursion is
immediate; in case (4) the function [join] creates the appropriate
branching. *)
let rec merge = function
| Empty, t -> t
| t, Empty -> t
| Leaf k, t -> add k t
| t, Leaf k -> add k t
| (Branch (p,m,s0,s1) as s), (Branch (q,n,t0,t1) as t) ->
if m == n && match_prefix q p m then
(* The trees have the same prefix. Merge the subtrees. *)
Branch (p, m, merge (s0,t0), merge (s1,t1))
else if m < n && match_prefix q p m then
(* [q] contains [p]. Merge [t] with a subtree of [s]. *)
if zero_bit q m then
Branch (p, m, merge (s0,t), s1)
else
Branch (p, m, s0, merge (s1,t))
else if m > n && match_prefix p q n then
(* [p] contains [q]. Merge [s] with a subtree of [t]. *)
if zero_bit p n then
Branch (q, n, merge (s,t0), t1)
else
Branch (q, n, t0, merge (s,t1))
else
(* The prefixes disagree. *)
join (p, s, q, t)
let union s t = merge (s,t)
(*s When checking if [s1] is a subset of [s2] only two of the above
four cases are relevant: when the prefixes are the same and when the
prefix of [s1] contains the one of [s2], and then the recursion is
obvious. In the other two cases, the result is [false]. *)
let rec subset s1 s2 = match (s1,s2) with
| Empty, _ -> true
| _, Empty -> false
| Leaf k1, _ -> mem k1 s2
| Branch _, Leaf _ -> false
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
subset l1 l2 && subset r1 r2
else if m1 > m2 && match_prefix p1 p2 m2 then
if zero_bit p1 m2 then
subset l1 l2 && subset r1 l2
else
subset l1 r2 && subset r1 r2
else
false
(*s To compute the intersection and the difference of two sets, we
still examine the same four cases as in [merge]. The recursion is
then obvious. *)
let rec inter s1 s2 = match (s1,s2) with
| Empty, _ -> Empty
| _, Empty -> Empty
| Leaf k1, _ -> if mem k1 s2 then s1 else Empty
| _, Leaf k2 -> if mem k2 s1 then s2 else Empty
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
merge (inter l1 l2, inter r1 r2)
else if m1 < m2 && match_prefix p2 p1 m1 then
inter (if zero_bit p2 m1 then l1 else r1) s2
else if m1 > m2 && match_prefix p1 p2 m2 then
inter s1 (if zero_bit p1 m2 then l2 else r2)
else
Empty
let rec diff s1 s2 = match (s1,s2) with
| Empty, _ -> Empty
| _, Empty -> s1
| Leaf k1, _ -> if mem k1 s2 then Empty else s1
| _, Leaf k2 -> remove k2 s1
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
merge (diff l1 l2, diff r1 r2)
else if m1 < m2 && match_prefix p2 p1 m1 then
if zero_bit p2 m1 then
merge (diff l1 s2, r1)
else
merge (l1, diff r1 s2)
else if m1 > m2 && match_prefix p1 p2 m2 then
if zero_bit p1 m2 then diff s1 l2 else diff s1 r2
else
s1
(*s All the following operations ([cardinal], [iter], [fold], [for_all],
[exists], [filter], [partition], [choose], [elements]) are
implemented as for any other kind of binary trees. *)
let rec cardinal = function
| Empty -> 0
| Leaf _ -> 1
| Branch (_,_,t0,t1) -> cardinal t0 + cardinal t1
let rec iter f = function
| Empty -> ()
| Leaf k -> f k
| Branch (_,_,t0,t1) -> iter f t0; iter f t1
let rec fold f s accu = match s with
| Empty -> accu
| Leaf k -> f k accu
| Branch (_,_,t0,t1) -> fold f t0 (fold f t1 accu)
let rec for_all p = function
| Empty -> true
| Leaf k -> p k
| Branch (_,_,t0,t1) -> for_all p t0 && for_all p t1
let rec exists p = function
| Empty -> false
| Leaf k -> p k
| Branch (_,_,t0,t1) -> exists p t0 || exists p t1
let rec filter pr = function
| Empty -> Empty
| Leaf k as t -> if pr k then t else Empty
| Branch (p,m,t0,t1) -> branch (p, m, filter pr t0, filter pr t1)
let partition p s =
let rec part (t,f as acc) = function
| Empty -> acc
| Leaf k -> if p k then (add k t, f) else (t, add k f)
| Branch (_,_,t0,t1) -> part (part acc t0) t1
in
part (Empty, Empty) s
let rec choose = function
| Empty -> raise Not_found
| Leaf k -> k
| Branch (_, _,t0,_) -> choose t0 (* we know that [t0] is non-empty *)
let elements s =
let rec elements_aux acc = function
| Empty -> acc
| Leaf k -> k :: acc
| Branch (_,_,l,r) -> elements_aux (elements_aux acc l) r
in
(* unfortunately there is no easy way to get the elements in ascending
order with little-endian Patricia trees *)
List.sort Pervasives.compare (elements_aux [] s)
let split x s =
let coll k (l, b, r) =
if k < x then add k l, b, r
else if k > x then l, b, add k r
else l, true, r
in
fold coll s (Empty, false, Empty)
(*s There is no way to give an efficient implementation of [min_elt]
and [max_elt], as with binary search trees. The following
implementation is a traversal of all elements, barely more
efficient than [fold min t (choose t)] (resp. [fold max t (choose
t)]). Note that we use the fact that there is no constructor
[Empty] under [Branch] and therefore always a minimal
(resp. maximal) element there. *)
let rec min_elt = function
| Empty -> raise Not_found
| Leaf k -> k
| Branch (_,_,s,t) -> min (min_elt s) (min_elt t)
let rec max_elt = function
| Empty -> raise Not_found
| Leaf k -> k
| Branch (_,_,s,t) -> max (max_elt s) (max_elt t)
(*s Another nice property of Patricia trees is to be independent of the
order of insertion. As a consequence, two Patricia trees have the
same elements if and only if they are structurally equal. *)
let equal = (=)
let compare = compare
(*i*)
let make l = List.fold_right add l empty
(*i*)
(*s Additional functions w.r.t to [Set.S]. *)
let rec intersect s1 s2 = match (s1,s2) with
| Empty, _ -> false
| _, Empty -> false
| Leaf k1, _ -> mem k1 s2
| _, Leaf k2 -> mem k2 s1
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
intersect l1 l2 || intersect r1 r2
else if m1 < m2 && match_prefix p2 p1 m1 then
intersect (if zero_bit p2 m1 then l1 else r1) s2
else if m1 > m2 && match_prefix p1 p2 m2 then
intersect s1 (if zero_bit p1 m2 then l2 else r2)
else
false
(*s Big-endian Patricia trees *)
module Big = struct
type elt = int
type t_ = t
type t = t_
let empty = Empty
let is_empty = function Empty -> true | _ -> false
let singleton k = Leaf k
let zero_bit k m = (k land m) == 0
let rec mem k = function
| Empty -> false
| Leaf j -> k == j
| Branch (_, m, l, r) -> mem k (if zero_bit k m then l else r)
let rec find k = function
| Empty -> raise Not_found
| Leaf j -> if k == j then j else raise Not_found
| Branch (_, m, l, r) -> find k (if zero_bit k m then l else r)
let mask k m = (k lor (m-1)) land (lnot m)
(* we first write a naive implementation of [highest_bit]
only has to work for bytes *)
let naive_highest_bit x =
assert (x < 256);
let rec loop i =
if i = 0 then 1 else if x lsr i = 1 then 1 lsl i else loop (i-1)
in
loop 7
(* then we build a table giving the highest bit for bytes *)
let hbit = Array.init 256 naive_highest_bit
(* to determine the highest bit of [x] we split it into bytes *)
let highest_bit_32 x =
let n = x lsr 24 in if n != 0 then hbit.(n) lsl 24
else let n = x lsr 16 in if n != 0 then hbit.(n) lsl 16
else let n = x lsr 8 in if n != 0 then hbit.(n) lsl 8
else hbit.(x)
let highest_bit_64 x =
let n = x lsr 32 in if n != 0 then (highest_bit_32 n) lsl 32
else highest_bit_32 x
let highest_bit = match Sys.word_size with
| 32 -> highest_bit_32
| 64 -> highest_bit_64
| _ -> assert false
let branching_bit p0 p1 = highest_bit (p0 lxor p1)
let join (p0,t0,p1,t1) =
(*i let m = function Branch (_,m,_,_) -> m | _ -> 0 in i*)
let m = branching_bit p0 p1 (*EXP (m t0) (m t1) *) in
if zero_bit p0 m then
Branch (mask p0 m, m, t0, t1)
else
Branch (mask p0 m, m, t1, t0)
let match_prefix k p m = (mask k m) == p
let add k t =
let rec ins = function
| Empty -> Leaf k
| Leaf j as t ->
if j == k then t else join (k, Leaf k, j, t)
| Branch (p,m,t0,t1) as t ->
if match_prefix k p m then
if zero_bit k m then
Branch (p, m, ins t0, t1)
else
Branch (p, m, t0, ins t1)
else
join (k, Leaf k, p, t)
in
ins t
let of_list =
List.fold_left (fun t e -> add e t) Empty
let remove k t =
let rec rmv = function
| Empty -> Empty
| Leaf j as t -> if k == j then Empty else t
| Branch (p,m,t0,t1) as t ->
if match_prefix k p m then
if zero_bit k m then
branch (p, m, rmv t0, t1)
else
branch (p, m, t0, rmv t1)
else
t
in
rmv t
let rec merge = function
| Empty, t -> t
| t, Empty -> t
| Leaf k, t -> add k t
| t, Leaf k -> add k t
| (Branch (p,m,s0,s1) as s), (Branch (q,n,t0,t1) as t) ->
if m == n && match_prefix q p m then
(* The trees have the same prefix. Merge the subtrees. *)
Branch (p, m, merge (s0,t0), merge (s1,t1))
else if m > n && match_prefix q p m then
(* [q] contains [p]. Merge [t] with a subtree of [s]. *)
if zero_bit q m then
Branch (p, m, merge (s0,t), s1)
else
Branch (p, m, s0, merge (s1,t))
else if m < n && match_prefix p q n then
(* [p] contains [q]. Merge [s] with a subtree of [t]. *)
if zero_bit p n then
Branch (q, n, merge (s,t0), t1)
else
Branch (q, n, t0, merge (s,t1))
else
(* The prefixes disagree. *)
join (p, s, q, t)
let union s t = merge (s,t)
let rec subset s1 s2 = match (s1,s2) with
| Empty, _ -> true
| _, Empty -> false
| Leaf k1, _ -> mem k1 s2
| Branch _, Leaf _ -> false
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
subset l1 l2 && subset r1 r2
else if m1 < m2 && match_prefix p1 p2 m2 then
if zero_bit p1 m2 then
subset l1 l2 && subset r1 l2
else
subset l1 r2 && subset r1 r2
else
false
let rec inter s1 s2 = match (s1,s2) with
| Empty, _ -> Empty
| _, Empty -> Empty
| Leaf k1, _ -> if mem k1 s2 then s1 else Empty
| _, Leaf k2 -> if mem k2 s1 then s2 else Empty
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
merge (inter l1 l2, inter r1 r2)
else if m1 > m2 && match_prefix p2 p1 m1 then
inter (if zero_bit p2 m1 then l1 else r1) s2
else if m1 < m2 && match_prefix p1 p2 m2 then
inter s1 (if zero_bit p1 m2 then l2 else r2)
else
Empty
let rec diff s1 s2 = match (s1,s2) with
| Empty, _ -> Empty
| _, Empty -> s1
| Leaf k1, _ -> if mem k1 s2 then Empty else s1
| _, Leaf k2 -> remove k2 s1
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
merge (diff l1 l2, diff r1 r2)
else if m1 > m2 && match_prefix p2 p1 m1 then
if zero_bit p2 m1 then
merge (diff l1 s2, r1)
else
merge (l1, diff r1 s2)
else if m1 < m2 && match_prefix p1 p2 m2 then
if zero_bit p1 m2 then diff s1 l2 else diff s1 r2
else
s1
(* same implementation as for little-endian Patricia trees *)
let cardinal = cardinal
let iter = iter
let fold = fold
let for_all = for_all
let exists = exists
let filter = filter
let partition p s =
let rec part (t,f as acc) = function
| Empty -> acc
| Leaf k -> if p k then (add k t, f) else (t, add k f)
| Branch (_,_,t0,t1) -> part (part acc t0) t1
in
part (Empty, Empty) s
let choose = choose
let elements s =
let rec elements_aux acc = function
| Empty -> acc
| Leaf k -> k :: acc
| Branch (_,_,l,r) -> elements_aux (elements_aux acc r) l
in
(* we still have to sort because of possible negative elements *)
List.sort Pervasives.compare (elements_aux [] s)
let split x s =
let coll k (l, b, r) =
if k < x then add k l, b, r
else if k > x then l, b, add k r
else l, true, r
in
fold coll s (Empty, false, Empty)
(* could be slightly improved (when we now that a branch contains only
positive or only negative integers) *)
let min_elt = min_elt
let max_elt = max_elt
let equal = (=)
let compare = compare
let make l = List.fold_right add l empty
let rec intersect s1 s2 = match (s1,s2) with
| Empty, _ -> false
| _, Empty -> false
| Leaf k1, _ -> mem k1 s2
| _, Leaf k2 -> mem k2 s1
| Branch (p1,m1,l1,r1), Branch (p2,m2,l2,r2) ->
if m1 == m2 && p1 == p2 then
intersect l1 l2 || intersect r1 r2
else if m1 > m2 && match_prefix p2 p1 m1 then
intersect (if zero_bit p2 m1 then l1 else r1) s2
else if m1 < m2 && match_prefix p1 p2 m2 then
intersect s1 (if zero_bit p1 m2 then l2 else r2)
else
false
end
(*s Big-endian Patricia trees with non-negative elements only *)
module BigPos = struct
include Big
let singleton x = if x < 0 then invalid_arg "BigPos.singleton"; singleton x
let add x s = if x < 0 then invalid_arg "BigPos.add"; add x s
let of_list =
List.fold_left (fun t e -> add e t) Empty
(* Patricia trees are now binary search trees! *)
let rec mem k = function
| Empty -> false
| Leaf j -> k == j
| Branch (p, _, l, r) -> if k <= p then mem k l else mem k r
let rec min_elt = function
| Empty -> raise Not_found
| Leaf k -> k
| Branch (_,_,s,_) -> min_elt s
let rec max_elt = function
| Empty -> raise Not_found
| Leaf k -> k
| Branch (_,_,_,t) -> max_elt t
(* we do not have to sort anymore *)
let elements s =
let rec elements_aux acc = function
| Empty -> acc
| Leaf k -> k :: acc
| Branch (_,_,l,r) -> elements_aux (elements_aux acc r) l
in
elements_aux [] s
end
(*s EXPERIMENT: Big-endian Patricia trees with swapped bit sign *)
module Bigo = struct
include Big
(* swaps the sign bit *)
let swap x = if x < 0 then x land max_int else x lor min_int
let mem x s = mem (swap x) s
let add x s = add (swap x) s
let singleton x = singleton (swap x)
let remove x s = remove (swap x) s
let elements s = List.map swap (elements s)
let choose s = swap (choose s)
let iter f = iter (fun x -> f (swap x))
let fold f = fold (fun x a -> f (swap x) a)
let for_all f = for_all (fun x -> f (swap x))
let exists f = exists (fun x -> f (swap x))
let filter f = filter (fun x -> f (swap x))
let partition f = partition (fun x -> f (swap x))
let split x s = split (swap x) s
let rec min_elt = function
| Empty -> raise Not_found
| Leaf k -> swap k
| Branch (_,_,s,_) -> min_elt s
let rec max_elt = function
| Empty -> raise Not_found
| Leaf k -> swap k
| Branch (_,_,_,t) -> max_elt t
end
let test empty add mem =
let seed = Random.int max_int in
Random.init seed;
let s =
let rec loop s i =
if i = 1000 then s else loop (add (Random.int max_int) s) (succ i)
in
loop empty 0
in
Random.init seed;
for i = 0 to 999 do assert (mem (Random.int max_int) s) done
coinst-1.9.3/upgrade_common.ml 0000644 0001750 0001750 00000171403 12657630652 015334 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let debug_coinst =
Debug.make "coinst" "Debug co-installability issue analyse" []
let debug_time = Debug.make "time" "Print execution times" []
let debug_cluster = Debug.make "cluster" "Debug clustering algorithm" []
let debug_problems =
Debug.make "coinst_prob"
"Debug enumeration of possible co-installability issues" []
let debug_problem_graph =
Debug.make "coinst_graph"
"Write the graph of new dependencies to /tmp/newdeps.dot" []
let debug = false
module IntSet = Util.IntSet
module StringSet = Util.StringSet
module M = Deb_lib
module Coinst = Coinst_common.F(M)
module Repository = Coinst.Repository
open Repository
module Quotient = Coinst.Quotient
module Graph = Graph.F (Coinst.Repository)
module PSetSet = Set.Make (PSet)
module Timer = Util.Timer
(****)
type ignored_sets = (StringSet.t list * bool) list ref
type ignored_sets_2 = (PSet.t list * bool) list
let ignored_set_domain l =
List.fold_left
(fun s (l, ext) ->
List.fold_left
(fun s s' ->
StringSet.fold (fun nm s -> M.PkgSet.add (M.add_name nm) s) s' s)
s l)
M.PkgSet.empty !l
let forced_packages l =
List.fold_left
(fun s (l, ext) ->
match l with
[s'] when not ext -> StringSet.union s s'
| _ -> s)
StringSet.empty !l
let intern_ignored_sets dist l =
List.fold_left
(fun r (l, ext) ->
let l =
List.map
(fun s ->
StringSet.fold
(fun nm s ->
match M.parse_package_name dist nm with
[p] -> PSet.add (Package.of_index p) s
| [] -> s
| _ :: _ -> assert false)
s PSet.empty)
l
in
if List.exists PSet.is_empty l then r else (l, ext) :: r)
[] l
let is_ignored_set l s =
List.exists
(fun (l, ext) ->
try
not
(StringSet.is_empty
(List.fold_left
(fun s s' ->
let p = StringSet.choose (StringSet.inter s s') in
StringSet.remove p s)
s l)
&&
ext)
with Not_found ->
false)
!l
let ignored_set_domain_2 l =
List.fold_left
(fun s (l, ext) -> List.fold_left PSet.union s l)
PSet.empty l
let is_ignored_set_2 l s =
List.exists
(fun (l, ext) ->
try
not
(PSet.is_empty
(List.fold_left
(fun s s' ->
let p = PSet.choose (PSet.inter s s') in
PSet.remove p s)
s l)
&&
ext)
with Not_found ->
false)
l
let print_ignore_spec dist f l =
Util.print_list
(fun f (l, ext) ->
Util.print_list
(fun f s ->
Util.print_list (Package.print_name dist) "|" f (PSet.elements s))
"," f l;
if ext then Format.fprintf f ",_")
" " f l
(****)
let new_deps pred possibly_ignored_packages deps1 dist2 deps2 =
PTbl.mapi
(fun p2 i ->
if i = -1 then
Formula._true
else begin
let p1 = Package.of_index i in
let f1 = PTbl.get deps1 p1 in
let f2 = PTbl.get deps2 p2 in
let f2 =
Formula.filter
(fun d2 ->
Disj.exists (fun p -> PSet.mem p possibly_ignored_packages) d2
||
let d1 =
Disj.fold
(fun p2 d2 ->
let i = PTbl.get pred p2 in
if i = -1 then d2 else
Disj.disj (Disj.lit (Package.of_index i)) d2)
d2 Disj._false
in
not (Formula.implies1 f1 d1))
f2
in
if debug && not (Formula.implies Formula._true f2) then begin
Format.printf "%a ==> %a@."
(Package.print_name dist2) p2
(Formula.print dist2) f2;
(*
Format.printf "%a --> %a@."
(Package.print_name dist1) p1
(Formula.print dist1) f1
*)
end;
f2
end)
pred
(****)
module ListTbl = Util.ListTbl
type st =
{ dist : M.pool; deps : Formula.t PTbl.t; confl : Conflict.t;
pieces : (int, Package.t * Disj.t) Hashtbl.t;
pieces_in_confl : (Package.t, int) ListTbl.t;
set : PSet.t;
installed : IntSet.t; not_installed : IntSet.t;
check : PSet.t -> bool }
let print_prob st =
IntSet.iter
(fun i ->
let (p, d) = Hashtbl.find st.pieces i in
Format.printf "%a => %a; "
(Package.print_name st.dist) p
(Disj.print st.dist) d)
st.installed;
Format.printf "@."
let rec add_piece st i cont =
assert (not (IntSet.mem i st.installed || IntSet.mem i st.not_installed));
let (p, d) = Hashtbl.find st.pieces i in
if
(* We do not add a dependency if it is implied by, or implies, a
dependency currently under consideration. *)
not (IntSet.exists
(fun i' ->
let (_, d') = Hashtbl.find st.pieces i' in
Disj.implies d d' || Disj.implies d' d)
st.installed)
&&
(* When adding a package in st.set, we check that d is not implied
by any of the dependencies of a package already in st.set *)
(PSet.mem p st.set ||
not (PSet.exists
(fun p -> Formula.implies1 (PTbl.get st.deps p) d)
st.set))
&&
(* If we are adding a package, we check whether the set is still
co-installable *)
(PSet.mem p st.set || st.check (PSet.add p st.set))
then begin
if debug_problems () then
Format.printf "Adding %a => %a@."
(Package.print_name st.dist) p (Disj.print st.dist) d;
let st =
{st with set = PSet.add p st.set;
installed = IntSet.add i st.installed}
in
if debug_problems () then print_prob st;
(* Make sure that there is at least one piece in conflict for all
dependencies, then consider all possible additions *)
Disj.fold
(fun p cont st ->
if
PSet.exists
(fun q ->
List.exists (fun i -> IntSet.mem i st.installed)
(ListTbl.find st.pieces_in_confl q))
(Conflict.of_package st.confl p)
then
cont st
else
ignore
(PSet.fold
(fun q st ->
List.fold_right (fun j st -> do_add_piece st j cont)
(ListTbl.find st.pieces_in_confl q) st)
(Conflict.of_package st.confl p) st))
d
(fun st ->
if debug_problems () then
Format.printf "Considering all possible additions in %d: %a...@."
i (Disj.print st.dist) d;
Disj.fold
(fun p cont ->
PSet.fold
(fun q cont ->
List.fold_right (fun j cont st -> maybe_add_piece st j cont)
(ListTbl.find st.pieces_in_confl q) cont)
(Conflict.of_package st.confl p) cont)
d cont st)
st
end else
if debug_problems () then
Format.printf "Could not add %a => %a@."
(Package.print_name st.dist) p (Disj.print st.dist) d;
and do_add_piece st i cont =
if IntSet.mem i st.installed then begin
cont st; st
end else if not (IntSet.mem i st.not_installed) then begin
add_piece st i cont;
{st with not_installed = IntSet.add i st.not_installed}
end else
st
and maybe_add_piece st i cont =
if
not (IntSet.mem i st.installed || IntSet.mem i st.not_installed)
then begin
add_piece st i cont;
cont {st with not_installed = IntSet.add i st.not_installed}
end else
cont st
let find_problems dist deps confl check =
let pieces = Hashtbl.create 101 in
let last_piece = ref (-1) in
let pieces_in_confl = ListTbl.create 101 in
PTbl.iteri
(fun p f ->
Formula.iter f
(fun d ->
incr last_piece;
let i = !last_piece in
Hashtbl.add pieces i (p, d);
Disj.iter d (fun p -> ListTbl.add pieces_in_confl p i)))
deps;
let st =
{ dist = dist; deps = deps; confl = confl;
pieces = pieces; pieces_in_confl = pieces_in_confl;
set = PSet.empty; check = check;
installed = IntSet.empty; not_installed = IntSet.empty }
in
for i = 0 to !last_piece do
add_piece st i (fun _ -> ())
done
(****)
type state =
{ dist : M.deb_pool;
deps : Formula.t PTbl.t;
confl : Conflict.t;
deps' : Formula.t PTbl.t;
confl' : Conflict.t;
st : M.Solver.state }
(****)
type pkg_ref = string * bool * bool
type reason =
R_depends of pkg_ref * string M.dep * pkg_ref list
| R_conflict of pkg_ref * string M.dep * pkg_ref
type clause = { pos : StringSet.t; neg : StringSet.t }
let print_clause ch clause =
Util.print_list (fun f -> Format.fprintf f "-%s") " | " ch
(StringSet.elements clause.neg);
if not (StringSet.is_empty clause.pos || StringSet.is_empty clause.neg) then
Format.fprintf ch " | ";
Util.print_list (fun f -> Format.fprintf f "%s") " | " ch
(StringSet.elements clause.pos)
let problematic_packages dist1 dist dist2 reasons =
let resolve_dep dist l =
List.fold_left
(fun s cstr ->
List.fold_left
(fun s p -> StringSet.add (M.name_of_id p.M.package) s)
s (M.resolve_package_dep_raw dist cstr))
StringSet.empty l
in
let extern_deps l =
List.map (fun (id, rel) -> (M.name_of_id id, rel)) l in
let (s1, s2, lst) =
List.fold_left
(fun (s1, s2, lst) r ->
match r with
M.R_depends (n, l) ->
let p = M.find_package_by_num dist n in
let id = p.M.package in
let nm = M.name_of_id id in
let d = resolve_dep dist l in
let d1 = resolve_dep dist1 l in
let d2 = resolve_dep dist2 l in
let s1 = StringSet.union (StringSet.diff d1 d) s1 in
let s2 = StringSet.union (StringSet.diff d2 d) s2 in
let unchanged_dep dist =
match M.find_packages_by_name dist id with
[] ->
false
| [q] ->
M.compare_version q.M.version p.M.version = 0
||
List.exists
(fun l' ->
let d1' = resolve_dep dist1 l' in
let d2' = resolve_dep dist2 l' in
not (StringSet.is_empty d1' && StringSet.is_empty d2')
&&
StringSet.subset d1' d1
&&
StringSet.subset d2' d2)
(q.M.pre_depends @ q.M.depends)
| _ ->
assert false
in
let u1 = unchanged_dep dist1 in
let u2 = unchanged_dep dist2 in
let s1 = if u1 then s1 else StringSet.add nm s1 in
let s2 = if u2 then s2 else StringSet.add nm s2 in
let pkgs d1 d2 =
List.map
(fun nm -> (nm, StringSet.mem nm d1, StringSet.mem nm d2))
(StringSet.elements (StringSet.union d1 d2))
in
let d12 = StringSet.union d1 d2 in
let other_deps u dist old lst =
if u then lst else
match M.find_packages_by_name dist id with
[] ->
lst
| [q] ->
List.fold_left
(fun lst l' ->
let d1' = resolve_dep dist1 l' in
let d2' = resolve_dep dist2 l' in
if
StringSet.subset d1' d12
&&
StringSet.subset d2' d12
then
R_depends ((nm, old, not old), extern_deps l',
pkgs d1' d2') :: lst
else
lst)
lst (q.M.pre_depends @ q.M.depends)
| _ ->
assert false
in
let lst = other_deps u1 dist1 true lst in
let lst = other_deps u2 dist2 false lst in
(s1, s2,
R_depends ((nm, u1, u2), extern_deps l, pkgs d1 d2) :: lst)
| M.R_conflict (j, k, Some (i, l)) ->
let i' = if i = j then k else j in
let p = M.find_package_by_num dist i in
let p' = M.find_package_by_num dist i' in
let id = p.M.package in
let nm = M.name_of_id id in
let nm' = M.name_of_id p'.M.package in
let c1 = resolve_dep dist1 l in
let c2 = resolve_dep dist2 l in
let u1' = StringSet.mem nm' c1 in
let s1 = if u1' then s1 else StringSet.add nm' s1 in
let u2' = StringSet.mem nm' c2 in
let s2 = if u2' then s2 else StringSet.add nm' s2 in
let unchanged_cfl dist =
match M.find_packages_by_name dist id with
[] ->
false
| [q] ->
(*
Format.eprintf "%s ## %s (%a): %b %b %b %b@." nm nm' M.print_package_dependency (q.M.breaks @ q.M.conflicts) u1' (StringSet.mem nm' (resolve_dep dist1 (List.flatten (q.M.breaks @ q.M.conflicts)))) u2' (StringSet.mem nm' (resolve_dep dist1 (List.flatten (q.M.breaks @ q.M.conflicts))));
*)
M.compare_version q.M.version p.M.version = 0
||
(let l' = List.flatten (q.M.breaks @ q.M.conflicts) in
(not u1' || StringSet.mem nm' (resolve_dep dist1 l'))
&&
(not u2' || StringSet.mem nm' (resolve_dep dist2 l')))
| _ ->
assert false
in
let u1 = unchanged_cfl dist1 in
let u2 = unchanged_cfl dist2 in
let s1 = if u1 then s1 else StringSet.add nm s1 in
let s2 = if u2 then s2 else StringSet.add nm s2 in
(s1, s2,
R_conflict ((nm, u1, u2), extern_deps l, (nm', u1', u2')) :: lst)
| M.R_conflict (_, _, None) ->
assert false)
(StringSet.empty, StringSet.empty, []) reasons
in
({pos = s1; neg = s2}, List.rev lst)
let compute_support dist1 dist2 reasons =
let add support (nm, _, _) = StringSet.add nm support in
let support =
List.fold_left
(fun support r ->
match r with
R_depends (p, _, pl) -> add (List.fold_left add support pl) p
| R_conflict (p1, _, p2) -> add (add support p2) p1)
StringSet.empty reasons
in
(support,
StringSet.filter
(fun nm -> M.has_package_of_name dist1 (M.add_name nm)) support,
StringSet.filter
(fun nm -> M.has_package_of_name dist2 (M.add_name nm)) support)
let problematic_packages dist1 dist dist2 s reasons =
let (clause, reasons) = problematic_packages dist1 dist dist2 reasons in
let (support_set, support1, support2) =
compute_support dist1 dist2 reasons in
let support = Array.of_list (StringSet.elements support_set) in
let package_index = Hashtbl.create 17 in
Array.iteri (fun n nm -> Hashtbl.add package_index nm n) support;
let n = Array.length support in
let conflict = Hashtbl.create 5 in
PSet.iter
(fun p ->
let p = M.find_package_by_num dist (Package.index p) in
Hashtbl.add conflict (M.name_of_id p.M.package) ())
s;
let in_testing nm =
match
M.find_packages_by_name dist1 (M.id_of_name nm),
M.find_packages_by_name dist (M.id_of_name nm)
with
[p1], [p] -> M.compare_version p1.M.version p.M.version = 0
| [], [] -> true
| _ -> false
in
let var nm t = (2 * Hashtbl.find package_index nm + if t then 0 else 1) in
let nlit nm t = M.Solver.lit_of_var (var nm t) false in
let plit nm t = M.Solver.lit_of_var (var nm t) true in
let print_var ch p =
Format.fprintf ch "%s(%s)"
support.(p / 2) (if p mod 2 = 0 then "testing" else "sid")
in
let pr = M.Solver.initialize_problem ~print_var (2 * n) in
let vars = ref [] in
Hashtbl.iter
(fun nm _ ->
vars := var nm true :: var nm false :: !vars;
M.Solver.add_rule pr [|plit nm true; plit nm false|] [])
conflict;
let lst = ref [] in
Hashtbl.iter
(fun nm _ ->
lst := var nm (not (in_testing nm)) :: !lst;
M.Solver.add_rule pr [|nlit nm true; nlit nm false|] [])
package_index;
(*
let print_ref f (nm, t, u) =
match t, u with
true, true -> Format.fprintf f "%s" nm
| true, false -> Format.fprintf f "%s (testing)" nm
| false, true -> Format.fprintf f "%s (sid)" nm
| false, false -> assert false
in
Format.eprintf "=======================@.";
*)
List.iter
(fun r ->
match r with
R_depends (p, _, pl) ->
(*
Format.eprintf "| %a => %a@." print_ref p
(Util.print_list print_ref " | ") pl;
*)
let lit = M.Solver.lit_of_var in
let l =
List.fold_right
(fun (nm, t, u) l ->
let l = if t then var nm true :: l else l in
let l = if u then var nm false :: l else l in
l)
pl []
in
let (nm, t, u) = p in
if t then begin
M.Solver.add_rule pr
(Array.of_list (lit (var nm true) false ::
List.map (fun x -> lit x true) l)) [];
M.Solver.associate_vars pr (lit (var nm true) true) l
end;
if u then begin
M.Solver.add_rule pr
(Array.of_list (lit (var nm false) false ::
List.map (fun x -> lit x true) l)) [];
M.Solver.associate_vars pr (lit (var nm false) true) l
end
| R_conflict ((nm1, t1, u1), _, (nm2, t2, u2)) ->
(*
Format.eprintf "| %a ## %a@." print_ref (nm1, t1, u1) print_ref (nm2, t2, u2);
*)
if t1 && t2 then
M.Solver.add_rule pr [|nlit nm1 true; nlit nm2 true|] [];
if t1 && u2 then
M.Solver.add_rule pr [|nlit nm1 true; nlit nm2 false|] [];
if u1 && t2 then
M.Solver.add_rule pr [|nlit nm1 false; nlit nm2 true|] [];
if u1 && u2 then
M.Solver.add_rule pr [|nlit nm1 false; nlit nm2 false|] [])
reasons;
(*
Format.eprintf ">> %a@." print_clause clause;
Format.eprintf "- "; List.iter (fun p -> Format.eprintf " %s (%s)" support.(p / 2)(if p mod 2 = 0 then "testing" else "sid")) !lst; Format.eprintf "@.";
*)
let rec minimize l l' f =
match l' with
[] ->
List.rev l
| x :: r ->
if f (List.rev_append l r) then
minimize (x :: l) r f
else
minimize l r f
in
let check lst =
(*
Format.eprintf ") - "; List.iter (fun p -> Format.eprintf " %s (%s)" support.(p / 2)(if p mod 2 = 0 then "testing" else "sid")) lst; Format.eprintf "@.";
*)
let res = M.Solver.solve_neg_list pr !vars lst in
(*
Format.eprintf ") ==> %b@." res;
*)
M.Solver.reset pr;
res
in
let lst = minimize [] !lst (fun lst -> check lst) in
(*
Format.eprintf "- "; List.iter (fun p -> Format.eprintf " %s (%s)" support.(p / 2)(if p mod 2 = 0 then "testing" else "sid")) lst; Format.eprintf "@.";
*)
let pos = ref StringSet.empty in
let neg = ref StringSet.empty in
List.iter
(fun x ->
let nm = support.(x / 2) in
if x mod 2 = 0 then
pos := StringSet.add nm !pos
else
neg := StringSet.add nm !neg)
lst;
({pos = !pos; neg = !neg}, reasons, support1, support2)
(****)
type problem =
{ p_clause : clause; p_issue : Util.StringSet.t; p_explain : reason list;
p_support1 : Util.StringSet.t; p_support2 : Util.StringSet.t }
type issue =
{ i_issue : PSet.t; i_problem : problem }
let prepare_analyze dist =
let (deps, confl) = Coinst.compute_dependencies_and_conflicts dist in
let (deps', confl') = Coinst.flatten_and_simplify dist deps confl in
let st = Coinst.generate_rules (Quotient.trivial dist) deps' confl' in
{ dist=dist; deps=deps; confl=confl; deps'=deps'; confl'=confl'; st=st }
let compute_predecessors dist1 dist2 =
PTbl.init dist2
(fun p2 ->
let nm = M.package_name dist2 (Package.index p2) in
match M.parse_package_name dist1 nm with
[] ->
if debug then Format.printf "%s is a new package@." nm;
-1
| [p1] ->
p1
| _ ->
assert false)
let analyze ?(check_new_packages = false) ignored_sets
?reference dist1_state dist2 =
let
{ dist = dist1; deps = deps1; confl = confl1;
deps' = deps1'; confl' = confl1'; st = st1 }
= dist1_state
in
let t = Timer.start () in
let t' = Timer.start () in
let (deps2, confl2) = Coinst.compute_dependencies_and_conflicts dist2 in
if debug_time () then
Format.eprintf " Deps and confls: %f@." (Timer.stop t');
let (deps2', confl2') = Coinst.flatten_and_simplify dist2 deps2 confl2 in
let t' = Timer.start () in
let st2 = Coinst.generate_rules (Quotient.trivial dist2) deps2' confl2' in
if debug_time () then begin
Format.eprintf " Rules: %f@." (Timer.stop t');
Format.eprintf " Target dist: %f@." (Timer.stop t)
end;
let t = Timer.start () in
let pred = compute_predecessors dist1 dist2 in
let new_conflicts = ref [] in
Conflict.iter confl2
(fun p2 q2 ->
let i = PTbl.get pred p2 in
let j = PTbl.get pred q2 in
if i <> -1 && j <> -1 then begin
let p1 = Package.of_index i in
let q1 = Package.of_index j in
if not (Conflict.check confl1 p1 q1) then begin
if debug_coinst () then begin
Format.eprintf "possible new conflict: %a %a@."
(Package.print_name dist1) p1
(Package.print_name dist1) q1;
end;
new_conflicts := (p2, q2) :: !new_conflicts;
end
end);
let results = ref PSetSet.empty in
let add_result s =
if not (PSetSet.mem s !results) then begin
if debug_coinst () then begin
Format.eprintf "==>";
PSet.iter
(fun p -> Format.eprintf " %a" (Package.print_name dist2) p) s;
Format.eprintf "@."
end;
results := PSetSet.add s !results
end
in
let is_installable p =
let res = M.Solver.solve st2 (Package.index p) in
M.Solver.reset st2;
res
and was_installable p =
let res = M.Solver.solve st1 (PTbl.get pred p) in
M.Solver.reset st1;
res
in
(*
(* Clearly non installable packages *)
PTbl.iteri
(fun p f ->
if
PTbl.get pred p <> -1 &&
Formula.implies f Formula._false && was_installable p
then
add_result (PSet.singleton p))
deps2';
*)
(* New conflict pairs *)
List.iter
(fun (p2, q2) ->
let pi = is_installable p2 in
let qi = is_installable q2 in
if not pi && was_installable p2 then add_result (PSet.singleton p2);
if not qi && was_installable q2 then add_result (PSet.singleton q2);
if pi && qi then begin
let i = PTbl.get pred p2 in
let j = PTbl.get pred q2 in
let p1 = Package.of_index i in
let q1 = Package.of_index j in
if M.Solver.solve_lst st1 [i; j] then begin
if debug then begin
Format.printf "new conflict: %a %a@."
(Package.print_name dist1) p1
(Package.print_name dist1) q1;
end;
add_result (PSet.add p2 (PSet.add q2 PSet.empty))
end else begin
if debug then begin
Format.printf "NOT new conflict: %a %a@."
(Package.print_name dist1) p1
(Package.print_name dist1) q1;
M.show_reasons dist1 (M.Solver.collect_reasons_lst st1 [i; j])
end
end;
M.Solver.reset st1
end)
!new_conflicts;
(* Only consider new dependencies. *)
let ignored_sets' = intern_ignored_sets dist2 !ignored_sets in
let possibly_ignored_packages =
ignored_set_domain_2 ignored_sets' in
let deps2 = new_deps pred possibly_ignored_packages deps1 dist2 deps2 in
(* Compute the corresponding flattened dependencies. *)
let deps2 =
PTbl.mapi
(fun p f ->
Formula.fold
(fun d f ->
Formula.conj
(PSet.fold
(fun p f -> Formula.disj (PTbl.get deps2' p) f)
(Disj.to_lits d) Formula._false) f)
f Formula._true)
deps2
in
(* Only keep those that are new... *)
let deps2 = new_deps pred PSet.empty deps1' dist2 deps2 in
(* ...and that are indeed in the flattened repository *)
let deps2 =
PTbl.mapi
(fun p f ->
let f' = PTbl.get deps2' p in
Formula.filter
(fun d ->
Formula.exists (fun d' -> Disj.equiv d d') f') f)
deps2
in
(* Only keep relevant conflicts. *)
let dep_targets = ref PSet.empty in
PTbl.iteri
(fun _ f ->
Formula.iter f
(fun d ->
Disj.iter d (fun p -> dep_targets := PSet.add p !dep_targets)))
deps2;
Conflict.iter confl2'
(fun p2 q2 ->
let i1 = PTbl.get pred p2 in
let j1 = PTbl.get pred q2 in
if
not ((PSet.mem p2 !dep_targets && j1 <> -1) ||
(PSet.mem q2 !dep_targets && i1 <> -1) ||
(PSet.mem p2 !dep_targets && PSet.mem q2 !dep_targets))
then
Conflict.remove confl2' p2 q2);
(*
List.iter
(fun (p2, q2) ->
if
not (PSet.mem p2 possibly_ignored_packages
||
PSet.mem q2 possibly_ignored_packages)
then
Conflict.remove confl2' p2 q2)
!new_conflicts;
*)
(* As a consequence, some new dependencies might not be relevant anymore. *)
let deps2 = Coinst.remove_clearly_irrelevant_deps confl2' deps2 in
(* Add self dependencies for packages with conflicts, as we want to
consider them as well to find possible problems. *)
let deps2 =
PTbl.mapi
(fun p f ->
if Conflict.has confl2' p && PTbl.get pred p <> -1 then
Formula.conj (Formula.lit p) f
else
f)
deps2
in
if debug_problem_graph () then
Graph.output "/tmp/newdeps.dot"
~package_weight:(fun p ->
if Formula.implies (Formula.lit p) (PTbl.get deps2 p) then
(if PTbl.get pred p = -1 then 1. else 10.)
else 1000.)
(Quotient.trivial dist2) deps2 confl2';
(*
Conflict.iter confl2' (fun p q -> Format.eprintf "%a ## %a@." (Package.print dist2) p (Package.print dist2) q);
PTbl.iteri (fun p f -> Format.eprintf "%a: %a@." (Package.print dist2) p (Formula.print dist2) f) deps2;
*)
if debug_time () then Format.eprintf " Init: %f@." (Timer.stop t);
let check s =
let now_installable s =
let res =
M.Solver.solve_lst st2 (List.map Package.index (PSet.elements s)) in
M.Solver.reset st2;
res
in
let l = PSet.elements s in
let was_coinstallable =
M.Solver.solve_lst st1 (List.map (fun p -> PTbl.get pred p) l)
in
M.Solver.reset st1;
if not was_coinstallable then begin
if debug then begin
Format.printf "Was not co-installable:";
List.iter (fun p -> Format.printf " %a" (Package.print_name dist2) p) l;
Format.printf "@.";
end;
false
end else if now_installable s then begin
if debug then begin
Format.printf "Still co-installable:";
List.iter (fun p -> Format.printf " %a" (Package.print_name dist2) p) l;
Format.printf "@.";
end;
true
end else begin
if
PSet.exists (fun p -> not (now_installable (PSet.remove p s))) s
then begin
if debug_coinst () then begin
Format.eprintf "Not minimal:";
List.iter (fun p -> Format.eprintf " %a" (Package.print_name dist2) p) l;
Format.eprintf "@.";
end;
end else begin
add_result s
end;
false
end
in
let t = Timer.start () in
find_problems dist2 deps2 confl2' check;
if debug_time () then
Format.eprintf " Enumerating problems: %f@." (Timer.stop t);
let results =
PSetSet.filter (fun s -> not (is_ignored_set_2 ignored_sets' s)) !results
in
(****)
let t = Timer.start () in
let all_pkgs = ref PSet.empty in
let all_conflicts = Conflict.create dist2 in
let dep_src = PTbl.create dist2 PSet.empty in
let dep_trg = PTbl.create dist2 PSet.empty in
let add_rel r p q = PTbl.set r p (PSet.add q (PTbl.get r p)) in
let broken_new_packages = ref PSet.empty in
if check_new_packages then begin
let forced_pkgs = forced_packages ignored_sets in
PTbl.iteri
(fun p _ ->
if
PTbl.get pred p = -1 &&
not (StringSet.mem (M.package_name dist2 (Package.index p))
forced_pkgs)
then begin
(*Format.eprintf "??? %a@." (Package.print dist2) p;*)
if not (M.Solver.solve st2 (Package.index p)) then begin
(*
M.Solver.solve st2init (Package.index p);
M.Solver.reset st2init;
*)
broken_new_packages := PSet.add p !broken_new_packages
end;
M.Solver.reset st2
end)
deps2
end;
(****)
let (graphs, broken_new_packages) =
if PSetSet.is_empty results && PSet.is_empty !broken_new_packages then
([], [])
else begin
let s = PSetSet.fold PSet.union results !broken_new_packages in
let t = Timer.start () in
let st2init = M.generate_rules_restricted dist2 (pset_indices s) in
if debug_time () then
Format.eprintf " Generating constraints: %f@." (Timer.stop t);
(List.map
(fun s ->
let l = List.map Package.index (PSet.elements s) in
let res = M.Solver.solve_lst st2init l in
assert (not res);
let r = M.Solver.collect_reasons_lst st2init l in
M.Solver.reset st2init;
let confl = Conflict.create dist2 in
let deps = PTbl.create dist2 Formula._true in
let pkgs = ref PSet.empty in
let package i =
let p = Package.of_index i in pkgs := PSet.add p !pkgs; p in
(*
if debug_coinst () then M.show_reasons dist2 r;
*)
List.iter
(fun r ->
match r with
M.R_conflict (n1, n2, _) ->
Conflict.add confl (package n1) (package n2);
Conflict.add all_conflicts (package n1) (package n2)
| M.R_depends (n, l) ->
let p = package n in
let l =
List.map package
(List.flatten
(List.map (M.resolve_package_dep dist2) l))
in
List.iter
(fun q ->
add_rel dep_src q p;
add_rel dep_trg p q)
l;
PTbl.set deps p
(Formula.conj (PTbl.get deps p)
(Formula.of_disj (Disj.lit_disj l))))
r;
all_pkgs := PSet.union !all_pkgs !pkgs;
let (clause, explanation, support1, support2) =
match reference with
Some dist2_state ->
problematic_packages
dist1_state.dist dist2 dist2_state.dist s r
| None ->
problematic_packages dist1_state.dist dist2 dist2 s r
in
(*
PSet.iter (fun p -> Format.printf " %a" (Package.print_name dist2) p) s;
Format.printf "==> %a@." (Formula.print dist1) ppkgs;
*)
{ i_issue = s;
i_problem =
{ p_clause = clause;
p_issue =
PSet.fold
(fun p s ->
StringSet.add (M.package_name dist2 (Package.index p))
s)
s StringSet.empty;
p_explain = explanation;
p_support1 = support1; p_support2 = support2 } })
(PSetSet.elements results),
PSet.fold
(fun p s ->
let i = Package.index p in
let res = M.Solver.solve st2init i in
assert (not res);
let r = M.Solver.collect_reasons st2init i in
M.Solver.reset st2init;
(*
if debug_coinst () then M.show_reasons dist2 r;
*)
let (clause, explanation, support1, support2) =
match reference with
Some dist2_state ->
problematic_packages
dist1_state.dist dist2 dist2_state.dist (PSet.singleton p) r
| None ->
problematic_packages
dist1_state.dist dist2 dist2 (PSet.singleton p) r
in
assert
(StringSet.mem (M.package_name dist2 (Package.index p))
clause.pos);
(p, clause, explanation, support1, support2) :: s)
!broken_new_packages [])
end
in
if debug_time () then
Format.eprintf " Analysing problems: %f@." (Timer.stop t);
(pred, !all_pkgs, all_conflicts, dep_src, graphs, broken_new_packages)
(****)
let get_clearly_broken_packages
dist1_state dist dist2_state can_break_package =
let t = Timer.start () in
let unsat_dep d =
not (List.exists (fun cstr -> M.dep_can_be_satisfied dist cstr) d) in
let was_installable p =
match M.find_packages_by_name dist1_state.dist p.M.package with
[] ->
true
| [q] ->
let res = M.Solver.solve dist1_state.st q.M.num in
M.Solver.reset dist1_state.st;
res
| _ ->
assert false
in
let problems = ref [] in
M.iter_packages dist
(fun p ->
let l =
List.filter unsat_dep p.M.depends @
List.filter unsat_dep p.M.pre_depends
in
if not (can_break_package p) && l <> [] && was_installable p then begin
List.iter
(fun d ->
if debug_coinst () then begin
let d' =
List.map (fun (id, rel) -> (M.name_of_id id, rel)) d in
Format.eprintf "Broken dependency: %a ==> %a@."
(Package.print dist) (Package.of_index p.M.num)
M.print_package_dependency [d']
end;
let r = [M.R_depends (p.M.num, d)] in
let (clause, explanation, support1, support2) =
problematic_packages dist1_state.dist dist dist2_state.dist
(PSet.singleton (Package.of_index p.M.num)) r
in
problems :=
{ p_clause = clause;
p_issue = StringSet.singleton (M.name_of_id p.M.package);
p_explain = explanation;
p_support1 = support1; p_support2 = support2 }
:: !problems)
l
end);
if debug_coinst () then
Format.eprintf ">>> %a@."
(Util.print_list (fun ch p -> print_clause ch p.p_clause) ", ")
!problems;
if debug_time () then Format.eprintf " Clearly broken: %f@." (Timer.stop t);
!problems
let analyze_installability dist1_state dist dist2_state can_break_package =
let t = Timer.start () in
let (deps, confl) = Coinst.compute_dependencies_and_conflicts dist in
if debug_time () then
Format.eprintf " Deps and confls: %f@." (Timer.stop t);
let (deps', confl') = Coinst.flatten_and_simplify dist deps confl in
let t' = Timer.start () in
let st = Coinst.generate_rules (Quotient.trivial dist) deps' confl' in
if debug_time () then
Format.eprintf " Generate rules: %f@." (Timer.stop t');
if debug_time () then Format.eprintf " Preparing: %f@." (Timer.stop t);
let package_name p =
(M.find_package_by_num dist (Package.index p)).M.package in
let is_installable p =
let res = M.Solver.solve st (Package.index p) in
M.Solver.reset st;
res
and was_installable p =
let nm = package_name p in
match M.find_packages_by_name dist1_state.dist nm with
[] ->
true
| [q] ->
let res = M.Solver.solve dist1_state.st q.M.num in
M.Solver.reset dist1_state.st;
res
| _ ->
assert false
in
let broken_pkgs = ref PSet.empty in
let to_consider = ListTbl.create 101 in
let add_package p f =
let f = Formula.normalize f in
ListTbl.add to_consider f p
in
PTbl.iteri
(fun p f ->
if
not (Formula.implies Formula._true f) &&
(Formula.implies f Formula._false ||
Formula.fold (fun _ n -> n + 1) f 0 > 1) &&
not (can_break_package (M.find_package_by_num dist (Package.index p)))
then
add_package p f)
deps';
ListTbl.iter
(fun f l ->
let p = List.hd l in
if not (is_installable p) then begin
let l = List.filter was_installable l in
broken_pkgs := List.fold_right PSet.add l !broken_pkgs
end)
to_consider;
let pr_t = Timer.start () in
let problems =
if PSet.is_empty !broken_pkgs then
[]
else begin
let st_init =
M.generate_rules_restricted dist (pset_indices !broken_pkgs) in
PSet.fold
(fun p l ->
let i = Package.index p in
let res = M.Solver.solve st_init i in
assert (not res);
let r = M.Solver.collect_reasons st_init i in
M.Solver.reset st_init;
let (clause, explanation, support1, support2) =
problematic_packages dist1_state.dist dist dist2_state.dist
(PSet.singleton p) r
in
{ p_clause = clause;
p_issue = StringSet.singleton (M.name_of_id (package_name p));
p_explain = explanation;
p_support1 = support1; p_support2 = support2 } :: l)
!broken_pkgs []
end
in
if debug_time () then begin
Format.eprintf " Computing problems: %f@." (Timer.stop pr_t);
Format.eprintf " Finding non-inst packages: %f@." (Timer.stop t)
end;
problems
(****)
let find_problematic_packages
?(check_new_packages = false) ignored_sets
dist1_state dist2_state is_preserved =
let t = Timer.start () in
let dist2 = M.new_pool () in
M.merge dist2 (fun p -> not (is_preserved p.M.package)) dist2_state.dist;
M.merge dist2 (fun p -> is_preserved p.M.package) dist1_state.dist;
if debug_time () then
Format.eprintf " Building target dist: %f@." (Timer.stop t);
let forced_pkgs = forced_packages ignored_sets in
let can_break_package p =
(*
(break_arch_all && p.M.architecture = "all")
||
*)
StringSet.mem (M.name_of_id p.M.package) forced_pkgs in
let problems =
get_clearly_broken_packages dist1_state dist2 dist2_state can_break_package
in
if
List.exists (fun p -> StringSet.cardinal p.p_clause.pos = 1)
problems
then
problems
else
let (_, _, _, _, graphs, broken_new_packages) =
analyze ~check_new_packages ignored_sets
~reference:dist2_state dist1_state dist2
in
let t = Timer.start () in
let problems =
List.map (fun i -> i.i_problem) graphs
@
List.map
(fun (p, ppkgs, explanation, support1, support2) ->
{ p_clause = ppkgs;
p_issue =
StringSet.singleton (M.package_name dist2 (Package.index p));
p_explain = explanation;
p_support1 = support1; p_support2 = support2 })
broken_new_packages
in
if debug_coinst () then
Format.eprintf ">>> %a@."
(Util.print_list (fun ch p -> print_clause ch p.p_clause) ", ")
problems;
if debug_time () then
Format.eprintf " Compute problematic package names: %f@." (Timer.stop t);
problems
let find_non_inst_packages
break_arch_all ignored_sets dist1_state dist2_state is_preserved =
let t = Timer.start () in
let dist = M.new_pool () in
M.merge dist (fun p -> not (is_preserved p.M.package)) dist2_state.dist;
M.merge dist (fun p -> is_preserved p.M.package) dist1_state.dist;
if debug_time () then
Format.eprintf " Building target dist: %f@." (Timer.stop t);
let forced_pkgs = forced_packages ignored_sets in
let can_break_package p =
(break_arch_all && p.M.architecture = "all")
||
StringSet.mem (M.name_of_id p.M.package) forced_pkgs
in
let problems =
get_clearly_broken_packages dist1_state dist dist2_state
can_break_package in
if
List.exists (fun p -> StringSet.cardinal p.p_clause.pos = 1)
problems
then
problems
else begin
let problems =
analyze_installability dist1_state dist dist2_state can_break_package in
if debug_coinst () then
Format.eprintf ">>> %a@."
(Util.print_list (fun ch p -> print_clause ch p.p_clause) ", ")
problems;
problems
end
(****)
module Union_find = Util.Union_find
let find_clusters dist1_state dist2_state is_preserved groups merge =
let dist2 = M.new_pool () in
M.merge dist2 (fun p -> true) dist1_state.dist;
let first_new = M.pool_size dist2 in
M.merge dist2 (fun p -> not (is_preserved p.M.package)) dist2_state.dist;
let first_dummy = M.pool_size dist2 in
let group_reprs = Hashtbl.create 101 in
let group_classes = Hashtbl.create 101 in
let group_pkgs = Hashtbl.create 101 in
let group_other_pkg = Hashtbl.create 101 in
List.iter
(fun (l, elt) ->
let q = List.hd l in
let pkg v =
let pseudo = "<" ^ q ^ "/" ^ v ^ ">" in
Hashtbl.add group_reprs pseudo q;
let provides = M.add_name ("<" ^ q ^ ">") in
let v = M.parse_version "0" in
{ M.num = 0; package = M.add_name pseudo;
version = v; source = (M.add_name pseudo, v);
section = ""; architecture = "";
depends = []; recommends = []; suggests = []; enhances = [];
pre_depends = []; provides = [[provides, None]];
conflicts = [[provides, None]];
breaks = []; replaces = [] }
in
let old_grp = Package.of_index (M.add_package dist2 (pkg "OLD")) in
let new_grp = Package.of_index (M.add_package dist2 (pkg "NEW")) in
Hashtbl.add group_pkgs q (old_grp, new_grp);
Hashtbl.add group_other_pkg old_grp new_grp;
Hashtbl.add group_other_pkg new_grp old_grp;
Hashtbl.add group_classes q elt;
List.iter (fun p -> Hashtbl.add group_reprs p q) l)
groups;
let group_repr p =
let nm = M.package_name dist2 (Package.index p) in
try Hashtbl.find group_reprs nm with Not_found -> ""
in
let same_group p q = group_repr p == group_repr q in
let group_class p =
try Some (Hashtbl.find group_classes p) with Not_found -> None
in
let old_version = PTbl.init dist2 (fun p -> p) in
let new_version = PTbl.init dist2 (fun p -> p) in
M.iter_packages_by_name dist2
(fun nm l ->
match l with
[p] ->
()
| [p; q] ->
let i = min p.M.num q.M.num in
let j = max p.M.num q.M.num in
PTbl.set old_version (Package.of_index j) (Package.of_index i);
PTbl.set new_version (Package.of_index i) (Package.of_index j)
| _ ->
assert false);
let is_old p = Package.index p < first_new in
let is_new p =
Package.index p >= first_new && Package.index p < first_dummy in
let is_dummy p = Package.index p >= first_dummy in
let is_removed = PTbl.create dist2 false in
M.iter_packages dist2
(fun p ->
if not (M.has_package_of_name dist2_state.dist p.M.package) then
PTbl.set is_removed (Package.of_index p.M.num) true);
let (deps2full, confl2full) =
Coinst.compute_dependencies_and_conflicts dist2 in
let confl2 = Conflict.create dist2 in
Conflict.iter confl2full
(fun p q ->
let p' = PTbl.get old_version p in
let q' = PTbl.get old_version q in
(* We omit conflicts between old and new version of packages
in a same group. *)
if
(is_old p && is_old q) || (is_new p && is_new q) ||
is_dummy p || not (same_group p q)
then
Conflict.add confl2 p' q');
let marked_conj o old_f n new_f =
let common_part f f' =
Formula.filter
(fun d -> Formula.exists (fun d' -> Disj.implies d' d) f) f'
in
let common_f =
Formula.conj (common_part old_f new_f) (common_part new_f old_f) in
Formula.conj
(Formula.conj common_f (Formula.disj (Formula.lit n) old_f))
(Formula.disj (Formula.lit o) new_f)
in
let quotient_formula p f =
Formula.fold
(fun d f ->
let disj = Disj.to_lits d in
let variable_part = PSet.filter (fun p -> group_repr p <> "") disj in
if PSet.is_empty variable_part then
Formula.conj (Formula.of_disj d) f
else begin
let stable_part = PSet.filter (fun p -> group_repr p = "") disj in
let s =
PSet.fold (fun p s -> StringSet.add (group_repr p) s)
variable_part StringSet.empty
in
(*
Format.eprintf "Involved (%s / %a):" (group_repr p) (Package.print dist2) p;
StringSet.iter (fun nm -> Format.eprintf " %s" nm) s;
Format.eprintf "@.";
*)
let f' =
StringSet.fold
(fun nm f ->
let s1 =
PSet.filter
(fun p -> is_new p && group_repr p = nm) variable_part
in
let s2 =
PSet.filter
(fun p -> is_old p && group_repr p = nm) variable_part
in
let d1 =
PSet.fold
(fun p d ->
Disj.disj (Disj.lit (PTbl.get old_version p)) d)
s1 Disj._false
in
let d2 = Disj.of_lits s2 in
(*
Format.eprintf "?? %b %b %a %a@." (nm = group_repr p) (is_old p) (Disj.print dist2) d1 (Disj.print dist2) d2;
*)
Formula.disj
(if Disj.equiv d1 d2 then
Formula.of_disj d1
else if nm <> group_repr p then
(*
Formula.conj
(Formula.of_disj d1)
(Formula.of_disj d2)
*)
let (o, n) = Hashtbl.find group_pkgs nm in
marked_conj
o (Formula.of_disj d2) n (Formula.of_disj d1)
(*
Formula.conj
(Formula.of_disj (Disj.disj d1 (Disj.lit o)))
(Formula.of_disj (Disj.disj d2 (Disj.lit n)))
*)
else if is_old p then
Formula.of_disj d2
else
Formula.of_disj d1)
f)
s Formula._false
in
let f' =
Formula.disj f' (Formula.of_disj (Disj.of_lits stable_part)) in
(*
Format.eprintf "%a ==> %a@." (Disj.print dist2) d (Formula.print dist2) f';
*)
Formula.conj f f'
end)
f Formula._true
in
let deps2 = PTbl.mapi quotient_formula deps2full in
PTbl.iteri
(fun p f ->
let q = PTbl.get old_version p in
if p <> q then begin
let nm = group_repr p in
let (o, n) = Hashtbl.find group_pkgs nm in
PTbl.set deps2 q
(marked_conj o (PTbl.get deps2 q) n (PTbl.get deps2 p));
(*
(Formula.conj (Formula.disj (Formula.lit n) (PTbl.get deps2 q)) (Formula.disj (Formula.lit o) (PTbl.get deps2 p)));
*)
(*
PTbl.set deps2 q (Formula.conj (PTbl.get deps2 q) (PTbl.get deps2 p));
*)
PTbl.set deps2 p Formula._true
end else if is_new q then begin
let nm = group_repr p in
let (o, n) = Hashtbl.find group_pkgs nm in
PTbl.set deps2 q (Formula.disj (Formula.lit o) (PTbl.get deps2 q))
end else if PTbl.get is_removed p then begin
let nm = group_repr p in
if nm <> "" then begin
let (o, n) = Hashtbl.find group_pkgs nm in
PTbl.set deps2 q (Formula.disj (Formula.lit n) (PTbl.get deps2 q))
end
end)
deps2;
(*
PTbl.iteri
(fun p f ->
Format.eprintf "%a: %a@." (Package.print dist2) p (Formula.print dist2) f)
deps2;
*)
let (deps2', confl2') = Coinst.flatten_and_simplify dist2 deps2 confl2 in
let pred = compute_predecessors dist1_state.dist dist2 in
let confl1 = dist1_state.confl in
let new_conflicts = ref [] in
Conflict.iter confl2
(fun p2 q2 ->
let i = PTbl.get pred p2 in
let j = PTbl.get pred q2 in
if i <> -1 && j <> -1 then begin
let p1 = Package.of_index i in
let q1 = Package.of_index j in
if not (Conflict.check confl1 p1 q1) then begin
if debug_coinst () then begin
Format.eprintf "possible new conflict: %a %a@."
(Package.print_name dist1_state.dist) p1
(Package.print_name dist1_state.dist) q1;
end;
new_conflicts := (p2, q2) :: !new_conflicts;
end
end);
(* Only consider new dependencies. *)
let deps2 = new_deps pred PSet.empty dist1_state.deps dist2 deps2 in
(* Compute the corresponding flattened dependencies. *)
let deps2 =
PTbl.mapi
(fun p f ->
Formula.fold
(fun d f ->
Formula.conj
(PSet.fold
(fun p f -> Formula.disj (PTbl.get deps2' p) f)
(Disj.to_lits d) Formula._false) f)
f Formula._true)
deps2
in
(* Only keep those that are new... *)
let deps2 = new_deps pred PSet.empty dist1_state.deps' dist2 deps2 in
(* ...and that are indeed in the flattened repository *)
let deps2 =
PTbl.mapi
(fun p f ->
let f' = PTbl.get deps2' p in
Formula.filter
(fun d ->
Formula.exists (fun d' -> Disj.equiv d d') f') f)
deps2
in
(* Only keep relevant conflicts. *)
let dep_targets = ref PSet.empty in
PTbl.iteri
(fun _ f ->
Formula.iter f
(fun d ->
Disj.iter d (fun p -> dep_targets := PSet.add p !dep_targets)))
deps2;
Conflict.iter confl2'
(fun p2 q2 ->
let i1 = PTbl.get pred p2 in
let j1 = PTbl.get pred q2 in
if
not (is_dummy p2 ||
(PSet.mem p2 !dep_targets && j1 <> -1) ||
(PSet.mem q2 !dep_targets && i1 <> -1) ||
(PSet.mem p2 !dep_targets && PSet.mem q2 !dep_targets))
then
Conflict.remove confl2' p2 q2);
(*
List.iter (fun (p2, q2) -> Conflict.remove confl2' p2 q2) !new_conflicts;
*)
(* As a consequence, some new dependencies might not be relevant anymore. *)
let deps2 = Coinst.remove_clearly_irrelevant_deps confl2' deps2 in
(* Add self dependencies for packages with conflicts, as we want to
consider them as well to find possible problems. *)
let deps2 =
PTbl.mapi
(fun p f ->
if Conflict.has confl2' p && PTbl.get pred p <> -1 then
Formula.conj (Formula.lit p) f
else
f)
deps2
in
let merge v v' =
match v, v' with
Some c, Some c' -> merge c c'; v
| Some _, None -> v
| None, Some _ -> v'
| None, None -> None
in
let group_confl = Hashtbl.create 101 in
PTbl.iteri
(fun p f ->
Formula.iter f
(fun d ->
if debug_cluster () then begin
Format.eprintf "New dep %a ==> %a@."
(Package.print_name dist2) p
(Disj.print dist2) d
end;
let c =
if Disj.implies1 p d then begin
if debug_cluster () then begin
let s = group_repr p in
if s <> "" then Format.eprintf " ==> %s@." s
end;
group_class (group_repr p)
end else
Disj.fold
(fun p c ->
if is_dummy p then begin
if debug_cluster () then begin
let s = group_repr p in
if s <> "" then Format.eprintf " ==> %s@." s
end;
merge c (group_class (group_repr p))
end else
c)
d None
in
let c = Union_find.elt c in
Disj.iter d
(fun p ->
if not (is_dummy p) then
let c' =
try
Hashtbl.find group_confl p
with Not_found ->
Union_find.elt None
in
Union_find.merge c c' merge;
Hashtbl.replace group_confl p c)))
deps2;
Conflict.iter confl2'
(fun p p' ->
if not (is_dummy p) then begin
(*
Format.eprintf "Old conflict %a ## %a@."
(Package.print dist2) p (Package.print dist2) p';
*)
try
let c = Hashtbl.find group_confl p in
let c' = Hashtbl.find group_confl p' in
Union_find.merge c c' merge
with Not_found ->
assert false
end);
List.iter
(fun (p, p') ->
let c = group_class (group_repr p) in
let c' = group_class (group_repr p') in
if debug_cluster () then
Format.eprintf "New conflict %s ## %s@." (group_repr p) (group_repr p');
ignore (merge c c'))
!new_conflicts;
PTbl.iteri
(fun p f ->
if is_new p && PTbl.get old_version p = p then begin
if debug_cluster () then
Format.eprintf "New package %a ==> %a@."
(Package.print_name dist2) p
(Formula.print dist2) f;
Formula.iter f
(fun d ->
ignore
(Disj.fold
(fun p c ->
if is_dummy p then
merge c (group_class (group_repr p))
else
c)
d None))
end)
deps2'
(****)
(*
type pkg_ref = string * bool * bool
type reason =
R_depends of pkg_ref * M.dep * pkg_ref list
| R_conflict of pkg_ref * M.dep * pkg_ref
*)
module D = Dot_file
let output_conflict_graph f problem =
let conflict = problem.p_issue in
let reasons = problem.p_explain in
let i = ref 0 in
let pkg (nm, _, _) = nm in
let line_style t u =
match t, u with
true, false -> ["dotted"]
| false, true -> ["dashed"]
| true, true -> []
| _ -> assert false
in
let make_style l = if l = [] then [] else ["style", String.concat "," l] in
let new_node () = incr i; D.node (string_of_int !i) in
let pkgs = Hashtbl.create 17 in
let pkg_node nm rem =
if Hashtbl.mem pkgs nm then rem else begin
Hashtbl.add pkgs nm ();
let t = StringSet.mem nm problem.p_support1 in
let u = StringSet.mem nm problem.p_support2 in
let st = line_style t u in
let color =
if StringSet.mem nm conflict then
make_style ("filled" :: st) @ ["fillcolor", "#ebc885"]
else
make_style st
in
`Compound ([D.node nm], ("label", nm) :: color) :: rem
end
in
let style (_, t, u) = make_style (line_style t u) in
let in_dep = Hashtbl.create 17 in
List.iter
(fun r ->
match r with
R_depends (_, _, l) ->
List.iter (fun (nm, _, _) -> Hashtbl.add in_dep nm ()) l
| R_conflict _ ->
())
reasons;
let l =
`Attributes (`Graph, ["rankdir", "LR"]) ::
`Attributes
(`Node, ["fontsize", "8"; "margin", "0.05,0"; "height", "0.2";
"style", "rounded"]) ::
List.fold_right
(fun r l ->
match r with
R_depends (p, _, []) ->
let n = new_node () in
pkg_node (pkg p) (
`Compound
([n], ["color", "blue"; "shape", "box"; "label", "NONE"]) ::
`Compound ([D.node (pkg p); n],
style p @ ["color", "blue"; "minlen", "2"]) :: l)
| R_depends (p, _, [q]) ->
let pstyle = style p in
let qstyle = style q in
pkg_node (pkg p) (
pkg_node (pkg q) (
if pstyle = qstyle then begin
`Compound ([D.node (pkg p); D.node (pkg q)],
pstyle @ ["color", "blue"; "minlen", "2"]) :: l
end else begin
let n = new_node () in
`Compound ([n], ["label", ""; "fixedsize", "true";
"width", "0.0"; "height", "0";
"shape", "none"]) ::
`Compound ([D.node (pkg p); n],
pstyle @ ["color", "blue"; "dir", "none"]) ::
`Compound ([n; D.node (pkg q)],
qstyle @ ["color", "blue"]) :: l
end))
| R_depends (p, _, pl) ->
let n = new_node () in
pkg_node (pkg p) (
List.fold_right (fun q rem -> pkg_node (pkg q) rem) pl (
`Compound
([n],
["label", "∨"; "shape", "circle";
"color", "blue"; "fontcolor", "blue"]) ::
`Compound
([D.node (pkg p); n],
style p @ ["color", "blue"; "dir", "none"]) ::
List.map
(fun p ->`Compound ([n; D.node (pkg p)],
style p @ ["color", "blue"]))
pl @
l))
| R_conflict (p1, _, p2) ->
(*
let print_ref f (nm, t, u) =
match t, u with
true, true -> Format.fprintf f "%s" nm
| true, false -> Format.fprintf f "%s (testing)" nm
| false, true -> Format.fprintf f "%s (sid)" nm
| false, false -> assert false
in
Format.eprintf "| %a ## %a@." print_ref p1 print_ref p2;
*)
let (p1, p2) =
if
Hashtbl.mem in_dep (pkg p2) &&
not (Hashtbl.mem in_dep (pkg p1))
then
(p2, p1)
else
(p1, p2)
in
let style1 = style p1 in
let style2 = style p2 in
let attrs = ["dir", "none"; "color", "red"] in
pkg_node (pkg p1) (
pkg_node (pkg p2) (
if style1 = style2 then begin
`Compound ([D.node (pkg p1); D.node (pkg p2)],
("minlen", "2") :: style1 @ attrs) :: l
end else begin
let n = new_node () in
`Compound ([n], ["label", ""; "fixedsize", "true";
"width", "0.0"; "height", "0";
"shape", "none"]) ::
`Compound ([D.node (pkg p1); n], style1 @ attrs) ::
`Compound ([n; D.node (pkg p2)], style2 @ attrs) :: l
end)))
reasons []
in
D.print f (D.graph `Digraph "G" l)
(****)
let conj_inter l l' =
match l, l' with
None, None -> None
| Some _ , None -> l
| None, Some _ -> l'
| Some s, Some s' -> Some (PSet.inter s s')
let conj_union l l' =
match l, l' with
| Some s, Some s' -> Some (PSet.union s s')
| _ -> None
let rec conj_deps tbl dist deps visited l =
Formula.fold
(fun d (l, r) ->
let (l', r') =
Disj.fold
(fun i (l, r) ->
let (l', r') = conj_dep tbl dist deps visited i in
(conj_inter l' l, PSet.union r r')) d (None, r)
in
(conj_union l' l, r'))
l (Some PSet.empty, PSet.empty)
and conj_dep tbl dist deps visited i =
try
(Hashtbl.find tbl i, PSet.empty)
with Not_found ->
let res =
if List.mem i visited then
(Some PSet.empty, PSet.singleton i)
else begin
let (l, r) =
conj_deps tbl dist deps (i :: visited) (PTbl.get deps i)
in
(*
Format.eprintf "XXX %a: %a (%d)@."
(Package.print_name dist) i (Formula.print dist) (PTbl.get deps i) (match l with Some s -> PSet.cardinal s | None -> -1);
*)
let r = PSet.remove i r in
(conj_union (Some (PSet.singleton i)) l, r)
end
in
(* Only cache the result if it is unconditionally true *)
if PSet.is_empty (snd res) then Hashtbl.add tbl i (fst res);
res
let conj_dependencies dist deps =
let tbl = Hashtbl.create 17 in
PTbl.init dist (fun p -> fst (conj_dep tbl dist deps [] p))
let reversed_conj_dependencies dist deps =
let tbl = PTbl.create dist PSet.empty in
let tbl' = conj_dependencies dist deps in
PTbl.iteri
(fun p l ->
match l with
None ->
()
| Some s ->
PSet.iter
(fun p' ->
(*
Format.eprintf "YYY %a -> %a@."
(Package.print_name dist) p (Package.print_name dist) p';
*)
PTbl.set tbl p' (PSet.add p (PTbl.get tbl p'))) s)
tbl';
tbl
(**** Breaking co-installability ****)
let comma_re = Str.regexp "[ \t]*,[ \t]*"
let bar_re = Str.regexp "[ \t]*|[ \t]*"
let empty_break_set () = ref []
let allow_broken_sets broken_sets s =
let l = Str.split comma_re (Util.trim s) in
let ext = List.mem "_" l in
let l = List.filter (fun s -> s <> "_") l in
(* XXXX Should disallow specs such that a,a *)
let l =
List.fold_left
(fun l s ->
List.fold_left
(fun s nm -> StringSet.add nm s)
StringSet.empty (Str.split bar_re s)
:: l)
[] l
in
broken_sets := (l, ext) :: !broken_sets
let copy_ignored_sets l = ref !l
coinst-1.9.3/solver.ml 0000644 0001750 0001750 00000037376 12657630652 013661 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let debug = ref false
module type S = sig
type reason
end
module type SOLVER = sig
type state
type reason
type var = int
type lit
val lit_of_var : var -> bool -> lit
val initialize_problem :
?print_var:(Format.formatter -> int -> unit) -> int -> state
val propagate : state -> unit
val protect : state -> unit
val reset : state -> unit
type value = True | False | Unknown
val assignment : state -> value array
val add_rule : state -> lit array -> reason list -> unit
val associate_vars : state -> lit -> var list -> unit
val solve : state -> var -> bool
val solve_lst : state -> var list -> bool
val solve_neg_list : state -> var list -> var list -> bool
val collect_reasons : state -> var -> reason list
val collect_reasons_lst : state -> var list -> reason list
end
module F (X : S) = struct
(* Variables *)
type var = int
(* Literals *)
type lit = int
type reason = X.reason
(* A clause is an array of literals *)
type clause =
{ lits : lit array;
all_lits : lit array;
reasons : reason list }
type value = True | False | Unknown
module LitMap =
Map.Make (struct type t = int let compare (x : int) y = compare x y end)
type state =
{ (* Indexed by var *)
st_assign : value array;
st_reason : clause option array;
st_level : int array;
st_seen_var : int array;
st_refs : int array;
st_pinned : bool array;
(* Indexed by lit *)
st_simpl_prop : clause LitMap.t array;
st_watched : clause list array;
st_associated_vars : var list array;
(* Queues *)
mutable st_trail : lit list;
mutable st_trail_lim : lit list list;
st_prop_queue : lit Queue.t;
(* Misc *)
mutable st_cur_level : int;
mutable st_min_level : int;
mutable st_seen : int;
mutable st_var_queue_head : var list;
st_var_queue : var Queue.t;
mutable st_cost : int; (* Total computational cost so far *)
st_print_var : Format.formatter -> int -> unit;
mutable st_coherent : bool }
(****)
let charge st x = st.st_cost <- st.st_cost + x
let get_bill st = st.st_cost
(****)
let pin_var st x = st.st_pinned.(x) <- true
let unpin_var st x = st.st_pinned.(x) <- false
let enqueue_var st x =
charge st 1;
pin_var st x;
Queue.push x st.st_var_queue
let requeue_var st x =
pin_var st x;
st.st_var_queue_head <- x :: st.st_var_queue_head
(* Returns -1 if no variable remains *)
let rec dequeue_var st =
let x =
match st.st_var_queue_head with
x :: r -> st.st_var_queue_head <- r; x
| [] -> try Queue.take st.st_var_queue with Queue.Empty -> -1
in
if x = -1 then x else begin
unpin_var st x;
if st.st_refs.(x) = 0 || st.st_assign.(x) <> Unknown then
dequeue_var st
else
x
end
(****)
let var_of_lit p = p lsr 1
let pol_of_lit p = p land 1 = 0
let lit_of_var v s = if s then v + v else v + v + 1
let lit_neg p = p lxor 1
let val_neg v =
match v with
True -> False
| False -> True
| Unknown -> Unknown
let val_of_bool b = if b then True else False
let val_of_lit st p =
let v = st.st_assign.(var_of_lit p) in
if pol_of_lit p then v else val_neg v
(****)
let print_val ch v =
Format.fprintf ch "%s"
(match v with True -> "True" | False -> "False" | Unknown -> "Unknown")
let print_lits st ch lits =
Format.fprintf ch "{";
Array.iter
(fun p ->
if pol_of_lit p then
Format.fprintf ch " +%a" st.st_print_var (var_of_lit p)
else
Format.fprintf ch " -%a" st.st_print_var (var_of_lit p))
lits;
Format.fprintf ch " }"
let print_rule st ch r = print_lits st ch r.lits
(****)
exception Conflict of clause option
let enqueue st p reason =
charge st 1;
if !debug then begin
match reason with
Some r -> Format.eprintf "Applying rule %a@." (print_rule st) r
| _ -> ()
end;
match val_of_lit st p with
False ->
if !debug then begin
if pol_of_lit p then
Format.eprintf "Cannot install %a@." st.st_print_var (var_of_lit p)
else
Format.eprintf "Already installed %a@."
st.st_print_var (var_of_lit p)
end;
raise (Conflict reason)
| True ->
()
| Unknown ->
if !debug then begin
if pol_of_lit p then
Format.eprintf "Installing %a@." st.st_print_var (var_of_lit p)
else
Format.eprintf "Should not install %a@."
st.st_print_var (var_of_lit p);
end;
let x = var_of_lit p in
st.st_assign.(x) <- val_of_bool (pol_of_lit p);
st.st_reason.(x) <- reason;
st.st_level.(x) <- st.st_cur_level;
st.st_trail <- p :: st.st_trail;
List.iter
(fun x ->
charge st 1;
let refs = st.st_refs.(x) in
if refs = 0 then enqueue_var st x;
st.st_refs.(x) <- st.st_refs.(x) + 1)
st.st_associated_vars.(p);
Queue.push p st.st_prop_queue
let rec find_not_false st lits i l =
if i = l then -1 else
if val_of_lit st lits.(i) <> False then i else
find_not_false st lits (i + 1) l
let propagate_in_clause st r p =
charge st 1;
let p' = lit_neg p in
if r.lits.(0) = p' then begin
r.lits.(0) <- r.lits.(1);
r.lits.(1) <- p'
end;
if val_of_lit st r.lits.(0) = True then
st.st_watched.(p) <- r :: st.st_watched.(p)
else begin
let i = find_not_false st r.lits 2 (Array.length r.lits) in
if i = -1 then begin
st.st_watched.(p) <- r :: st.st_watched.(p);
enqueue st r.lits.(0) (Some r)
end else begin
r.lits.(1) <- r.lits.(i);
r.lits.(i) <- p';
let p = lit_neg r.lits.(1) in
st.st_watched.(p) <- r :: st.st_watched.(p)
end
end
let propagate st =
try
while not (Queue.is_empty st.st_prop_queue) do
charge st 1;
let p = Queue.take st.st_prop_queue in
LitMap.iter (fun p r -> enqueue st p (Some r)) st.st_simpl_prop.(p);
let l = ref (st.st_watched.(p)) in
st.st_watched.(p) <- [];
begin try
while
match !l with
r :: rem ->
l := rem;
propagate_in_clause st r p;
true
| [] ->
false
do () done
with Conflict _ as e ->
st.st_watched.(p) <- !l @ st.st_watched.(p);
raise e
end
done
with Conflict _ as e ->
Queue.clear st.st_prop_queue;
raise e
(****)
let raise_level st =
st.st_cur_level <- st.st_cur_level + 1;
st.st_trail_lim <- st.st_trail :: st.st_trail_lim;
st.st_trail <- []
let assume st p =
raise_level st;
enqueue st p None
let protect st =
propagate st;
raise_level st;
st.st_min_level <- st.st_cur_level
let undo_one st p =
let x = var_of_lit p in
if !debug then Format.eprintf "Cancelling %a@." st.st_print_var x;
st.st_assign.(x) <- Unknown;
st.st_reason.(x) <- None;
st.st_level.(x) <- -1;
List.iter
(fun x -> charge st 1; st.st_refs.(x) <- st.st_refs.(x) - 1)
st.st_associated_vars.(p);
if st.st_refs.(x) > 0 && not st.st_pinned.(x) then enqueue_var st x
let cancel st =
st.st_cur_level <- st.st_cur_level - 1;
List.iter (fun p -> undo_one st p) st.st_trail;
match st.st_trail_lim with
[] -> assert false
| l :: r -> st.st_trail <- l; st.st_trail_lim <- r
let reset st =
if !debug then Format.eprintf "Reset@.";
while st.st_trail_lim <> [] do cancel st done;
for i = 0 to Array.length st.st_refs - 1 do
st.st_refs.(i) <- 0;
st.st_pinned.(i) <- false
done;
st.st_var_queue_head <- [];
st.st_min_level <- 0;
Queue.clear st.st_var_queue;
st.st_coherent <- true
(****)
let rec find_next_lit st =
match st.st_trail with
[] ->
assert false
| p :: rem ->
st.st_trail <- rem;
if st.st_seen_var.(var_of_lit p) = st.st_seen then
let reason = st.st_reason.(var_of_lit p) in
undo_one st p;
(p, reason)
else begin
undo_one st p;
find_next_lit st
end
let analyze st conflict =
st.st_seen <- st.st_seen + 1;
let counter = ref 0 in
let learnt = ref [] in
let bt_level = ref 0 in
let reasons = ref [] in
let r = ref conflict in
while
if !debug then begin
Array.iter
(fun p ->
Format.eprintf "%d:%a (%b/%d) "
p print_val (val_of_lit st p)
(st.st_reason.(var_of_lit p) <> None)
st.st_level.(var_of_lit p))
!r.lits;
Format.eprintf "@."
end;
reasons := !r.reasons @ !reasons;
for i = 0 to Array.length !r.all_lits - 1 do
let p = !r.all_lits.(i) in
let x = var_of_lit p in
if st.st_seen_var.(x) <> st.st_seen then begin
assert (val_of_lit st p = False);
st.st_seen_var.(x) <- st.st_seen;
let level = st.st_level.(x) in
if level = st.st_cur_level then begin
incr counter
end else (* if level > 0 then*) begin
learnt := p :: !learnt;
bt_level := max level !bt_level
end
end
done;
let (p, reason) = find_next_lit st in
decr counter;
if !counter = 0 then
learnt := lit_neg p :: !learnt
else
begin match reason with
Some r' -> r := r'
| None -> assert false
end;
!counter > 0
do () done;
if !debug then begin
List.iter
(fun p ->
Format.eprintf "%d:%a/%d "
p print_val (val_of_lit st p) st.st_level.(var_of_lit p))
!learnt;
Format.eprintf "@."
end;
(Array.of_list !learnt, !reasons, !bt_level)
let find_highest_level st lits =
let level = ref (-1) in
let i = ref 0 in
Array.iteri
(fun j p ->
if st.st_level.(var_of_lit p) > !level then begin
level := st.st_level.(var_of_lit p);
i := j
end)
lits;
!i
let rec solve_rec st =
match try propagate st; None with Conflict r -> Some r with
None ->
let x = dequeue_var st in
x < 0 ||
begin
assume st (lit_of_var x false);
solve_rec st
end
| Some r ->
let r =
match r with
None -> assert false
| Some r -> r
in
let (learnt, reasons, level) = analyze st r in
let level = max st.st_min_level level in
while st.st_cur_level > level do cancel st done;
assert (val_of_lit st learnt.(0) = Unknown);
let rule = { lits = learnt; all_lits = learnt; reasons = reasons } in
if !debug then Format.eprintf "Learning %a@." (print_rule st) rule;
if Array.length learnt > 1 then begin
let i = find_highest_level st learnt in
assert (i > 0);
let p' = learnt.(i) in
learnt.(i) <- learnt.(1);
learnt.(1) <- p';
let p = lit_neg learnt.(0) in
let p' = lit_neg p' in
st.st_watched.(p) <- rule :: st.st_watched.(p);
st.st_watched.(p') <- rule :: st.st_watched.(p')
end;
enqueue st learnt.(0) (Some rule);
st.st_cur_level > st.st_min_level &&
solve_rec st
let rec solve st x =
assert (st.st_cur_level = st.st_min_level);
propagate st;
try
let p = lit_of_var x true in
assume st p;
assert (st.st_cur_level = st.st_min_level + 1);
if solve_rec st then begin
protect st;
true
end else
solve st x
with Conflict _ ->
st.st_coherent <- false;
false
let rec solve_lst_rec st l0 l =
match l with
[] ->
true
| x :: r ->
protect st;
List.iter (fun x -> enqueue st (lit_of_var x true) None) l0;
propagate st;
if solve st x then begin
if r <> [] then reset st;
solve_lst_rec st (x :: l0) r
end else
false
let solve_lst st l = solve_lst_rec st [] l
let rec solve_not st x =
assert (st.st_cur_level = st.st_min_level);
propagate st;
try
let p = lit_of_var x false in
assume st p;
assert (st.st_cur_level = st.st_min_level + 1);
if solve_rec st then begin
protect st;
true
end else
solve_not st x
with Conflict _ ->
st.st_coherent <- false;
false
let rec solve_lst_rec st vars l0 l =
match l with
[] ->
true
| x :: r ->
protect st;
List.iter
(fun x ->
let refs = st.st_refs.(x) in
if refs = 0 then enqueue_var st x;
st.st_refs.(x) <- st.st_refs.(x) + 1)
vars;
List.iter (fun x -> enqueue st (lit_of_var x false) None) l0;
propagate st;
if solve_not st x then begin
if r <> [] then reset st;
solve_lst_rec st vars (x :: l0) r
end else
false
let solve_neg_list st vars neg = solve_lst_rec st vars [] neg
let initialize_problem ?(print_var = (fun fmt -> Format.fprintf fmt "%d")) n =
{ st_assign = Array.make n Unknown;
st_reason = Array.make n None;
st_level = Array.make n (-1);
st_seen_var = Array.make n (-1);
st_refs = Array.make n 0;
st_pinned = Array.make n false;
st_simpl_prop = Array.make (2 * n) LitMap.empty;
st_watched = Array.make (2 * n) [];
st_associated_vars = Array.make (2 * n) [];
st_trail = [];
st_trail_lim = [];
st_prop_queue = Queue.create ();
st_cur_level = 0;
st_min_level = 0;
st_seen = 0;
st_var_queue_head = [];
st_var_queue = Queue.create ();
st_cost = 0;
st_print_var = print_var;
st_coherent = true }
let insert_simpl_prop st r p p' =
let p = lit_neg p in
if not (LitMap.mem p' st.st_simpl_prop.(p)) then
st.st_simpl_prop.(p) <- LitMap.add p' r st.st_simpl_prop.(p)
let add_bin_rule st lits p p' reasons =
let r = { lits = [|p; p'|]; all_lits = lits; reasons = reasons } in
insert_simpl_prop st r p p';
insert_simpl_prop st r p' p
let add_un_rule st lits p reasons =
let r = { lits = [|p|]; all_lits = lits; reasons = reasons } in
enqueue st p (Some r)
let add_rule st lits reasons =
let all_lits = Array.copy lits in
let is_true = ref false in
let j = ref 0 in
for i = 0 to Array.length lits - 1 do
match val_of_lit st lits.(i) with
True -> is_true := true
| False -> ()
| Unknown -> lits.(!j) <- lits.(i); incr j
done;
let lits = Array.sub lits 0 !j in
if not !is_true then
match Array.length lits with
0 -> assert false
| 1 -> add_un_rule st all_lits lits.(0) reasons
| 2 -> add_bin_rule st all_lits lits.(0) lits.(1) reasons
| _ -> let rule = { lits = lits; all_lits = all_lits; reasons = reasons } in
let p = lit_neg rule.lits.(0) in let p' = lit_neg rule.lits.(1) in
assert (val_of_lit st p <> False);
assert (val_of_lit st p' <> False);
st.st_watched.(p) <- rule :: st.st_watched.(p);
st.st_watched.(p') <- rule :: st.st_watched.(p')
let associate_vars st lit l =
st.st_associated_vars.(lit) <- l @ st.st_associated_vars.(lit)
let rec collect_rec st x l =
if st.st_seen_var.(x) = st.st_seen then l else begin
st.st_seen_var.(x) <- st.st_seen;
match st.st_reason.(x) with
None ->
l
| Some r ->
r.reasons @
Array.fold_left
(fun l p -> collect_rec st (var_of_lit p) l) l r.all_lits
end
let collect_reasons st x =
st.st_seen <- st.st_seen + 1;
collect_rec st x []
let collect_reasons_lst st l =
st.st_seen <- st.st_seen + 1;
let x = List.find (fun x -> st.st_assign.(x) = False) l in
collect_rec st x []
let assignment st = st.st_assign
end
coinst-1.9.3/cudf_lib.mli 0000644 0001750 0001750 00000001502 12657630652 014245 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
include Api.S
coinst-1.9.3/coinst_common.ml 0000644 0001750 0001750 00000027006 12657630652 015203 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let debug_time = Debug.make "time" "Print execution times" []
let debug_irrelevant =
Debug.make "irrelevant" "Debug irrelevant dependency removal" []
module F (M : Api.S) = struct
module Repository = Repository.F(M)
open Repository
module Quotient = Quotient.F (Repository)
(****)
let compute_dependencies_and_conflicts dist =
let confl = Conflict.create dist in
let c = M.compute_conflicts dist in
Array.iteri
(fun p1 l ->
List.iter
(fun p2 ->
Conflict.add confl (Package.of_index p1) (Package.of_index p2))
l)
c;
let deps =
let d = M.compute_deps dist in
PTbl.init dist
(fun p ->
Formula.conjl
(List.map (fun l' -> Formula.lit_disj (Package.of_index_list l'))
d.(Package.index p)))
in
(deps, confl)
let generate_rules quotient deps confl =
let dist = Quotient.pool quotient in
let st =
M.Solver.initialize_problem
~print_var:(M.print_pack dist) (M.pool_size dist) in
Conflict.iter confl
(fun p1 p2 ->
let p1 = M.Solver.lit_of_var (Package.index p1) false in
let p2 = M.Solver.lit_of_var (Package.index p2) false in
M.Solver.add_rule st [|p1; p2|] []);
Quotient.iter
(fun p ->
let f = PTbl.get deps p in
Formula.iter f
(fun d ->
let l = Disj.to_lits d in
if not (PSet.mem p l) then begin
let l = List.map (fun p -> Package.index p) (PSet.elements l) in
M.Solver.add_rule st
(Array.of_list
(M.Solver.lit_of_var (Package.index p) false ::
List.map (fun p -> M.Solver.lit_of_var p true) l))
[];
match l with
[] | [_] ->
()
| _ ->
M.Solver.associate_vars st
(M.Solver.lit_of_var (Package.index p) true) l
end))
quotient;
st
(****)
(*
let t = ref (Unix.gettimeofday ())
let sample f =
let t' = Unix.gettimeofday () in
if t' -. !t > 1. then begin t := t'; f () end
*)
let not_clearly_irrelevant confl d =
Disj.for_all
(fun p -> Conflict.exists confl (fun q -> not (Disj.implies1 q d)) p) d
let simplify_formula confl f =
Formula.filter (fun d -> not_clearly_irrelevant confl d) f
type flatten_data = {
f_computed : bool PTbl.t; f_flatten_deps : dependencies;
f_dist : pool; f_deps : dependencies; f_confl : Conflict.t }
let rec flatten_deps data visited l =
Formula.fold
(fun d (l, r) ->
let (l', r') =
Disj.fold
(fun i (l, r) ->
(*
sample (fun () -> Format.eprintf "(2) %a@." (Formula.print data.f_dist) l);
*)
let (l', r') = flatten_dep data visited i in
(simplify_formula data.f_confl (Formula.disj l' l),
PSet.union r r'))
d (Formula._false, r)
in
(Formula.conj l' l, r'))
l (Formula._true, PSet.empty)
and flatten_dep data visited i =
let res =
if PTbl.get data.f_computed i then
(PTbl.get data.f_flatten_deps i, PSet.empty)
else
let res =
if List.mem i visited then
(Formula._true, PSet.singleton i)
else begin
let (l, r) =
flatten_deps data (i :: visited) (PTbl.get data.f_deps i)
in
let r = PSet.remove i r in
if Conflict.has data.f_confl i then
(Formula.conj (Formula.lit i) l, r)
else
(l, r)
end
in
(* Only cache the result if it is unconditionally true *)
if PSet.is_empty (snd res) then begin
PTbl.set data.f_flatten_deps i (fst res);
PTbl.set data.f_computed i true
end;
res
in
(*
sample (fun () -> Format.eprintf "(1) %a@." (Formula.print data.f_dist) (fst res));
*)
res
let flatten_dependencies dist deps confl =
let data =
{ f_flatten_deps = PTbl.create dist Formula._true;
f_computed = PTbl.create dist false;
f_dist = dist; f_deps = deps; f_confl = confl }
in
PTbl.iteri (fun p _ -> ignore (flatten_dep data [] p)) data.f_computed;
data.f_flatten_deps
(****)
let remove_redundant_conflicts dist deps confl =
let conj_deps p =
let f = PTbl.get deps p in
Formula.fold
(fun d s -> match Disj.to_lit d with Some p -> PSet.add p s | None -> s)
f PSet.empty
in
let try_remove_conflict p1 p2 =
let f1 = PTbl.get deps p1 in
let d2 = conj_deps p2 in
if
Formula.exists
(fun d1 ->
Disj.for_all
(fun q1 ->
PSet.exists
(fun q2 ->
(p1 <> q1 || p2 <> q2) &&
(p1 <> q2 || p2 <> q1) &&
Conflict.check confl q1 q2)
d2)
d1)
f1
then begin
(*
Format.eprintf "%a ## %a@."
(Package.print_name dist) p1 (Package.print_name dist) p2;
*)
Conflict.remove confl p1 p2
end
in
Conflict.iter confl try_remove_conflict;
Conflict.iter confl (fun p1 p2 -> try_remove_conflict p2 p1)
(****)
let remove_self_conflicts dist deps confl =
let clearly_broken p f =
Formula.exists
(fun d ->
match Disj.to_lit d with
Some q -> Conflict.check confl p q
| None -> false)
f
in
let changed = ref false in
let deps =
PTbl.mapi
(fun p f ->
if clearly_broken p f then begin
Format.printf "self conflict: %a@." (Package.print_name dist) p;
changed := true; Formula._false
end else
f)
deps
in
(deps, !changed)
(****)
let remove_clearly_irrelevant_deps confl deps =
PTbl.map (simplify_formula confl) deps
let is_composition add_dependency (*dist*) confl deps p d0 =
let f = PTbl.get deps p in
Formula.exists
(fun d' ->
not (Disj.equiv d0 d') && not (Disj.equiv (Disj.lit p) d') &&
let s = Disj.diff d0 d' in
Disj.exists
(fun q ->
let d = if Disj.implies1 q d0 then Disj.disj1 q s else s in
Formula.exists
(fun d'' ->
let res =
Disj.implies d d'' &&
not_clearly_irrelevant confl (Disj.cut d' q d'')
in
(*
if res then Format.eprintf "%a %a@." (Package.print_name dist) p (Package.print_name dist) q;
*)
if res then begin add_dependency p q; add_dependency p p end;
res)
(PTbl.get deps q))
d')
f
let possibly_irrelevant confl deps d =
Disj.exists
(fun q ->
Conflict.for_all confl
(fun r ->
Formula.exists
(fun d' ->
Disj.implies d' d && not (Disj.implies1 q d'))
(PTbl.get deps r))
q)
d
let remove_irrelevant_deps dist confl deps blacklist =
let deps = PTbl.copy deps in
let removed_deps = PTbl.create dist Formula._true in
let dependencies = PTbl.create dist PSet.empty in
let considered = PTbl.create dist false in
let in_queue = PTbl.create dist false in
let queue = Queue.create () in
let push p =
if not (PTbl.get in_queue p) then begin
Queue.push p queue;
PTbl.set in_queue p true
end
in
let add_dependency p q =
if debug_irrelevant () then
Format.eprintf "YY %a => %a@."
(Package.print_name dist) p (Package.print_name dist) q;
PTbl.set dependencies q (PSet.add p (PTbl.get dependencies q));
if not (PTbl.get considered q) then push q
in
let rec dequeue f =
try
let p = Queue.pop queue in
PTbl.set in_queue p false;
PTbl.set considered p true;
let changed = f p in
if changed then begin
let s = PTbl.get dependencies p in
PTbl.set dependencies p PSet.empty;
if PSet.mem p s then push p;
PSet.iter push s
end;
dequeue f
with Queue.Empty ->
()
in
let check_all f =
PTbl.iteri (fun p c -> if not c then begin push p; dequeue f end)
considered
in
check_all
(fun p ->
let changed = ref false in
let f = PTbl.get deps p in
let count f = Formula.fold (fun _ n -> n + 1) f 0 in
PTbl.set deps p
(Formula.filter
(fun d ->
let remove =
Disj.cardinal d > 1 &&
not (Disj.Set.mem d blacklist) &&
possibly_irrelevant confl deps d &&
not (is_composition add_dependency confl deps p d)
in
if remove then begin
changed := true;
PTbl.set removed_deps p
(Formula.conj (PTbl.get removed_deps p) (Formula.of_disj d))
end;
not remove)
f);
if debug_irrelevant () then
Format.eprintf "XXX %a %b (%d %d)@."
(Package.print_name dist) p !changed
(count f) (count (PTbl.get deps p));
!changed);
(deps, removed_deps)
let flatten_and_simplify ?(aggressive=false) dist deps0 confl =
let confl = Conflict.copy confl in
let t = Unix.gettimeofday () in
let deps = flatten_dependencies dist deps0 confl in
let rec remove_conflicts deps =
let (deps, changed) = remove_self_conflicts dist deps confl in
remove_redundant_conflicts dist deps confl;
let deps = flatten_dependencies dist deps confl in
if changed then remove_conflicts deps else deps
in
let deps =
if aggressive then
remove_conflicts deps
else begin
remove_redundant_conflicts dist deps confl;
remove_clearly_irrelevant_deps confl deps
end
in
let rec try_remove_deps blacklist deps =
let (deps', removed_deps) =
remove_irrelevant_deps dist confl deps blacklist in
let problems = ref Disj.Set.empty in
PTbl.iteri
(fun p f ->
if not (Formula.implies Formula._true f) then begin
Formula.iter (PTbl.get deps0 p)
(fun d' ->
Disj.iter d'
(fun q ->
Formula.iter (PTbl.get removed_deps q)
(fun d'' ->
if
Formula.exists (fun d -> Disj.implies d'' d) f
then begin
problems :=
Disj.Set.add d'' !problems;
(*
Format.eprintf "XXXX %a => %a => %a (%a)@." (Package.print_name dist) p (Package.print_name dist) q (Disj.print dist) d''
(Formula.print dist) f
*)
end)))
end)
deps';
if Disj.Set.is_empty !problems then
deps'
else
try_remove_deps (Disj.Set.union blacklist !problems) deps
in
let t' = Unix.gettimeofday () in
let deps = try_remove_deps Disj.Set.empty deps in
if debug_time () then
Format.eprintf " Removing irrelevant deps: %fs@."
(Unix.gettimeofday () -. t');
if debug_time () then
Format.eprintf "Flattening: %fs@." (Unix.gettimeofday () -. t);
(deps, confl)
end
coinst-1.9.3/TODO.txt 0000644 0001750 0001750 00000005202 12657630652 013302 0 ustar mehdi mehdi - Focus
==> Work on the quotiented graph
==> Highlight the roots
==> Show exactly the selected subgraph
==> Generate all focus graphs (and show to which nodes they correspond)
- Viwever: key bindings + redraw optimizations + tooltips
- Graph creation: focus on a package
- Bug in Lwt_pool (???)
- Fix bug in eliom client (unwrapping elements)
- Fix performance issue in Ocaml
=============================
- smarter way to remove conflicts at the initial stage
exist d, forall p, p in d -> exist q, q ## p /\ f ==> q
- try to associate a set of package and virtual packages to each
disjunctive depends and conflict cliques
- find a way to automatically remove uninteresting nodes
===> not part of a non-trivial conflict clique
(or only conflicts with nodes with no other conflicts?)
+ no package depends on it
(and does not depend on any package?)
- improve algorithm for finding cliques of conflicts
==> Data Reduction and Exact Algorithms for Clique Cover
http://theinf1.informatik.uni-jena.de/ecc/
A note on the problem of reporting maximal cliques
==> clique partitioning
==> Exact Coloring of Real-Life Graphs is Easy
New Graph Coloring Algorithms
RESEARCH ON GREEDY CLIQUE PARTITION-GCP ALGORITHM (?)
====> we want to cluster clique
=> biclique covering
Fast Exact and Heuristic Methods for Role Minimization Problems
Confluent Layered Drawings
Biclique Edge Cover Graphs and Confluent Drawings (?)
Confluent Drawings: Visualizing Non-planar Diagrams in a Planar Way
- generate directly a dot file with position informations
- remove some edges that can be obtained by transitivity
- investigate the edges that was not removed
====
- what can we say about updates: desemphasize edges that are unchanged
=================================
Britney updates
===============
- Write "HeidiResultDelta" file containing the changes of the run
Based on Colin Watson's code to do the same from the "britney2-ubuntu"
repository[1] revision 306, 308 and 309.
Notable differences include:
* output include version of source package being removed
* output prefix removals with a "-" (otherwise it would be identical to
a upgrade/new source with the change above).
[1] http://bazaar.launchpad.net/~ubuntu-release/britney/britney2-ubuntu/revision/306
- Support :any architecture qualifiers for multiarch
Multiarch adds a Depends: foo:any syntax, permitted only if the
target of the dependency is "Multi-Arch: allowed". This has
been supported by dpkg and apt for some time and is now safe to
use in unstable.
coinst-1.9.3/.boring 0000644 0001750 0001750 00000000247 12657630652 013261 0 ustar mehdi mehdi \.cm[iox]$
\.o$
~$
^viewer/viewer$
^viewer/dot_parser\.mli?$
^viewer/dot_lexer\.ml$
^check_coinstall$
^viewer/jsviewer\.js$
^viewer/jsviewer\.byte$
^viewer/converter$
coinst-1.9.3/upgrade.ml 0000644 0001750 0001750 00000045430 12657630652 013764 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let _ =
Gc.set {(Gc.get ())
with Gc.space_overhead = 300; Gc.max_overhead = 1000000}
module M = Deb_lib
module Repository = Upgrade_common.Repository
open Repository
module Quotient = Quotient.F (Repository)
module Graph = Graph.F (Repository)
module PSetSet = Upgrade_common.PSetSet
module PSetMap = Map.Make (PSet)
module L = Layout
let (&) = L.(&)
(****)
let whitespaces = Str.regexp "[ \t]+"
let load_popcon file =
let tbl = Hashtbl.create 4096 in
let ch = File.open_in file in
begin try
while true do
let l = input_line ch in
if l <> "" && l.[0] = '-' then raise End_of_file;
if l <> "" && l.[0] <> '#' then begin
let l = Str.split whitespaces l in
match l with
_ :: name :: inst :: _ ->
Hashtbl.add tbl name (int_of_string inst)
| _ ->
assert false
end
done
with End_of_file -> () end;
close_in ch;
tbl
(**** Conversion from dot to svg ****)
let send_to_dot_process (oc, _) s = output_string oc s; flush oc
let send_to_dot_process = Task.funct send_to_dot_process
let shutdown_dot_process (oc, pid) () =
close_out oc; ignore (Unix.waitpid [] pid)
let shutdown_dot_process = Task.funct shutdown_dot_process
let create_dot_process () =
let (out_read, out_write) = Unix.pipe () in
flush_all ();
let helper =
Task.spawn
(fun () ->
Unix.close out_read;
let (in_read, in_write) = Unix.pipe () in
match Unix.fork () with
0 ->
Unix.close in_write;
Unix.dup2 in_read Unix.stdin; Unix.dup2 out_write Unix.stdout;
Unix.close in_read; Unix.close out_write;
Unix.execv "/bin/sh" [| "/bin/sh"; "-c"; "dot" |]
| pid ->
Unix.close in_read;
(Unix.out_channel_of_descr in_write, pid))
in
Unix.close out_write;
(helper, Unix.in_channel_of_descr out_read)
let dot_process = lazy (create_dot_process ())
let dot_to_svg s =
let (t, ic) = Lazy.force dot_process in
let send = send_to_dot_process t s in
let (_, g) = Dot_graph.of_channel ic in
ignore (Task.wait send);
let (bbox, scene) = Dot_render.f g in
let l = Scene.get scene in
let b = Buffer.create 200 in
Scene_svg.format (Format.formatter_of_buffer b) (bbox, l);
Buffer.contents b
let formatted_dot_to_svg f =
let ic = open_in f in
let lst = ref [] in
let lb = Lexing.from_channel ic in
begin try
while true do
let (_, g) = Dot_graph.from_lexbuf lb in
let (bbox, scene) = Dot_render.f g in
let l = Scene.get scene in
let b = Buffer.create 200 in
Scene_svg.format (Format.formatter_of_buffer b) (bbox, l);
lst := Buffer.contents b :: !lst
done
with End_of_file -> () end;
close_in ic;
List.rev !lst
(****)
let output_conflicts filename dist2 results =
let in_conflict p p' =
p <> p' && PSetSet.exists (fun s -> PSet.mem p s && PSet.mem p' s) results
in
let involved = PSet.elements (PSetSet.fold PSet.union results PSet.empty) in
let partition =
if involved = [] then [] else
List.fold_left
(fun l p ->
List.fold_left
(fun l s ->
let (s1, s2) = List.partition (fun p' -> in_conflict p p') s in
let l = if s1 = [] then l else s1 :: l in
let l = if s2 = [] then l else s2 :: l in
l)
[] l)
[involved] involved
in
let classes = Hashtbl.create 101 in
let repr = Hashtbl.create 101 in
List.iter
(fun s ->
let p = List.hd s in
Hashtbl.add classes p s;
List.iter (fun q -> Hashtbl.add repr q p) s)
partition;
let results =
PSetSet.filter (fun s -> PSet.for_all (fun p -> Hashtbl.find repr p = p) s)
results
in
PSetSet.iter
(fun s ->
let start = ref true in
PSet.iter
(fun p ->
if not !start then Format.printf ", ";
start := false;
let l = Hashtbl.find classes p in
let start = ref true in
List.iter
(fun p ->
if not !start then Format.printf " | ";
start := false;
Format.printf "%a" (Package.print_name dist2) p)
l)
s;
Format.printf "@.")
results;
let ch = open_out filename in
let f = Format.formatter_of_out_channel ch in
Format.fprintf f "digraph G {@.";
Format.fprintf f "rankdir=LR;@.";
(*Format.fprintf f "overlap=false;@.";*)
(*Format.fprintf f "ratio=1.4;@.margin=5;@.ranksep=3;@.";*)
Format.fprintf f "node[fontsize=8];@.";
Format.fprintf f "node[margin=\"0,0\"];@.";
Format.fprintf f "node[height=0.2];@.";
Format.fprintf f "node [style=rounded];@.";
let confl_style = ",color=red" in
let confl_clique_style = ",color=red,fontcolor=red" in
let n = ref 0 in
PSetSet.iter
(fun s ->
if PSet.cardinal s = 2 then begin
let i = PSet.choose s in
let j = PSet.choose (PSet.remove i s) in
Format.fprintf f "%d -> %d [dir=none%s];@."
(Package.index i) (Package.index j) confl_style
end else begin
incr n;
Format.fprintf f
"confl%d [label=\" \",shape=circle%s];@."
!n confl_clique_style;
PSet.iter
(fun i ->
Format.fprintf f
"%d -> confl%d [dir=none%s];@."
(Package.index i) !n confl_style)
s
end)
results;
List.iter
(fun i ->
if Hashtbl.find repr i = i then begin
let print_name f i =
let l = List.length (Hashtbl.find classes i) in
if l = 1 then Package.print_name dist2 f i else
Format.fprintf f "%a (x %d)" (Package.print_name dist2) i l
in
Format.fprintf f
"%d [label=\"%a\",style=\"filled\",\
fillcolor=\"0.0,%f,1.0\"];@."
(Package.index i) print_name i 0.
end)
involved;
Format.fprintf f "}@.";
close_out ch
(****)
module StringSet = Util.StringSet
module F = struct
let overlaps s s' = StringSet.exists (fun nm -> StringSet.mem nm s) s'
let _true = (StringSet.empty, [])
let is_true (s, l) = StringSet.is_empty s && l = []
let conj1 (s, l) s' =
if StringSet.cardinal s' = 1 then begin
let nm = StringSet.choose s' in
if StringSet.mem nm s then
(s, l)
else
(StringSet.add nm s,
List.filter (fun s -> not (StringSet.mem nm s)) l)
end else begin
if
overlaps s s'
||
List.exists (fun s -> StringSet.subset s s') l
then
(s, l)
else
(s, s' :: List.filter (fun s -> not (StringSet.subset s' s)) l)
end
let conj (s1, l1) (s2, l2) =
let l1 = List.filter (fun s -> not (overlaps s2 s)) l1 in
let l2 = List.filter (fun s -> not (overlaps s1 s)) l2 in
let l1 =
List.filter
(fun s1 -> not (List.exists (fun s2 -> StringSet.subset s2 s1) l2)) l1
in
let l2 =
List.filter
(fun s2 -> not (List.exists (fun s1 -> StringSet.subset s1 s2) l1)) l2
in
(StringSet.union s1 s2, l1 @ l2)
let print print_package ch (s, l) =
if is_true (s, l) then Format.fprintf ch "TRUE" else begin
Util.print_list print_package ", " ch
(StringSet.elements s);
if not (StringSet.is_empty s) && l <> [] then Format.fprintf ch ", ";
Util.print_list
(fun ch s ->
Util.print_list print_package " | " ch (StringSet.elements s))
", " ch l
end
let format dist format_package (s, l) =
let format_package nm =
match M.find_packages_by_name dist (M.id_of_name nm) with
[p] -> format_package (Package.of_index p.M.num)
| _ -> L.s nm
in
if is_true (s, l) then
L.s "TRUE"
else begin
L.seq ", " format_package (StringSet.elements s) &
(if not (StringSet.is_empty s) && l <> [] then L.s ", " else L.emp) &
L.seq ", "
(fun s -> L.seq " | " format_package (StringSet.elements s))
l
end
end
(****)
module IntSet = Util.IntSet
let read_data file =
let ch = File.open_in file in
let dist = M.new_pool () in
M.parse_packages dist [] ch;
close_in ch;
M.only_latest dist
type t =
M.pool * (Repository.Package.t -> L.outside_anchor L.phrasing L.t) *
Upgrade_common.issue list * PSet.t PTbl.t *
(string, int) Hashtbl.t * (StringSet.t * StringSet.t list) PSetMap.t
let compute broken_sets ?popcon_file dist1 dist2 format_package =
let popcon =
match popcon_file with
Some file -> load_popcon file
| None -> Hashtbl.create 1
in
let dist1_state = Upgrade_common.prepare_analyze dist1 in
let dist2_state = Upgrade_common.prepare_analyze dist2 in
let (pred, all_pkgs, all_conflicts, dep_src, graphs, _) =
Upgrade_common.analyze broken_sets dist1_state dist2 in
(* Compute not new conjunctive dependencies *)
let cdeps1 =
Upgrade_common.conj_dependencies dist1 dist1_state.Upgrade_common.deps in
let cdeps2 =
Upgrade_common.reversed_conj_dependencies
dist2 dist2_state.Upgrade_common.deps
in
let cdeps =
PTbl.mapi
(fun p2 rev ->
let p1 = Package.of_index (PTbl.get pred p2) in
PSet.filter
(fun p' ->
let i' = PTbl.get pred p' in
i' <> -1 &&
match PTbl.get cdeps1 (Package.of_index i') with
None -> true
| Some s -> PSet.mem p1 s)
rev)
cdeps2
in
(* Filter out some of the non co-installable sets *)
let last_id = ref (-1) in
let package_to_graph = PTbl.create dist2 IntSet.empty in
let id_to_graph = Hashtbl.create 4096 in
let register_graph p g =
PTbl.set package_to_graph p (IntSet.add g (PTbl.get package_to_graph p))
in
List.iter
(fun g ->
incr last_id;
let id = !last_id in
let s = g.Upgrade_common.i_issue in
PSet.iter
(fun p ->
PSet.iter (fun p' -> register_graph p' id) (PTbl.get cdeps p))
s;
Hashtbl.add id_to_graph id (g, ref true))
graphs;
let graphs = ref [] in
Hashtbl.iter
(fun id (g, active) ->
if !active then begin
let s = g.Upgrade_common.i_issue in
let p = PSet.choose s in
let grs =
PSet.fold
(fun p gr -> IntSet.inter (PTbl.get package_to_graph p) gr)
s (PTbl.get package_to_graph p)
in
let inactivate =
IntSet.exists
(fun id' ->
id <> id' &&
let (g', active') = Hashtbl.find id_to_graph id' in
!active' &&
PSet.for_all
(fun p ->
PSet.exists (fun p' -> PSet.mem p' s) (PTbl.get cdeps p))
g'.Upgrade_common.i_issue)
grs
in
if inactivate then active := false else graphs := g :: !graphs
end)
id_to_graph;
let prob_pkgs = ref PSetMap.empty in
List.iter
(fun {Upgrade_common.i_issue = s;
i_problem =
{Upgrade_common.p_clause = {Upgrade_common.pos = pos}}} ->
prob_pkgs :=
PSetMap.add s
(F.conj1
(try PSetMap.find s !prob_pkgs with Not_found -> F._true)
pos)
!prob_pkgs)
!graphs;
(dist2, format_package, !graphs, cdeps, popcon, !prob_pkgs)
let conflict_graph (dist2, _, graphs, _, _, _) =
let tmpname = Filename.temp_file "conflicts" ".dot" in
let results =
List.fold_left (fun res gr -> PSetSet.add gr.Upgrade_common.i_issue res)
PSetSet.empty graphs
in
output_conflicts tmpname dist2 results;
let tmpname' = Filename.temp_file "conflicts" ".dot" in
ignore
(Sys.command
(Format.sprintf "ccomps -x %s | dot -o > %s" tmpname tmpname'));
(*
ignore (Sys.command (Format.sprintf "dot %s -o /tmp/full.dot" tmpname));
*)
let figs = formatted_dot_to_svg tmpname' in
Sys.remove tmpname; Sys.remove tmpname';
L.section
(L.heading (L.s "Graph of new conflicts") &
L.list (fun s -> L.p & L.raw_html (fun _ -> s)) figs)
let format_package dist p = L.s (M.package_name dist (Package.index p))
let explanations (dist2, format_package, graphs, cdeps, popcon, prob_pkgs) =
let popcon_weight s =
PSet.fold
(fun p2 w ->
let rev = PSet.add p2 (PTbl.get cdeps p2) in
min w (PSet.fold
(fun p' w' ->
max (try
Hashtbl.find popcon
(M.package_name dist2 (Package.index p'))
with Not_found ->
0)
w')
rev 0))
s max_int
in
let format_issue { Upgrade_common.i_issue = s; i_problem = problem } =
let l = PSet.elements s in
begin match l with
[p] ->
L.dt (L.s "Package " & format_package p &
L.s " can no longer be installed")
| _ ->
L.dt (L.s "Packages " &
L.seq2 ", " " and " format_package l &
L.s " can no longer be installed together")
end
&
L.dd
(let fig =
let b = Buffer.create 200 in
Upgrade_common.output_conflict_graph (Format.formatter_of_buffer b)
problem;
dot_to_svg (Buffer.contents b)
in
L.p & L.raw_html (fun () -> fig)
&
let w = popcon_weight s in
begin if w > 0 then(* Format.fprintf f "
Weight: %d
@." w;*)
L.p & L.span ~clss:"title" (L.s "Estimated popularity (popcon):") &
L.s " " & L.s (string_of_int w)
else
L.emp
end
&
begin if
PSet.for_all (fun p -> PSet.cardinal (PTbl.get cdeps p) <= 1) s
then
L.emp
else
L.p & L.span ~clss:"title" (L.s "Other impacted packages:") &
L.ul
(PSet.fold
(fun p2 doc ->
let rev = PTbl.get cdeps p2 in
if PSet.cardinal rev > 1 then begin
doc &
L.li
(L.span ~clss:"title"
(L.s "packages depending strongly on " &
format_package p2 & L.s ":") & L.s " "
&
L.seq ", " format_package
(PSet.elements (PSet.remove p2 rev)))
end else
doc)
s L.emp)
end
&
let ppkgs = PSetMap.find s prob_pkgs in
if not (F.is_true ppkgs) then begin
(*
Format.fprintf f "
Problematic packages: %a
@."
F.print ppkgs
*)
L.p & L.span ~clss:"title" (L.s "Problematic packages:") & L.s " " &
F.format dist2 format_package ppkgs
end else
L.emp)
in
let compare_graphs =
if Hashtbl.length popcon = 0 then
fun {Upgrade_common.i_issue = s} {Upgrade_common.i_issue = s'} ->
compare (PSet.cardinal s') (PSet.cardinal s)
else
fun {Upgrade_common.i_issue = s} {Upgrade_common.i_issue = s'} ->
compare (popcon_weight s') (popcon_weight s)
in
L.dl ~clss:"coinst-issue"
(L.list format_issue (List.sort compare_graphs graphs))
let has_issues (_, _, graphs, _, _, _) = graphs <> []
let f broken_sets ?popcon_file dist1 dist2 output_file =
let (_, _, _, _, _, prob_pkgs) as state =
compute broken_sets ?popcon_file dist1 dist2 (format_package dist2) in
Format.eprintf "Outputting results...@.";
(*
let graph =
L.section
(L.heading (L.s "Graph of new conflicts") & conflict_graph state) in
*)
Format.printf "Generating explanations...@.";
let t = Unix.gettimeofday () in
let explanations =
(*
L.heading (L.s "Explanations of conflicts") &
*)
explanations state &
let ppkgs =
PSetMap.fold (fun _ s s' -> F.conj s s') prob_pkgs F._true in
L.p & L.span ~clss:"title" (L.s "Full list of problematic packages:") &
L.s " " & F.format dist2 (format_package dist2) ppkgs;
in
Format.printf "Generating explanations... %fs@." (Unix.gettimeofday () -. t);
let ch = open_out output_file in
let style = "\
dt { font-weight:bold; font-size: large; }\n\
span.title { font-weight:bold; }\n\
svg { display: block; margin:auto; }\n\
@media print {\n \
svg { max-width:100%; }\n \
svg { max-height:23cm; }\n \
body { font-size:10px; }\n\
}\n\
footer {\n \
border-top: 2px solid #000;\n \
border-bottom: 0;\n \
font-size: small;\n \
margin-top: 2em;\n\
}\n"
in
let pr = new Layout.html_printer ch ~style "Upgrade issues" in
Layout.print pr
(L.heading (L.s "Upgrade issues") & (*graph & L.section*) explanations &
L.footer (L.s "Page generated by " &
L.anchor "http://coinst.irill.org/upgrades/"
(L.s "coinst-upgrades") &
L.s (" on " ^ Util.date () ^ ".")));
close_out ch;
(*
libjpeg8-dev "replaces" libjpeg62-dev, so why does the tools do not
propose me to install it instead?
========================
jerome@keithp:~/Mancoosi$ LC_ALL=C sudo apt-get dist-upgrade
Reading package lists... Done
Building dependency tree
Reading state information... Done
Calculating upgrade... Done
The following packages will be REMOVED:
libhdf4-dev
The following packages will be upgraded:
libhdf4-0
1 upgraded, 0 newly installed, 1 to remove and 0 not upgraded.
Need to get 353 kB of archives.
After this operation, 2227 kB disk space will be freed.
Do you want to continue [Y/n]?
========================
jerome@keithp:~/Mancoosi$ LC_ALL=C sudo aptitude dist-upgrade
The following NEW packages will be installed:
libjpeg8-dev{ab}
The following packages will be upgraded:
libhdf4-0 libhdf4-dev
2 packages upgraded, 1 newly installed, 0 to remove and 0 not upgraded.
Need to get 1141 kB of archives. After unpacking 652 kB will be used.
The following packages have unmet dependencies:
libjpeg8-dev: Conflicts: libjpeg62-dev but 6b1-2 is installed.
The following actions will resolve these dependencies:
Remove the following packages:
1) libhdf4-dev
Keep the following packages at their current version:
2) libjpeg8-dev [Not Installed]
Accept this solution? [Y/n/q/?]
*)
coinst-1.9.3/debug.ml 0000644 0001750 0001750 00000003146 12657630652 013421 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
type t = { mutable state : bool; name : string; desc : string }
let debugs = ref []
let association = Hashtbl.create 11
let make s desc l =
let d =
try
List.assoc s !debugs
with Not_found ->
let d = { state = false; name = s; desc = desc } in
debugs := (s, d) :: !debugs;
d
in
List.iter (fun s' -> Hashtbl.add association s' s) l;
fun () -> d.state
let print () =
Format.eprintf "Debug options:@.";
List.iter
(fun (_, d) -> Format.eprintf " %s: %s@." d.name d.desc) !debugs;
exit 1
let rec set s =
if s = "help" || not (List.mem_assoc s !debugs) then
print ()
else
try
let d = List.assoc s !debugs in
if not d.state then begin
d.state <- true;
List.iter set (Hashtbl.find_all association s)
end
with Not_found -> ()
coinst-1.9.3/cudf_lib.ml 0000644 0001750 0001750 00000025443 12657630652 014106 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
type cudf_reason =
R_conflict of int * int
| R_depends of int * Cudf_types.vpkglist
| R_install of Cudf_types.vpkg
type version
type p = Cudf.package
type pool =
{ mutable size : int;
packages : (string * version, p) Hashtbl.t;
packages_by_name : (string, int list ref) Hashtbl.t;
packages_by_num : (int, p) Hashtbl.t;
num_of_package : (Cudf_types.pkgname * Cudf_types.version, int) Hashtbl.t;
provided_packages :
(string, (Cudf_types.version option * p) list ref) Hashtbl.t }
let new_pool () =
{ size = 0;
packages = Hashtbl.create 101;
packages_by_name = Hashtbl.create 101;
packages_by_num = Hashtbl.create 101;
num_of_package = Hashtbl.create 101;
provided_packages = Hashtbl.create 101 }
(****)
let pp_loc ch (start_pos, end_pos) =
let line { Lexing.pos_lnum = l } = l in
if line start_pos = line end_pos
then Format.fprintf ch "line %d, char %d-%d" (line start_pos) start_pos.Lexing.pos_cnum end_pos.Lexing.pos_cnum
else Format.fprintf ch "lines: %d-%d" (line start_pos) (line end_pos)
let load ic =
try
let p = Cudf_parser.from_in_channel ic in
let infos = Cudf_parser.load p in
Cudf_parser.close p;
infos
with Cudf_parser.Parse_error (s, l) as e ->
Format.eprintf "%a: %s@." pp_loc l s;
raise e
let pkgid p = (p.Cudf.package, p.Cudf.version)
let veqpkg p = (p.Cudf.package, Some (`Eq, p.Cudf.version))
(****)
let get_package_list' h n =
try
Hashtbl.find h n
with Not_found ->
let r = ref [] in
Hashtbl.add h n r;
r
let add_to_package_list h n p =
let l = get_package_list' h n in
l := p :: !l
let get_package_list h n = try !(Hashtbl.find h n) with Not_found -> []
(****)
let print_pack pool ch p =
Format.fprintf ch "%s"
(Cudf_types_pp.string_of_veqpkg
(veqpkg (Hashtbl.find pool.packages_by_num p)))
let print_pack_name pool ch p =
Format.fprintf ch "%s"
(Cudf_types_pp.string_of_pkgname
(Hashtbl.find pool.packages_by_num p).Cudf.package)
(****)
let rec remove_duplicates_rec x (l : int list) =
match l with
[] ->
[x]
| y :: r ->
if x = y then
remove_duplicates_rec x r
else
x :: remove_duplicates_rec y r
let remove_duplicates l =
match l with
[] -> []
| x :: r -> remove_duplicates_rec x r
let normalize_set (l : int list) =
remove_duplicates (List.sort (fun x y -> compare x y) l)
(****)
let print_rules = ref false
module Solver = Solver.F (struct type reason = cudf_reason end)
type reason = cudf_reason
let lookup_packages ?(filter=None) dist pkgname =
let packages = get_package_list dist.provided_packages pkgname in
if filter = None then packages else
List.filter
(fun (v, _) ->
match v with
None -> true
| Some v -> Cudf.version_matches v filter)
packages
let resolve_package_dep dist (p, v) =
List.map (fun (_, p) -> Hashtbl.find dist.num_of_package (pkgid p))
(lookup_packages ~filter:v dist p)
(*
(*XXX*)
let rec print_package_disj ch l =
match l with
[] -> ()
| [p] -> Cudf_types_pp.pp_vpkg ch p
| p :: r -> Cudf_types_pp.pp_vpkg ch p; Format.fprintf ch " | ";
print_package_disj ch r
let rec print_package_list_rec print_var ch l =
match l with
[] -> Format.fprintf ch "NOT AVAILABLE"
| [x] -> print_var ch x
| x :: r -> Format.fprintf ch "%a, %a"
print_var x (print_package_list_rec print_var) r
let print_package_list pool ch l =
Format.fprintf ch "{%a}" (print_package_list_rec pool) l
let resolve_package_dep dist p =
let res = resolve_package_dep dist p in
Format.eprintf "%a == %a@." Cudf_types_pp.pp_vpkg p (print_package_list (print_pack dist)) res;
res
*)
let add_conflict st l =
let l = normalize_set l in
if List.length l > 1 then begin
if !print_rules then begin
Format.printf "conflict (";
List.iter (fun c -> Format.printf " %d" c) l;
Format.printf ")@."
end;
let a = Array.of_list l in
let len = Array.length a in
for i = 0 to len - 2 do
for j = i + 1 to len - 1 do
let p = Solver.lit_of_var a.(i) false in
let p' = Solver.lit_of_var a.(j) false in
Solver.add_rule st [|p; p'|] [R_conflict (a.(i), a.(j))]
done
done
end
let add_depend st deps n l =
let l = normalize_set l in
(* Some packages depend on themselves... *)
if not (List.memq n l) then begin
if !print_rules then begin
Format.printf "%d -> any-of (" n;
List.iter (fun c -> Format.printf " %d" c) l;
Format.printf ")@."
end;
Solver.add_rule st
(Array.of_list
(Solver.lit_of_var n false ::
List.map (fun n' -> Solver.lit_of_var n' true) l))
[R_depends (n, deps)]
end
let generate_rules pool =
let pr = Solver.initialize_problem ~print_var:(print_pack pool) pool.size in
Hashtbl.iter
(fun i p ->
if !print_rules then
Format.eprintf "%a@." (print_pack pool) i;
(* Dependences *)
List.iter
(fun l ->
add_depend pr l i
(List.flatten
(List.map (fun p -> resolve_package_dep pool p) l)))
p.Cudf.depends;
(* Conflicts *)
List.iter
(fun n -> add_conflict pr [i; n])
(normalize_set
(List.flatten
(List.map (fun p -> resolve_package_dep pool p)
p.Cudf.conflicts))))
pool.packages_by_num;
Solver.propagate pr;
pr
(****)
let all_packages = ref true
let parse_packages pool ignored_packages ch =
if pool.size <> 0 then invalid_arg "Cudf_lib.parse_packages";
let st = Common.start_parsing true ch in
let (preamble, pkgs, req) = load ch in
let i = ref 0 in
let versions = Hashtbl.create 107 in
Cudf.iter_packages
(fun p ->
try
let v = Hashtbl.find versions p.Cudf.package in
if v < p.Cudf.version then
Hashtbl.replace versions p.Cudf.package p.Cudf.version
with Not_found ->
Hashtbl.replace versions p.Cudf.package p.Cudf.version)
pkgs;
Cudf.iter_packages
(fun p ->
if
!all_packages || p.Cudf.version = Hashtbl.find versions p.Cudf.package
then begin
Common.parsing_tick st;
Hashtbl.add pool.packages_by_num !i p;
let id = pkgid p in
assert (not (Hashtbl.mem pool.num_of_package id));
Hashtbl.add pool.num_of_package id !i;
add_to_package_list pool.packages_by_name p.Cudf.package !i;
add_to_package_list pool.provided_packages p.Cudf.package
(Some p.Cudf.version, p);
List.iter
(fun (q, v) ->
let v = match v with Some (_, v) -> Some v | None -> None in
add_to_package_list pool.provided_packages q (v, p))
p.Cudf.provides;
incr i
end)
pkgs;
Common.stop_parsing st;
pool.size <- !i
(****)
let package_re = Str.regexp "^\\([^ (]+\\) *( *\\([<=>]+\\) *\\([0-9]+\\) *)$"
let parse_package_dependency pool s =
if not (Str.string_match package_re s 0) then
failwith (Format.sprintf "Bad package name '%s'" s);
let name = Str.matched_group 1 s in
let ver =
try
let rel =
match Str.matched_group 2 s with
"<<" -> `Lt
| "<=" | "<" -> `Leq
| "=" -> `Eq
| ">=" | ">" -> `Geq
| ">>" -> `Gt
| s -> failwith (Format.sprintf "Bad relation '%s'" s)
in
Some (rel, int_of_string (Str.matched_group 3 s))
with Not_found ->
None
in
resolve_package_dep pool (name, ver)
let parse_package_name pool s = get_package_list pool.packages_by_name s
(****)
let rec print_package_disj ch l =
match l with
[] -> ()
| [p] -> Format.fprintf ch "%s" (Cudf_types_pp.string_of_vpkg p)
| p :: r -> Format.fprintf ch "%s | %a"
(Cudf_types_pp.string_of_vpkg p) print_package_disj r
let rec print_package_list_rec print_var ch l =
match l with
[] -> Format.fprintf ch "NOT AVAILABLE"
| [x] -> print_var ch x
| x :: r -> Format.fprintf ch "%a, %a"
print_var x (print_package_list_rec print_var) r
let print_package_list pool ch l =
Format.fprintf ch "{%a}" (print_package_list_rec pool) l
let show_reasons pool l =
if l <> [] then begin
Format.printf "The following constraints cannot be satisfied:@.";
List.iter
(fun r ->
match r with
R_conflict (n1, n2) ->
Format.printf " %a conflicts with %a@."
(print_pack pool) n1 (print_pack pool) n2
| R_depends (n, l) ->
Format.printf " %a depends on %a %a@."
(print_pack pool) n print_package_disj l
(print_package_list (print_pack pool))
(List.flatten (List.map (resolve_package_dep pool) l))
| R_install p ->
Format.printf " need to install %s %a@."
(Cudf_types_pp.string_of_vpkg p)
(print_package_list (print_pack pool))
(resolve_package_dep pool p))
l
end
let conflicts_in_reasons rl = List.fold_left (fun cl -> function R_conflict (i,j) -> (min i j, max i j)::cl | _ -> cl) [] rl
(****)
let compute_conflicts pool =
let conflict_pairs = Hashtbl.create 1000 in
let conflicts = Hashtbl.create 1000 in
Hashtbl.iter
(fun i p ->
List.iter
(fun n ->
let pair = (min n i, max n i) in
if n <> i && not (Hashtbl.mem conflict_pairs pair) then begin
Hashtbl.add conflict_pairs pair ();
add_to_package_list conflicts i n;
add_to_package_list conflicts n i
end)
(normalize_set
(List.flatten
(List.map (fun p -> resolve_package_dep pool p)
p.Cudf.conflicts))))
pool.packages_by_num;
Array.init pool.size (fun i -> get_package_list conflicts i)
let compute_deps dist =
Array.init dist.size (fun i ->
let p = Hashtbl.find dist.packages_by_num i in
List.map
(fun l ->
normalize_set
(List.flatten
(List.map (fun p -> resolve_package_dep dist p)
l)))
p.Cudf.depends)
(****)
let pool_size p = p.size
coinst-1.9.3/upgrade_common.mli 0000644 0001750 0001750 00000005333 12657630652 015503 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module Repository : Repository.S with type pool = Deb_lib.pool
open Repository
module PSetSet : Set.S with type elt = PSet.t
type state =
{ dist : Deb_lib.deb_pool;
deps : Formula.t PTbl.t;
confl : Conflict.t;
deps' : Formula.t PTbl.t;
confl' : Conflict.t;
st : Deb_lib.Solver.state }
val prepare_analyze : pool -> state
type pkg_ref = string * bool * bool
type reason =
R_depends of pkg_ref * string Deb_lib.dep * pkg_ref list
| R_conflict of pkg_ref * string Deb_lib.dep * pkg_ref
type clause = { pos : Util.StringSet.t; neg : Util.StringSet.t }
type problem =
{ p_clause : clause; p_issue : Util.StringSet.t; p_explain : reason list;
p_support1 : Util.StringSet.t; p_support2 : Util.StringSet.t }
type issue =
{ i_issue : PSet.t; i_problem : problem }
type ignored_sets
val analyze :
?check_new_packages:bool -> ignored_sets ->
?reference:state ->
state -> pool ->
Deb_lib.Solver.var PTbl.t * PSet.t * Conflict.t * PSet.t PTbl.t *
issue list *
(Package.t * clause * reason list * Util.StringSet.t * Util.StringSet.t) list
val find_problematic_packages :
?check_new_packages:bool -> ignored_sets ->
state -> state -> (Deb_lib.package_name -> bool) -> problem list
val find_non_inst_packages :
bool -> ignored_sets -> state -> state -> (Deb_lib.package_name -> bool) ->
problem list
val find_clusters :
state -> state -> (Deb_lib.package_name -> bool) ->
(string list * 'a) list -> ('a -> 'a -> unit) -> unit
val output_conflict_graph : Format.formatter -> problem -> unit
val ignored_set_domain : ignored_sets -> Deb_lib.PkgSet.t
val is_ignored_set : ignored_sets -> Util.StringSet.t -> bool
val conj_dependencies : pool -> Formula.t PTbl.t -> PSet.t option PTbl.t
val reversed_conj_dependencies : pool -> Formula.t PTbl.t -> PSet.t PTbl.t
val empty_break_set : unit -> ignored_sets
val allow_broken_sets : ignored_sets -> string -> unit
val copy_ignored_sets : ignored_sets -> ignored_sets
coinst-1.9.3/bytearray.mli 0000644 0001750 0001750 00000001231 12657630652 014477 0 ustar mehdi mehdi (* Unison file synchronizer: src/bytearray.mli *)
(* Copyright 1999-2010, Benjamin C. Pierce (see COPYING for details) *)
type t =
(char, Bigarray.int8_unsigned_elt, Bigarray.c_layout) Bigarray.Array1.t
val create : int -> t
val length : t -> int
val to_string : t -> bytes
val of_string : string -> t
val sub : t -> int -> int -> bytes
val blit_from_bytes : bytes -> int -> t -> int -> int -> unit
val blit_to_bytes : t -> int -> bytes -> int -> int -> unit
val prefix : t -> t -> int -> bool
val marshal : 'a -> Marshal.extern_flags list -> t
val unmarshal : t -> int -> 'a
val marshal_to_buffer : t -> int -> 'a -> Marshal.extern_flags list -> int
coinst-1.9.3/util.ml 0000644 0001750 0001750 00000017311 12657630652 013307 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let can_enable_msgs = Unix.isatty Unix.stderr
let enable_msgs = ref can_enable_msgs
let enable_messages b = if can_enable_msgs then enable_msgs := b
let cur_msg = ref ""
let hide_msg () =
if !cur_msg <> "" then begin
prerr_string "\r";
prerr_string (String.make (String.length !cur_msg) ' ');
prerr_string "\r";
flush stderr;
end
let show_msg () =
if !cur_msg <> "" then begin prerr_string !cur_msg; flush stderr end
let set_msg s =
if !enable_msgs && s <> !cur_msg then begin
hide_msg (); cur_msg := s; show_msg ()
end
let progress_bar f =
let s = "[ ]" in
let s = Bytes.of_string s in
let p = truncate (f *. 38.99) + 1 in
for i = 1 to p - 1 do Bytes.set s i '=' done;
Bytes.set s p '>';
for i = p + 1 to 39 do Bytes.set s i ' ' done;
Bytes.to_string s
(****)
let warn_loc = ref None
let set_warning_location s = warn_loc := Some s
let reset_warning_location () = warn_loc := None
let print_warning s =
hide_msg ();
begin match !warn_loc with
None -> Format.eprintf "Warning: %s@." s
| Some s' -> Format.eprintf "Warning (%s): %s@." s' s
end;
show_msg ()
let fail s =
hide_msg ();
Format.eprintf "Failure: %s@." s;
exit 1
(****)
let title s = Format.printf "%s@.%s@." s (String.make (String.length s) '=')
(****)
module Timer = struct
type t = float
let start () = Unix.gettimeofday ()
let stop t = Unix.gettimeofday () -. t
end
module Utimer = struct
type t = float
let start () = (Unix.times ()).Unix.tms_utime
let stop t = start () -. t
end
module IntSet = Ptset
(*
Set.Make (struct type t = int let compare x (y : int) = compare x y end)
*)
module IntMap =
Map.Make (struct type t = int let compare x (y : int) = compare x y end)
module StringSet = Set.Make (String)
(****)
module ListTbl = struct
type ('a, 'b) t = ('a, 'b list ref) Hashtbl.t
let create : int -> ('a, 'b) t = Hashtbl.create
let add h n p =
try
let l = Hashtbl.find h n in
l := p :: !l
with Not_found ->
Hashtbl.add h n (ref [p])
let find h n = try !(Hashtbl.find h n) with Not_found -> []
let mem = Hashtbl.mem
let iter f h = Hashtbl.iter (fun k l -> f k !l) h
let copy h =
let h' = Hashtbl.create (2 * Hashtbl.length h) in
Hashtbl.iter (fun k l -> Hashtbl.add h' k (ref !l)) h;
h'
let remove h n f =
try
let l = Hashtbl.find h n in
l := List.filter (fun p -> not (f p)) !l;
if !l = [] then Hashtbl.remove h n
with Not_found ->
()
end
module StringTbl =
Hashtbl.Make
(struct
type t = string
let hash = Hashtbl.hash
let equal (s : string) s' = s = s'
end)
module IntTbl =
Hashtbl.Make
(struct
type t = int
let hash i = i
let equal (i : int) i' = i = i'
end)
(****)
let print_list pr sep ch l =
match l with
[] -> ()
| x :: r -> pr ch x; List.iter (fun x -> Format.fprintf ch "%s%a" sep pr x) r
(****)
let rec make_directories f =
let f = Filename.dirname f in
if not (Sys.file_exists f) then begin
try
Unix.mkdir f (0o755)
with Unix.Unix_error (Unix.ENOENT, _, _) ->
make_directories f;
Unix.mkdir f (0o755)
end
(****)
let bytes_extend s n c =
let s' = Bytes.make n c in
Bytes.blit s 0 s' 0 (Bytes.length s);
s'
let array_extend a n v =
let a' = Array.make n v in
Array.blit a 0 a' 0 (Array.length a);
a'
(****)
module BitVect = struct
type t = bytes
let make n v = Bytes.make n (if v then 'T' else 'F')
let test vect x = Bytes.get vect x <> 'F'
let set vect x = Bytes.set vect x 'T'
let clear vect x = Bytes.set vect x 'F'
let copy = Bytes.copy
let extend vect n v = bytes_extend vect n (if v then 'T' else 'F')
let sub = Bytes.sub
let implies vect1 vect2 =
let l = Bytes.length vect1 in
assert (Bytes.length vect2 = l);
let rec implies_rec vect1 vect2 i l =
i = l ||
((Bytes.get vect1 i <> 'T' || Bytes.get vect2 i = 'T') &&
implies_rec vect1 vect2 (i + 1) l)
in
implies_rec vect1 vect2 0 l
let lnot vect =
let l = Bytes.length vect in
let vect' = Bytes.make l 'F' in
for i = 0 to l - 1 do
Bytes.set vect' i (if Bytes.get vect i = 'F' then 'T' else 'F')
done;
vect'
let (land) vect1 vect2 =
let l = Bytes.length vect1 in
assert (Bytes.length vect2 = l);
let vect = Bytes.make l 'F' in
for i = 0 to l - 1 do
Bytes.set vect i (if Bytes.get vect1 i = 'F' || Bytes.get vect2 i = 'F' then 'F' else 'T')
done;
vect
let (lor) vect1 vect2 =
let l = Bytes.length vect1 in
assert (Bytes.length vect2 = l);
let vect = Bytes.make l 'F' in
for i = 0 to l - 1 do
Bytes.set vect i (if Bytes.get vect1 i = 'F' && Bytes.get vect2 i = 'F' then 'F' else 'T')
done;
vect
end
(****)
let sort_and_uniq compare l =
let rec uniq v l =
match l with
[] -> [v]
| v' :: r -> if compare v v' = 0 then uniq v r else v :: uniq v' r
in
match List.sort compare l with
[] -> []
| v :: r -> uniq v r
let compare_pair compare1 compare2 (a1, a2) (b1, b2) =
let c = compare1 a1 b1 in
if c = 0 then compare2 a2 b2 else c
let rec compare_list compare l1 l2 =
match l1, l2 with
[], [] ->
0
| [], _ ->
-1
| _, [] ->
1
| v1 :: r1, v2 :: r2 ->
let c = compare v1 v2 in if c = 0 then compare_list compare r1 r2 else c
let group compare l =
match l with
[] ->
[]
| (a, b) :: r ->
let rec group_rec a bl l =
match l with
[] ->
[(a, List.rev bl)]
| (a', b) :: r ->
if compare a a' = 0 then
group_rec a (b :: bl) r
else
(a, List.rev bl) :: group_rec a' [b] r
in
group_rec a [b] r
(****)
module Union_find = struct
type 'a link =
Link of 'a t
| Value of 'a
and 'a t =
{ mutable state : 'a link }
let rec repr t =
match t.state with
Link t' ->
let r = repr t' in
t.state <- Link r;
r
| Value _ ->
t
let rec get t =
match (repr t).state with
Link _ -> assert false
| Value v -> v
let merge t t' f =
let t = repr t in
let t' = repr t' in
if t != t' then begin
t.state <- Value (f (get t) (get t'));
t'.state <- Link t
end
let elt v = { state = Value v }
end
(****)
let (>>) v f = f v
let leading_whitespaces_re = Str.regexp "^[ \t\n]+"
let trailing_whitespaces_re = Str.regexp "[ \t\n]+$"
let trim s =
s >> Str.replace_first leading_whitespaces_re ""
>> Str.replace_first trailing_whitespaces_re ""
(****)
let days = [|"Mon"; "Tue"; "Wed"; "Thu"; "Fri"; "Sat"; "Sun"|]
let months = [|"Jan"; "Feb"; "Mar"; "Apr"; "May"; "Jun";
"Jul"; "Aug"; "Sep"; "Oct"; "Nov"; "Dec"|]
let date () =
let t = Unix.gmtime (Unix.gettimeofday ()) in
Format.sprintf "%s, %d %s %d %02d:%02d:%02d UTC"
days.(t.Unix.tm_wday - 1) t.Unix.tm_mday months.(t.Unix.tm_mon)
(t.Unix.tm_year + 1900) t.Unix.tm_hour t.Unix.tm_min t.Unix.tm_sec
coinst-1.9.3/bytearray_stubs.c 0000644 0001750 0001750 00000002755 12657630652 015374 0 ustar mehdi mehdi /* Unison file synchronizer: src/bytearray_stubs.c */
/* Copyright 1999-2010 (see COPYING for details) */
#include
#include "caml/intext.h"
#include "caml/bigarray.h"
#define Array_data(a, i) (((char *) a->data) + Long_val(i))
CAMLprim value ml_marshal_to_bigarray(value v, value flags)
{
char *buf;
long len;
output_value_to_malloc(v, flags, &buf, &len);
return alloc_bigarray(BIGARRAY_UINT8 | BIGARRAY_C_LAYOUT | BIGARRAY_MANAGED,
1, buf, &len);
}
CAMLprim value ml_marshal_to_bigarray_buffer(value b, value ofs,
value v, value flags)
{
struct caml_bigarray *b_arr = Bigarray_val(b);
return Val_long(caml_output_value_to_block(v, flags, Array_data (b_arr, ofs),
b_arr->dim[0] - Long_val(ofs)));
}
CAMLprim value ml_unmarshal_from_bigarray(value b, value ofs)
{
struct caml_bigarray *b_arr = Bigarray_val(b);
return input_value_from_block (Array_data (b_arr, ofs),
b_arr->dim[0] - Long_val(ofs));
}
CAMLprim value ml_blit_string_to_bigarray
(value s, value i, value a, value j, value l)
{
char *src = String_val(s) + Int_val(i);
char *dest = Array_data(Bigarray_val(a), j);
memcpy(dest, src, Long_val(l));
return Val_unit;
}
CAMLprim value ml_blit_bigarray_to_string
(value a, value i, value s, value j, value l)
{
char *src = Array_data(Bigarray_val(a), i);
char *dest = String_val(s) + Long_val(j);
memcpy(dest, src, Long_val(l));
return Val_unit;
}
coinst-1.9.3/ptset.mli 0000644 0001750 0001750 00000006332 12657630652 013643 0 ustar mehdi mehdi (**************************************************************************)
(* *)
(* Copyright (C) Jean-Christophe Filliatre *)
(* *)
(* This software is free software; you can redistribute it and/or *)
(* modify it under the terms of the GNU Library General Public *)
(* License version 2.1, with the special exception on linking *)
(* described in file LICENSE. *)
(* *)
(* This software is distributed in the hope that it will be useful, *)
(* but WITHOUT ANY WARRANTY; without even the implied warranty of *)
(* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. *)
(* *)
(**************************************************************************)
(*i $Id: ptset.mli,v 1.10 2008-07-21 14:53:06 filliatr Exp $ i*)
(*s Sets of integers implemented as Patricia trees. The following
signature is exactly [Set.S with type elt = int], with the same
specifications. This is a purely functional data-structure. The
performances are similar to those of the standard library's module
[Set]. The representation is unique and thus structural comparison
can be performed on Patricia trees. *)
type t
type elt = int
val empty : t
val is_empty : t -> bool
val mem : int -> t -> bool
val find : int -> t -> int
val add : int -> t -> t
val of_list : elt list -> t
val singleton : int -> t
val remove : int -> t -> t
val union : t -> t -> t
val subset : t -> t -> bool
val inter : t -> t -> t
val diff : t -> t -> t
val equal : t -> t -> bool
val compare : t -> t -> int
val elements : t -> int list
val choose : t -> int
val cardinal : t -> int
val iter : (int -> unit) -> t -> unit
val fold : (int -> 'a -> 'a) -> t -> 'a -> 'a
val for_all : (int -> bool) -> t -> bool
val exists : (int -> bool) -> t -> bool
val filter : (int -> bool) -> t -> t
val partition : (int -> bool) -> t -> t * t
val split : int -> t -> t * bool * t
(*s Warning: [min_elt] and [max_elt] are linear w.r.t. the size of the
set. In other words, [min_elt t] is barely more efficient than [fold
min t (choose t)]. *)
val min_elt : t -> int
val max_elt : t -> int
(*s Additional functions not appearing in the signature [Set.S] from ocaml
standard library. *)
(* [intersect u v] determines if sets [u] and [v] have a non-empty
intersection. *)
val intersect : t -> t -> bool
(*s Big-endian Patricia trees *)
module Big : sig
include Set.S with type elt = int
val intersect : t -> t -> bool
end
(*s Big-endian Patricia trees with non-negative elements. Changes:
- [add] and [singleton] raise [Invalid_arg] if a negative element is given
- [mem] is slightly faster (the Patricia tree is now a search tree)
- [min_elt] and [max_elt] are now O(log(N))
- [elements] returns a list with elements in ascending order
*)
module BigPos : sig
include Set.S with type elt = int
val intersect : t -> t -> bool
end
coinst-1.9.3/horn.mli 0000644 0001750 0001750 00000003071 12657630652 013447 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module type S = sig
type reason
end
module type SOLVER = sig
type state
type reason
type var = int
type id
val initialize : ?signal_assign:(var array -> reason -> unit) -> int -> state
val extend : state -> int -> unit
val set_var_printer : state -> (Format.formatter -> var -> unit) -> unit
val assignment : state -> Util.BitVect.t
val direct_reasons : state -> var -> (var array * reason) list
val reason : state -> var -> (var array * reason) option
val assumptions : state -> var -> reason list
val add_rule : state -> var array -> reason -> id
val assume : state -> var -> reason -> unit
val retract_rule : state -> id -> unit
val retract_assumptions : state -> var -> unit
end
module F (X : S) : SOLVER with type reason = X.reason
coinst-1.9.3/bytearray.ml 0000644 0001750 0001750 00000005371 12657630652 014337 0 ustar mehdi mehdi (* Unison file synchronizer: src/bytearray.ml *)
(* Copyright 1999-2010, Benjamin C. Pierce
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program. If not, see .
*)
open Bigarray
type t = (char, int8_unsigned_elt, c_layout) Array1.t
let length = Bigarray.Array1.dim
let create l = Bigarray.Array1.create Bigarray.char Bigarray.c_layout l
(*
let unsafe_blit_from_string s i a j l =
for k = 0 to l - 1 do
a.{j + k} <- s.[i + k]
done
let unsafe_blit_to_string a i s j l =
for k = 0 to l - 1 do
s.[j + k] <- a.{i + k}
done
*)
external unsafe_blit_from_bytes : bytes -> int -> t -> int -> int -> unit
= "ml_blit_string_to_bigarray" "noalloc"
external unsafe_blit_to_bytes : t -> int -> bytes -> int -> int -> unit
= "ml_blit_bigarray_to_string" "noalloc"
let to_string a =
let l = length a in
if l > Sys.max_string_length then invalid_arg "Bytearray.to_bytes" else
let s = Bytes.create l in
unsafe_blit_to_bytes a 0 s 0 l;
s
let of_string s =
let l = String.length s in
let a = create l in
unsafe_blit_from_bytes (Bytes.of_string s) 0 a 0 l;
a
let sub a ofs len =
if
ofs < 0 || len < 0 || ofs > length a - len || len > Sys.max_string_length
then
invalid_arg "Bytearray.sub"
else begin
let s = Bytes.create len in
unsafe_blit_to_bytes a ofs s 0 len;
s
end
let rec prefix_rec a i a' i' l =
l = 0 ||
(a.{i} = a'.{i'} && prefix_rec a (i + 1) a' (i' + 1) (l - 1))
let prefix a a' i =
let l = length a in
let l' = length a' in
i <= l' - l &&
prefix_rec a 0 a' i l
let blit_from_bytes s i a j l =
if l < 0 || i < 0 || i > Bytes.length s - l
|| j < 0 || j > length a - l
then invalid_arg "Bytearray.blit_from_string"
else unsafe_blit_from_bytes s i a j l
let blit_to_bytes a i s j l =
if l < 0 || i < 0 || i > length a - l
|| j < 0 || j > Bytes.length s - l
then invalid_arg "Bytearray.blit_to_string"
else unsafe_blit_to_bytes a i s j l
external marshal : 'a -> Marshal.extern_flags list -> t
= "ml_marshal_to_bigarray"
external marshal_to_buffer : t -> int -> 'a -> Marshal.extern_flags list -> int
= "ml_marshal_to_bigarray_buffer"
external unmarshal : t -> int -> 'a
= "ml_unmarshal_from_bigarray"
coinst-1.9.3/cache.mli 0000644 0001750 0001750 00000001712 12657630652 013544 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
val cached :
?force:bool -> string list -> string -> string ->
?is_valid:('a -> bool) -> (unit -> 'a) -> 'a * string
val set_disabled : bool -> unit
coinst-1.9.3/api.ml 0000644 0001750 0001750 00000003023 12657630652 013076 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module type S = sig
type pool
type reason
module Solver : Solver.SOLVER with type reason = reason
val new_pool : unit -> pool
val parse_packages : pool -> string list -> in_channel -> unit
val parse_package_dependency : pool -> string -> int list
val parse_package_name : pool -> string -> int list
val print_pack : pool -> Format.formatter -> int -> unit
val print_pack_name : pool -> Format.formatter -> int -> unit
val show_reasons : pool -> reason list -> unit
val conflicts_in_reasons : reason list -> (int * int) list
val generate_rules : pool -> Solver.state
val compute_conflicts : pool -> int list array
val compute_deps : pool -> int list list array
val pool_size : pool -> int
end
coinst-1.9.3/man/ 0000755 0001750 0001750 00000000000 12657630652 012550 5 ustar mehdi mehdi coinst-1.9.3/man/comigrate.1 0000644 0001750 0001750 00000021466 12657630652 014615 0 ustar mehdi mehdi .TH COMIGRATE 1
.SH NAME
comigrate \- managing package migrations from Debian
.IR unstable " to " testing
.SH SYNOPSIS
.B comigrate
.RI [\| options \|]
.RB [\| \-\^\-heidi
.IR file \]
.RB [\| \-\^\-hints
.IR file \]
.br
.B comigrate
.RI [\| options \|]
.B \-\^\-update
.br
.B comigrate
.RI [\| options \|]
.BI \-\^\-migrate " package"
.br
.B comigrate
.RI [\| options \|]
.B \-\^\-equivocal
.br
.B comigrate
.RI [\| options \|]
.BI \-\^\-excuses " file"
.RB [\| \-\^\-svg \|]
.br
.B comigrate
.RI [\| options \|]
.BI \-\^\-explain " dir"
.SH DESCRIPTION
.B comigrate
is a tool designed to manage the migration of packages
from Debian
.IR unstable " to " testing .
It can be used in different ways. First,
it can compute which packages can migrate into testing; it can output
either an
.I HeidiResult
file listing the updated contents of
testing, or a set of hints that can be fed to
.I Britney
to help it perform the migration. Second, it can output detailed
reports of what prevents packages from migrating. Last, it can be used
to interactively troubleshoot the migration of a given package.
Unless an alternative command is given,
.B comigrate
will perform package migration and output the corresponding
.I HeidiResult
file at the location indicated in the configuration file.
.SH OPTIONS
.SS Commands
The default behavior of
.B comigrate
is to compute which packages can migrate from
.IR unstable " to " testing .
This behavior can be overriden by the options below.
.TP
.B \-\^\-equivocal
Output the set of packages that can migrate without making any package
non-installable but that will make it impossible to install some set
of packages together (package co-installability would no be preserved).
This makes it possible to find the packages that would be allowed to
migrate when using the
.B \-\^\-inst
option (preserving only package installability), but that could
nonetheless be problematic.
.TP
.BI \-\^\-excuses " file"
Write to this HTML file a detailed explanation of why some packages cannot
migrate. With the
.B \-\^\-svg
option, an SVG graph is also included for each installability or
co-installability issue (set of packages that one would not be able to
install together anymore) that prevents the migration. The
.B dot
tool is required to produce these graphs.
.TP
.BI \-\^\-explain " dir"
This command is designed to produce a report that can be published over
HTTP. An HTML file is created for each package that cannot
migrate, providing a detailed explanation of why this package cannot
migrate. A file listing
co-installability issues (that is, set of
packages that can no longer be installed together) that would result
from forthcoming migrations is also created. The
.B \-\^\-popcon
option can be used to specify popcon data to use for the report.
The
.B dot
tool is required for this command.
.TP
.BI \-\^\-migrate " package"
Compute whether it is possible to migrate this source package. If this
is indeed possible, a corresponding
.I Britney
hint is outputted, by default on the standard output (this can be
overridden with the
.B \-\^\-hints
option).
.TP
.B \-\^\-update
Initialize or update the data directory.
.SS Common Options
.TP
.BI \-\^\-arches " lst"
Comma-separated list of architectures to consider (default to all).
.TP
.BI \-c " file" "\fR,\fP \-\^\-config " file
Use this Britney configuration file.
.SS Package Migration Options
.TP
.B \-\^\-all-hints
Show all hints. By default, hints consisting of a single package are
omitted when outputting hints.
.TP
.BI \-\^\-break " sets"
Override the default migration constraint that set of packages that
could be install together can still be installed together after
migration (package co-installability). This option allows to specify
that some precise set of packages can become non co-installable (or,
in the case of a single package, that this package can become non
installable). This is crucial to allow the migration of packages that
are no longer compatible. The argument
.I sets
is a comma-separated list of sets of packages. Each set is either a
list of binary package names separated by a vertical bar symbol |, or
a wildcard\~_ standing for any package.
We explain this option through examples.
You can write
.BI \-\^\-break " libjpeg62-dev"
to state that package
.I libjpeg62-dev
does not have to remain installable.
But it is usually better to indicate that the package should remain
installable but that it is fine if it is no longer installable with
some other packages:
.B \-\^\-break
.IR libjpeg62-dev,_ .
You can be even more precise and specify that two given packages can
become incompatible, but no other incompatibility should be
introduced:
.B \-\^\-break
.IR parallel,moreutils .
Finally, you can use the vertical bar symbol to factorize several sets
of packages:
.B \-\^\-break
.I 'unoconv,python-uno|docvert-libreoffice'
means that package
.I unoconv
does not have to remain installable together with
.I python-uno
nor
.IR docvert-libreoffice .
.TP
.BI \-\^\-heidi " HeidiResult"
Write the result of package migration to file
.IR HeidiResult .
When
.I HeidiResult
is
.BR \- ,
write to standard output.
The option only make sense when no specific command is given.
.TP
.BI \-\^\-hints " file"
Output hints to this file. When
.I file
is
.BR \- ,
write to standard output.
This disable the ouput of the
.I HeidiResult
file, unless an explicit
.B \-\^\-heidi
option is provided as well.
.TP
.B \-\^\-inst
When computing possible migration, only preserves single package
installability. This is similar to what
.I Britney
does. The default is to ensure the stronger requirement that
set of packages that could be install together can still be installed
together after migration (that is, package co-installability).
.TP
.BI \-\^\-offset " n"
Move
.I n
days into the future. This is convenient to see what packages will be
able to migrate in a few days.
.TP
.BI \-\^\-remove " pkg"
Compute package migration as if the source package
.I pkg
and its associated binary packages had been removed from
.IR unstable .
This is a convenient way to migrate an important package when its
migration is prevented by packages of low importance.
Together with the
.B \-\^\-migrate
command, this option can help finding out all issues preventing the
migration of a given package.
.SS Command-Specific Options
.TP
.B \-\^\-svg
Include conflict graphs (in SVG format) in excuse output. This option
only makes sense together with the
.B \-\^\-excuses
option.
.TP
.BI \-\^\-popcon " file"
Use popcon data from this file. This option only makes sense together
with the
.B \-\^\-explain
option.
.TP
.BI \-\^\-source " url"
Download package information from the given url. This option only
makes sense together with the
.B \-\^\-update
option.
.SS Miscellaneous Options
.TP
.BI \-\^\-debug " name"
Activate debug option
.IR name .
Use
.B \-\^\-debug help
to list available debug options.
.TP
.BR \-help ", " \-\^\-help
Print a usage message briefly summarizing the command-line options.
.TP
.BI \-\^\-input " dir"
Select the directory containing Britney data.
.TP
.B \-\^\-no\-cache
Disable on-disk caching.
.TP
.BI \-\^\-proc " n"
Provide number of processors. Use 1 to disable concurrency.
Defaults to use all processors.
.SS Ignored Options
These two
.I Britney
options are currently ignored and are present only for compatibility.
.TP
.B \-\^\-control\-files
Currently ignored.
.TP
.B \-v
Currently ignored.
.SH EXAMPLES
To get started, you need to use a
.I Britney
configuration file
.IR britney.conf .
The files specifies in particular the location of migration data
(control files, hint files, ...). These data can then be downloaded
(or updated) with the command below.
comigrate -c britney.conf --update
Running
.B comigrate
without option will make it behave like
.IR Britney :
it will compute the set of packages that can migrate
and write a corresponding
.I HeidiResult
file at the location indicated in the configuration file.
comigrate -c britney.conf
By default,
.B comigrate
is more picky than
.IR Britney :
it will not allow packages to migrate if any set of packages that
could be installed together can no longer be installed together.
With the
.B --inst
option,
.B comigrate
will only check that packages remain installable, just like
.I Britney
does.
comigrate -c britney.conf --inst
Alternatively, you can get the set of
.I Britney
easy hints corresponding to the migration.
comigrate -c britney.conf --hints - --all-hints
The
.B --migrate
option will give you an explanation of why a package cannot migrate.
(If the package can in fact migrate, the corresponding easy hint will
be printed.)
comigrate -c britney.conf --migrate ghc
The
.B --remove
and
.B --break
options can be used together with this option to get a clear
understand of what needs to be done to migrate the package.
.SH AUTHOR
Comigrate has been written by Jérôme Vouillon.
.SH SEE ALSO
.BR dot (1)
.br
The tool Web page:
.RB < http://coinst.irill.org/comigrate >.
coinst-1.9.3/man/coinst-upgrades.1 0000644 0001750 0001750 00000004651 12657630652 015747 0 ustar mehdi mehdi .TH COINST-UPGRADES 1
.SH NAME
coinst-upgrades \- finding upgrade issues between to versions of a
Debian distribution
.SH SYNOPSIS
.B coinst-upgrades
.RI [\| options \|]
.BI -o " file"
.I control-file1 control-file2
.SH DESCRIPTION
.B coinst-upgrades
takes as input two Debian control files corresponding to two versions
of a Debian repository and output a report listing all packages that
coult be installed together in the initial version of the repository
.RI "(specified by " control-file1 )
and that can no longer be installed together in the final version of
the repository
.RI "(specified by " control-file2 ),
and explaining why they can no longer be installed together.
If the control files are compressed, they will be automatically
uncompressed by the tool.
.SH OPTIONS
.TP
.BI \-\^\-break " sets"
Specify that some packages does not have to be compatible any longer
and that the corresponding issue should be omitted from the report.
The argument
.I sets
is a comma-separated list of sets of packages. Each set is either a
list of binary package names separated by a vertical bar symbol |, or
a wildcard\~_ standing for any package.
We explain this option through examples.
You can write
.BI \-\^\-break " libjpeg62-dev"
to state that package
.I libjpeg62-dev
does not have to remain installable.
But it is usually better to indicate that the package should remain
installable but that it is fine if it is no longer installable with
some other packages:
.B \-\^\-break
.IR libjpeg62-dev,_ .
You can be even more precise and specify that two given packages can
become incompatible, but that any other incompatibility should be
reported:
.B \-\^\-break
.IR parallel,moreutils .
Finally, you can use the vertical bar symbol to factorize several sets
of packages:
.B \-\^\-break
.I 'unoconv,python-uno|docvert-libreoffice'
means that package
.I unoconv
does not have to remain installable together with
.I python-uno
nor
.IR docvert-libreoffice .
.TP
.BI \-\^\-debug " name"
Activate debug option
.IR name .
Use
.B \-\^\-debug help
to list available debug options.
.TP
.BR \-help ", " \-\^\-help
Print a usage message briefly summarizing the command-line options.
.TP
.BI \-o " file"
Write the report to this file.
.TP
.BI \-\^\-popcon " file"
Use popcon data from this file to order issues.
.SH AUTHOR
Coinst-upgrades has been written by Jérôme Vouillon.
.SH SEE ALSO
.BR dot (1)
.br
The tool Web page:
.RB < http://coinst.irill.org/upgrades >.
coinst-1.9.3/file.ml 0000644 0001750 0001750 00000006724 12657630652 013257 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let rec read_write ic oc =
let bufsize = 4096 in
let buf = Bytes.create bufsize in
let rec read () =
let n = input ic buf 0 bufsize in
if n > 0 then begin
output oc buf 0 n;
read ()
end
in
read ()
let pipe_to_command cmd input output =
if Unix.fork () = 0 then begin
Unix.dup2 input Unix.stdin; Unix.dup2 output Unix.stdout;
Unix.close input; Unix.close output;
Unix.execv "/bin/sh" [| "/bin/sh"; "-c"; cmd |]
end
let spawn ?(sync=false) f =
let (read_fd, write_fd) = Unix.pipe () in
begin match Unix.fork () with
0 ->
Unix.close read_fd;
f write_fd;
exit 0
| pid ->
Unix.close write_fd;
if sync then ignore (Unix.waitpid [] pid)
end;
read_fd
let pipe_gen feeder cmd =
flush_all ();
let in_read =
(spawn ~sync:true
(fun in_write ->
let out_read =
spawn ~sync:false
(fun out_write ->
feeder (Unix.out_channel_of_descr out_write); exit 0)
in
pipe_to_command cmd out_read in_write;
exit 0))
in
Unix.in_channel_of_descr in_read
let pipe_from_string s cmd = pipe_gen (fun ch -> output_string ch s) cmd
let pipe ic cmd =
let in_read =
(spawn ~sync:true
(fun in_write ->
let out_read =
spawn ~sync:false
(fun out_write ->
read_write ic (Unix.out_channel_of_descr out_write);
exit 0)
in
close_in ic;
pipe_to_command cmd out_read in_write;
exit 0))
in
close_in ic;
Unix.in_channel_of_descr in_read
let has_magic ch s =
let l = String.length s in
let buf = Bytes.create l in
let i = ref 0 in
while
!i < l && (let n = input ch buf !i (l - !i) in i := !i + n; n > 0)
do () done;
if !i > 0 then seek_in ch (pos_in ch - !i);
!i = l && (Bytes.to_string buf) = s
let filter ch =
if has_magic ch "\031\139" then pipe ch "exec gzip -cd" else
if has_magic ch "BZh" then pipe ch "exec bzcat" else
ch
let open_in file = filter (open_in file)
let open_in_multiple files =
let ics = List.map Pervasives.open_in files in
match ics with
[ic] ->
filter ic
| _ ->
let ic =
Unix.in_channel_of_descr
(spawn ~sync:true
(fun write_fd ->
if Unix.fork () = 0 then begin
let oc = Unix.out_channel_of_descr write_fd in
List.iter
(fun ic ->
let ic = filter ic in
read_write ic oc;
flush oc)
ics
end;
exit 0))
in
List.iter close_in ics;
ic
coinst-1.9.3/api.mli 0000644 0001750 0001750 00000003021 12657630652 013245 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module type S = sig
type pool
type reason
module Solver : Solver.SOLVER with type reason = reason
val new_pool : unit -> pool
val parse_packages : pool -> string list -> in_channel -> unit
val parse_package_dependency : pool -> string -> int list
val parse_package_name : pool -> string -> int list
val print_pack : pool -> Format.formatter -> int -> unit
val print_pack_name : pool -> Format.formatter -> int -> unit
val show_reasons : pool -> reason list -> unit
val conflicts_in_reasons : reason list -> (int * int) list
val generate_rules : pool -> Solver.state
val compute_conflicts : pool -> int list array
val compute_deps : pool -> int list list array
val pool_size : pool -> int
end
coinst-1.9.3/task.mli 0000644 0001750 0001750 00000003033 12657630652 013441 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
type 'a t
type 'a future
val spawn : (unit -> 'a) -> 'a t
val funct : ('a -> 'b -> 'c) -> 'a t -> 'b -> 'c future
val wait : 'a future -> 'a
val kill : 'a t -> unit
val map : 'a list -> ('a -> 'b future) -> ('b -> 'c) -> 'c list
val iter : 'a list -> ('a -> 'b future) -> ('b -> unit) -> unit
val iteri : 'a list -> ('a -> ('b * 'c future)) -> ('b -> 'c -> unit) -> unit
val iter_ordered : 'a list -> ('a -> 'b future) -> ('b -> unit) -> unit
val iteri_ordered :
'a list -> ('a -> ('b * 'c future)) -> ('b -> 'c -> unit) -> unit
type scheduler
val scheduler : unit -> scheduler
val async : scheduler -> 'a future -> ('a -> unit) -> unit
val run : scheduler -> unit
val get_processor_count : unit -> int
val set_processor_count : int -> unit
coinst-1.9.3/file.mli 0000644 0001750 0001750 00000002171 12657630652 013420 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
val filter : in_channel -> in_channel
val open_in : string -> in_channel
val open_in_multiple : string list -> in_channel
val has_magic : in_channel -> string -> bool
val pipe : in_channel -> string -> in_channel
val pipe_from_string : string -> string -> in_channel
val pipe_gen : (out_channel -> unit) -> string -> in_channel
coinst-1.9.3/deb_lib.ml 0000644 0001750 0001750 00000113200 12657630652 013704 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module ListTbl = Util.ListTbl
module StringTbl = Util.StringTbl
module PkgTbl = Util.IntTbl
module PkgSet = Util.IntSet
module Extarray = struct
type 'a t =
{ def : 'a; mutable a : 'a array; mutable b : bool array }
let create def =
{ def = def;
a = Array.make 16000 def;
b = Array.make 16000 false }
let get a i =
a.a.(i)
let get_list a i =
if i >= Array.length a.a then [] else a.a.(i)
let find a i =
if i >= Array.length a.a || not a.b.(i) then
raise Not_found
else
a.a.(i)
let iter f a =
for i = 0 to Array.length a.a - 1 do
if a.b.(i) then f a.a.(i)
done
let iteri f a =
for i = 0 to Array.length a.a - 1 do
if a.b.(i) then f i a.a.(i)
done
let resize a i =
let l = Array.length a.a in
let a' = Array.make (2 * l) a.def in
Array.blit a.a 0 a' 0 l;
a.a <- a';
let b' = Array.make (2 * l) false in
Array.blit a.b 0 b' 0 l;
a.b <- b'
let add a i v =
while i >= Array.length a.a do resize a i done;
assert (not a.b.(i));
a.a.(i) <- v;
a.b.(i) <- true
let add_to_list a i v =
while i >= Array.length a.a do resize a i done;
a.a.(i) <- v :: a.a.(i);
a.b.(i) <- true
let replace a i v =
while i >= Array.length a.a do resize a i done;
a.a.(i) <- v;
a.b.(i) <- true
let remove a i =
assert (a.b.(i));
a.a.(i) <- a.def;
a.b.(i) <- false
let remove_from_list a i p =
let l = List.filter (fun v -> not (p v)) a.a.(i) in
a.a.(i) <- l;
a.b.(i) <- l <> []
let copy a = {a with a = Array.copy a.a; b = Array.copy a.b}
let mem a i = i < Array.length a.a && a.b.(i)
let is_prefix eq a a' =
let l = Array.length a.a in
let l' = Array.length a'.a in
let res = ref true in
for i = 0 to min l l' - 1 do
if a.b.(i) && not (a'.b.(i) && eq a.a.(i) a'.a.(i)) then res := false
done;
for i = l' to l - 1 do
if a.b.(i) then res := false
done;
!res
end
module PkgDenseTbl = Extarray
module Dict = struct
type t =
{ mutable next : int; to_id : int StringTbl.t; of_id : string Extarray.t }
let create () =
{ next = 0;
to_id = StringTbl.create 32768; of_id = Extarray.create "" }
let to_id d s = StringTbl.find d.to_id s
let add d s =
try
to_id d s
with Not_found ->
let n = d.next in
d.next <- n + 1;
StringTbl.add d.to_id s n;
Extarray.add d.of_id n s;
n
let of_id d n = Extarray.get d.of_id n
let exists d s = StringTbl.mem d.to_id s
let is_extended d d' = Extarray.is_prefix (fun x y -> x = y) d.of_id d'.of_id
end
(****)
let len = 4096
type st =
{ buf : bytes;
mutable pos : int;
mutable last : int;
mutable start : int;
mutable eof : bool;
input : bytes -> int -> int -> int }
let start_token st = st.start <- st.pos
let get_token st ofs =
let t = Bytes.sub st.buf st.start (st.pos - st.start - ofs) in
st.start <- -1;
Bytes.to_string t
let get_token_suffixed st ofs suffix =
let len = st.pos - st.start - ofs in
let len' = String.length suffix in
let t = Bytes.create (len + len') in
Bytes.blit st.buf st.start t 0 len;
Bytes.blit (Bytes.of_string suffix) 0 t len len';
st.start <- -1;
t
let ignore_token st = st.start <- -1
let from_channel ch =
let buf = Bytes.create len in
{ buf = buf; pos = 0; last = 0; eof = false; start = -1;
input = fun buf pos len -> input ch buf pos len }
let from_bytes s =
{ buf = s; pos = 0; last = Bytes.length s; eof = false; start = -1;
input = fun _ _ _ -> 0 }
let refill st =
if st.start <> -1 then begin
st.pos <- st.pos - st.start;
Bytes.blit st.buf st.start st.buf 0 st.pos;
st.start <- 0
end else
st.pos <- 0;
assert (len > st.pos); (*FIX: error message...*)
st.last <- st.pos + st.input st.buf st.pos (len - st.pos);
if st.last = st.pos then st.eof <- true
let rec next st =
let pos = st.pos in
if pos < st.last then begin
st.pos <- st.pos + 1;
Bytes.get st.buf pos
end else if st.eof then '\n' else begin
refill st;
next st
end
let unread st =
if not st.eof then begin
assert (st.pos > st.start);
assert (st.start <> -1);
st.pos <- st.pos - 1
end
let rec accept st c =
let pos = st.pos in
if pos < st.last then begin
if Bytes.get st.buf pos = c then begin
st.pos <- st.pos + 1;
true
end else
false
end else if st.eof then
false
else begin
refill st;
accept st c
end
let rec find st c =
let pos = st.pos in
if pos < st.last then begin
let c' = Bytes.get st.buf pos in
st.pos <- st.pos + 1;
c' = c
||
(c' <> '\n' &&
find st c)
end else if st.eof then
false
else begin
refill st;
find st c
end
let rec find_rec st c buf last =
let pos = st.pos in
if pos < last then begin
let c' = Bytes.unsafe_get buf pos in
st.pos <- pos + 1;
c' = c
||
(c' <> '\n' &&
find_rec st c buf last)
end else if st.eof then
false
else begin
refill st;
find_rec st c st.buf st.last
end
let find st c = find_rec st c st.buf st.last
let at_eof st =
if st.pos = st.last then refill st;
st.eof
let print_location st =
let i = ref (max (st.pos - 2) 0) in
while !i > 0 && (Bytes.get st.buf !i <> '\n' || Bytes.get st.buf (!i + 1) <> '\n') do
decr i
done;
if Bytes.get st.buf !i = '\n' && Bytes.get st.buf (!i + 1) = '\n' then i := !i + 2;
Format.eprintf "%s%s@."
(String.sub (Bytes.to_string st.buf) !i (st.pos - !i))
(String.sub (Bytes.to_string st.buf) st.pos (st.last - st.pos))
let fail st s =
print_location st;
Format.eprintf "Parsing error: %s@." s;
exit 1
(****)
let rec skip_blank_lines st = if accept st '\n' then skip_blank_lines st
let ignore_line st = ignore (find st '\n')
let accept_whitespace st = accept st ' ' || accept st '\t'
let skip_whitespaces st = while accept_whitespace st do () done
let parse_field ~field s st =
start_token st;
if not (find st ':') then fail st "incorrect field (missing ':')";
let name = get_token st 1 in
skip_whitespaces st;
if not (field s name st) then begin
ignore_line st;
while accept_whitespace st do
ignore_line st
done
end
let parse_stanza ~start ~field ~finish st =
skip_blank_lines st;
if not (at_eof st) then begin
let s = start () in
while
not (at_eof st || accept st '\n')
do
parse_field ~field s st
done;
finish s
end
let parse_stanzas ~start ~field ~finish st =
skip_blank_lines st;
while not (at_eof st) do
parse_stanza ~start ~field ~finish st
done
let parse_field_end st =
skip_whitespaces st;
if not (accept st '\n' || at_eof st) then
fail st "garbage at end of field"
let parse_simple_field_content st =
start_token st;
let rec skip n =
match next st with
' ' | '\t' -> skip (n + 1)
| '\n' -> unread st; n
| _ -> skip 0
in
let s = get_token st (skip 0) in
parse_field_end st;
s
(****)
let strings = StringTbl.create 101
let common_string s =
try StringTbl.find strings s with Not_found -> StringTbl.add strings s s; s
(****)
type rel = SE | E | EQ | L | SL
type package_name = int
type version = string
type 'a dep = ('a * (rel * version) option) list
type deps = package_name dep list
type p =
{ mutable num : int;
mutable package : package_name;
mutable version : version;
mutable source : package_name * version;
mutable section : string;
mutable architecture : string;
mutable depends : deps;
mutable recommends : deps;
mutable suggests : deps;
mutable enhances : deps;
mutable pre_depends : deps;
mutable provides : deps;
mutable conflicts : deps;
mutable breaks : deps;
mutable replaces : deps }
let dummy_package =
{ num = -1; package = -1; version = ""; source = (-1, ""); section = "";
architecture = ""; depends = []; recommends = []; suggests = [];
enhances = []; pre_depends = []; provides = []; conflicts = [];
breaks = []; replaces = [] }
type dict = Dict.t
let dict = ref (Dict.create ())
let current_dict () = !dict
let valid_directory d = Dict.is_extended !dict d
let set_dict d =
assert (valid_directory d);
dict := d
let name_of_id id = Dict.of_id !dict id
let id_of_name nm = Dict.to_id !dict nm
let add_name nm = Dict.add !dict nm
let name_exists nm = Dict.exists !dict nm
(****)
module Version = struct
let rec epoch s i =
let c = String.unsafe_get s i in
match c with
'0' .. '9' -> epoch s (i + 1)
| _ -> if c = ':' then i else -1
let rec compare_substring s i s' i' n =
if n = 0 then 0 else begin
let c = Char.code (String.unsafe_get s i) in
let c' = Char.code (String.unsafe_get s' i') in
if c < c' then -1 else
if c > c' then 1 else
compare_substring s (i + 1) s' (i' + 1) (n - 1)
end
let rec skip_zeroes s i =
if String.unsafe_get s i = '0' then skip_zeroes s (i + 1) else i
let rec skip_digits s i =
match String.unsafe_get s i with
'0' .. '9' -> skip_digits s (i + 1)
| _ -> i
let rec digit_start s i =
if i = 0 then 0 else
let i' = i - 1 in
match String.unsafe_get s i' with
'0'..'9' -> digit_start s (i - 1)
| _ -> i
let is_letter c = (c >= 'A' && c <= 'Z') || (c >= 'a' && c <= 'z')
let is_digit c = c >= '0' && c <= '9'
let char_map =
Array.init 256
(fun c ->
if Char.chr c = '~' then c - 512 else
if Char.chr c = ' ' || is_digit (Char.chr c) then c - 256 else
if is_letter (Char.chr c) then c else
c + 256)
let rec compare_versions_rec s s' i i' c'' =
let c = String.unsafe_get s i in
let c' = String.unsafe_get s' i' in
if c = c' then
compare_versions_rec s s' (i + 1) (i' + 1) c
else
match c, c', c'' with
'0'..'9', _, '0'..'9'
| _, '0'..'9', '0'..'9'
| '0'..'9', '0'..'9', _ ->
let j = digit_start s i in
let j' = i' - i + j in
let j = skip_zeroes s j in
let j' = skip_zeroes s' j' in
let l = skip_digits s i in
let l' = skip_digits s' i' in
let n = l - j in
let n' = l' - j' in
if n < n' then -1 else
if n > n' then 1 else
let c = compare_substring s j s' j' n in
if c <> 0 then c else
compare_versions_rec s s' l l' ' '
| _ ->
let c = char_map.(Char.code c) in
let c' = char_map.(Char.code c') in
if c < c' then -1 else
if c > c' then 1 else
0
let compare s s' =
if s = s' then 0 else
let i = epoch s 0 in
let i' = epoch s' 0 in
if i >= 0 || i' >= 0 then begin
let j = skip_zeroes s 0 in
let j' = skip_zeroes s' 0 in
let l = max 0 i in
let l' = max 0 i' in
let n = l - j in
let n' = l' - j' in
if n < n' then -1 else
if n > n' then 1 else
let c = compare_substring s j s' j' n in
if c <> 0 then c else
compare_versions_rec s s' (i + 1) (i' + 1) ' '
end else
compare_versions_rec s s' 0 0 ' '
let print ch v =
let len = String.length v - 2 in
let s = Bytes.sub (Bytes.of_string v) 0 len in
for i = 0 to len - 1 do
if Bytes.get s i = ' ' then Bytes.set s i '-'
done;
Format.fprintf ch "%s" (Bytes.to_string s)
let to_string v =
let len = String.length v - 2 in
let s = Bytes.sub (Bytes.of_string v) 0 len in
for i = 0 to len - 1 do
if Bytes.get s i = ' ' then Bytes.set s i '-'
done;
Bytes.to_string s
let dummy = ""
let get st =
let v = get_token_suffixed st 0 " " in
try
let i = Bytes.rindex v '-' in
Bytes.set v i ' ';
Bytes.to_string v
with Not_found ->
Bytes.to_string v
end
let print_version = Version.print
let compare_version = Version.compare
let dummy_version = Version.dummy
let string_of_version = Version.to_string
(****)
let parse_package st =
start_token st;
let bad = ref false in
begin match next st with
'a'..'z' | '0'..'9' -> ()
| 'A'..'Z' ->
bad := true
| _ ->
fail st "missing package name"
end;
while
match next st with
'a'..'z' | '0'..'9' | '.' | '+' | '-' ->
true
| 'A'..'Z' | '_' ->
bad := true; true
| _ ->
unread st; false
do () done;
let s = get_token st 0 in
if !bad || String.length s < 2 then
Util.print_warning (Format.sprintf "bad package name '%s'" s);
s
let parse_arch st =
start_token st;
while
match next st with
'a'..'z' | '0'..'9' | '.' | '+' | '-' ->
true
| _ ->
unread st; false
do () done;
get_token st 0
let debug_versions = Debug.make "versions" "Print bad version warnings" []
let parse_version_end st n bad hyphen =
unread st;
if n = 0 then
fail st (Format.sprintf "bad version %s" (get_token st 0));
let s = Version.get st in
if bad && debug_versions () then
Util.print_warning (Format.sprintf "bad version '%s'" s);
s
let rec parse_upstream_version st n bad hyphen =
match next st with
'0'..'9' ->
parse_upstream_version st (n + 1) bad hyphen
| '-' ->
parse_upstream_version st (n + 1) (bad || n = 0) n
| 'A'..'Z' | 'a'..'z' | '.' | '_' | '+' | '~' | ':' ->
parse_upstream_version st (n + 1) (bad || n = 0) hyphen
| _ ->
parse_version_end st n bad hyphen
let rec parse_epoch st n =
match next st with
'0'..'9' ->
parse_epoch st (n + 1)
| ':' when n > 0 ->
parse_upstream_version st 0 false (-1)
| 'A'..'Z' | 'a'..'z' | '.' | '_' | '+' | '~' | ':' ->
parse_upstream_version st (n + 1) (n = 0) (-1)
| '-' ->
parse_upstream_version st (n + 1) (n = 0) n
| _ ->
parse_version_end st n false (-1)
let parse_version st =
start_token st;
parse_epoch st 0
let versions = Hashtbl.create 32768
let parse_version st =
let v = parse_version st in
try Hashtbl.find versions v with Not_found -> Hashtbl.add versions v v; v
let parse_relation st =
match next st with
'<' ->
start_token st;
let rel =
match next st with
'<' -> SE
| '=' -> E
| _ -> unread st; E
in
ignore_token st;
rel
| '=' ->
EQ
| '>' ->
start_token st;
let rel =
match next st with
'>' -> SL
| '=' -> L
| _ -> unread st; L
in
ignore_token st;
rel
| c ->
fail st (Format.sprintf "bad relation '%c'" c)
let parse_package_dep f vers st =
let name = parse_package st in
skip_whitespaces st;
let name =
if accept st ':' then begin
let arch = parse_arch st in
skip_whitespaces st;
if arch = "any" then name else name ^ ":" ^ arch
end else
name
in
let name = Dict.add !dict name in
if accept st '(' then begin
if not vers then
fail st (Format.sprintf "package version not allowed in '%s'" f);
skip_whitespaces st;
let comp = parse_relation st in
skip_whitespaces st;
let version = parse_version st in
skip_whitespaces st;
if not (accept st ')') then assert false;
skip_whitespaces st;
(name, Some (comp, version))
end else
(name, None)
let rec parse_package_disj f vers disj st =
let nm = parse_package_dep f vers st in
if not (accept st '|') then
[nm]
else begin
if not disj then begin
if f = "Enhances" then
(*XXX Turn disjunction into conjunction? *)
Util.print_warning
(Format.sprintf "package disjunction not allowed in field '%s'" f)
else
fail st (Format.sprintf "package disjunction not allowed in '%s'" f)
end;
skip_whitespaces st;
nm :: parse_package_disj f vers disj st
end
let rec parse_package_conj f vers disj st =
let nm = parse_package_disj f vers disj st in
if accept st '\n' || at_eof st then
[nm]
else if accept st ',' then begin
skip_whitespaces st;
(* Hack to parse multiline Binary fields... *)
if accept st '\n' then skip_whitespaces st;
nm :: parse_package_conj f vers disj st
end else
fail st (Format.sprintf "bad character '%c'" (next st))
let parse_rel f vers disj st = parse_package_conj f vers disj st
let parse_package_source st =
let name = Dict.add !dict (parse_package st) in
skip_whitespaces st;
if accept st '(' then begin
skip_whitespaces st;
let version = parse_version st in
skip_whitespaces st;
if not (accept st ')') then assert false;
skip_whitespaces st;
if not (accept st '\n' || at_eof st) then assert false;
(name, version)
end else begin
if not (accept st '\n' || at_eof st) then assert false;
(name, dummy_version)
end
(****)
type deb_pool =
{ mutable size : int;
packages_by_name : p list Extarray.t;
packages_by_num : p Extarray.t;
provided_packages : p list Extarray.t }
type pool = deb_pool
let new_pool () =
{ size = 0;
packages_by_name = Extarray.create [];
packages_by_num = Extarray.create dummy_package;
provided_packages = Extarray.create [] }
let find_package_by_num pool n = Extarray.get pool.packages_by_num n
let find_packages_by_name pool nm = Extarray.get_list pool.packages_by_name nm
let has_package_of_name pool nm =
Extarray.get_list pool.packages_by_name nm <> []
let iter_packages_by_name pool f = Extarray.iteri f pool.packages_by_name
let iter_packages pool f =
(*iter_packages_by_name pool (fun _ l -> List.iter f l)*)
Extarray.iter f pool.packages_by_num
let pool_size pool = pool.size
let find_provided_packages pool nm =
find_packages_by_name pool nm @ Extarray.get_list pool.provided_packages nm
let package_is_provided pool nm =
has_package_of_name pool nm ||
Extarray.get_list pool.provided_packages nm <> []
let has_package pool nm v =
List.exists (fun p -> compare_version p.version v = 0)
(find_packages_by_name pool nm)
let insert_package pool p =
if not (has_package pool p.package p.version) then begin
p.num <- pool.size;
pool.size <- pool.size + 1;
Extarray.add pool.packages_by_num p.num p;
Extarray.add_to_list pool.packages_by_name p.package p;
List.iter
(fun l ->
match l with
[n,_] -> Extarray.add_to_list pool.provided_packages n p
| _ -> assert false)
p.provides
end
let remove_package pool p =
Extarray.remove pool.packages_by_num p.num;
Extarray.remove_from_list
pool.packages_by_name p.package (fun q -> q.num = p.num);
List.iter
(fun l ->
match l with
[n,_] -> Extarray.remove_from_list pool.provided_packages n
(fun q -> q.num = p.num)
| _ -> assert false)
p.provides
let replace_package pool q p =
let p = {p with num = q.num} in
remove_package pool q;
assert (not (has_package pool p.package p.version));
Extarray.add pool.packages_by_num p.num p;
Extarray.add_to_list pool.packages_by_name p.package p;
List.iter
(fun l ->
match l with
[n,_] -> Extarray.add_to_list pool.provided_packages n p
| _ -> assert false)
p.provides
let parse_packages pool ignored_packages ch =
let ignored_packages = List.map (Dict.add !dict) ignored_packages in
let info = Common.start_parsing true ch in
let st = from_channel ch in
let start () =
Common.parsing_tick info;
{ num = 0; package = -1; version = dummy_version;
source = (-1, dummy_version); section = ""; architecture = "";
depends = []; recommends = []; suggests = []; enhances = [];
pre_depends = []; provides = []; conflicts = []; breaks = [];
replaces = [] }
in
let finish q =
assert (q.package <> -1); assert (q.version <> dummy_version);
if fst q.source = -1 then q.source <- (q.package, q.version);
if snd q.source = dummy_version then q.source <- (fst q.source, q.version);
if not (List.mem q.package ignored_packages) then insert_package pool q
in
let field q f st =
match f with
"Package" -> q.package <- Dict.add !dict (parse_package st);
parse_field_end st; true
| "Version" -> q.version <- parse_version st; parse_field_end st; true
| "Source" -> q.source <- parse_package_source st; true
| "Section" -> q.section <-
common_string (parse_simple_field_content st);
true
| "Architecture" -> q.architecture <-
common_string (parse_simple_field_content st);
true
| "Depends" -> q.depends <- parse_rel f true true st; true
| "Recommends" -> q.recommends <- parse_rel f true true st; true
| "Suggests" -> q.suggests <- parse_rel f true true st; true
| "Enhances" -> q.enhances <- parse_rel f true false st; true
| "Pre-Depends" -> q.pre_depends <- parse_rel f true true st; true
| "Provides" -> q.provides <- parse_rel f true false st; true
| "Conflicts" -> q.conflicts <- parse_rel f true false st; true
| "Breaks" -> q.breaks <- parse_rel f true false st; true
| "Replaces" -> q.replaces <- parse_rel f true false st; true
| _ -> false
in
parse_stanzas ~start ~field ~finish st;
Common.stop_parsing info
(****)
type s =
{ mutable s_name : package_name;
mutable s_version : version;
mutable s_section : string;
mutable s_binary : package_name list;
mutable s_extra_source : bool}
type s_pool =
{ mutable s_size : int;
s_packages : s list Extarray.t }
let new_src_pool () = { s_size = 0; s_packages = Extarray.create [] }
let find_source_by_name pool nm =
match Extarray.get_list pool.s_packages nm with
[] -> raise Not_found
| [s] -> s
| _ -> assert false
let has_source pool nm = Extarray.get_list pool.s_packages nm <> []
let remove_source pool nm = Extarray.remove pool.s_packages nm
let add_source pool s = Extarray.add_to_list pool.s_packages s.s_name s
let iter_sources f pool =
Extarray.iter
(fun l -> match l with [] -> () | [s] -> f s | _ -> List.iter f l)
pool.s_packages
let parse_src_packages pool ch =
let info = Common.start_parsing true ch in
let st = from_channel ch in
let start () =
Common.parsing_tick info;
{ s_name = -1; s_version = dummy_version; s_section = "unknown";
s_binary = []; s_extra_source = false }
in
let field q f st =
match f with
"Package" -> q.s_name <- Dict.add !dict (parse_package st);
parse_field_end st; true
| "Version" -> q.s_version <- parse_version st; parse_field_end st; true
| "Section" -> q.s_section <-
common_string (parse_simple_field_content st);
true
| "Binary" -> q.s_binary <-
List.map
(function d ->
match d with [(nm, None)] -> nm | _ -> assert false)
(parse_rel f false false st);
true
| "Extra-Source-Only" ->
q.s_extra_source <- parse_simple_field_content st = "yes";
true
| _ -> false
in
let finish q =
assert (q.s_name <> -1); assert (q.s_version <> dummy_version);
Extarray.add_to_list pool.s_packages q.s_name q;
pool.s_size <- pool.s_size + 1
in
parse_stanzas ~start ~field ~finish st;
Common.stop_parsing info
(****)
let package_name pool n =
let p = Extarray.get pool.packages_by_num n in
Dict.of_id !dict p.package
let print_pack pool ch n =
let p = Extarray.get pool.packages_by_num n in
Format.fprintf ch "%s (= %a)"
(Dict.of_id !dict p.package) print_version p.version
let print_pack_name pool ch n = Format.fprintf ch "%s" (package_name pool n)
(****)
let rec remove_duplicates_rec x (l : int list) =
match l with
[] ->
[x]
| y :: r ->
if x = y then
remove_duplicates_rec x r
else
x :: remove_duplicates_rec y r
let remove_duplicates l =
match l with
[] -> []
| x :: r -> remove_duplicates_rec x r
let normalize_set (l : int list) =
match l with
[] | [_] -> l
| _ -> remove_duplicates (List.sort (fun x y -> compare x y) l)
(****)
type deb_reason =
R_conflict of int * int * (int * package_name dep) option
| R_depends of int * package_name dep
type reason = deb_reason
(****)
module Solver = Solver.F (struct type t = reason type reason = t end)
let print_rules = ref false
let add_conflict st confl l =
let l = normalize_set l in
if List.length l > 1 then begin
if !print_rules then begin
Format.printf "conflict (";
List.iter (fun c -> Format.printf " %d" c) l;
Format.printf ")@."
end;
let a = Array.of_list l in
let len = Array.length a in
for i = 0 to len - 2 do
for j = i + 1 to len - 1 do
let p = Solver.lit_of_var a.(i) false in
let p' = Solver.lit_of_var a.(j) false in
Solver.add_rule st [|p; p'|] [R_conflict (a.(i), a.(j), confl)]
done
done
end
let add_depend st deps n l =
let l = normalize_set l in
(* Some packages depend on themselves... *)
if not (List.memq n l) then begin
if !print_rules then begin
Format.printf "%d -> any-of (" n;
List.iter (fun c -> Format.printf " %d" c) l;
Format.printf ")@."
end;
Solver.add_rule st
(Array.of_list
(Solver.lit_of_var n false ::
List.map (fun n' -> Solver.lit_of_var n' true) l))
[R_depends (n, deps)];
match l with
[] | [_] -> ()
| _ -> Solver.associate_vars st (Solver.lit_of_var n true) l
end
(****)
let filter_rel rel c =
match rel with
SE -> c < 0
| E -> c <= 0
| EQ -> c = 0
| L -> c >= 0
| SL -> c > 0
let resolve_package_dep_raw pool (n, cstr) =
match cstr with
None ->
find_provided_packages pool n
| Some (rel, vers) ->
List.filter
(fun p -> filter_rel rel (compare_version p.version vers))
(Extarray.get_list pool.packages_by_name n)
let resolve_package_dep pool d =
List.map (fun p -> p.num) (resolve_package_dep_raw pool d)
let dep_can_be_satisfied pool (n, cstr) =
match cstr with
None ->
package_is_provided pool n
| Some (rel, vers) ->
List.exists
(fun p -> filter_rel rel (compare_version p.version vers))
(Extarray.get_list pool.packages_by_name n)
let single l =
match l with
[x] -> x
| _ -> assert false
let generate_rules pool =
let st = Common.start_generate (not !print_rules) pool.size in
let pr = Solver.initialize_problem ~print_var:(print_pack pool) pool.size in
(* Cannot install two packages with the same name *)
Extarray.iter
(fun l -> add_conflict pr None (List.map (fun p -> p.num) l))
pool.packages_by_name;
iter_packages pool
(fun p ->
Common.generate_next st;
if !print_rules then
Format.eprintf "%s %a@."
(Dict.of_id !dict p.package) print_version p.version;
(* Dependences *)
List.iter
(fun l ->
add_depend pr l p.num
(List.flatten
(List.map (fun p -> resolve_package_dep pool p) l)))
p.depends;
List.iter
(fun l ->
add_depend pr l p.num
(List.flatten
(List.map (fun p -> resolve_package_dep pool p) l)))
p.pre_depends;
(* Conflicts *)
let c = List.map (fun p -> single p) p.conflicts in
List.iter
(fun cstr ->
List.iter
(fun n -> add_conflict pr (Some (p.num, [cstr])) [p.num; n])
(normalize_set (resolve_package_dep pool cstr)))
c;
let c = List.map (fun p -> single p) p.breaks in
List.iter
(fun cstr ->
List.iter
(fun n -> add_conflict pr (Some (p.num, [cstr])) [p.num; n])
(normalize_set (resolve_package_dep pool cstr)))
c);
Common.stop_generate st;
Solver.propagate pr;
pr
module IntSet = Util.IntSet
let generate_rules_restricted pool s =
let pr = Solver.initialize_problem ~print_var:(print_pack pool) pool.size in
let visited = ref IntSet.empty in
let s = ref s in
while not (IntSet.is_empty !s) do
let n = IntSet.choose !s in
s := IntSet.remove n !s;
visited := IntSet.add n !visited;
let p = Extarray.get pool.packages_by_num n in
(* Dependences *)
let add_deps l =
let l' =
List.flatten
(List.map (fun p -> resolve_package_dep pool p) l)
in
List.iter
(fun n -> if not (IntSet.mem n !visited) then s := IntSet.add n !s) l';
add_depend pr l p.num l'
in
List.iter add_deps p.depends;
List.iter add_deps p.pre_depends;
(* Conflicts *)
let c = List.map (fun p -> single p) p.conflicts in
List.iter
(fun cstr ->
List.iter
(fun n -> add_conflict pr (Some (p.num, [cstr])) [p.num; n])
(normalize_set (resolve_package_dep pool cstr)))
c;
let c = List.map (fun p -> single p) p.breaks in
List.iter
(fun cstr ->
List.iter
(fun n -> add_conflict pr (Some (p.num, [cstr])) [p.num; n])
(normalize_set (resolve_package_dep pool cstr)))
c
done;
(* Cannot install two packages with the same name *)
Extarray.iter (fun l -> add_conflict pr None (List.map (fun p -> p.num) l))
pool.packages_by_name;
Solver.propagate pr;
pr
(****)
let parse_package_dependency pool s =
let st = from_bytes (Bytes.of_string s) in
let d = parse_package_dep "" true st in
if not (at_eof st) then
fail st (Format.sprintf "bad character '%c'" (next st));
resolve_package_dep pool d
let parse_package_name pool s =
List.map (fun p -> p.num)
(Extarray.get_list pool.packages_by_name (Dict.add !dict s))
let parse_version s =
let st = from_bytes (Bytes.of_string s) in
skip_whitespaces st;
let v = parse_version st in
skip_whitespaces st;
if not (at_eof st) then
fail st (Format.sprintf "bad character '%c'" (next st));
v
(****)
let print_rel ch rel =
Format.fprintf ch "%s"
(match rel with
SE -> "<<"
| E -> "<="
| EQ -> "="
| L -> ">="
| SL -> ">>")
let print_package_ref pr ch (p, v) =
pr ch p;
match v with
None ->
()
| Some (rel, vers) ->
Format.fprintf ch " (%a %a)" print_rel rel print_version vers
let rec print_package_disj pr ch l =
match l with
[] -> ()
| [p] -> print_package_ref pr ch p
| p :: r -> print_package_ref pr ch p; Format.fprintf ch " | ";
print_package_disj pr ch r
let print_package_dependency ch l =
let pr ch nm = Format.fprintf ch "%s" nm in
Util.print_list (print_package_disj pr) ", " ch l
let check pool st =
let assign = Solver.assignment st in
Array.iteri
(fun i v ->
if v = Solver.True then begin
let p = Extarray.get pool.packages_by_num i in
Format.printf "Package: %a@." (print_pack pool) i;
(* XXX No other package of the same name *)
List.iter
(fun p ->
if p.num <> i && assign.(p.num) = Solver.True then begin
Format.eprintf "PACKAGE %a ALSO INSTALLED!@."
(print_pack pool) p.num;
exit 1
end)
(Extarray.get_list pool.packages_by_name p.package);
let pr_pkg ch nm = Format.fprintf ch "%s" (Dict.of_id !dict nm) in
if p.depends <> [] then begin
Format.printf "Depends: ";
List.iter
(fun l ->
Format.printf "%a " (print_package_disj pr_pkg) l;
try
let n =
List.find (fun n -> assign.(n) = Solver.True)
(List.flatten (List.map (resolve_package_dep pool) l))
in
Format.printf "{%a}, " (print_pack pool) n
with Not_found ->
Format.printf "{UNSATISFIED}@.";
exit 1)
p.depends;
Format.printf "@."
end;
if p.pre_depends <> [] then begin
Format.printf "Pre-Depends: ";
List.iter
(fun l ->
Format.printf "%a " (print_package_disj pr_pkg) l;
try
let n =
List.find (fun n -> assign.(n) = Solver.True)
(List.flatten (List.map (resolve_package_dep pool) l))
in
Format.printf "{%a}, " (print_pack pool) n
with Not_found ->
Format.printf "{UNSATISFIED}@.";
exit 1)
p.pre_depends;
Format.printf "@."
end;
if p.conflicts <> [] then begin
Format.printf "Conflicts: ";
List.iter
(fun l ->
Format.printf "%a " (print_package_disj pr_pkg) l;
try
let n =
List.find
(fun n -> n <> i && assign.(n) = Solver.True)
(resolve_package_dep pool (single l))
in
Format.printf "{CONFLICT: %a}" (print_pack pool) n;
exit 1
with Not_found ->
Format.printf "{ok}, ")
p.conflicts;
Format.printf "@."
end;
if p.breaks <> [] then begin
Format.printf "Breaks: ";
List.iter
(fun l ->
Format.printf "%a " (print_package_disj pr_pkg) l;
try
let n =
List.find
(fun n -> n <> i && assign.(n) = Solver.True)
(resolve_package_dep pool (single l))
in
Format.printf "{CONFLICT: %a}" (print_pack pool) n;
exit 1
with Not_found ->
Format.printf "{ok}, ")
p.breaks;
Format.printf "@."
end
end)
assign
let rec print_package_list_rec pool ch l =
match l with
[] -> Format.fprintf ch "NOT AVAILABLE"
| [x] -> print_pack pool ch x
| x :: r -> Format.fprintf ch "%a, %a"
(print_pack pool) x (print_package_list_rec pool) r
let print_package_list pool ch l =
Format.fprintf ch "{%a}" (print_package_list_rec pool) l
let show_reasons pool l =
if l <> [] then begin
Format.printf "The following constraints cannot be satisfied:@.";
let pr_pkg ch nm = Format.fprintf ch "%s" (Dict.of_id !dict nm) in
List.iter
(fun r ->
match r with
R_conflict (n1, n2, _) ->
Format.printf " %a conflicts with %a@."
(print_pack pool) n1 (print_pack pool) n2
| R_depends (n, l) ->
Format.printf " %a depends on %a %a@."
(print_pack pool) n (print_package_disj pr_pkg) l
(print_package_list pool)
(List.flatten (List.map (resolve_package_dep pool) l)))
l
end
let conflicts_in_reasons rl =
List.fold_left
(fun cl ->
function R_conflict (i,j,_) -> (min i j, max i j)::cl | _ -> cl) [] rl
(****)
(*XXX Build the array directly *)
let compute_conflicts pool =
let conflict_pairs = Hashtbl.create 1000 in
let conflicts = ListTbl.create 1000 in
iter_packages pool
(fun p ->
List.iter
(fun n ->
let pair = (min n p.num, max n p.num) in
if n <> p.num && not (Hashtbl.mem conflict_pairs pair) then begin
Hashtbl.add conflict_pairs pair ();
ListTbl.add conflicts p.num n;
ListTbl.add conflicts n p.num
end)
(normalize_set
(List.flatten
(List.map (fun p -> resolve_package_dep pool (single p))
(p.breaks @ p.conflicts)))));
Array.init pool.size (fun i -> ListTbl.find conflicts i)
let compute_deps dist =
Array.init dist.size (fun i ->
let p = Extarray.get dist.packages_by_num i in
List.map
(fun l ->
match l with
[p] ->
normalize_set (resolve_package_dep dist p)
| _ ->
normalize_set
(List.flatten
(List.map (fun p -> resolve_package_dep dist p) l)))
(p.pre_depends @ p.depends))
(****)
let pool_size p = p.size
(****)
let only_latest pool' =
let pool = new_pool () in
Extarray.iter
(fun l ->
let l =
List.sort (fun p1 p2 -> - compare_version p1.version p2.version) l in
insert_package pool {(List.hd l) with num = pool.size})
pool'.packages_by_name;
pool
let copy pool =
{ size = pool.size;
packages_by_name = Extarray.copy pool.packages_by_name;
packages_by_num = Extarray.copy pool.packages_by_num;
provided_packages = Extarray.copy pool.provided_packages }
let merge pool filter pool' =
iter_packages pool'
(fun p -> if filter p then insert_package pool {p with num = pool.size})
let add_package pool p =
insert_package pool {p with num = pool.size};
(List.find (fun q -> compare_version q.version p.version = 0)
(find_packages_by_name pool p.package)).num
let src_only_latest h =
let h' = new_src_pool () in
Extarray.iter
(fun l ->
let l = List.filter (fun s -> not s.s_extra_source) l in
let l =
List.sort (fun s1 s2 -> - compare_version s1.s_version s2.s_version) l
in
match l with
[] -> ()
| s :: _ -> Extarray.add_to_list h'.s_packages s.s_name s)
h.s_packages;
h'
coinst-1.9.3/.gitignore 0000644 0001750 0001750 00000000317 12657630652 013766 0 ustar mehdi mehdi *.o
*.cm[tiox]*
*.byte
*.annot
graph.dot
*~
coinst
coinst-upgrades
comigrate
viewer/coinst_converter
viewer/coinst_viewer
viewer/jsviewer.js
viewer/dot_lexer.ml
viewer/dot_parser.ml
viewer/dot_parser.mli
coinst-1.9.3/graph.mli 0000644 0001750 0001750 00000002314 12657630652 013601 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module F (R : Repository.S) : sig
open R
val output :
?options:string list ->
?package_weight:(Package.t -> float) ->
?package_emph:(Package.t -> bool) ->
?edge_color:(Package.t -> Formula.t -> Disj.t -> string option) ->
?grayscale:bool ->
string -> ?mark_all:bool -> ?mark_reversed:bool -> ?roots:Package.t list ->
Quotient.F(R).t -> dependencies -> Conflict.t -> unit
end
coinst-1.9.3/layout.mli 0000644 0001750 0001750 00000004755 12657630652 014030 0 ustar mehdi mehdi
type (+'a) t
val (&) : 'a t -> 'a t -> 'a t
val emp : 'a t
(****)
type +'a flow
type +'a phras
type 'a phrasing = 'a phras flow
val s : string -> _ phrasing t
val i : int -> _ phrasing t
val format : (Format.formatter -> 'a -> unit) -> 'a -> _ phrasing t
val seq : string -> ('a -> _ phrasing t) -> 'a list -> _ phrasing t
val seq2 : string -> string -> ('a -> _ phrasing t) -> 'a list -> _ phrasing t
val code : _ phrasing t -> _ phrasing t
val raw_html : (unit -> string) -> _ phrasing t
type in_anchor
type outside_anchor
val anchor : string -> in_anchor phrasing t -> outside_anchor phrasing t
val p : _ flow t
val div : ?clss:string -> _ flow t -> _ flow t
val span : ?clss:string -> _ phrasing t -> _ flow t
val pre : ?clss:string -> _ phrasing t -> _ flow t
val heading : _ phrasing t -> _ flow t
val section : ?clss:string -> _ flow t -> _ flow t
val footer : _ flow t -> _ flow t
(****)
type +'a lst
val list : ('a -> 'b t) -> 'a list -> 'b t
type u
val ul : ?prefix:string -> u lst t -> _ flow t
val li : _ flow t -> u lst t
type d
val dl : ?clss:string -> d lst t -> _ flow t
val dt : ?clss:string -> _ phrasing t -> d lst t
val dd : _ flow t -> d lst t
val dli : ?id:string -> _ phrasing t -> _ flow t -> d lst t
(****)
class type printer = object
method start_doc : unit -> unit
method end_doc : unit -> unit
method text : string -> unit
method change_p : unit -> unit
method start_code : unit -> unit
method end_code : unit -> unit
method start_ul : string -> unit
method li : unit -> unit
method end_ul : unit -> unit
method start_a : string -> unit
method end_a : unit -> unit
method start_dl : ?clss:string -> unit -> unit
method dt : ?clss:string -> string option -> unit
method dd : unit -> unit
method end_dl : unit -> unit
method start_div : ?clss:string -> unit -> unit
method end_div : unit -> unit
method start_span : ?clss:string -> unit -> unit
method end_span : unit -> unit
method start_pre : ?clss:string -> unit -> unit
method end_pre : unit -> unit
method start_heading : unit -> unit
method end_heading : unit -> unit
method start_section : ?clss:string -> unit -> unit
method end_section : unit -> unit
method start_footer : unit -> unit
method end_footer : unit -> unit
method raw_html : (unit -> string) -> unit
end
class html_printer :
out_channel -> ?stylesheet:string -> ?style:string ->
?scripts:(string list) -> string -> printer
class format_printer : Format.formatter -> printer
val print : printer -> _ flow t -> unit
coinst-1.9.3/coinst_json.mli 0000644 0001750 0001750 00000002450 12657630652 015031 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module F (R : Repository.S) : sig
open R
val output :
?options:string list ->
?package_weight:(Package.t -> float) ->
?package_emph:(Package.t -> bool) ->
?edge_color:(Package.t -> Formula.t -> Disj.t -> string option) ->
?grayscale:bool ->
string -> ?mark_all:bool -> ?mark_reversed:bool -> ?roots:Package.t list ->
Quotient.F(R).t -> dependencies -> Conflict.t -> unit
val output_non_coinstallable_sets :
string -> Quotient.F(R).t -> PSet.t list -> unit
end
coinst-1.9.3/common.ml 0000644 0001750 0001750 00000005035 12657630652 013622 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
type st =
{ time : float;
active : bool;
channel : in_channel;
length : int;
mutable count : int;
mutable percent : float }
let start_parsing active ch =
{ time = Unix.gettimeofday ();
active = active; channel = ch;
length = begin try in_channel_length ch with Sys_error _ -> 0 end;
count = 0; percent = 0. }
let parsing_tick st =
st.count <- st.count + 1;
if st.active then begin
if st.length > 0 then begin
let p = pos_in st.channel in
let pc = float p *. 100. /. float st.length in
if pc >= st.percent then begin
Util.set_msg (Format.sprintf
"Parsing package file... %3.f%% %6d packages"
pc st.count);
st.percent <- pc +. 1.
end
end else if st.count mod 10 = 0 then
Util.set_msg
(Format.sprintf "Parsing package file... %6d packages" st.count)
end
let stop_parsing st =
Util.set_msg "";
Format.eprintf "Parsing package file... %.1f seconds %6d packages@."
(Unix.gettimeofday () -. st.time) st.count
(****)
type st' =
{ time : float;
active : bool;
num : int;
step : int;
mutable count : int }
let start_generate active num =
if active then Util.set_msg "Generating constraints...";
{ time = Unix.gettimeofday ();
active = active; num = num; step = max 1 (num / 100); count = 0 }
let generate_next st =
st.count <- st.count + 1;
if st.active && st.count mod st.step = 0 then
Util.set_msg (Format.sprintf "Generating constraints... %3.f%%"
(float st.count *. 100. /. float st.num))
let stop_generate st =
Util.set_msg "";
Format.eprintf "Generating constraints... %.1f seconds@."
(Unix.gettimeofday () -. st.time);
coinst-1.9.3/horn.ml 0000644 0001750 0001750 00000023041 12657630652 013275 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
let debug = Debug.make "horn" "Debug Horn clause solver." []
let stats =
Debug.make "horn_stats" "Output stats regarding Horn clause solver." ["horn"]
let debug_retract =
Debug.make "horn_retract" "Debug Horn assumption retraction." ["horn"]
(****)
let n1 = ref 0
let n2 = ref 0
let d = Array.make 10 0
let _ = at_exit (fun _ ->
if stats () && (!n1 > 0 || !n2 > 0) then begin
Format.eprintf "%d rules / %d assumptions@." !n1 !n2;
Array.iter (fun n -> Format.eprintf " %d" n) d;
Format.eprintf "@."
end)
(****)
module BitVect = Util.BitVect
module type S = sig
type reason
end
module type SOLVER = sig
type state
type reason
type var = int
type id
val initialize : ?signal_assign:(var array -> reason -> unit) -> int -> state
val extend : state -> int -> unit
val set_var_printer : state -> (Format.formatter -> var -> unit) -> unit
val assignment : state -> BitVect.t
val direct_reasons : state -> var -> (var array * reason) list
val reason : state -> var -> (var array * reason) option
val assumptions : state -> var -> reason list
val add_rule : state -> var array -> reason -> id
val assume : state -> var -> reason -> unit
val retract_rule : state -> id -> unit
val retract_assumptions : state -> var -> unit
end
module F (X : S) : SOLVER with type reason = X.reason = struct
(* Variables *)
type var = int
type reason = X.reason
type clause =
{ lits : var array;
reason : reason }
type id = clause
type explanation = Assumption of reason | Clause of clause | Unconstrained
type state =
{ (* Indexed by var *)
mutable st_assign : BitVect.t;
mutable st_reason : explanation array;
mutable st_forward : clause list array;
mutable st_backward : clause list array;
mutable st_assumptions : reason list array;
mutable st_weight : int array;
(* Queues *)
st_prop_queue : var Queue.t;
(* Misc *)
st_signal_assign : (var array -> reason -> unit) option;
mutable st_var_printer : (Format.formatter -> var -> unit) option }
let set_var_printer st pr = st.st_var_printer <- Some pr
let print_var st f x =
match st.st_var_printer with
None -> Format.fprintf f "%d" x
| Some pr -> Format.fprintf f "%d (%a)" x pr x
let print_clause st f r =
let r = r.lits in
if Array.length r > 1 then begin
for i = 1 to Array.length r - 1 do
Format.fprintf f "%a " (print_var st) r.(i)
done;
Format.fprintf f " => "
end;
Format.fprintf f "%a" (print_var st) r.(0)
let is_unit st r =
let lits = r.lits in
let l = Array.length lits in
let i = ref 1 in
while !i < l && BitVect.test st.st_assign lits.(!i) do
incr i
done;
!i = l
let weight st reason =
match reason with
Assumption _ ->
1
| Clause r ->
let lits = r.lits in
let w = ref 0 in
for i = 1 to Array.length lits - 1 do
w := !w + st.st_weight.(lits.(i))
done;
1 + !w
| Unconstrained ->
assert false
let rec enqueue st p reason =
let w = weight st reason in
let w' = st.st_weight.(p) in
if not (BitVect.test st.st_assign p) || w' > w then begin
BitVect.set st.st_assign p;
st.st_weight.(p) <- w;
st.st_reason.(p) <- reason;
begin match st.st_signal_assign, reason with
Some f, Assumption reason -> f [|p|] reason
| Some f, Clause r -> f r.lits r.reason
| Some _, Unconstrained -> assert false
| None, _ -> ()
end;
Queue.add p st.st_prop_queue
end else if w = w' && w > 1 then
match st.st_reason.(p), reason with
Clause {lits = r}, Clause {lits = r'} when r.(1) > r'.(1) ->
st.st_reason.(p) <- reason
| _ ->
()
and propagate_in_clause st r =
if debug () then Format.eprintf "Trying rule %a@." (print_clause st) r;
if is_unit st r then enqueue st r.lits.(0) (Clause r)
let check st =
for p = 0 to Array.length st.st_weight - 1 do
if BitVect.test st.st_assign p then begin
if st.st_assumptions.(p) <> [] then
assert (st.st_weight.(p) = 0)
else begin
List.iter
(fun r ->
if
is_unit st r && st.st_weight.(p) > weight st (Clause r)
then begin
Format.eprintf "!!! %a: %d/%d %a@." (print_var st) p
st.st_weight.(p) (weight st (Clause r))
(print_clause st) r
end)
st.st_backward.(p);
assert (List.exists (fun r -> st.st_weight.(p) = weight st (Clause r))
st.st_backward.(p))
end
end
done
let rec propagate st =
while not (Queue.is_empty st.st_prop_queue) do
let p = Queue.take st.st_prop_queue in
List.iter (fun r -> propagate_in_clause st r)
(List.rev st.st_forward.(p))
done
let add_rule st lits reason =
incr n1;
let len = Array.length lits in
if len <= 10 then d.(len - 1) <- d.(len - 1) + 1;
let r = { lits = lits; reason = reason } in
if debug () then Format.eprintf "Adding rule %a@." (print_clause st) r;
let l = Array.length lits in
for i = 1 to l - 1 do
let p = lits.(i) in
st.st_forward.(p) <- r :: st.st_forward.(p)
done;
let p = lits.(0) in
st.st_backward.(p) <- r :: st.st_backward.(p);
propagate_in_clause st r;
r
let assume st p reason =
incr n2;
st.st_assumptions.(p) <- reason :: st.st_assumptions.(p);
enqueue st p (Assumption reason)
let rec propagate_retraction st l p =
if debug_retract () then
Format.eprintf "Retracting assignment to variable %a@." (print_var st) p;
st.st_reason.(p) <- Unconstrained;
BitVect.clear st.st_assign p;
p ::
List.fold_left
(fun l r ->
if debug_retract () then
Format.eprintf "Considering rule %a:@." (print_clause st) r;
match st.st_reason.(r.lits.(0)) with
Assumption _ | Unconstrained ->
if debug_retract () then Format.eprintf " does not apply.@.";
l
| Clause r' when r' != r ->
if debug_retract () then Format.eprintf " does not apply.@.";
l
| Clause _ ->
if debug_retract () then Format.eprintf " the rule was applied.@.";
propagate_retraction st l r.lits.(0))
l st.st_forward.(p)
let update_after_retraction st p =
let l = propagate_retraction st [] p in
(* Then, we see whether other rules apply instead. *)
List.iter
(fun q ->
List.iter (fun r -> propagate_in_clause st r)
(List.rev st.st_backward.(q)))
l;
if debug_retract () then
List.iter
(fun q ->
match st.st_reason.(q) with
Unconstrained ->
()
| Assumption _ ->
Format.eprintf
"Variable %a constrained for another reason (assumption).@."
(print_var st) q
| Clause r ->
Format.eprintf
"Variable %a constrained for another reason (%a).@."
(print_var st) q (print_clause st) r)
l
let retract_assumptions st p =
propagate st;
(* We remove all the assumptions associated to variable p *)
st.st_assumptions.(p) <- [];
match st.st_reason.(p) with
Assumption _ ->
(* If variable p were directly constrained by an assumption,
we recursively cancel the consequences of the this
assumption. *)
update_after_retraction st p
| _ ->
()
let retract_rule st r =
propagate st;
let lits = r.lits in
let l = Array.length lits in
for i = 1 to l - 1 do
let p = lits.(i) in
st.st_forward.(p) <- List.filter (fun r' -> r' != r) st.st_forward.(p)
done;
let p = lits.(0) in
st.st_backward.(p) <- List.filter (fun r' -> r' != r) st.st_backward.(p);
match st.st_reason.(p) with
Clause r' when r == r' ->
update_after_retraction st p
| _ ->
()
let initialize ?signal_assign n =
{ st_assign = BitVect.make n false;
st_reason = Array.make n Unconstrained;
st_forward = Array.make n [];
st_backward = Array.make n [];
st_assumptions = Array.make n [];
st_weight = Array.make n 0;
st_prop_queue = Queue.create ();
st_signal_assign = signal_assign;
st_var_printer = None }
let extend st n =
let n = max n (Array.length st.st_reason) in
st.st_assign <- BitVect.extend st.st_assign n false;
st.st_reason <- Util.array_extend st.st_reason n Unconstrained;
st.st_forward <- Util.array_extend st.st_forward n [];
st.st_backward <- Util.array_extend st.st_backward n [];
st.st_weight <- Util.array_extend st.st_weight n 0;
st.st_assumptions <- Util.array_extend st.st_assumptions n []
let assignment st = propagate st; st.st_assign
let direct_reasons st p =
List.map (fun r -> (r.lits, r.reason))
(List.filter (fun p -> is_unit st p) st.st_backward.(p)) @
List.map (fun reason -> ([|p|], reason)) st.st_assumptions.(p)
let reason st p =
match st.st_reason.(p) with
Clause r -> Some (r.lits, r.reason)
| _ -> None
let assumptions st p = st.st_assumptions.(p)
end
coinst-1.9.3/.depend 0000644 0001750 0001750 00000014734 12657630652 013246 0 ustar mehdi mehdi api.cmo : solver.cmi api.cmi
api.cmx : solver.cmx api.cmi
api.cmi : solver.cmi
bytearray.cmo : bytearray.cmi
bytearray.cmx : bytearray.cmi
bytearray.cmi :
cache.cmo : util.cmi cache.cmi
cache.cmx : util.cmx cache.cmi
cache.cmi :
coinst_common.cmo : repository.cmi quotient.cmi debug.cmi api.cmi \
coinst_common.cmi
coinst_common.cmx : repository.cmx quotient.cmx debug.cmx api.cmx \
coinst_common.cmi
coinst_common.cmi : repository.cmi quotient.cmi api.cmi
coinst_json.cmo : repository.cmi quotient.cmi conflicts.cmo coinst_json.cmi
coinst_json.cmx : repository.cmx quotient.cmx conflicts.cmx coinst_json.cmi
coinst_json.cmi : repository.cmi quotient.cmi
coinst.cmo : util.cmi rpm_lib.cmi repository.cmi quotient.cmi graph.cmi \
file.cmi deb_lib.cmi cudf_lib.cmi coinst_json.cmi api.cmi
coinst.cmx : util.cmx rpm_lib.cmx repository.cmx quotient.cmx graph.cmx \
file.cmx deb_lib.cmx cudf_lib.cmx coinst_json.cmx api.cmx
common.cmo : util.cmi common.cmi
common.cmx : util.cmx common.cmi
common.cmi :
conflicts.cmo : repository.cmi quotient.cmi
conflicts.cmx : repository.cmx quotient.cmx
cudf_lib.cmo : solver.cmi common.cmi cudf_lib.cmi
cudf_lib.cmx : solver.cmx common.cmx cudf_lib.cmi
cudf_lib.cmi : api.cmi
deb_lib.cmo : util.cmi solver.cmi debug.cmi common.cmi deb_lib.cmi
deb_lib.cmx : util.cmx solver.cmx debug.cmx common.cmx deb_lib.cmi
deb_lib.cmi : util.cmi solver.cmi api.cmi
debug.cmo : debug.cmi
debug.cmx : debug.cmi
debug.cmi :
file.cmo : file.cmi
file.cmx : file.cmi
file.cmi :
graph.cmo : repository.cmi quotient.cmi conflicts.cmo graph.cmi
graph.cmx : repository.cmx quotient.cmx conflicts.cmx graph.cmi
graph.cmi : repository.cmi quotient.cmi
horn.cmo : util.cmi debug.cmi horn.cmi
horn.cmx : util.cmx debug.cmx horn.cmi
horn.cmi : util.cmi
layout.cmo : layout.cmi
layout.cmx : layout.cmi
layout.cmi :
ptset.cmo : ptset.cmi
ptset.cmx : ptset.cmi
ptset.cmi :
quotient.cmo : util.cmi repository.cmi quotient.cmi
quotient.cmx : util.cmx repository.cmx quotient.cmi
quotient.cmi : repository.cmi
repository.cmo : util.cmi api.cmi repository.cmi
repository.cmx : util.cmx api.cmx repository.cmi
repository.cmi : util.cmi api.cmi
rpm_lib.cmo : util.cmi solver.cmi common.cmi rpm_lib.cmi
rpm_lib.cmx : util.cmx solver.cmx common.cmx rpm_lib.cmi
rpm_lib.cmi : api.cmi
solver.cmo : solver.cmi
solver.cmx : solver.cmi
solver.cmi :
task.cmo : util.cmi debug.cmi bytearray.cmi task.cmi
task.cmx : util.cmx debug.cmx bytearray.cmx task.cmi
task.cmi :
transition.cmo : util.cmi upgrade_common.cmi upgrade.cmi update_data.cmi \
task.cmi viewer/scene_svg.cmi viewer/scene.cmi layout.cmi horn.cmi \
file.cmi viewer/dot_render.cmi viewer/dot_graph.cmi debug.cmi deb_lib.cmi \
cache.cmi
transition.cmx : util.cmx upgrade_common.cmx upgrade.cmx update_data.cmx \
task.cmx viewer/scene_svg.cmx viewer/scene.cmx layout.cmx horn.cmx \
file.cmx viewer/dot_render.cmx viewer/dot_graph.cmx debug.cmx deb_lib.cmx \
cache.cmx
update_data.cmo : task.cmi update_data.cmi
update_data.cmx : task.cmx update_data.cmi
update_data.cmi :
upgrade_common.cmo : util.cmi graph.cmi viewer/dot_file.cmi debug.cmi \
deb_lib.cmi coinst_common.cmi upgrade_common.cmi
upgrade_common.cmx : util.cmx graph.cmx viewer/dot_file.cmx debug.cmx \
deb_lib.cmx coinst_common.cmx upgrade_common.cmi
upgrade_common.cmi : util.cmi repository.cmi deb_lib.cmi
upgrade_main.cmo : upgrade_common.cmi upgrade.cmi debug.cmi
upgrade_main.cmx : upgrade_common.cmx upgrade.cmx debug.cmx
upgrade.cmo : util.cmi upgrade_common.cmi task.cmi viewer/scene_svg.cmi \
viewer/scene.cmi quotient.cmi layout.cmi graph.cmi file.cmi \
viewer/dot_render.cmi viewer/dot_graph.cmi deb_lib.cmi upgrade.cmi
upgrade.cmx : util.cmx upgrade_common.cmx task.cmx viewer/scene_svg.cmx \
viewer/scene.cmx quotient.cmx layout.cmx graph.cmx file.cmx \
viewer/dot_render.cmx viewer/dot_graph.cmx deb_lib.cmx upgrade.cmi
upgrade.cmi : upgrade_common.cmi layout.cmi deb_lib.cmi
util.cmo : ptset.cmi util.cmi
util.cmx : ptset.cmx util.cmi
util.cmi :
viewer/converter.cmo : viewer/scene_json.cmi viewer/scene_extents.cmi \
viewer/scene.cmi viewer/dot_render.cmi viewer/dot_graph.cmi
viewer/converter.cmx : viewer/scene_json.cmx viewer/scene_extents.cmx \
viewer/scene.cmx viewer/dot_render.cmx viewer/dot_graph.cmx
viewer/dot_file.cmo : viewer/dot_file.cmi
viewer/dot_file.cmx : viewer/dot_file.cmi
viewer/dot_file.cmi :
viewer/dot_graph.cmo : viewer/dot_parser.cmi viewer/dot_lexer.cmi \
viewer/dot_file.cmi viewer/dot_graph.cmi
viewer/dot_graph.cmx : viewer/dot_parser.cmx viewer/dot_lexer.cmx \
viewer/dot_file.cmx viewer/dot_graph.cmi
viewer/dot_graph.cmi : viewer/dot_file.cmi
viewer/dot_lexer.cmo : viewer/dot_parser.cmi viewer/dot_lexer.cmi
viewer/dot_lexer.cmx : viewer/dot_parser.cmx viewer/dot_lexer.cmi
viewer/dot_lexer.cmi : viewer/dot_parser.cmi
viewer/dot_parser.cmo : viewer/dot_file.cmi viewer/dot_parser.cmi
viewer/dot_parser.cmx : viewer/dot_file.cmx viewer/dot_parser.cmi
viewer/dot_parser.cmi : viewer/dot_file.cmi
viewer/dot_render.cmo : viewer/scene.cmi viewer/dot_graph.cmi \
viewer/dot_render.cmi
viewer/dot_render.cmx : viewer/scene.cmx viewer/dot_graph.cmx \
viewer/dot_render.cmi
viewer/dot_render.cmi : viewer/scene.cmi viewer/dot_graph.cmi
viewer/main.cmo : viewer/viewer.cmi viewer/dot_render.cmi \
viewer/dot_graph.cmi
viewer/main.cmx : viewer/viewer.cmx viewer/dot_render.cmx \
viewer/dot_graph.cmx
viewer/scene_extents.cmo : viewer/scene.cmi viewer/scene_extents.cmi
viewer/scene_extents.cmx : viewer/scene.cmx viewer/scene_extents.cmi
viewer/scene_extents.cmi : viewer/scene.cmi
viewer/scene_json.cmo : viewer/scene.cmi viewer/scene_json.cmi
viewer/scene_json.cmx : viewer/scene.cmx viewer/scene_json.cmi
viewer/scene_json.cmi : viewer/scene.cmi
viewer/scene.cmo : viewer/scene.cmi
viewer/scene.cmx : viewer/scene.cmi
viewer/scene.cmi :
viewer/scene_svg.cmo : viewer/scene.cmi viewer/scene_svg.cmi
viewer/scene_svg.cmx : viewer/scene.cmx viewer/scene_svg.cmi
viewer/scene_svg.cmi : viewer/scene.cmi
viewer/svg.cmo :
viewer/svg.cmx :
viewer/viewer_common.cmo : viewer/scene.cmi viewer/viewer_common.cmi
viewer/viewer_common.cmx : viewer/scene.cmx viewer/viewer_common.cmi
viewer/viewer_common.cmi : viewer/scene.cmi
viewer/viewer_js.cmo : viewer/viewer_common.cmi
viewer/viewer_js.cmx : viewer/viewer_common.cmx
viewer/viewer.cmo : viewer/viewer_common.cmi viewer/scene_extents.cmi \
viewer/scene.cmi viewer/viewer.cmi
viewer/viewer.cmx : viewer/viewer_common.cmx viewer/scene_extents.cmx \
viewer/scene.cmx viewer/viewer.cmi
viewer/viewer.cmi : viewer/scene.cmi
coinst-1.9.3/coinst_common.mli 0000644 0001750 0001750 00000002604 12657630652 015351 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module F (M : Api.S) : sig
module Repository : Repository.S with type pool = M.pool
open Repository
module Quotient : Quotient.S(Repository).S with type t = Quotient.F(Repository).t
val compute_dependencies_and_conflicts :
pool -> Formula.t PTbl.t * Conflict.t
val generate_rules :
Quotient.t -> Formula.t PTbl.t -> Conflict.t -> M.Solver.state
val remove_clearly_irrelevant_deps :
Conflict.t -> Formula.t PTbl.t -> Formula.t PTbl.t
val flatten_and_simplify :
?aggressive:bool ->
pool -> Formula.t PTbl.t -> Conflict.t -> Formula.t PTbl.t * Conflict.t
end
coinst-1.9.3/coinst_json.ml 0000644 0001750 0001750 00000024752 12657630652 014671 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module F (R : Repository.S) = struct
open R
module Quotient = Quotient.F(R)
module Conflicts = Conflicts.F (R)
(* Our JSON package description format: *)
type package = {
package_name : string;
package_depend : string list list; (* Conjunction of disjunctions of dependencies. *)
package_conflict : string list;
}
let make_package ~name ?(depend=[[]]) ?(conflict=[]) () = {
package_name = name;
package_depend = depend;
package_conflict = conflict;
}
(* Printing JSON packages: *)
(* Pretty-print or squeeze into a single one line omitting default values? *)
type json_printing = Pretty | Dense
let json_of_list (l : string list) = Printf.sprintf "[%s]" (String.concat ", " l)
let json_of_package ?(printing=Pretty) package =
let json_of_conjunction_of_disjunctions (conjunction_of_disjunctions : string list list) =
json_of_list (List.map json_of_list conjunction_of_disjunctions) in
(* Half-prepared output: *)
let name = package.package_name in
let depend = json_of_conjunction_of_disjunctions package.package_depend in
let conflict = json_of_list package.package_conflict in
match printing with
| Pretty ->
Printf.sprintf
"{\n \"name\" : %s,\n \"depend\" : %s,\n \"conflict\" : %s\n}"
name depend conflict
| Dense ->
Printf.sprintf "{ \"name\" : %s%s%s }"
name
(match package.package_depend with
| [[]] -> "" (* Default *)
| _ -> Printf.sprintf ", \"depend\" : %s" depend)
(match package.package_conflict with
| [] -> "" (* Default *)
| _ -> Printf.sprintf ", \"conflict\" : %s" conflict)
(* Helper functions: *)
(* Transform an iterator over a collection into a map function returning a list. *)
let map_of_iter (collection_iter : ('a -> unit) -> 'c -> unit) (f : 'a -> 'b) (collection : 'c) : 'b list =
(* Prepare an empty list for the result. *)
let (result_list : (('b list) ref)) = ref [] in
(* Use the provoided iter function to iterate over every element of the colection and add it to the list. *)
collection_iter (fun collection_element ->
let result = f collection_element in
result_list := result :: !result_list;
) collection;
(* The list is now inversed with respect to the iter order, we need to reverse it. *)
result_list := List.rev !result_list;
!result_list
(* The simpliest map_of_iter which returns a list of the elements of the collection. *)
let list_of_iter (collection_iter : ('a -> unit) -> 'c -> unit) (collection : 'c) : 'a list =
map_of_iter collection_iter (fun x -> x) collection
(* Collection iterators with usual sequence of arguments (i.e. first the function, then the collection). *)
(* We define them here to be able to use them consistently with map_of_iter and list_of_iter. *)
let quotient_iter (f : R.Package.t -> unit) (quotient : Quotient.t) : unit = Quotient.iter f quotient
and formula_iter (f : R.Disj.t -> unit) (formula : R.Formula.t) : unit = Formula.iter formula f
and disj_iter (f : R.Package.t -> unit) (disj : R.Disj.t) : unit = R.Disj.iter disj f
let output
?options
?package_weight
?package_emph
?(edge_color = fun _ _ _ -> Some "blue") ?(grayscale =false)
file ?(mark_all = false) ?(mark_reversed = false) ?(roots = [])
quotient deps confl =
(* Mark the packages to be included in the graph *)
let marks = Hashtbl.create 101 in
let marked i = Hashtbl.mem marks i in
let has_dependencies p =
let dep = PTbl.get deps p in
not (Formula.implies Formula._true dep ||
Formula.implies (Formula.lit p) dep)
in
let rec mark p =
if not (marked p) then begin
Hashtbl.add marks p ();
PSet.iter mark (Conflict.of_package confl p)
end
in
if mark_all then
Quotient.iter (fun p -> Hashtbl.add marks p ()) quotient
else if roots = [] then begin
Quotient.iter
(fun p ->
if has_dependencies p then begin
mark p;
Formula.iter (PTbl.get deps p) (fun d -> Disj.iter d mark)
end)
quotient;
if mark_reversed then begin
let m = Hashtbl.copy marks in
Hashtbl.clear marks;
Quotient.iter
(fun p -> if not (Hashtbl.mem m p) then Hashtbl.add marks p ())
quotient
end
end else (*XXX Find the right algorithm...
Work on transitive closure of dependencies
Mark all conflicts; marks all packages at the other side of
these conflicts and all the alternative in the dependency.
Proceed recursively...
Backward mode:
mark source package and all edges but the one considered
A package is not relevant if installing it or not has no
impact on the considered package
*)
List.iter mark roots;
let ch = open_out file in
let f = Format.formatter_of_out_channel ch in
(* JZ: Until here I've only removed some code in the "output" function,
from now I'm replacing it almost completely. *)
(* List of all the marked packages (i.e. all the equivalence classes). *)
let (quotient_packages : R.Package.t list) =
let all_packages = list_of_iter quotient_iter quotient in
List.filter marked all_packages in
(* Some string_of_* functions to extract the names of things: *)
let string_of_eq_class (package : R.Package.t) : string =
Format.fprintf Format.str_formatter "\"%a\"" (Quotient.print_class quotient) package;
Format.flush_str_formatter () in
let string_of_package (package : R.Package.t) : string =
(* TODO: Print only the name or the name with version? Maybe add a command line option for this. *)
Format.fprintf Format.str_formatter "\"%a\"" (R.Package.print_name (Quotient.pool quotient)) package;
(*
Format.fprintf Format.str_formatter "\"%a\"" (R.Package.print (Quotient.pool quotient)) package;
*)
Format.flush_str_formatter () in
(* 1. Dependencies and conflicts between package equivalence classes. *)
(* List of json packages describing equivalence classes. *)
let eq_classes_packages : package list =
List.map (fun (eq_class : R.Package.t) ->
(* Prepare required coinst data about the equivalence class. *)
let (coinst_dependencies : Formula.t) = PTbl.get deps eq_class in
let (coinst_conflicts : PSet.t) = Conflict.of_package confl eq_class in
(* A list of lists of R.Package.t representing a conjunction of disjunctions of dependencies. *)
let conjunction_of_disjunctions =
map_of_iter formula_iter (fun (coinst_disjunction : R.Disj.t) ->
list_of_iter disj_iter coinst_disjunction
) coinst_dependencies in
(* A list of R.Package.t representing conflicts. *)
let conflict_list = list_of_iter PSet.iter coinst_conflicts in
(* The JSON package: *)
make_package
~name: (string_of_eq_class eq_class)
~depend: (List.map (List.map string_of_eq_class) conjunction_of_disjunctions)
~conflict: (List.map string_of_eq_class conflict_list)
()
) quotient_packages in
(* Debug: *)(* Quotient.print quotient deps; *)
(* 2. Links between packages and their equivalence classes. *)
(* List of json packages describing real packages: each package depends on his equivalence class. *)
let packages_in_eq_classes : package list =
List.flatten (List.map (fun (eq_class : R.Package.t) ->
(* Prepare required coinst data about the representants of this equivalence class. *)
let (representants : R.PSet.t) =
try Quotient.clss quotient eq_class
with Not_found -> failwith "Json module: Problem with Quotient.clss!" in
if R.PSet.cardinal representants = 1
(* If the class of equivalence contains just one package, we do not need
to make this package depend on itself. Moreover this package will be
already outputed in the equivalence class part so we are done here. *)
then []
(* Else each package in the equivalence class should depend on that class. *)
else map_of_iter PSet.iter (fun (package : R.Package.t) ->
(* The JSON package: *)
make_package
~name: (string_of_package package)
~depend: ([[string_of_eq_class eq_class]])
()
) representants
) quotient_packages) in
(* Print the whole list of equivalence class descriptions and package implementations. *)
Format.fprintf f
"[\n%s,\n%s\n]@."
(String.concat ",\n" (List.map (json_of_package ~printing:Pretty) eq_classes_packages))
(String.concat ",\n" (List.map (json_of_package ~printing:Dense) packages_in_eq_classes));
close_out ch
let output_list f g l =
Format.fprintf f "@[<1>[";
begin match l with
[] -> ()
| x :: r -> g f x; List.iter (fun x -> Format.fprintf f ",@,%a" g x) r
end;
Format.fprintf f "]@]"
let output_packages quotient f s =
output_list f
(fun f p ->
Format.fprintf f "\"%a\""
(R.Package.print_name (Quotient.pool quotient)) p)
s
let output_classes quotient f l =
output_list f
(fun f p ->
Format.fprintf f "@[<1>[\"%a\",@,%a]@]"
(R.Package.print_name (Quotient.pool quotient)) p
(output_packages quotient) (PSet.elements (Quotient.clss quotient p)))
l
let output_sets quotient f l = output_list f (output_packages quotient) l
let output_non_coinstallable_sets file quotient sets =
let packages = List.fold_left PSet.union PSet.empty sets in
let ch = open_out file in
let f = Format.formatter_of_out_channel ch in
Format.fprintf f
"@[<1>{@[<2>\"classes\":@,%a,@]@,@[<2>\"incompatibilities\":@,%a@]}@]@."
(output_classes quotient) (PSet.elements packages)
(output_sets quotient) (List.map PSet.elements sets);
close_out ch
end
coinst-1.9.3/COPYING 0000644 0001750 0001750 00000044253 12657630652 013040 0 ustar mehdi mehdi Copyright (C) 2005-2011 Jerome Vouillon
These programs are free software; you can redistribute them and/or
modify them under the terms of the GNU General Public License as
published by the Free Software Foundation; either version 2 of the
License, or (at your option) any later version.
These programs are distributed in the hope that they will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See (below) the
GNU General Public License for more details.
---------------------------------------------------------------------------
GNU GENERAL PUBLIC LICENSE
Version 2, June 1991
Copyright (C) 1989, 1991 Free Software Foundation, Inc.
59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Everyone is permitted to copy and distribute verbatim copies
of this license document, but changing it is not allowed.
Preamble
The licenses for most software are designed to take away your
freedom to share and change it. By contrast, the GNU General Public
License is intended to guarantee your freedom to share and change free
software--to make sure the software is free for all its users. This
General Public License applies to most of the Free Software
Foundation's software and to any other program whose authors commit to
using it. (Some other Free Software Foundation software is covered by
the GNU Library General Public License instead.) You can apply it to
your programs, too.
When we speak of free software, we are referring to freedom, not
price. Our General Public Licenses are designed to make sure that you
have the freedom to distribute copies of free software (and charge for
this service if you wish), that you receive source code or can get it
if you want it, that you can change the software or use pieces of it
in new free programs; and that you know you can do these things.
To protect your rights, we need to make restrictions that forbid
anyone to deny you these rights or to ask you to surrender the rights.
These restrictions translate to certain responsibilities for you if you
distribute copies of the software, or if you modify it.
For example, if you distribute copies of such a program, whether
gratis or for a fee, you must give the recipients all the rights that
you have. You must make sure that they, too, receive or can get the
source code. And you must show them these terms so they know their
rights.
We protect your rights with two steps: (1) copyright the software, and
(2) offer you this license which gives you legal permission to copy,
distribute and/or modify the software.
Also, for each author's protection and ours, we want to make certain
that everyone understands that there is no warranty for this free
software. If the software is modified by someone else and passed on, we
want its recipients to know that what they have is not the original, so
that any problems introduced by others will not reflect on the original
authors' reputations.
Finally, any free program is threatened constantly by software
patents. We wish to avoid the danger that redistributors of a free
program will individually obtain patent licenses, in effect making the
program proprietary. To prevent this, we have made it clear that any
patent must be licensed for everyone's free use or not licensed at all.
The precise terms and conditions for copying, distribution and
modification follow.
GNU GENERAL PUBLIC LICENSE
TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION
0. This License applies to any program or other work which contains
a notice placed by the copyright holder saying it may be distributed
under the terms of this General Public License. The "Program", below,
refers to any such program or work, and a "work based on the Program"
means either the Program or any derivative work under copyright law:
that is to say, a work containing the Program or a portion of it,
either verbatim or with modifications and/or translated into another
language. (Hereinafter, translation is included without limitation in
the term "modification".) Each licensee is addressed as "you".
Activities other than copying, distribution and modification are not
covered by this License; they are outside its scope. The act of
running the Program is not restricted, and the output from the Program
is covered only if its contents constitute a work based on the
Program (independent of having been made by running the Program).
Whether that is true depends on what the Program does.
1. You may copy and distribute verbatim copies of the Program's
source code as you receive it, in any medium, provided that you
conspicuously and appropriately publish on each copy an appropriate
copyright notice and disclaimer of warranty; keep intact all the
notices that refer to this License and to the absence of any warranty;
and give any other recipients of the Program a copy of this License
along with the Program.
You may charge a fee for the physical act of transferring a copy, and
you may at your option offer warranty protection in exchange for a fee.
2. You may modify your copy or copies of the Program or any portion
of it, thus forming a work based on the Program, and copy and
distribute such modifications or work under the terms of Section 1
above, provided that you also meet all of these conditions:
a) You must cause the modified files to carry prominent notices
stating that you changed the files and the date of any change.
b) You must cause any work that you distribute or publish, that in
whole or in part contains or is derived from the Program or any
part thereof, to be licensed as a whole at no charge to all third
parties under the terms of this License.
c) If the modified program normally reads commands interactively
when run, you must cause it, when started running for such
interactive use in the most ordinary way, to print or display an
announcement including an appropriate copyright notice and a
notice that there is no warranty (or else, saying that you provide
a warranty) and that users may redistribute the program under
these conditions, and telling the user how to view a copy of this
License. (Exception: if the Program itself is interactive but
does not normally print such an announcement, your work based on
the Program is not required to print an announcement.)
These requirements apply to the modified work as a whole. If
identifiable sections of that work are not derived from the Program,
and can be reasonably considered independent and separate works in
themselves, then this License, and its terms, do not apply to those
sections when you distribute them as separate works. But when you
distribute the same sections as part of a whole which is a work based
on the Program, the distribution of the whole must be on the terms of
this License, whose permissions for other licensees extend to the
entire whole, and thus to each and every part regardless of who wrote it.
Thus, it is not the intent of this section to claim rights or contest
your rights to work written entirely by you; rather, the intent is to
exercise the right to control the distribution of derivative or
collective works based on the Program.
In addition, mere aggregation of another work not based on the Program
with the Program (or with a work based on the Program) on a volume of
a storage or distribution medium does not bring the other work under
the scope of this License.
3. You may copy and distribute the Program (or a work based on it,
under Section 2) in object code or executable form under the terms of
Sections 1 and 2 above provided that you also do one of the following:
a) Accompany it with the complete corresponding machine-readable
source code, which must be distributed under the terms of Sections
1 and 2 above on a medium customarily used for software interchange; or,
b) Accompany it with a written offer, valid for at least three
years, to give any third party, for a charge no more than your
cost of physically performing source distribution, a complete
machine-readable copy of the corresponding source code, to be
distributed under the terms of Sections 1 and 2 above on a medium
customarily used for software interchange; or,
c) Accompany it with the information you received as to the offer
to distribute corresponding source code. (This alternative is
allowed only for noncommercial distribution and only if you
received the program in object code or executable form with such
an offer, in accord with Subsection b above.)
The source code for a work means the preferred form of the work for
making modifications to it. For an executable work, complete source
code means all the source code for all modules it contains, plus any
associated interface definition files, plus the scripts used to
control compilation and installation of the executable. However, as a
special exception, the source code distributed need not include
anything that is normally distributed (in either source or binary
form) with the major components (compiler, kernel, and so on) of the
operating system on which the executable runs, unless that component
itself accompanies the executable.
If distribution of executable or object code is made by offering
access to copy from a designated place, then offering equivalent
access to copy the source code from the same place counts as
distribution of the source code, even though third parties are not
compelled to copy the source along with the object code.
4. You may not copy, modify, sublicense, or distribute the Program
except as expressly provided under this License. Any attempt
otherwise to copy, modify, sublicense or distribute the Program is
void, and will automatically terminate your rights under this License.
However, parties who have received copies, or rights, from you under
this License will not have their licenses terminated so long as such
parties remain in full compliance.
5. You are not required to accept this License, since you have not
signed it. However, nothing else grants you permission to modify or
distribute the Program or its derivative works. These actions are
prohibited by law if you do not accept this License. Therefore, by
modifying or distributing the Program (or any work based on the
Program), you indicate your acceptance of this License to do so, and
all its terms and conditions for copying, distributing or modifying
the Program or works based on it.
6. Each time you redistribute the Program (or any work based on the
Program), the recipient automatically receives a license from the
original licensor to copy, distribute or modify the Program subject to
these terms and conditions. You may not impose any further
restrictions on the recipients' exercise of the rights granted herein.
You are not responsible for enforcing compliance by third parties to
this License.
7. If, as a consequence of a court judgment or allegation of patent
infringement or for any other reason (not limited to patent issues),
conditions are imposed on you (whether by court order, agreement or
otherwise) that contradict the conditions of this License, they do not
excuse you from the conditions of this License. If you cannot
distribute so as to satisfy simultaneously your obligations under this
License and any other pertinent obligations, then as a consequence you
may not distribute the Program at all. For example, if a patent
license would not permit royalty-free redistribution of the Program by
all those who receive copies directly or indirectly through you, then
the only way you could satisfy both it and this License would be to
refrain entirely from distribution of the Program.
If any portion of this section is held invalid or unenforceable under
any particular circumstance, the balance of the section is intended to
apply and the section as a whole is intended to apply in other
circumstances.
It is not the purpose of this section to induce you to infringe any
patents or other property right claims or to contest validity of any
such claims; this section has the sole purpose of protecting the
integrity of the free software distribution system, which is
implemented by public license practices. Many people have made
generous contributions to the wide range of software distributed
through that system in reliance on consistent application of that
system; it is up to the author/donor to decide if he or she is willing
to distribute software through any other system and a licensee cannot
impose that choice.
This section is intended to make thoroughly clear what is believed to
be a consequence of the rest of this License.
8. If the distribution and/or use of the Program is restricted in
certain countries either by patents or by copyrighted interfaces, the
original copyright holder who places the Program under this License
may add an explicit geographical distribution limitation excluding
those countries, so that distribution is permitted only in or among
countries not thus excluded. In such case, this License incorporates
the limitation as if written in the body of this License.
9. The Free Software Foundation may publish revised and/or new versions
of the General Public License from time to time. Such new versions will
be similar in spirit to the present version, but may differ in detail to
address new problems or concerns.
Each version is given a distinguishing version number. If the Program
specifies a version number of this License which applies to it and "any
later version", you have the option of following the terms and conditions
either of that version or of any later version published by the Free
Software Foundation. If the Program does not specify a version number of
this License, you may choose any version ever published by the Free Software
Foundation.
10. If you wish to incorporate parts of the Program into other free
programs whose distribution conditions are different, write to the author
to ask for permission. For software which is copyrighted by the Free
Software Foundation, write to the Free Software Foundation; we sometimes
make exceptions for this. Our decision will be guided by the two goals
of preserving the free status of all derivatives of our free software and
of promoting the sharing and reuse of software generally.
NO WARRANTY
11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY
FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN
OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES
PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED
OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS
TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE
PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING,
REPAIR OR CORRECTION.
12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING
WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR
REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES,
INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING
OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED
TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY
YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER
PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE
POSSIBILITY OF SUCH DAMAGES.
END OF TERMS AND CONDITIONS
How to Apply These Terms to Your New Programs
If you develop a new program, and you want it to be of the greatest
possible use to the public, the best way to achieve this is to make it
free software which everyone can redistribute and change under these terms.
To do so, attach the following notices to the program. It is safest
to attach them to the start of each source file to most effectively
convey the exclusion of warranty; and each file should have at least
the "copyright" line and a pointer to where the full notice is found.
Copyright (C) 19yy
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Also add information on how to contact you by electronic and paper mail.
If the program is interactive, make it output a short notice like this
when it starts in an interactive mode:
Gnomovision version 69, Copyright (C) 19yy name of author
Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'.
This is free software, and you are welcome to redistribute it
under certain conditions; type `show c' for details.
The hypothetical commands `show w' and `show c' should show the appropriate
parts of the General Public License. Of course, the commands you use may
be called something other than `show w' and `show c'; they could even be
mouse-clicks or menu items--whatever suits your program.
You should also get your employer (if you work as a programmer) or your
school, if any, to sign a "copyright disclaimer" for the program, if
necessary. Here is a sample; alter the names:
Yoyodyne, Inc., hereby disclaims all copyright interest in the program
`Gnomovision' (which makes passes at compilers) written by James Hacker.
, 1 April 1989
Ty Coon, President of Vice
This General Public License does not permit incorporating your program into
proprietary programs. If your program is a subroutine library, you may
consider it more useful to permit linking proprietary applications with the
library. If this is what you want to do, use the GNU Library General
Public License instead of this License.
coinst-1.9.3/task.ml 0000644 0001750 0001750 00000014454 12657630652 013301 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
(*
TODO:
- error handling
- clear marshalled when large
- should keep track of the state of each process (idle or not)
==> deal with several function invocation (either failure or queueing?)
*)
let debug_task = Debug.make "tasks" "debug client/server communication" []
module Utimer = Util.Utimer
type stats =
{ mutable marshal_time : float;
mutable unmarshal_time : float }
let stats = { marshal_time = 0.; unmarshal_time = 0. }
let side = ref "SRV"
type indirect =
{ pipe_in : Unix.file_descr;
pipe_out : Unix.file_descr;
mem : Bytearray.t;
pid : int }
type 'a t = Local of 'a | Remote of indirect
type 'a future_state = Running of indirect | Finished of 'a
type 'a future = 'a future_state ref
let mem_size = 1 lsl 24
external processor_count : unit -> int = "task_processor_count"
let proc_count = ref (processor_count ())
let get_processor_count () = !proc_count
let set_processor_count n = proc_count := if n < 1 then 1 else n
let function_count = ref 0
let functions = Hashtbl.create 17
let send pipe i l =
let s = Bytes.of_string (Printf.sprintf "%d %d\n" i l) in
ignore (Unix.write pipe s 0 (Bytes.length s))
let receive pipe =
let s = Bytes.create 50 in
let len = Unix.read pipe s 0 (Bytes.length s) in
if len = 0 then exit 1;
Scanf.sscanf (Bytes.to_string s) "%d %d" (fun i l -> (i, l))
let read mem l =
let t = Utimer.start () in
let res = Bytearray.unmarshal mem 0 in (*XXX Clear the data if large*)
let dt = Utimer.stop t in
stats.unmarshal_time <- stats.unmarshal_time +. dt;
if debug_task () then Format.eprintf "Unmarshal: %s %.3f (%d)@." !side dt l;
res
let write mem v =
let t = Utimer.start () in
let res = Bytearray.marshal_to_buffer mem 0 v [] in
let dt = Utimer.stop t in
stats.marshal_time <- stats.marshal_time +. dt;
if debug_task () then Format.eprintf "Marshal: %s %.3f (%d)@." !side dt res;
res
let funct f =
let i = !function_count in
incr function_count;
Hashtbl.add functions i
(fun st mem l -> write mem (f (Obj.obj st) (read mem l)));
fun st x ->
match st with
Local st ->
ref (Finished (f st x))
| Remote st ->
send st.pipe_out i (write st.mem x);
ref (Running st)
let _ =
at_exit (fun _ ->
if debug_task () then
Format.eprintf "===>> marshal: %.3f / unmarshal: %.3f / user: %.3f@."
stats.marshal_time stats.unmarshal_time (Unix.times ()).Unix.tms_utime)
let spawn f =
if !proc_count <= 1 then
Local (f ())
else begin
let (cr, sw) = Unix.pipe () in
let (sr, cw) = Unix.pipe () in
let fd = Unix.openfile "/dev/zero" [Unix.O_RDWR] 0 in
let mem =
Bigarray.Array1.map_file
fd Bigarray.char Bigarray.c_layout true mem_size
in
Unix.close fd;
match Unix.fork () with
0 ->
Unix.close sr; Unix.close sw;
stats.marshal_time <- 0.; stats.unmarshal_time <- 0.;
side := "CLI";
let st = Obj.repr (f ()) in
let rec loop () =
let (i, l) = receive cr in
if i < 0 then
exit 0
else begin
let g = Hashtbl.find functions i in
let l = g st mem l in
send cw 0 l;
loop ()
end
in
loop ()
| pid ->
Unix.close cr; Unix.close cw;
Remote { pipe_in = sr; pipe_out = sw; mem = mem; pid = pid }
end
let kill st =
match st with
Local _ ->
()
| Remote st ->
send st.pipe_out (-1) 0;
Unix.close st.pipe_in; Unix.close st.pipe_out;
(*XXX Clear mmapped memory *)
ignore (Unix.waitpid [] st.pid)
let wait fut =
match !fut with
Finished v ->
v
| Running st ->
let t = Unix.gettimeofday () in
let (i, l) = receive st.pipe_in in
if debug_task () then
Format.eprintf "Wait: %.3f@." (Unix.gettimeofday () -. t);
let v = read st.mem l in
fut := Finished v;
v
type scheduler =
{ mutable fds : Unix.file_descr list;
conts : (Unix.file_descr, int -> unit) Hashtbl.t }
let scheduler () = { fds = []; conts = Hashtbl.create 11 }
let async sched fut f =
match !fut with
Finished v ->
f v
| Running st ->
let g l =
let v = read st.mem l in
fut := Finished v;
f v
in
sched.fds <- st.pipe_in :: sched.fds;
Hashtbl.add sched.conts st.pipe_in g
let run sched =
while sched.fds <> [] do
let t = Unix.gettimeofday () in
let (avail, _, _) = Unix.select sched.fds [] [] (-1.) in
if debug_task () then
Format.eprintf "Wait: %.3f@." (Unix.gettimeofday () -. t);
sched.fds <- List.filter (fun fd -> not (List.mem fd avail)) sched.fds;
List.iter
(fun fd ->
let cont = Hashtbl.find sched.conts fd in
Hashtbl.remove sched.conts fd;
let (i, l) = receive fd in
cont l)
avail
done
let map l pre post =
List.map (fun x -> post (wait x)) (List.map pre l)
let iter_ordered l pre post =
List.iter (fun x -> post (wait x)) (List.map pre l)
let iteri_ordered l pre post =
List.iter (fun (x, y) -> post x (wait y)) (List.map pre l)
let iter l pre post =
let s = scheduler () in
List.iter (fun v -> async s (pre v) post) l;
run s
let iteri l pre post =
let s = scheduler () in
List.iter (fun x -> let (y, t) = pre x in async s t (fun z -> post y z)) l;
run s
(*
#ifdef MADV_REMOVE
if (madvise(ptr, size, MADV_REMOVE) >= 0)
return;
#endif
#ifdef MADV_FREE
if (madvise(ptr, size, MADV_FREE) >= 0)
return;
#endif
#ifdef MADV_DONTNEED
madvise(ptr, size, MADV_DONTNEED);
#endif
}
*)
coinst-1.9.3/util.mli 0000644 0001750 0001750 00000005710 12657630652 013460 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
val set_msg : string -> unit
val hide_msg : unit -> unit
val show_msg : unit -> unit
val enable_messages : bool -> unit
val progress_bar : float -> string
val set_warning_location : string -> unit
val reset_warning_location : unit -> unit
val print_warning : string -> unit
val fail : string -> 'a
val title : string -> unit
module Timer : sig
type t
val start : unit -> t
val stop : t -> float
end
module Utimer : sig
type t
val start : unit -> t
val stop : t -> float
end
module IntSet : Set.S with type elt = int
module StringSet : Set.S with type elt = string
module ListTbl : sig
type ('a, 'b) t
val create : int -> ('a, 'b) t
val add : ('a, 'b) t -> 'a -> 'b -> unit
val find : ('a, 'b) t -> 'a -> 'b list
val mem : ('a, 'b) t -> 'a -> bool
val iter : ('a -> 'b list -> unit) -> ('a, 'b) t -> unit
val copy : ('a, 'b) t -> ('a, 'b) t
val remove : ('a, 'b) t -> 'a -> ('b -> bool) -> unit
end
module StringTbl : Hashtbl.S with type key = string
module IntTbl : Hashtbl.S with type key = int
val array_extend : 'a array -> int -> 'a -> 'a array
val bytes_extend : bytes -> int -> char -> bytes
val print_list :
(Format.formatter -> 'a -> unit) -> string ->
Format.formatter -> 'a list -> unit
val make_directories : string -> unit
(* Make sure that the directory containing the file given in argument
exists. *)
module BitVect : sig
type t
val make : int -> bool -> t
val test : t -> int -> bool
val set : t -> int -> unit
val clear : t -> int -> unit
val sub : t -> int -> int -> t
val copy : t -> t
val extend : t -> int -> bool -> t
val implies : t -> t -> bool
val lnot : t -> t
val (land) : t -> t -> t
val (lor) : t -> t -> t
end
val sort_and_uniq : ('a -> 'a -> int) -> 'a list -> 'a list
val compare_pair :
('a -> 'b -> int) -> ('c -> 'd -> int) -> 'a * 'c -> 'b * 'd -> int
val compare_list : ('a -> 'b -> int) -> 'a list -> 'b list -> int
val group : ('a -> 'a -> int) -> ('a * 'b) list -> ('a * 'b list) list
module Union_find : sig
type 'a t
val elt : 'a -> 'a t
val get : 'a t -> 'a
val merge : 'a t -> 'a t -> ('a -> 'a -> 'a) -> unit
end
val trim : string -> string
val date : unit -> string
coinst-1.9.3/CHANGES 0000644 0001750 0001750 00000003570 12657630652 012775 0 ustar mehdi mehdi ===== 1.9.3 (2016-02-13) =====
* Show single-package hints when asked to (using --all-hints)
* Fix buffering bug when printing hints
* Fix space/tab issue in Makefile
===== 1.9.2 (2016-01-24) =====
* Add build targets for bytecode binaries
* Do not generate easy hints with one single package in comigrate
* Do not try to hint removal of binary packages in comigrate since
britney doesn't know how to handle those. Only source removals
are supported for now
* Avoid crashing when reading a verisoned Provides field. Support
to fully handle versioned provides will come in a later version
* Build using -annot and -bin-annot by default
* Update list of architectures in comigrate: i386, amd64, arm64,
armel, armhf, mips, mipsel, powerpc, ppc64el and s390x
* Build with -safe-string
* Stop using Format.bprintf
* Compiles with OCaml 4.02.3
* Use http://http.debian.net/debian as a default mirror
* Coinst: Print package version when printing final report
===== 1.9.1 (2014-01-17) =====
* Comigrate and coinst-upgrades can now be used to compute a detailed
report of the package migration status (coinst.irill.org/report)
* Coinst now outputs all minimal non co-installable set of packages
* Added a JSON output to Coinst
* Adapted 'comigrate --update' to repository changes
* Compiles with OCaml 4.01
* Many other small bugs fixed
===== 1.9 (2013-10-21) =====
* Addition of two new tools: coinst-upgrades and comigrate
* Improvements to coinst:
- Automatically calls gzip or bzip2 to decompress files, when needed
- Several files can now be provided on the command line
- File digest fields in hdlist files sometimes contains meaningless
data beside the MD5 digest; this could result in spurious conflicts,
and this data is now properly ignored.
===== 1.01 (2011-09-19) =====
* Fixed '-explain' option
* Fixed to work with Mandriva 2011.0
===== 1.0 (2011-09-02) =====
Initial release
coinst-1.9.3/rpm_lib.mli 0000644 0001750 0001750 00000001502 12657630652 014122 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
include Api.S
coinst-1.9.3/Proofs/ 0000755 0001750 0001750 00000000000 12657630652 013245 5 ustar mehdi mehdi coinst-1.9.3/Proofs/Lattice.v 0000644 0001750 0001750 00000021477 12657630652 015034 0 ustar mehdi mehdi
Set Implicit Arguments.
Unset Strict Implicit.
Require Export Po.
(****)
Record least_upper_bound (A : po) : Type :=
{ lub_def :> (A -> Prop) -> A;
lub_upper_bound : forall P : A -> Prop, is_upper_bound P (lub_def P);
lub_least :
forall (P : A -> Prop) (x : A),
is_upper_bound P x -> sub (lub_def P) x }.
Record lattice : Type :=
{ l_carrier :> po;
sup : least_upper_bound l_carrier;
inf : least_upper_bound (opposite_po l_carrier) }.
Definition sup_upper_bound (A : lattice) := lub_upper_bound (sup A).
Definition sup_least (A : lattice) := lub_least (sup A).
Definition inf_lower_bound (A : lattice) := lub_upper_bound (inf A).
Definition inf_greatest (A : lattice) := lub_least (inf A).
Implicit Arguments sup [l].
Implicit Arguments inf [l].
Definition opp_opp (A : po) (lub : least_upper_bound A) :=
Build_least_upper_bound (A:=opposite_po (opposite_po A))
(lub_upper_bound lub) (lub_least lub).
Definition opposite_lattice (A : lattice) :=
Build_lattice (inf (l:=A)) (opp_opp (sup (l:=A))).
(****)
Definition bottom (A : lattice) := sup (fun x : A => False).
Lemma bottom_prop : forall (A : lattice) (x : A), sub (bottom A) x.
intros A x; unfold bottom in |- *; apply sup_least; red in |- *;
contradiction.
Qed.
Definition top (A : lattice) : A := bottom (opposite_lattice A).
Lemma top_prop : forall (A : lattice) (x : A), sub x (top A).
exact (fun A => bottom_prop (A:=opposite_lattice A)).
Qed.
Section binary_sup.
Variable A : lattice.
Definition sup2 (x y : A) := sup (fun z => z = x \/ z = y).
Lemma sup2_upper_bound_1 : forall x y : A, sub x (sup2 x y).
intros x y; unfold sup2 in |- *; apply sup_upper_bound; auto.
Qed.
Lemma sup2_upper_bound_2 : forall x y : A, sub y (sup2 x y).
intros x y; unfold sup2 in |- *; apply sup_upper_bound; auto.
Qed.
Lemma sup2_least : forall x y z : A, sub x z -> sub y z -> sub (sup2 x y) z.
intros x y z H1 H2; unfold sup2 in |- *; apply sup_least; intros t [E| E];
rewrite E; clear t E; trivial.
Qed.
End binary_sup.
Section binary_inf.
Variable A : lattice.
Definition inf2 (x y : A) : A := sup2 (A:=opposite_lattice A) x y.
Lemma inf2_lower_bound_1 : forall x y : A, sub (inf2 x y) x.
exact (sup2_upper_bound_1 (A:=opposite_lattice A)).
Qed.
Lemma inf2_lower_bound_2 : forall x y : A, sub (inf2 x y) y.
exact (sup2_upper_bound_2 (A:=opposite_lattice A)).
Qed.
Lemma inf2_greatest :
forall x y z : A, sub z x -> sub z y -> sub z (inf2 x y).
exact (sup2_least (A:=opposite_lattice A)).
Qed.
End binary_inf.
(****)
Definition inf_of_sup (A : po) (sup : (A -> Prop) -> A)
(P : A -> Prop) := sup (fun x => forall y : A, P y -> sub x y).
Definition inf_of_sup_inf :
forall A : po,
least_upper_bound A -> least_upper_bound (opposite_po A).
intros A H; case H; clear H; intros sp prop1 prop2;
apply
Build_least_upper_bound
with (A := opposite_po A) (lub_def := inf_of_sup sp);
[ intros P y H; simpl in |- *; unfold inf_of_sup in |- *; apply prop2;
red in |- *; auto
| simpl in |- *; unfold inf_of_sup in |- *; intros P x H; apply prop1; auto ].
Defined.
Definition Build_lattice_2 (A : po) (sup : least_upper_bound A) :=
Build_lattice sup (inf_of_sup_inf sup).
(****)
Definition lfp (A : lattice) (f : monotone_fun A A) : A :=
inf (fun x => sub (f x) x).
Theorem induction :
forall (A : lattice) (f : monotone_fun A A) (x : A),
sub (f x) x -> sub (lfp f) x.
intros A f x H; unfold lfp in |- *; apply inf_lower_bound; trivial.
Qed.
Theorem lfp_fold :
forall (A : lattice) (f : monotone_fun A A), sub (f (lfp f)) (lfp f).
intros A f; unfold lfp in |- *; apply inf_greatest; simpl in |- *; intros x H;
simpl in |- *; apply sub_transitive with (y := f x);
[ apply monotone; apply inf_lower_bound; trivial | trivial ].
Qed.
Theorem lfp_unfold :
forall (A : lattice) (f : monotone_fun A A), sub (lfp f) (f (lfp f)).
intros A f; apply induction; apply monotone; apply lfp_fold.
Qed.
Theorem strong_induction :
forall (A : lattice) (f : monotone_fun A A) (x : A),
sub (f (inf2 x (lfp f))) x -> sub (lfp f) x.
intros A f x H; assert (H' : sub (lfp f) (inf2 x (lfp f)));
[ apply induction; apply inf2_greatest;
[ trivial
| apply sub_transitive with (2 := lfp_fold f); apply monotone;
apply inf2_lower_bound_2 ]
| apply sub_transitive with (1 := H'); apply inf2_lower_bound_1 ].
Qed.
(****)
Definition gfp (A : lattice) (f : monotone_fun A A) : A :=
lfp (A:=opposite_lattice A) (opposite_monotone f).
Theorem coinduction :
forall (A : lattice) (f : monotone_fun A A) (x : A),
sub x (f x) -> sub x (gfp f).
intros A f;
exact (induction (A:=opposite_lattice A) (f:=opposite_monotone f)).
Qed.
Theorem gfp_fold :
forall (A : lattice) (f : monotone_fun A A), sub (f (gfp f)) (gfp f).
intros A f; exact (lfp_unfold (A:=opposite_lattice A) (opposite_monotone f)).
Qed.
Theorem gfp_unfold :
forall (A : lattice) (f : monotone_fun A A), sub (gfp f) (f (gfp f)).
intros A f; exact (lfp_fold (A:=opposite_lattice A) (opposite_monotone f)).
Qed.
Theorem strong_coinduction :
forall (A : lattice) (f : monotone_fun A A) (x : A),
sub x (f (sup2 x (gfp f))) -> sub x (gfp f).
intros A f;
exact (strong_induction (A:=opposite_lattice A) (f:=opposite_monotone f)).
Qed.
(****)
Definition sup_product (A B : lattice) (P : product_po A B -> Prop) :=
pairT (sup (fun x => exists y : _, P (pairT x y)))
(sup (fun y => exists x : _, P (pairT x y))).
Definition sup_product_prop :
forall A B : lattice, least_upper_bound (product_po A B).
intros A B;
apply
Build_least_upper_bound
with (A := product_po A B) (lub_def := sup_product (A:=A) (B:=B));
[ red in |- *; simpl in |- *; intros P y H; split;
[ simpl in |- *; apply sup_upper_bound; exists (sndT y); induction y;
trivial
| simpl in |- *; apply sup_upper_bound; exists (fstT y); induction y;
trivial ]
| simpl in |- *; intros P x H; split;
[ simpl in |- *; apply sup_least; intros y (y', H');
exact (proj1 (H _ H'))
| simpl in |- *; apply sup_least; intros y (y', H');
exact (proj2 (H _ H')) ] ].
Defined.
Definition prod_opp (A B : po)
(lub : least_upper_bound
(product_po (opposite_po A) (opposite_po B))) :=
Build_least_upper_bound (A:=opposite_po (product_po A B))
(lub_upper_bound lub) (lub_least lub).
Definition product_lattice (A B : lattice) :=
Build_lattice (sup_product_prop A B)
(prod_opp (sup_product_prop (opposite_lattice A) (opposite_lattice B))).
Lemma fstT_monotone :
forall A B : lattice,
is_monotone (A:=product_lattice A B) (B:=A) (fstT (A:=A) (B:=B)).
intros A B x y (H, H'); trivial.
Qed.
Lemma sndT_monotone :
forall A B : lattice,
is_monotone (A:=product_lattice A B) (B:=B) (sndT (A:=A) (B:=B)).
intros A1 B1 x y (H, H'); trivial.
Qed.
(****)
Definition sup_pwe (A : Type) (B : lattice) (P : pwe_po A B -> Prop) x :=
sup (fun y => exists f : _, P f /\ y = f x).
Definition sup_pwe_prop :
forall (A : Type) (B : lattice), least_upper_bound (pwe_po A B).
intros A B;
apply
Build_least_upper_bound
with (A := pwe_po A B) (lub_def := sup_pwe (A:=A) (B:=B));
[ intros P f H x; unfold sup_pwe in |- *; apply sup_upper_bound; exists f;
split; trivial
| intros P f H x; unfold sup_pwe in |- *; apply sup_least;
intros y (g, (H', H'')); rewrite H''; clear y H'';
apply (H _ H') ].
Defined.
Definition pwe_opp (A : Type) (B : po)
(lub : least_upper_bound (pwe_po A (opposite_po B))) :
least_upper_bound (opposite_po (pwe_po A B)) :=
match lub with
| Build_least_upper_bound sp prop1 prop2 =>
Build_least_upper_bound (A:=opposite_po (pwe_po A B)) prop1 prop2
end.
Definition pwe_lattice (A : Type) (B : lattice) :=
Build_lattice (sup_pwe_prop A B)
(pwe_opp (sup_pwe_prop A (opposite_lattice B))).
Lemma pwe_bottom_prop :
forall (A : Type) (B : lattice) (x : A),
equiv (bottom (pwe_lattice A B) x) (bottom B).
intros A B x; apply equiv_intro;
[ exact (bottom_prop (A:=pwe_lattice A B) (fun x => bottom B) x)
| apply bottom_prop ].
Qed.
Lemma pwe_top_prop :
forall (A : Type) (B : lattice) (x : A),
equiv (top (pwe_lattice A B) x) (top B).
intros A B x; apply equiv_intro;
[ apply top_prop
| exact (top_prop (A:=pwe_lattice A B) (fun x => top B) x) ].
Qed.
(****)
Definition image (A B : Type) (f : A -> B) (P : A -> Prop) y :=
exists x : A, P x /\ y = f x.
Lemma image_prop_1 :
forall (A B : Type) (f : A -> B) (P : A -> Prop) x, P x -> image f P (f x).
intros A B f P x H1; exists x; split; trivial.
Qed.
Lemma monotony_and_sup :
forall (A B : lattice) (f : monotone_fun A B) (P : A -> Prop),
sub (sup (image f P)) (f (sup P)).
intros A B f P; apply sup_least; intros y (x, (H1, E)); subst;
apply monotone; apply sup_upper_bound; trivial.
Qed.
Lemma monotony_and_inf :
forall (A B : lattice) (f : monotone_fun A B) (P : A -> Prop),
sub (f (inf P)) (inf (image f P)).
intros A B f P; apply inf_greatest; intros y (x, (H1, E)); subst;
change (sub (f (inf P)) (f x)); apply monotone;
apply inf_lower_bound; trivial.
Qed.
coinst-1.9.3/Proofs/Po.v 0000644 0001750 0001750 00000012704 12657630652 014016 0 ustar mehdi mehdi
Set Implicit Arguments.
Unset Strict Implicit.
(****)
Definition is_transitive (A : Type) (r : A -> A -> Prop) :=
forall x y z : A, r x y -> r y z -> r x z.
Definition is_reflexive (A : Type) (r : A -> A -> Prop) :=
forall x : A, r x x.
Definition is_symmetric (A : Type) (r : A -> A -> Prop) :=
forall x y : A, r x y -> r y x.
(****)
Record po : Type :=
{ po_carrier :> Type;
sub : po_carrier -> po_carrier -> Prop;
sub_transitive : is_transitive sub;
sub_reflexive : is_reflexive sub }.
Section equivalence.
Variable A : po.
Definition equiv (x y : A) := sub x y /\ sub y x.
(* Antisymmetry *)
Lemma equiv_intro : forall x y : A, sub x y -> sub y x -> equiv x y.
intros; split; trivial.
Qed.
Lemma equiv_elim_1 : forall x y : A, equiv x y -> sub x y.
intros x y (H, H'); trivial.
Qed.
Lemma equiv_elim_2 : forall x y : A, equiv x y -> sub y x.
intros x y (H, H'); trivial.
Qed.
Lemma equiv_transitive : is_transitive equiv.
intros x y z (H1, H2) (H3, H4); split;
[ exact (sub_transitive H1 H3) | exact (sub_transitive H4 H2) ].
Qed.
Lemma equiv_reflexive : is_reflexive equiv.
intros x; split; apply sub_reflexive.
Qed.
Lemma equiv_symmetric : is_symmetric equiv.
intros x y (H1, H2); split; trivial.
Qed.
End equivalence.
Opaque equiv.
(****)
Lemma opposite_transitive :
forall (A : Type) (r : A -> A -> Prop),
is_transitive r -> is_transitive (fun x y => r y x).
unfold is_transitive in |- *; eauto.
Qed.
Lemma opposite_reflexive :
forall (A : Type) (r : A -> A -> Prop),
is_reflexive r -> is_reflexive (fun x y => r y x).
trivial.
Qed.
Section opposite.
Variable A : po.
Definition opposite_po :=
Build_po (opposite_transitive (sub_transitive (p:=A)))
(opposite_reflexive (sub_reflexive (p:=A))).
Lemma equiv_opp_intro :
forall x y : A, equiv x y -> equiv (A:=opposite_po) x y.
intros x y H; apply equiv_intro;
[ apply equiv_elim_2; trivial | apply equiv_elim_1; trivial ].
Qed.
Lemma equiv_opp_elim :
forall x y : A, equiv (A:=opposite_po) x y -> equiv x y.
intros x y H; apply equiv_intro;
[ apply equiv_elim_2; trivial | apply equiv_elim_1; trivial ].
Qed.
End opposite.
(****)
Definition is_monotone (A B : po) (f : A -> B) :=
forall x y : A, sub x y -> sub (f x) (f y).
Record monotone_fun (A B : po) : Type :=
{ m_fun :> A -> B;
monotone : is_monotone m_fun }.
Definition monotone_sub_def (A B : po) (f g : monotone_fun A B) :=
forall x : A, sub (f x) (g x).
Lemma monotone_sub_refl :
forall A B : po, is_reflexive (monotone_sub_def (A:=A) (B:=B)).
intros A B f x; apply sub_reflexive.
Qed.
Lemma monotone_sub_trans :
forall A B : po, is_transitive (monotone_sub_def (A:=A) (B:=B)).
intros A B f g h H1 H2 x; exact (sub_transitive (H1 x) (H2 x)).
Qed.
Definition monotone_fun_po (A B : po) :=
Build_po (monotone_sub_trans (A:=A) (B:=B))
(monotone_sub_refl (A:=A) (B:=B)).
Lemma monotone_eq :
forall (A B : po) (f : monotone_fun A B) (x y : A),
equiv x y -> equiv (f x) (f y).
intros A B f x y H; apply equiv_intro;
[ apply monotone; exact (equiv_elim_1 H)
| apply monotone; exact (equiv_elim_2 H) ].
Qed.
Let compose_monotone :
forall (A B C : po) (f : monotone_fun A B)
(g : monotone_fun B C), is_monotone (fun x => g (f x)).
unfold is_monotone in |- *; intros; apply monotone; apply monotone; trivial.
Qed.
Definition compose (A B C : po) (f : monotone_fun A B)
(g : monotone_fun B C) := Build_monotone_fun (compose_monotone f g).
Let opp_monotone :
forall (A B : po) (f : A -> B),
is_monotone f -> is_monotone (A:=opposite_po A) (B:=opposite_po B) f.
unfold is_monotone in |- *; simpl in |- *; eauto.
Qed.
Definition opposite_monotone (A B : po) (f : monotone_fun A B) :=
Build_monotone_fun (opp_monotone (monotone f)).
Lemma constant_implies_monotone :
forall (A B : po) (y : B), is_monotone (fun x : A => y).
intros A B y x x' H; apply sub_reflexive.
Qed.
Definition constant_monotone (A B : po) (y : B) :=
Build_monotone_fun (@constant_implies_monotone A B y).
(****)
Definition is_fixpoint (A : po) (f : A -> A) (a : A) := equiv a (f a).
Definition is_upper_bound (A : po) (P : A -> Prop) (x : A) :=
forall y : A, P y -> sub y x.
Definition postfixpoint (A : po) (f : A -> A) (x : A) := sub x (f x).
Definition prefixpoint (A : po) (f : A -> A) (x : A) := sub (f x) x.
(****)
Definition sub_product (A B : po) (x y : prodT A B) :=
sub (fstT x) (fstT y) /\ sub (sndT x) (sndT y).
Lemma sub_product_transitive :
forall A B : po, is_transitive (sub_product (A:=A) (B:=B)).
intros A B x y z (H1, H1') (H2, H2'); split;
[ exact (sub_transitive H1 H2) | exact (sub_transitive H1' H2') ].
Qed.
Lemma sub_product_reflexive :
forall A B : po, is_reflexive (sub_product (A:=A) (B:=B)).
intros A B x; split; apply sub_reflexive.
Qed.
Definition product_po (A B : po) :=
Build_po (sub_product_transitive (A:=A) (B:=B))
(sub_product_reflexive (A:=A) (B:=B)).
(****)
Definition pwe_lift (A : Type) (B : po) (r : B -> B -> Prop) (f g : A -> B) :=
forall x : A, r (f x) (g x).
Definition sub_pwe (A : Type) (B : po) (f g : A -> B) :=
forall x : A, sub (f x) (g x).
Lemma sub_pwe_transitive :
forall (A : Type) (B : po), is_transitive (sub_pwe (A:=A) (B:=B)).
intros A B f g h H1 H2 x; apply sub_transitive with (1 := H1 x); apply H2.
Qed.
Lemma sub_pwe_reflexive :
forall (A : Type) (B : po), is_reflexive (sub_pwe (A:=A) (B:=B)).
intros A B f x; apply sub_reflexive.
Qed.
Definition pwe_po (A : Type) (B : po) :=
Build_po (sub_pwe_transitive (A:=A) (B:=B))
(sub_pwe_reflexive (A:=A) (B:=B)).
coinst-1.9.3/Proofs/Makefile 0000644 0001750 0001750 00000000516 12657630652 014707 0 ustar mehdi mehdi
OBJS=Po.vo Lattice.vo Relation.vo coinst.vo
all: $(OBJS)
########################################################################
# Coq proofs
COQC=coqc
%.vo : %.v
$(COQC) $<
######################################################################
# Dependencies
COQDEP=coqdep
depend:
$(COQDEP) *.v > .depend
include .depend
coinst-1.9.3/Proofs/Relation.v 0000644 0001750 0001750 00000012157 12657630652 015217 0 ustar mehdi mehdi
(**** Lattice of relations, of sets ****)
Set Implicit Arguments.
Unset Strict Implicit.
Require Import Lattice.
(****)
Inductive tuple : Type :=
| t_empty : tuple
| t_cons : Type -> tuple -> tuple.
Fixpoint tuple_elem (t : tuple) : Type :=
match t with
| t_empty => True
| t_cons t r => prodT t (tuple_elem r)
end.
Fixpoint nary_fun (A : Type) (t : tuple) {struct t} : Type :=
match t with
| t_empty => A
| t_cons t r => t -> nary_fun A r
end.
Fixpoint curry (A : Type) (t : tuple) {struct t} :
nary_fun A t -> tuple_elem t -> A :=
match t return (nary_fun A t -> tuple_elem t -> A) with
| t_empty => fun f _ => f
| t_cons t rem => fun f p => let (x, p') := p in curry (f x) p'
end.
Definition uncurry (A : Type) (t : tuple) :
(tuple_elem t -> A) -> nary_fun A t.
induction t;
[ intros f; exact (f I)
| intros f x; apply IHt; intro p; apply f; split; [ exact x | exact p ] ].
Defined.
Definition rel := nary_fun Prop.
Fixpoint rel_sub (t : tuple) : rel t -> rel t -> Prop :=
match t return (rel t -> rel t -> Prop) with
| t_empty => fun r r' => r -> r'
| t_cons t rem => fun r r' => forall x : t, rel_sub (r x) (r' x)
end.
Lemma rel_sub_transitive : forall t : tuple, is_transitive (rel_sub (t:=t)).
red in |- *; induction t; simpl in |- *; eauto.
Qed.
Lemma rel_sub_reflexive : forall t : tuple, is_reflexive (rel_sub (t:=t)).
red in |- *; induction t; simpl in |- *; auto.
Qed.
Definition rel_po (t : tuple) :=
Build_po (rel_sub_transitive (t:=t)) (rel_sub_reflexive (t:=t)).
Definition rel_union (t : tuple) (s : rel_po t -> Prop) :
rel_po t := uncurry (fun p => exists r : _, s r /\ curry r p).
Definition rel_inter (t : tuple) (s : rel_po t -> Prop) :
rel_po t := uncurry (fun p => forall r : rel_po t, s r -> curry r p).
Lemma curry_monotone :
forall t : tuple,
@is_monotone (rel_po t) (rel_po (t_cons (tuple_elem t) t_empty))
(@curry Prop t).
red in |- *; induction t; simpl in |- *;
[ trivial | intros r r' H (x, p); apply IHt; exact (H x) ].
Qed.
Lemma uncurry_monotone :
forall t : tuple,
@is_monotone (rel_po (t_cons (tuple_elem t) t_empty)) (rel_po t)
(@uncurry Prop t).
red in |- *; induction t; simpl in |- *;
[ auto | intros r r' H x; apply IHt; intro p; apply H ].
Qed.
Lemma uncurry_curry_prop :
forall (t : tuple) (r : rel_po t), equiv r (uncurry (curry r)).
intros t r; apply equiv_intro;
[ induction t;
[ simpl in |- *; trivial
| intro x; apply rel_sub_transitive with (1 := IHt (r x)); simpl in |- *;
apply uncurry_monotone; simpl in |- *; trivial ]
| induction t;
[ simpl in |- *; trivial
| intro x; apply rel_sub_transitive with (2 := IHt (r x)); simpl in |- *;
apply uncurry_monotone; simpl in |- *; trivial ] ].
Qed.
Lemma rel_union_sup : forall t : tuple, least_upper_bound (rel_po t).
intro t;
apply Build_least_upper_bound
with (A := rel_po t) (lub_def := rel_union (t:=t));
[ intros P r H; simpl in |- *;
apply rel_sub_transitive with (1 := proj1 (uncurry_curry_prop r));
unfold rel_union in |- *; apply uncurry_monotone;
intros x H'; exists r; split; trivial
| intros P r H;
apply
(sub_transitive (p:=rel_po t)) with (2 := proj2 (uncurry_curry_prop r));
unfold rel_union in |- *; apply uncurry_monotone;
intros x (r', (H1, H2)); generalize x H2; clear x H2;
apply curry_monotone; exact (H _ H1) ].
Defined.
Definition relation (t : tuple) := Build_lattice_2 (rel_union_sup t).
(****)
Definition set (A : Type) := relation (t_cons A t_empty).
Definition singleton (A : Type) (x : A) : set A := fun y => y = x.
Definition inter (A : Type) (t t' : set A) : set A := fun v => t v /\ t' v.
Lemma inter_lower_bound_1 :
forall (A : Type) (t t' : set A), sub (inter t t') t.
intros A t t' x (H1, H2); trivial.
Qed.
Lemma inter_lower_bound_2 :
forall (A : Type) (t t' : set A), sub (inter t t') t'.
intros A t t' x (H1, H2); trivial.
Qed.
Lemma inter_greatest :
forall (A : Type) (t t' t'': set A),
sub t'' t -> sub t'' t' -> sub t'' (inter t t').
intros A t t' t'' H1 H2 x H3; split;
[ apply H1; trivial | apply H2; trivial ].
Qed.
Lemma sub_inter_split :
forall A (t t' u u' : set A),
sub t t' -> sub u u' -> sub (inter t u) (inter t' u').
intros A t t' u u' H1 H2; apply inter_greatest;
[ apply (@sub_transitive (set A)) with (2 := H1);apply inter_lower_bound_1
| apply (@sub_transitive (set A)) with (2 := H2);apply inter_lower_bound_2 ].
Qed.
Lemma monotony_and_inter :
forall A B (f : monotone_fun (set A) (set B)) x x',
sub (f (inter x x')) (inter (f x) (f x')).
intros A B f x x'; apply inter_greatest; apply monotone;
[ apply inter_lower_bound_1
| apply inter_lower_bound_2 ].
Qed.
Definition union (A : Type) (t t' : set A) : set A := fun v => t v \/ t' v.
Lemma union_upper_bound_1 :
forall (A : Type) (t t' : set A), sub t (union t t').
intros A t t' x H1; left; trivial.
Qed.
Lemma union_upper_bound_2 :
forall (A : Type) (t t' : set A), sub t' (union t t').
intros A t t' x H1; right; trivial.
Qed.
Lemma union_least :
forall (A : Type) (t t' t'': set A),
sub t t'' -> sub t' t'' -> sub (union t t') t''.
intros A t t' t'' H1 H2 x [H3 | H3];
[ apply H1; trivial | apply H2; trivial ].
Qed.
coinst-1.9.3/Proofs/.depend 0000644 0001750 0001750 00000000143 12657630652 014503 0 ustar mehdi mehdi formel.vo: formel.v
Lattice.vo: Lattice.v ./Po.vo
Po.vo: Po.v
Relation.vo: Relation.v ./Lattice.vo
coinst-1.9.3/Proofs/coinst.v 0000644 0001750 0001750 00000240437 12657630652 014745 0 ustar mehdi mehdi
Set Implicit Arguments.
Unset Strict Implicit.
Require Import Po.
Require Import Relation.
Require Import Lattice.
Require Import List.
Require Import Classical.
Axiom choice :
forall (A : Type) (B : A -> Type) (R : forall x : A, B x -> Prop),
(forall x:A, exists y : B x, R x y) ->
exists f : forall x : A, B x, (forall x:A, R x (f x)).
(****)
Definition is_injective A B (r : A -> B -> Prop) :=
forall x y z, r x y -> r x z -> y = z.
Definition reverse A B (r : A -> B -> Prop) x y := r y x.
Definition minimal (A : po) (P : A -> Prop) (x : A) :=
P x /\ forall y, P y -> sub y x -> sub x y.
Definition least (A : po) (P : A -> Prop) (x : A) :=
P x /\ forall y, P y -> sub x y.
Lemma least_implies_minimal :
forall (A : po) (P : A -> Prop) x, least P x -> minimal P x.
intros A P X (H1, H2); split; auto.
Qed.
Definition maximal (A : po) (P : A -> Prop) (x : A) :=
P x /\ forall y, P y -> sub x y -> sub y x.
(* f(s) = {f(q) | q in s} *)
Definition img (A B : Type) (f : A -> B) (s : set A) : set B :=
fun p => exists q, s q /\ p = f q.
(*
{p | forall q, p = f(q) => q in s},
complement of the image of the complement
*)
Definition complimg (A B : Type) (f : A -> B) (s : set A) : set B :=
fun p => forall q, p = f q -> s q.
(* f^-1(s) = {p | exists q in s, q = f(p)} *)
Definition preimg (A B : Type) (f : A -> B) (s : set B) : set A :=
fun p => exists q, s q /\ q = f p.
(*************************************************************)
(*
We first define repositories (Section 2.1)
We assume given a fixed set of packages.
*)
Variable package : Set.
(*
The two axioms corresponds to the assumption that the set of
packages is finite.
*)
Axiom package_set_maximality :
forall (P : set package -> Prop) s,
P s -> exists s', maximal P s' /\ sub s s'.
Axiom package_set_minimality :
forall (P : set package -> Prop) s,
P s -> exists s', minimal P s' /\ sub s' s.
(*
The dependency function and the conflict relation.
We do not assume here that the conflict relation is symmetric and
irreflexive. Instead, we systematically use the [in_conflict]
function define below to symmetrise the relation, and we explicitly
assume that the relation is irreflexive ([no_self_conflict]
predicate) when needed.
*)
Definition confl_rel := package -> set package.
Definition dep_fun := package -> set (set package).
(*
A repository is composed of the set of packages defined above
together with the dependency and conflict relations below.
*)
Record constraints : Type :=
{ depends : dep_fun;
conflicts : confl_rel }.
(*
We define healthy installations (Section 2.1), and then installable
packages and co-installable set of packages (Section 2.2).
*)
Section Installation.
Variable c : constraints.
Definition in_conflict p q := conflicts c p q \/ conflicts c q p.
Definition has_conflict p := exists q, in_conflict p q.
Definition no_self_conflict c := forall p, ~ conflicts c p p.
Definition dep_satisfied (i d : set package) := exists p, i p /\ d p.
Record healthy (i : set package) : Prop :=
{ abundance : forall p d, i p -> depends c p d -> dep_satisfied i d;
peace : forall p p', i p -> i p' -> conflicts c p p' -> False }.
Definition installable p := exists i, healthy i /\ i p.
Definition co_installable s := exists i, healthy i /\ sub s i.
End Installation.
(*************************************************************)
(*
We define a preorder on repositories (Section 4)
*)
Definition dsub (ds ds' : dep_fun) :=
forall p, forall d, ds p d -> exists d', sub d' d /\ ds' p d'.
Remark dsub_trans : is_transitive dsub.
intros ds ds' ds'' H1 H2 p s H3;
generalize (H1 _ _ H3); intros (s', (H4, H5));
generalize (H2 _ _ H5); intros (s'', (H6, H7));
exists s''; split; trivial;
exact (sub_transitive H6 H4).
Qed.
Remark dsub_refl : is_reflexive dsub.
intros ds p s H1; exists s; split; trivial; apply sub_reflexive.
Qed.
Definition dep_fun_po := Build_po dsub_trans dsub_refl.
Canonical Structure dep_fun_po.
Definition csub c c' :=
sub (depends c) (depends c')
/\
(forall p, sub (conflicts c p) (conflicts c' p)).
Remark csub_trans : is_transitive csub.
intros c c' c'' (H1, H2) (H3, H4); split;
[ exact (sub_transitive H1 H3)
| intro p; exact (sub_transitive (H2 p) (H4 p)) ].
Qed.
Remark csub_refl : is_reflexive csub.
intros c; split; [ apply sub_reflexive | intro p; apply sub_reflexive ].
Qed.
Definition constraints_po := Build_po csub_trans csub_refl.
Canonical Structure constraints_po.
(* The preorder is coarser than point-wise inclusion (Remark 23). *)
Remark dsub_incl :
forall ds ds' : dep_fun, (forall p, sub (ds p) (ds' p)) -> sub ds ds'.
intros ds ds' H1 p d H2; exists d; split;
[ apply sub_reflexive
| apply H1; trivial ].
Qed.
(* Theorem 2 and an immediate corollary (remark 22). *)
Theorem constraint_weakening :
forall c c' i, sub c c' -> healthy c' i -> healthy c i.
intros c c' i (H1, H2) (H3, H4); split; trivial;
[ intros p d H5 H6; generalize (H1 _ _ H6); intros (d', (H7, H8));
generalize (H3 _ _ H5 H8); intros (q, (G1, G2)); exists q;
split; trivial; apply H7; trivial
| intros p p' H5 H6 H7; generalize (H2 _ _ H7); eauto ].
Qed.
Remark constraint_weakening_and_co_installability :
forall c c' s, sub c c' -> co_installable c' s -> co_installable c s.
intros c c' s H1 (i, (H2, H3)); exists i; split; trivial;
exact (constraint_weakening H1 H2); trivial.
Qed.
(*************************************************************)
(* We now define the flattening operation (Section 5). *)
Section Flattening.
Variable c : constraints.
(*
These three definitions implement rules Refl and Trans.
We first define derivation trees build from these rules.
As we must be able to reason by induction on these derivations,
they are of sort [Type].
Then, given such a derivation, we can read a dependency.
Finally, the resulting dependency function is build by collecting
all these dependencies.
*)
Inductive below_conflicts p : Type :=
immediate_conflict :
has_conflict c p -> below_conflicts p
| higher_conflicts :
forall d,
depends c p d -> (forall q, d q -> below_conflicts q) ->
below_conflicts p.
Fixpoint flattened_dep p (H : below_conflicts p) : set package :=
fun q =>
match H with
immediate_conflict _ =>
q = p
| higher_conflicts d H1 H2 =>
exists p, exists H3 : d p, flattened_dep (H2 _ H3) q
end.
Definition flattened_dependencies : package -> set (set package) :=
fun p => fun s => exists H : below_conflicts p, s = flattened_dep H.
(*
This is the repository after flattening.
Only the dependency function is changed.
*)
Definition flattened :=
Build_constraints flattened_dependencies (conflicts c).
End Flattening.
(*************************************************************)
(* Strongly flat repositories (Section 6). *)
(* Definition of \Delta_C. *)
Definition confl_deps c : dep_fun :=
fun p d => exists p', in_conflict c p p' /\ d = singleton p.
(* Definition of the dependency function composition D;D. *)
Definition dep_fun_compose (ds ds' : dep_fun) : dep_fun :=
fun p d' =>
exists d,
ds p d /\
exists f, (forall q (H : d q), ds' q (f q H)) /\
d' = (fun p => exists q, exists H : d q, f q H p).
(* Definition of strongly flat repositories *)
Record strongly_flat c :=
{ sf_refl : sub (confl_deps c) (depends c);
sf_trans : sub (dep_fun_compose (depends c) (depends c)) (depends c) }.
(*
This lemma shows that we can normalize the dependencies (see
Section 4) without breaking the property.
*)
Lemma strongly_flat_preserved :
forall c c', equiv c c' -> strongly_flat c -> strongly_flat c'.
intros c c' ((H1, H2), (H3, H4)) (H5, H6); split;
[ refine (sub_transitive _ (sub_transitive H5 H1));
intros p d H7; exists d; generalize H7; clear H7;
intros (q ,(H7, H8));
split; try apply sub_reflexive;
exists q; split; trivial;
case H7; intro H9; [ left | right]; apply H4; trivial
| intros p d (d', (H7, (f, (H8, E)))); subst d;
generalize (H3 _ _ H7); intros (d, (G1, G2));
generalize (choice (fun qH => H3 _ _ (H8 (proj1_sig qH) (proj2_sig qH))));
intros (f', G3);
pose
(d'' := fun p' => exists q, exists H : d q, f' (exist d' q (G1 q H)) p');
case (H6 p d'');
[ exists d; split; trivial;
exists (fun q H => f' (exist _ q (G1 _ H))); split;
[ intros q G4;
generalize (G3 (exist _ q (G1 _ G4))); intros (G5, G6); trivial
| trivial ]
| subst d''; intros d'' (G4, G5);
generalize (H1 _ _ G5); intros (d''', (G6, G7));
exists d'''; split; trivial;
refine (sub_transitive G6 _);
refine (sub_transitive G4 _);
intros p' (q, (G8, G9)); exists q; exists (G1 _ G8);
apply (proj1 (G3 (exist _ q (G1 _ G8)))); trivial ] ].
Qed.
(* We know prove Theorem 3. We use two intermediate lemmas for that. *)
Remark flattened_reflexive :
forall c, sub (confl_deps (flattened c)) (depends (flattened c)).
intros c p d (p', (H2, H3)); subst d;
assert (H1 : has_conflict c p);
[ exists p'; trivial
| exists (flattened_dep (immediate_conflict H1)); simpl; split; trivial;
exists (immediate_conflict H1); trivial ].
Qed.
Remark flattened_and_composition :
forall c,
sub (dep_fun_compose (depends (flattened c)) (depends (flattened c)))
(depends (flattened c)).
intros c p s (d, ((H1, E1), (f, (H2, E)))); subst d s;
cut (exists H : below_conflicts c p,
forall q, flattened_dep H q -> exists q', exists H', f q' H' q);
[ intros (H3, H4); exists (flattened_dep H3); split;
[ intros q H5; exact (H4 _ H5)
| exists H3; trivial ]
| induction H1 as [p H1 | p d H1 H3 H4];
[ generalize (H2 _ (refl_equal _)); clear H2; intros (H2, E);
exists H2; intros q H3; exists p; exists (refl_equal p);
rewrite E; trivial
| assert (H5 :
forall q H q', flattened_dep (H3 q H) q' ->
flattened_dep (higher_conflicts H1 H3) q');
[ simpl; intros q H q' H5; exists q; exists H; trivial
| generalize
(choice (fun qH => H4 (proj1_sig qH) (proj2_sig qH) _
(fun p H => H2 _ (H5 _ _ _ H))));
intros (g, H6);
pose (H7 := higher_conflicts H1 (fun q H => g (exist _ q H)));
exists H7;
simpl; intros q (q', (H8, H9));
generalize (H6 (exist d q' H8) _ H9);
intros (q'', (G1, G2));
exists q''; exists (H5 _ H8 _ G1);
trivial ] ] ].
Qed.
Theorem flattened_strongly_flat : forall c, strongly_flat (flattened c).
intro c; split;
[ apply flattened_reflexive
| apply flattened_and_composition ].
Qed.
(*
A configuration is a pair of two sets of packages [i] and [i'].
We define healthy configurations and weakly co-installable set of
packages.
(Section 5.)
*)
Section Configuration.
Variable c : constraints.
Record healthy_config (i i' : set package) : Prop :=
{ abundance_config : forall p d, i p -> depends c p d -> dep_satisfied i' d;
peace_config : forall p p', i' p -> i' p' -> conflicts c p p' -> False }.
Definition weakly_co_installable s := exists s', healthy_config s s'.
End Configuration.
(*
This is the counterpart of Theorem 2 for configurations, and an
immediate corollary (Lemma 32).
*)
Lemma constraint_weakening_config :
forall c c' i i', sub c c' -> healthy_config c' i i' -> healthy_config c i i'.
intros c c' i i' (H1, H2) (H3, H4); split; trivial;
[ intros p d H5 H6; generalize (H1 _ _ H6); intros (d', (H7, H8));
generalize (H3 _ _ H5 H8); intros (q, (G1, G2)); exists q;
split; trivial; apply H7; trivial
| intros p p' H5 H6 H7; generalize (H2 _ _ H7); eauto ].
Qed.
Lemma constraint_weakening_config_and_co_installability :
forall c c' s,
sub c c' -> weakly_co_installable c' s -> weakly_co_installable c s.
intros c c' s H1 (i, H2); exists i; exact (constraint_weakening_config H1 H2).
Qed.
(* Remark 24 corresponds to these remarks. *)
Remark healthy_implies_healthy_config :
forall c i, healthy c i -> healthy_config c i i.
intros c i (H1, H2); split; tauto.
Qed.
Remark healthy_config_implies_healthy :
forall c i, healthy_config c i i -> healthy_config c i i.
intros c i (H1, H2); split; tauto.
Qed.
Remark healthy_config_antimonotony :
forall c i1 i2 i, sub i2 i1 -> healthy_config c i1 i -> healthy_config c i2 i.
intros c i1 i2 i H1 (H2, H3); split; trivial;
intros p d H4; apply H2; apply H1; trivial.
Qed.
(* Lemma 25. *)
Lemma co_installable_implies_weakly_co_installable :
forall c i, co_installable c i -> weakly_co_installable c i.
intros c i (s, (H1, H2)); exists s;
apply healthy_config_antimonotony with (1 := H2);
apply healthy_implies_healthy_config; trivial.
Qed.
(* Technical lemma 26 (used in the proof of Theorems 4 and 10). *)
Lemma dep_on_conflicts_prop :
forall c p i s,
sub (confl_deps c) (depends c) -> healthy_config c i s ->
has_conflict c p -> i p -> s p.
intros c p i s H1 H2 (q, H3) H4;
case (H1 p (singleton p));
[ exists q; split; trivial
| clear q H3; intros d (H5, H6);
generalize (abundance_config H2 H4 H6);
intros (q, (H7, H8)); rewrite <- (H5 _ H8); trivial ].
Qed.
(* Another small technical lemma. *)
Remark maximal_healthy_config :
forall c i i'',
healthy_config c i i'' ->
exists i', maximal (fun i => healthy_config c i i'') i' /\ sub i i'.
intros c i i'' H1; apply package_set_maximality; trivial.
Qed.
(*
Lemma 27.
This lemma specify a condition in which a weakly co-installable set
of packages in a repository [c'] is co-installable in repository [c].
It is crucial to prove Theorems 4 and 6.
*)
Lemma weakly_co_installable_implies_co_installable_1 :
forall c c' i,
sub (confl_deps c') (depends c') ->
sub (dep_fun_compose (depends c) (depends c')) (depends c') ->
(forall p p', conflicts c p p' -> conflicts c' p p') ->
weakly_co_installable c' i -> co_installable c i.
intros c c' i' H1 H2 H3 (s, H4);
generalize (maximal_healthy_config H4); clear H4;
intros (i, (H4, H5)); exists i; split; trivial;
clear i' H5; split;
[ intros p d H5 H6;
assert (H7 : exists q, d q /\
forall d', depends c' q d' -> exists q', s q' /\ d' q');
[ assert (H7 : forall d', depends c' p d' ->
exists q', s q' /\ d' q');
[ intros d' H7; exact (abundance_config (proj1 H4) H5 H7)
| apply NNPP; intro H8;
generalize
(choice (fun pH => not_all_ex_not _ _
(fun H' => not_ex_all_not _ _ H8
(proj1_sig pH) (conj (proj2_sig pH) H'))));
clear H8; intros (f, H8);
assert (H9 := fun q H => imply_to_and _ _ (H8 (exist _ q H)));
clear H8;
pose
(d'' := fun p' => exists q, exists H : d q, f (exist d q H) p');
case (H2 p d'');
[ exists d; split; trivial;
exists (fun q H => f (exist _ q H)); split; trivial;
intros q H; exact (proj1 (H9 q H))
| intros d' (G2, G1);
generalize (H7 _ G1); intros (q', (G3, G4));
generalize (G2 _ G4); intros (q, (G5, G6));
apply (proj2 (H9 _ G5)); exists q'; split; trivial ] ]
| generalize H7; clear H7; intros (q, (H7, H8));
exists q; split; trivial; apply NNPP; intro H9;
apply H9; apply (proj2 H4 (fun p => i p \/ p = q)); simpl; auto;
clear p d H5 H6 H7; split;
[ intros p d [G1 | G1] G2;
[ generalize (abundance_config (proj1 H4) G1 G2);
intros (p', (G3, G4)); exists p'; auto
| subst p; exact (H8 _ G2) ]
| exact (peace_config (proj1 H4)) ] ]
| intros p p' G1 G2 G3;
refine
(peace_config (proj1 H4)
(dep_on_conflicts_prop H1 (proj1 H4) _ G1)
(dep_on_conflicts_prop H1 (proj1 H4) _ G2) (H3 _ _ G3));
[ exists p' | exists p ];
red; auto ].
Qed.
(* Theorem 4. *)
Lemma weakly_co_installable_implies_co_installable_2 :
forall c i,
strongly_flat c ->
weakly_co_installable c i -> co_installable c i.
intros c i (H1, H2);
apply weakly_co_installable_implies_co_installable_1; trivial.
Qed.
(* Lemma 5. *)
Lemma flattened_least :
forall c c',
(forall p, sub (conflicts (flattened c) p) (conflicts c' p)) ->
sub (confl_deps c') (depends c') ->
sub (dep_fun_compose (depends c) (depends c')) (depends c') ->
sub (flattened c) c'.
intros c c' H0 H1 H2; split; trivial;
intros p d (H, E); subst d; induction H as [p (p', H3)| p d H3 H4 H5];
[ lapply (H1 p (singleton p));
[ intros (d, (H4, H5)); exists d; auto
| exists p'; split; trivial;
case H3; [left | right]; apply H0; trivial ]
| generalize (choice (fun pH => H5 (proj1_sig pH) (proj2_sig pH)));
intros (f, H6);
lapply (H2 p (fun p => exists q, exists H : d q, f (exist _ _ H) p));
[ intros (d', (H7, H8)); exists d'; split; trivial;
refine (sub_transitive H7 _);
simpl; intros q (q', (G1, G2)); exists q'; exists G1;
exact (proj1 (H6 (exist _ _ G1)) _ G2)
| exists d; split; trivial;
exists (fun p H => f (exist _ _ H)); split; trivial;
intros q H; exact (proj2 (H6 (exist _ _ H))) ] ].
Qed.
(* A technical lemma used to prove Theorem 6 (case: 2 implies 1). *)
Lemma flattened_and_composition_2 :
forall c,
sub (dep_fun_compose (depends c) (depends (flattened c)))
(depends (flattened c)).
intros c p s (d, (H1, (f, (H2, E)))); subst s;
generalize (choice (fun qH => H2 (proj1_sig qH) (proj2_sig qH)));
intros (g, H3);
pose (H4 := higher_conflicts H1 (fun q H => g (exist _ q H)));
exists (flattened_dep H4);
simpl; split;
[ intros q (p', (H5, H6)); exists p'; exists H5;
generalize (H3 (exist _ _ H5));simpl; intro E; rewrite E; trivial
| exists H4; trivial ].
Qed.
(*
We prove theorem 6.
More precisely, we prove that:
- 1 implies 3 (easy, by induction on each derivation involving rules
Refl and Trans);
- 1 implies 2 (redundant);
- 2 implies 1 (difficult case, by Lemmas 27 and 5);
- 2 implies 3 (redundant);
- 3 implies 2 (immediate, by Lemma 25).
*)
Lemma flatten_co_inst_prop_1 :
forall c s, co_installable c s -> co_installable (flattened c) s.
intros c s (i, ((H1, H2), H3)); exists i; split; trivial; split; trivial;
intros p s' H4 (H5, H6); subst s'; clear s H3;
induction H5;
[ exists p; simpl; split; trivial
| generalize (H1 _ _ H4 d0); intros (q, (H7, H8));
generalize (H q H8 H7); intros (q', (G1, G2));
exists q'; split; trivial; exists q; exists H8; trivial ].
Qed.
Lemma flatten_co_inst_prop_2 :
forall c s, co_installable c s -> weakly_co_installable (flattened c) s.
intros c s (i, ((H1, H2), H3)); exists i; split; trivial;
intros p s' H4 (H5, H6); subst s'; assert (H6 := H3 _ H4); clear H4;
induction H5;
[ exists p; simpl; split; trivial
| generalize (H1 _ _ H6 d0); intros (q, (H7, H8));
generalize (H q H8 H7); intros (q', (G1, G2));
exists q'; split; trivial; exists q; exists H8; trivial ].
Qed.
Lemma flatten_co_inst_prop_3 :
forall c s, weakly_co_installable (flattened c) s -> co_installable c s.
intros c s; apply weakly_co_installable_implies_co_installable_1; trivial;
[ apply flattened_reflexive
| apply flattened_and_composition_2 ].
Qed.
Lemma flatten_co_inst_prop_4 :
forall c s,
weakly_co_installable (flattened c) s -> co_installable (flattened c) s.
intros c s;
apply weakly_co_installable_implies_co_installable_2;
apply flattened_strongly_flat.
Qed.
Lemma flatten_co_inst_prop_5 :
forall c s,
co_installable (flattened c) s -> weakly_co_installable (flattened c) s.
intros c s; apply co_installable_implies_weakly_co_installable.
Qed.
(*************************************************************)
(* Flat repositories (Section 7). *)
(* Definition 7: \nabla_C. *)
Definition always_sat (c : confl_rel) :=
fun d =>
forall i,
forall c' : confl_rel, (forall p, sub (c' p) (c p)) ->
maximal
(fun i : set package =>
forall p p', i p -> i p' -> c' p p' -> False) i ->
dep_satisfied i d.
(*
Dependencies containing a package with no conflict are in
\nabla_C.
*)
Lemma always_sat_when_no_conflict :
forall c (d : set package) q,
d q -> ~ has_conflict c q -> always_sat (conflicts c) d.
intros c d q H1 H2 i c' H3 H4;
pose (i' := fun p' => i p' \/ p' = q);
assert (H6 : forall p p' : package, i' p -> i' p' -> c' p p' -> False);
[ intros p1 p2 [H6 | H6] [H7 | H7];
[ apply (proj1 H4 _ _ H6 H7)
| subst p2; intro H7; apply H2; exists p1; right; apply H3; trivial
| subst p1; intro H6; apply H2; exists p2; left; apply H3; trivial
| subst p1 p2; intro H6; apply H2; exists q; left; apply H3; trivial ]
| lapply (proj2 H4 i' H6);
[ intro H7; exists q; split; trivial; apply H7; right; trivial
| intros p H7; red; auto ] ].
Qed.
(*
We define the dependencies containing a package with only internal
conflicts.
*)
Definition internal_conflicts c (d : set package) :=
exists p, d p /\ forall q, in_conflict c p q -> d q.
(* Then, we prove Theorem 8. We prove each direction in turn. *)
Theorem always_sat_implies_internal_conflicts :
forall c d,
always_sat (conflicts c) d -> internal_conflicts c d.
intros c d H1; apply NNPP; intro H0;
case
(H1 (fun p => ~ d p)
(fun p q => conflicts c p q /\ ((d p /\ ~ d q) \/ (d q /\ ~ d p))));
[ intros p1 p2 (H3, _); trivial
| split;
[ intros p p' H3 H4 (H5, [(H6, H7) | (H6, H7)]);
[ case (H3 H6)
| case (H4 H6) ]
| intros i H3 H4 p H5 H6;
apply H0; exists p; split; trivial;
intros q [H8 | H8]; apply NNPP; intro H7;
[ apply (H3 _ _ H5 (H4 _ H7)); auto
| apply (H3 _ _ (H4 _ H7) H5); auto ] ]
| intros q (H3, H4); case (H3 H4) ].
Qed.
Theorem always_sat_when_internal_conflicts :
forall c d,
no_self_conflict c -> internal_conflicts c d -> always_sat (conflicts c) d.
intros c d H0 (p, (H1, H2)) i c' H3 H4;
case (classic (forall q, in_conflict c p q -> ~i q));
[ intro H5; pose (i' := fun p' => i p' \/ p' = p);
assert (H6 : forall p p' : package, i' p -> i' p' -> c' p p' -> False);
[ intros p1 p2 [H6 | H6] [H7 | H7];
[ apply (proj1 H4 _ _ H6 H7)
| subst p2; intro H7; apply (H5 p1); trivial;
right; apply (H3 _ _ H7)
| subst p1; intro H6; apply (H5 p2); trivial;
left; apply (H3 _ _ H6)
| subst p1 p2; intro H6; apply (H0 p); apply (H3 _ _ H6) ]
| lapply (proj2 H4 i' H6);
[ intro H7; exists p; split; trivial; apply H7; right; trivial
| intros q H7; red; auto ] ]
| intros H5; generalize (not_all_ex_not _ _ H5); clear H5;
intros (q, H5); generalize (imply_to_and _ _ H5); clear H5;
intros (H5, H6); exists q; generalize (NNPP _ H6); auto ].
Qed.
(* Remark 28. *)
Remark always_sat_upward_closed :
forall c s s', sub s s' -> always_sat c s -> always_sat c s'.
intros c s s' H1 H2 i c' H3 H4; generalize (H2 _ _ H3 H4);
intros (q, (H5, H6)); exists q; split; trivial;
apply H1; trivial.
Qed.
(* Another simple properties of \nabla_C. *)
Remark always_sat_antimonotone :
forall c c' s, (forall p, sub (c' p) (c p)) ->
always_sat c s -> always_sat c' s.
intros c c' s H1 H2 i c'' H3; apply H2; intro p;
exact (sub_transitive (H3 p) (H1 p)).
Qed.
(*
We define a coarser preorder on dependency functions that ignores
dependencies in \nabla_C (Section 7).
*)
Definition dsubc (c : confl_rel) (ds ds' : dep_fun) :=
forall p,
forall d, ds p d -> always_sat c d \/ exists d', sub d' d /\ ds' p d'.
Lemma dsubc_trans : forall c, is_transitive (dsubc c).
intros c ds ds' ds'' H1 H2 p s H3;
generalize (H1 _ _ H3); intros [H4 | (s', (H4, H5))]; auto;
generalize (H2 _ _ H5); intros [H6 | (s'', (H6, H7))];
[ left; exact (always_sat_upward_closed H4 H6)
| right; exists s''; split; trivial;
exact (sub_transitive H6 H4) ].
Qed.
Lemma dsubc_refl : forall c, is_reflexive (dsubc c).
intros c ds p s H1; right; exists s; split; trivial; apply sub_reflexive.
Qed.
Definition dep_fun_alt_po c := Build_po (@dsubc_trans c) (@dsubc_refl c).
(*
Remark 29, propsition 1: if we remove conflicts, the dependency
functions remain related.
*)
Remark dsubc_weaken :
forall c c' d d',
(forall p, sub (c' p) (c p)) ->
@sub (dep_fun_alt_po c) d d' -> @sub (dep_fun_alt_po c') d d'.
intros c c' d d' H1 H2 p d'' H3;
generalize (H2 _ _ H3); intros [H4 | H4]; auto; left;
intros i c'' H5; apply (H4 i c'');
intro q; exact (sub_transitive (H5 q) (H1 q)).
Qed.
(* Remark 29, propsition 2: it is indeed a coarser preorder. *)
Remark dsubc_coarser :
forall c (d d' : dep_fun_po), sub d d' -> @sub (dep_fun_alt_po c) d d'.
intros c d d' H1 p d'' H2; right; exact (H1 _ _ H2).
Qed.
(* We lift the preorder to repositories. *)
Definition csubc c c' :=
@sub (dep_fun_alt_po (conflicts c)) (depends c) (depends c')
/\
(forall p, sub (conflicts c p) (conflicts c' p)).
Lemma csubc_trans : is_transitive csubc.
intros c c' c'' (H1, H2) (H3, H4); split;
[ refine (sub_transitive H1 _);
intros p d H5; generalize (H3 _ _ H5); intros [H6 | H6]; auto; left;
apply always_sat_antimonotone with (2 := H6); auto
| intro p; exact (sub_transitive (H2 p) (H4 p)) ].
Qed.
Lemma csubc_refl : is_reflexive csubc.
intros c; split; [ apply sub_reflexive | intro p; apply sub_reflexive ].
Qed.
Definition constraints_alt_po := Build_po csubc_trans csubc_refl.
(* Remark 29, propsition 3. *)
Remark alt_sub_coarser :
forall c c' : constraints_po, sub c c' -> @sub constraints_alt_po c c'.
intros c c' (H1, H2); split; trivial;
apply dsubc_coarser; trivial.
Qed.
(* We now define flat repositories (Section 7). *)
Record flat c :=
{ f_refl : @sub (dep_fun_alt_po (conflicts c)) (confl_deps c) (depends c);
f_trans : @sub (dep_fun_alt_po (conflicts c))
(dep_fun_compose (depends c) (depends c)) (depends c) }.
(* Lemma 9. *)
Lemma strongly_flat_implies_flat : forall c, strongly_flat c -> flat c.
intros c (H1, H2); split;
apply dsubc_coarser; trivial.
Qed.
(* Technical remark 30. *)
Remark confl_dep_sub_confl :
forall c q,
sub (confl_deps c) (depends c) -> has_conflict c q ->
exists d, sub d (singleton q) /\ depends c q d.
intros c q H1 (q', H2); apply H1; exists q'; split; trivial.
Qed.
(* Lemma 31. *)
Lemma flat_preservation :
forall c c',
@sub constraints_alt_po c c' ->
@sub constraints_po c' c ->
flat c -> flat c'.
intros c c' (H1, H2) (H3, H4) (H5, H6); split;
[ refine (sub_transitive _ (dsubc_weaken H4 (sub_transitive H5 H1)));
apply dsubc_coarser; apply dsub_incl;
intros p d (q, (H7, H8)); exists q; split; trivial;
case H7; [left | right]; apply H4; trivial
| intros p d (d', (H7, (f, (H8, E)))); subst d;
generalize (H3 _ _ H7); intros (d, (G1, G2));
generalize (choice (fun qH => H3 _ _ (H8 (proj1_sig qH) (proj2_sig qH))));
intros (f', G3);
pose
(d'' := fun p' => exists q, exists H : d q, f' (exist d' q (G1 q H)) p');
case (H6 p d'');
[ exists d; split; trivial;
exists (fun q H => f' (exist _ q (G1 _ H))); split;
[ intros q G4;
generalize (G3 (exist _ q (G1 _ G4))); intros (G5, G6); trivial
| trivial ]
| intro G4; left; subst d'';
apply always_sat_antimonotone with (1 := H4);
intros i c'' G5 G6;generalize (G4 _ _ G5 G6);
intros (q, (G7, (q', (G8, G9))));
exists q; split; trivial; exists q'; exists (G1 _ G8);
apply (proj1 (G3 (exist _ _ (G1 _ G8)))); trivial
| subst d''; intros (d'', (G4, G5));
generalize (H1 _ _ G5); intros [G6 | (d''', (G6, G7))];
[ left; apply always_sat_antimonotone with (1 := H4);
intros i c'' G7 G8; generalize (G6 _ _ G7 G8);
intros (q, (F1, F2)); generalize (G4 _ F2);
intros (q', (F3, F4));
exists q; split; trivial;
exists q'; exists (G1 _ F3);
apply (proj1 (G3 (exist _ _ (G1 _ F3)))); trivial
| right; exists d'''; split; trivial;
refine (sub_transitive G6 _);
refine (sub_transitive G4 _);
intros p' (q, (G8, G9)); exists q; exists (G1 _ G8);
apply (proj1 (G3 (exist _ q (G1 _ G8)))); trivial ] ] ].
Qed.
(* Two technical lemma used to prove Theorem 10. *)
Lemma feature_maximality :
forall c s i,
maximal (fun i => healthy_config c s i) i ->
maximal
(fun i : set package =>
forall p p' : package, i p -> i p' -> conflicts c p p' -> False)
i.
intros c s i (H1, H2); split;
[ exact (peace_config H1)
| intros i' H3 H4; apply H2; trivial;
split; trivial;
intros p d H5 H6; generalize (abundance_config H1 H5 H6);
intros (q, (H7, H8)); exists q; split; trivial;
apply H4; trivial ].
Qed.
Lemma confl_dep_sub :
forall c,
sub (p:=dep_fun_alt_po (conflicts c)) (confl_deps c) (depends c) ->
sub (confl_deps c) (depends c).
intros c H1 p d H2; generalize (H1 _ _ H2); intros [H3 | H3]; trivial;
generalize H2; clear H2; intros (q, (H2, E)); subst d;
case (classic (conflicts c p p));
[ intro H4;
case (H3 (fun q => q <> p)
(fun p' q' => conflicts c p' q' /\ (p' = p /\ q' = p)));
[ intros p1 p2 (H5, H6); trivial
| split;
[ intros p1 p2 H5 H6 (H7, (H8, H9)); case (H5 H8)
| intros s H5 H6 p' H7 H8; subst p';
apply (H5 _ _ H7 H7); auto ]
| intros p' (H5, H6); case (H5 H6) ]
| intro H0;
case (H3 (fun q => q <> p)
(fun p' q' => conflicts c p' q' /\
((p' = p /\ q' = q) \/ (p' = q /\ q' = p))));
[ intros p1 p2 (H4, H5); trivial
| split;
[ intros p1 p2 H4 H5 (H6, [(H7, H8) | (H7, H8)]);
[ case (H4 H7)
| case (H5 H8) ]
| intros i H4 H5 p1 H6 H7; subst p1;
assert (H7 : i q);
[ apply H5; intro E; subst q; apply H0; case H2; trivial
| case H2; clear H2; intro H2;
[ apply (H4 p q); auto
| apply (H4 q p); auto ] ] ]
| intros p' (H4, H5); case (H4 H5) ] ].
Qed.
(* Theorem 10. *)
Theorem weakly_co_installable_implies_co_installable_3 :
forall c i,
flat c -> weakly_co_installable c i -> co_installable c i.
intros c i (H1, H2) (s', H3);
generalize (package_set_maximality H3); clear H3;
intros (s, (H4, H4')); clear s' H4';
assert (H3' := feature_maximality H4);
assert (H3'' := abundance_config (proj1 H4));
pattern i in H3''; generalize (package_set_maximality H3''); clear H4 H3'';
intros (i', (H3, H4)); exists i'; split; trivial;
clear i H4; split;
[ intros p d H5 H6;
assert (H7 : exists q, d q /\
forall d', depends c q d' -> exists q', s q' /\ d' q');
[ assert (H7 : forall d', depends c p d' ->
exists q', s q' /\ d' q');
[ intros d' H7; exact (proj1 H3 _ _ H5 H7)
| apply NNPP; intro H8;
generalize
(choice (fun pH => not_all_ex_not _ _
(fun H' => not_ex_all_not _ _ H8
(proj1_sig pH) (conj (proj2_sig pH) H'))));
clear H8; intros (f, H8);
assert (H9 := fun q H => imply_to_and _ _ (H8 (exist _ q H)));
clear H8;
pose
(d'' := fun p' => exists q, exists H : d q, f (exist d q H) p');
case (H2 p d'');
[ exists d; split; trivial;
exists (fun q H => f (exist _ q H)); split; trivial;
intros q H; exact (proj1 (H9 q H))
| intro G1;
generalize (G1 _ _ (fun p => sub_reflexive _) H3');
intros (q, (G2, (q', (G3, G4))));
apply (proj2 (H9 _ G3));
exists q; auto
| intros (d', (G2, G1));
generalize (H7 _ G1); intros (q', (G3, G4));
generalize (G2 _ G4); intros (q, (G5, G6));
apply (proj2 (H9 _ G5)); exists q'; split; trivial ] ]
| generalize H7; clear H7; intros (q, (H7, H8));
exists q; split; trivial; apply NNPP; intro H9;
apply H9; apply (proj2 H3 (fun p => i' p \/ p = q)); simpl; auto;
clear p d H5 H6 H7;
intros p d [G1 | G1] G2;
[ generalize (proj1 H3 _ _ G1 G2);
intros (p', (G3, G4)); exists p'; auto
| subst p; exact (H8 _ G2) ] ]
| intros p p' G1 G2 G3;
assert (G4 := Build_healthy_config (proj1 H3) (proj1 H3'));
refine
(peace_config G4
(dep_on_conflicts_prop (confl_dep_sub H1) G4 _ G1)
(dep_on_conflicts_prop (confl_dep_sub H1) G4 _ G2) G3);
[ exists p' | exists p ];
red; auto ].
Qed.
(*
We specify what it means to remove all dependencies in \nabla_C from
a repository.
*)
Definition simplified c :=
Build_constraints
(fun p d => depends c p d /\ ~ always_sat (conflicts c) d) (conflicts c).
(* Lemma 33, proposition 1: we get less dependencies *)
Lemma simplified_smaller : forall c, sub (simplified c) c.
intros c; split;
[ apply dsub_incl; intros p d (H1, H2); trivial
| intro p; apply sub_reflexive ].
Qed.
(*
Lemma 33, proposition 2: we remain equivalent wrt the coarser
relation.
*)
Lemma simplified_alt_larger :
forall c, @sub constraints_alt_po c (simplified c).
intros c; split;
[ intros p d H1; case (classic (always_sat (conflicts c) d)); auto;
intro H2; right; exists d; split;
[ apply sub_reflexive
| simpl; auto ]
| intro p; apply sub_reflexive ].
Qed.
(* We need this small lemma to complete the proof of theorem 11. *)
(*
XXX Missing in the paper proof!
*)
Lemma constraint_alt_weakening :
forall c c' i,
@sub constraints_alt_po c c' ->
weakly_co_installable c' i -> weakly_co_installable c i.
intros c c' i (H1, H2) (i', (H3, H4));
pose
(P := fun i' : set package =>
forall p p' : package, i' p -> i' p' -> conflicts c p p' -> False);
lapply (@package_set_maximality P i');
[ intros (i'', (H5, H6)); exists i''; split;
[ intros p d H7 H8; generalize (H1 _ _ H8); intros [G1 | (d', (G1, G2))];
[ apply (G1 i'' (conflicts c)); trivial;
intro q; apply sub_reflexive
| generalize (H3 _ _ H7 G2); intros (q, (G3, G4));
exists q; split;
[ apply H6; trivial
| apply G1; trivial ] ]
| exact (proj1 H5) ]
| intros p p' H5 H6 H7; apply (H4 _ _ H5 H6); apply H2; trivial ].
Qed.
(* Theorem 11. *)
Theorem removing_clearly_irrelevant_dependencies_preserves_flatness :
forall c, flat c -> flat (simplified c).
intro c; apply flat_preservation;
[ apply simplified_alt_larger
| apply simplified_smaller ].
Qed.
Theorem removing_clearly_irrelevant_dependencies_and_weak_co_installability :
forall c i,
weakly_co_installable c i <-> weakly_co_installable (simplified c) i.
intros c i; split;
[ apply constraint_weakening_config_and_co_installability;
apply simplified_smaller
| apply constraint_alt_weakening; apply simplified_alt_larger ].
Qed.
(*
Lemma 34.
Crucial lemma for reasoning in flat repositories: dependency
composition (see remark at the end of Section 7.)
*)
Lemma dep_comp :
forall c p d,
flat c ->
depends c p d ->
forall s, sub s d ->
forall f : (forall p', s p' -> set package),
(forall p' (H : s p'), depends c p' (f p' H)) ->
exists d'', (depends c p d'' \/ always_sat (conflicts c) d'') /\
sub d'' (fun p => (d p /\ ~s p) \/
exists p', exists H : s p', f p' H p).
intros c p d H1 H2 s H3 f H4;
case (classic (forall q', d q' -> ~ s q' -> has_conflict c q'));
[ intro H5;
assert
(H6 : forall q, d q ->
exists d'',
depends c q d'' /\
sub d'' (fun p => (d p /\ ~s p) \/
exists p', exists H : s p', f p' H p));
[ intros q H6; case (classic (s q));
[ intro H7; exists (f _ H7); split; auto;
intros q' H8; right; exists q; exists H7; trivial
| intro H7;
generalize
(confl_dep_sub_confl
(confl_dep_sub (f_refl H1)) (H5 _ H6 H7));
intros (d', (H8, H9)); exists d'; split; trivial;
intros p' G1; rewrite (H8 _ G1); auto ]
| generalize (choice (fun qH => H6 (proj1_sig qH) (proj2_sig qH)));
clear H6; intros (g, H6);
case (@f_trans _ H1 p
(fun p => exists q, exists H : d q, g (exist _ _ H) p));
[ exists d; split; trivial;
exists (fun p H => g (exist _ _ H)); split; trivial;
intros q H7; exact (proj1 (H6 (exist _ _ H7)))
| intro H7;
exists (fun p => exists q, exists H : d q, g (exist _ _ H) p);
split; auto;
intros q (q', (H8, H9));
apply (proj2 (H6 (exist _ _ H8))); trivial
| intros (d', (H7, H8)); exists d'; split; auto;
refine (sub_transitive H7 _);
intros q (q', (G1, G2));
apply (proj2 (H6 (exist _ _ G1))); trivial ] ]
| intro H5; generalize (not_all_ex_not _ _ H5); clear H5; intros (q, H5);
generalize (imply_to_and _ _ H5); clear H5; intros (H5, H6);
generalize (imply_to_and _ _ H6); clear H6; intros (H6, H7);
exists (singleton q);
split;
[ right; apply always_sat_when_no_conflict with (2 := H7); red; trivial
| intros q' H8; rewrite H8; auto ] ].
Qed.
(*XXX Remove Lemma 35? *)
(*************************************************************)
(* Conflict covered dependencies (Section 8.2). *)
(* Definition of conflict covered dependencies. *)
Definition conflict_covered c (d : set package) q :=
d q /\ forall q', in_conflict c q' q ->
exists d', depends c q' d' /\ sub d' d /\ ~ d' q.
(* What it means to remove a single dependency. *)
Definition remove_dep c p d :=
Build_constraints
(fun p' d' => depends c p' d' /\ ~(p' = p /\ d' = d)) (conflicts c).
(*
Lemma 12: a conflict covered dependency can be removed in a flat
repository, while leaving (weak) co-instability unchanged.
(We first prove an intermediate lemma.)
*)
Lemma remove_conflict_covered_0 :
forall c p d s i q,
flat c ->
conflict_covered c d q -> ~dep_satisfied i d ->
let c' := remove_dep c p d in
let i' := fun p => i p /\ forall p', in_conflict c p' q -> p <> p' in
maximal (fun i => healthy_config c' s i) i ->
forall p' d', s p' -> depends c' p' d' -> ~d' q -> dep_satisfied i' d'.
intros c p d s i q H1 H2 H3 c' i' H4;
intros p' d' H5 H6 H0;
apply NNPP; intro H7;
case (classic (forall q'', i q'' -> d' q'' -> in_conflict c q'' q));
[ intro G1;
generalize
(choice
(fun qP : sig (fun p => i p /\ d' p) =>
let P := proj2_sig qP in
(proj2 H2 _ (G1 (proj1_sig qP) (proj1 P) (proj2 P)))));
intros (f, G2);
assert (G3 : @sub (set package) (fun p => i p /\ d' p) d');
[ intros p0 (G3, G4); trivial
| generalize
(dep_comp H1 (proj1 H6) G3
(fun p s => proj1 (G2 (exist _ p s))));
intros (d'', (G5, G6));
assert (G7 : ~dep_satisfied i d'');
[ intros (q', (G7, G8));
generalize (G6 _ G8); intros [(F1, F2) | (p'', (F1, F2))];
[ auto
| generalize (G2 (exist _ _ F1)); intros (F3, (F4, F5));
assert (F6 := F4 _ F2);
apply H3; exists q'; auto ]
| apply G7; generalize G5; clear G5; intros [G5 | G5];
[ apply (fun H => abundance_config (proj1 H4) H5 H);
split; trivial;
intros (G8, G9); subst p' d'';
generalize (G6 _ (proj1 H2));
intros [(F1, F2) | (p'', (F1, F2))];
[ case (H0 F1)
| generalize (G2 (exist _ _ F1)); intros (F3, (F4, F5));
case (F5 F2) ]
| exact
(G5 _ _ (fun p => sub_reflexive _)
(feature_maximality H4)) ] ] ]
| intro G3; generalize (not_all_ex_not _ _ G3); clear G3;
intros (q'', G3); generalize (imply_to_and _ _ G3); clear G3;
intros (G3, G4); generalize (imply_to_and _ _ G4); clear G4;
intros (G4, G5); apply H7;
exists q''; split; trivial; split; trivial;
intros q1 G6 G7; subst q1; case (G5 G6) ].
Qed.
Lemma remove_conflict_covered :
forall c p d s q, no_self_conflict c ->
flat c -> conflict_covered c d q ->
weakly_co_installable (remove_dep c p d) s -> weakly_co_installable c s.
intros c p d s q H0 H1 H2 (i', H4);
generalize (package_set_maximality H4); intros (i, (H3, _)); clear i' H4;
case (classic (dep_satisfied i d)); intro H4;
[ exists i; split;
[ intros p' d' H5 H6;
case (classic (p' = p /\ d' = d));
[ intros (E1, E2); subst d'; trivial
| intro H7; apply (abundance_config (proj1 H3) H5); split; trivial ]
| exact (peace_config (proj1 H3)) ]
| exists
(fun p => (i p /\ forall p', in_conflict c p' q -> p <> p') \/ p = q);
split;
[ intros p' d' H5 H6;
case (classic (d' q)); intro H7;
[ exists q; auto
| lapply (fun H => remove_conflict_covered_0 H1 H2 H4 H3 H5 H H7);
[ intros (q', ((G1, G2), G3)); exists q'; auto
| split; trivial;
intros (E1, E2); subst p' d'; exact (H7 (proj1 H2)) ] ]
| intros p1 p2 [(H5, H6) | H5] [(H7, H8) | H7];
[ apply (peace_config (proj1 H3)); trivial
| subst p2; intro H7; apply (H6 p1); unfold in_conflict; auto
| subst p1; intro H5; apply (H8 p2); unfold in_conflict; auto
| subst p1 p2; apply H0 ] ] ].
Qed.
(* Lemma 13. *)
Lemma removal_preserves_flatness :
forall c p d,
let c' := remove_dep c p d in
~ sub d (singleton p) ->
(forall d' : set package,
dep_fun_compose (depends c') (depends c') p d' -> ~ sub d d') ->
flat c -> flat c'.
intros c p d c' A1 A2 (H1, H2); split;
[ intros p' d' H3; generalize (H1 _ _ H3); generalize H3; clear H3;
intros (q, (H3, H4)); subst d'; intros [H4 | (d', (H4, H5))]; auto;
right; exists d'; split; trivial; split; trivial;
intros (E1, E2); subst p' d'; exact (A1 H4)
| intros p' d'' (d', (H4, (f, (H5, E)))); subst d'';
case (H2 p' (fun p => exists q, exists H : d' q, f q H p));
[ exists d'; split;
[ exact (proj1 H4)
| exists f; split; trivial;
intros q H; exact (proj1 (H5 q H)) ]
| auto
| intros (d'', (H6, H7)); right;
exists d''; split; trivial; split; trivial;
intros (E1, E2); subst p' d'';
apply A2 with (2 := H6);
exists d'; split; trivial;
exists f; auto ] ].
Qed.
(*************************************************************)
(* Section 8.3: redundant conflicts *)
(* We specify what it means to remove a single conflict. *)
Definition remove_confl c p1 p2 :=
Build_constraints
(depends c)
(fun q1 q2 =>
conflicts c q1 q2 /\
~(q1 = p1 /\ q2 = p2) /\ ~(q1 = p2 /\ q2 = p1)).
(* Definition of a redundant conflict. *)
Definition redundant_conflict c p1 p2 :=
exists d1,
depends c p1 d1 /\
forall q1, d1 q1 ->
exists q2,
exists d2, sub d2 (singleton q2) /\ depends c p2 d2 /\
conflicts (remove_confl c p1 p2) q1 q2.
(*
Lemma 14: healthiness is preserved when a redundant conflict is removed.
*)
Lemma redundant_conflict_removal_and_healthiness :
forall c p1 p2 i,
redundant_conflict c p1 p2 ->
healthy (remove_confl c p1 p2) i ->
healthy c i.
intros c p1 p2 i H1 H2; split;
[ exact (abundance H2)
| assert (G1 : i p1 -> i p2 -> False);
[ intros H3 H4;
generalize H1; clear H1; intros (d, (H1, H6));
generalize (abundance H2 H3 H1);
intros (q1, (H7, H8));
generalize (H6 _ H8);
intros (q2, (d', (G1, (G2, G3))));
generalize (abundance H2 H4 G2);
intros (q, (G4, G5));
generalize (G1 _ G5); unfold singleton; intro E; subst q;
exact (peace H2 H7 G4 G3)
| intros p p' H3 H4 H5; apply (peace H2 H3 H4); split; trivial; split;
[ intros (H6, H7); subst p p'; auto
| intros (H6, H7); subst p p'; auto ] ] ].
Qed.
(*
We can actually prove a lot more regarding redundant conflict removal:
- the repository remains flat;
- weak co-installability is preserved.
*)
Lemma conflict_removal_flat :
forall c (confl : confl_rel),
(forall p, sub (confl p) (conflicts c p)) ->
flat c -> flat (Build_constraints (depends c) confl).
intros c confl H1 (H2, H3); split;
[ refine (sub_transitive _ (dsubc_weaken H1 H2));
simpl; intros p d (p', (H5, H6));
right; exists d; split;
[ apply sub_reflexive
| exists p'; split; trivial;
generalize H1 H5; unfold in_conflict; simpl; intuition ]
| exact (dsubc_weaken H1 H3) ].
Qed.
Lemma redundant_conflict_removal_and_weak_co_installability :
forall c p1 p2 i,
flat c ->
redundant_conflict c p1 p2 ->
weakly_co_installable (remove_confl c p1 p2) i ->
weakly_co_installable c i.
intros c p1 p2 i A2 H0; generalize H0; intros (d1, (H1, H2)) (s', H4);
generalize (package_set_maximality H4); intros (s, (H3, _)); clear s' H4;
case (classic (dep_satisfied s d1));
[ intros (q1, (H4, H5));
generalize (H2 _ H5); intros (q2, (d2, (H6, (H7, H7'))));
exists (fun p => s p /\ ~ p = p2); split;
[ intros p d G1 G2; generalize (abundance_config (proj1 H3) G1 G2);
intros (q, (G3, G4));
case (classic (q = p2));
[ intro E; subst q;
case
(fun H H' => @dep_comp _ _ _
(conflict_removal_flat
(confl := conflicts (remove_confl c p1 p2)) H' A2)
G2 (singleton p2) H (fun _ _ => d2));
[ simpl; tauto
| intros q E; rewrite E; trivial
| intros q G5; rewrite G5; trivial
| intros d' (G6, G7);
cut (dep_satisfied s d');
[ intros (q, (G8, G9)); generalize (G7 _ G9);
intros [(F1, F2) | (q', (F1, F2))];
[ exists q; auto
| rewrite (H6 _ F2) in G8;
case (peace_config (proj1 H3) H4 G8);
trivial ]
| case G6; clear G6; intro G6;
[ exact (abundance_config (proj1 H3) G1 G6)
| exact (G6 _ _ (fun p => sub_reflexive _)
(feature_maximality H3)) ] ] ]
| intros G5; exists q; auto ]
| intros q1' q2' (G1, G2) (G3, G4) G5;
apply (peace_config (proj1 H3) G1 G3); split; trivial; split;
[ intros (E1, E2); exact (G4 E2)
| intros (E1, E2); exact (G2 E1) ] ]
| intro H4; exists (fun p => s p /\ ~ p = p1); split;
[ intros p d G1 G2; generalize (abundance_config (proj1 H3) G1 G2);
intros (q, (G3, G4));
case (classic (q = p1));
[ intro E; subst q;
case
(fun H H' => @dep_comp _ _ _
(conflict_removal_flat
(confl := conflicts (remove_confl c p1 p2)) H' A2)
G2 (singleton p1) H (fun _ _ => d1));
[ simpl; tauto
| intros q E; rewrite E; trivial
| intros q G5; rewrite G5; trivial
| intros d' (G6, G7);
cut (dep_satisfied s d');
[ intros (q, (G8, G9)); generalize (G7 _ G9);
intros [(F1, F2) | (q', (F1, F2))];
[ exists q; auto
| case H4; exists q; auto ]
| case G6; clear G6; intro G6;
[ exact (abundance_config (proj1 H3) G1 G6)
| exact (G6 _ _ (fun p => sub_reflexive _)
(feature_maximality H3)) ] ] ]
| intros G5; exists q; auto ]
| intros q1' q2' (G1, G2) (G3, G4) G5;
apply (peace_config (proj1 H3) G1 G3); split; trivial; split;
[ intros (E1, E2); exact (G2 E1)
| intros (E1, E2); exact (G4 E2) ] ] ].
Qed.
(*************************************************************)
(* Section 8.4: dependence on conflicting packages. *)
Definition strength_dep c p :=
Build_constraints
(fun p' d => (p' <> p /\ depends c p' d) \/ (p' = p /\ d = fun _ => False))
(conflicts c).
(* The class of packages that we consider as clearly broken. *)
Definition clearly_broken c p :=
exists d, exists q,
depends c p d /\ sub d (singleton q) /\ in_conflict c p q.
(* Such packages cannot be installed. *)
Lemma clearly_broken_not_installable :
forall c p, clearly_broken c p -> ~ installable c p.
intros c p (d, (q, (H1, (H2, H3)))) (i, ((H4, H5), H6));
generalize (H4 _ _ H6 H1); intros (p', (H7, H8));
generalize (H2 _ H8); unfold singleton; intro E; subst p';
case H3; eauto.
Qed.
(* The [strength_dep] is rightly named. *)
Lemma strength_dep_prop : forall c p, sub c (strength_dep c p).
intros c p; split;
[ intros p' d H1; case (classic (p' = p));
[ intro E; exists (fun _ => False); split;
[ simpl; contradiction
| right; auto ]
| intro H2; exists d; split;
[ apply sub_reflexive
| left; auto ] ]
| intro p'; apply sub_reflexive ].
Qed.
(* Lemma 15. *)
Lemma strenghten_dependence_of_conflicting_package :
forall c p i,
~ installable c p -> (healthy c i <-> healthy (strength_dep c p) i).
intros c p i H1; split;
[ intros (H2, H3); split; trivial;
intros p' d H4 [(H5, H6)|(H5, H6)];
[ eauto
| case H1; exists i; subst p'; split; trivial;
split; trivial ]
| apply constraint_weakening; apply strength_dep_prop ].
Qed.
(*************************************************************)
(* Quotienting (Section 9). *)
(*
A quotient is defined by a representative function, that maps each
package to its representative. The representative of a package
should have the same dependencies.
*)
Definition representative c (f : package -> package) :=
forall p, equiv (depends c p) (depends c (f p)).
(*
Given a representative function, we can define the quotient of a
repository.
*)
Definition quotient c f :=
Build_constraints
(fun p d => exists d', depends c p d' /\ d = img f d')
(fun p p' => exists q,
exists q', p = f q /\ p' = f q' /\ conflicts c q q').
(*
Lemma 16.
We show that the quotient repository is indeed a repository, as
long as no package depends on a package it conflicts with.
(That is, there is no clearly broken packages.)
*)
Definition no_dep_on_conflict c :=
forall p d q,
depends c p d -> sub d (singleton q) -> ~ in_conflict c p q.
Lemma quotient_and_self_conflicts :
forall c f,
flat c -> representative c f -> no_dep_on_conflict c ->
no_self_conflict (quotient c f).
intros c f H2 H3 H4 p (q, (q', (E1, (E2, H6))));
assert (H7 : has_conflict c q');
[ exists q; right; trivial
| generalize (confl_dep_sub_confl (confl_dep_sub (@f_refl _ H2)) H7);
intros (d, (H8, H9));
generalize (proj1 (H3 q') _ H9); rewrite <- E2; rewrite E1;
intro G1; assert (G2 := proj2 (H3 q) _ G1);
apply (H4 _ _ _ G2 H8); left; trivial ].
Qed.
(*
Note that is a package has an empty dependency, all the conflicts it
is involved in are redundant and can be removed.
The [no_dep_on_conflict] assumption is thus not too strong.
*)
Lemma conflict_and_empty_dep :
forall c p p' d,
depends c p d -> (forall q, ~ d q) -> redundant_conflict c p p'.
intros c p p' d H1 H2; exists d; split; trivial;
intros q H3; case (H2 _ H3).
Qed.
(* Technical lemma: Remark 36. *)
Remark missing_feature_implies_conflict :
forall c s i,
no_self_conflict c -> maximal (fun i => healthy_config c s i) i ->
forall p, ~ i p -> has_conflict c p.
intros c s i A0 H1 p H2;
assert (H3 : ~always_sat (conflicts c) (singleton p));
[ intro H3; apply H2; red in H3;
generalize (H3 _ _ (fun p => sub_reflexive _) (feature_maximality H1));
intros (q, (H4, E)); rewrite <- E; trivial
| assert (H4 := fun H => H3 (always_sat_when_internal_conflicts A0 H));
generalize (not_ex_all_not _ _ H4 p); clear H4; intro H4;
apply NNPP; intro H5; apply H4; split;
[ red; trivial
| intros q H6; case H5; exists q; trivial ] ].
Qed.
(* Technical lemma: Lemma 37. *)
Lemma quotient_and_conflicts :
forall c f s i p p',
no_self_conflict c -> flat c -> representative c f ->
maximal (fun i => healthy_config c s i) i ->
f p = f p' -> ~ i p' ->
exists d, sub d (singleton p') /\ depends c p d.
intros c f s i p p' A0 A1 A2 H1 E H3;
assert (H4 := missing_feature_implies_conflict A0 H1 H3);
generalize (confl_dep_sub_confl (confl_dep_sub (@f_refl _ A1)) H4);
intros (d, (H5, H6)); exists d; split; trivial;
apply (proj2 (A2 p)); rewrite E; apply (proj1 (A2 p')); trivial.
Qed.
(*
Lemma 38: we can map maximal healthy configurations in the original
repository to healthy configurations in the quotiented repository.
*)
Lemma quotient_healthy_1 :
forall c f s i,
no_self_conflict c -> flat c -> representative c f ->
maximal (fun i => healthy_config c s i) i ->
healthy_config (quotient c f) (img f s) (complimg f i).
intros c f s i A0 A1 H1 H2; split;
[ intros p d (q, (H3, H4)) (d', (H5, H6)); subst p d;
generalize (abundance_config (proj1 H2) H3 (proj2 (H1 q) _ H5));
intros (p, (H6, H7));
case (classic (forall p, i p -> d' p -> exists p', f p = f p' /\ ~ i p'));
[ intro G1;
assert (G2 :
forall p, i p -> d' p ->
exists d, exists p', ~ i p' /\ sub d (singleton p') /\ depends c p d);
[ intros p' G2 G3; generalize (G1 _ G2 G3);
intros (p'', (E, G4));
generalize (quotient_and_conflicts A0 A1 H1 H2 E G4);
intros (d, (G5, G6)); exists d; exists p''; auto
| generalize
(choice (fun pH : {p | i p /\ d' p} =>
G2 (proj1_sig pH)
(proj1 (proj2_sig pH)) (proj2 (proj2_sig pH))));
intros (g, G3);
lapply (fun H => @dep_comp _ _ _ A1 (proj2 (H1 _) _ H5) _ H
(fun p H => g (exist _ p H)));
[ intro G4; lapply G4; clear G4;
[ intros (d, (G4, G5));
cut (dep_satisfied i d);
[ intros (p', (G6, G7)); generalize (G5 _ G7);
intros [(G8, G9) | (p'', (F1, F2))];
[ tauto
| generalize (G3 (exist _ _ F1));
intros (q', (F3, (F4, F5)));
generalize (F4 _ F2); intro E; red in E; subst q';
case (F3 G6) ]
| case G4; clear G4; intro G4;
[ exact (abundance_config (proj1 H2) H3 G4)
| exact (G4 _ _ (fun p => sub_reflexive _)
(feature_maximality H2)) ] ]
| intros p' G4; generalize (G3 (exist _ _ G4));
intros (p'', (_, (_, G5))); trivial ]
| simpl; tauto ] ]
| intro G1; generalize (not_all_ex_not _ _ G1); clear G1;
intros (p', G1); generalize (imply_to_and _ _ G1); clear G1;
intros (G1, G2); generalize (imply_to_and _ _ G2); clear G2;
intros (G2, G3); generalize (not_ex_all_not _ _ G3); clear G3;
intro G3;
exists (f p'); split;
[ intros p'' G4; generalize (G3 p''); intro G5;
apply NNPP; intro G6; apply G5; auto
| exists p'; auto ] ]
| intros p1 p2 H3 H4 (q1, (q2, (H5, (H6, H7))));
exact (peace_config (proj1 H2) (H3 _ H5) (H4 _ H6) H7) ].
Qed.
(*
Lemma 39: one can associate an healthy configuration in the original
repository to any healthy configuration in the quotiented
repository.
*)
Lemma quotient_healthy_2 :
forall c f i s,
representative c f ->
healthy_config (quotient c f) i s ->
healthy_config c (preimg f i) (preimg f s).
intros c f i s H0 (H1, H2); split;
[ intros p d (q, (H3, E)) H4; subst q;
lapply (H1 (f p) (img f d) H3);
[ intros (q, (H5, (q', (H6, H7)))); subst q;
exists q'; split; trivial;
exists (f q'); auto
| exists d; split; trivial;
exact (proj1 (H0 p) _ H4) ]
| intros p p' (q, (H3, E1)) (q', (H4, E2)) H5; subst q q';
apply (H2 _ _ H3 H4);exists p; exists p'; auto ].
Qed.
(* Theorem 17: co-installability is left invariant by quotienting. *)
Theorem quotient_and_co_installability :
forall c f s, no_self_conflict c -> flat c -> representative c f ->
(weakly_co_installable c s <->
weakly_co_installable (quotient c f) (img f s)).
intros c f s A1 A2 A3; split;
[ intros (s', H1);
generalize (package_set_maximality H1);
intros (s'', (H2, H3));
exists (complimg f s'');
exact (quotient_healthy_1 A1 A2 A3 H2)
| intros (s', H1);
exists (preimg f s');
apply healthy_config_antimonotony with (2 := quotient_healthy_2 A3 H1);
intros p H2; exists (f p); split; trivial;
exists p; auto ].
Qed.
(* Technical lemma used to prove Theorem 18. *)
Lemma quotient_in_conflict :
forall c f p p',
in_conflict (quotient c f) p p' ->
exists q, exists q', p = f q /\ p' = f q' /\ in_conflict c q q'.
intros c f p p' [(q, (q', H1)) | (q', (q, H1))];
exists q; exists q'; unfold in_conflict; tauto.
Qed.
(*
Theorem 18: the quotiented repository is flat when the original
repository is.
*)
Lemma quotient_flat :
forall c f,
no_self_conflict c -> representative c f -> no_dep_on_conflict c ->
flat c -> flat (quotient c f).
intros c f A0 A1 A2 A3; case A3; intros H1 H2; split;
[ intros p d (p', (H3, E)); subst d; right;
generalize (quotient_in_conflict H3);
intros (q, (q', (E1, (E2, H4)))); subst p p';
lapply (@confl_dep_sub _ H1 q (singleton q));
[ intros (d, (H5, H6)); exists (img f d); split;
[ intros p (q'', (H7, E)); subst p;
generalize (H5 _ H7); intro E; rewrite E; red; trivial
| exists d; split; trivial;
apply (proj1 (A1 q)); trivial ]
| exists q'; auto ]
| intros p d'' (d', ((d, (H3, E1)), (g, (H4, E2)))); subst d' d'';
case
(classic (always_sat (conflicts (quotient c f))
(fun p => exists q, exists H : img f d q, g q H p)));
auto;
intro H5; right;
generalize
(fun H =>
H5 (@always_sat_when_internal_conflicts _ _
(quotient_and_self_conflicts A3 A1 A2) H));
clear H5; intro H5;
generalize
(choice (fun pH : {p | img f d p} => H4 _ (proj2_sig pH)));
clear H4; intros (dg, H4);
assert (H6 :
forall p, (exists H, dg H p) ->
exists p'',
f p = f p'' /\
exists q'', in_conflict c p'' q'' /\
forall H : {q' | img f d q'}, ~ img f (dg H) (f q''));
[ intros p1 (H6, H7);
generalize (not_ex_all_not _ _ H5);
clear H5; intro H5; generalize (not_and_or _ _ (H5 (f p1)));
clear H5; intro H5; generalize (or_to_imply _ _ H5);
clear H5; intro H5; lapply H5;
[ clear H5; intro H5; generalize (not_all_ex_not _ _ H5);
clear H5; intros (q1, H5); generalize (imply_to_and _ _ H5);
clear H5; intros (G1, G2);red in G1;
assert (G3 : exists p3, exists q3,
f p1 = f p3 /\ q1 = f q3 /\ in_conflict c p3 q3);
[ case G1;
[ intros (p3, (q3, (G3, (G4, G5)))); exists p3; exists q3;
unfold in_conflict; auto
| intros (q3, (p3, (G3, (G4, G5)))); exists p3; exists q3;
unfold in_conflict; auto ]
| revert G3; intros (p3, (q3, (G3, (G4, G5))));
exists p3; split; trivial; exists q3; split; trivial;
intros H; rewrite <- (proj2 (H4 H));
revert H; intros (q2, G6);
generalize (not_ex_all_not _ _ G2 q2);
clear G1 G2; intro G2; subst q1;
exact (not_ex_all_not _ _ G2 G6) ]
| exists (proj1_sig H6); exists (proj2_sig H6);
rewrite (proj2 (H4 H6)); exists p1; auto ]
| clear H5;
generalize
(choice (fun pH : {p | exists H, dg H p} =>
H6 _ (proj2_sig pH)));
clear H6; intros (h, H6);
assert (G1 :
forall d, @sub (set package) d (fun p => exists H, p = h H) ->
~ always_sat (conflicts c) d);
[ intros d' G1 G2;
generalize (always_sat_implies_internal_conflicts G2);
clear G2; intros (q, (G2, G3));
generalize (G1 _ G2); clear G2; intros (H, E); subst q;
generalize (H6 H); intros (G4, (q'', (G5, G6)));
generalize (G1 _ (G3 _ G5));
intros ((p', (G7, G8)), G9);
subst q'';
apply (G6 G7);
exists p'; split; trivial;
symmetry;
apply
(proj1 (H6 (exist (fun p' => _) _ (ex_intro (fun H => _) _ G8))))
| assert (G2 : forall p (H : d p),
exists d' : set package,
sub d' (fun p => exists H, p = h H) /\
depends c p d');
[ intros p' H5;
assert (G2 : forall H p'' (H' : dg H p''),
exists d' : set package,
sub d' (fun p => exists H, p = h H) /\
depends c p'' d');
[ intros H7 p'' H8;
pose (G3 := exist (fun p => exists H, dg H p) _
(ex_intro (fun H => _) _ H8));
assert (G2 : has_conflict c (h G3));
[ generalize (proj2 (H6 G3));
intros (q, (G4, _)); exists q; trivial
| generalize
(confl_dep_sub_confl (confl_dep_sub (f_refl A3)) G2);
intros (d', (G4, G5)); exists d'; split;
[ refine (sub_transitive G4 _);
intros q E; rewrite E; exists G3; trivial
| apply (proj2 (A1 p''));
generalize (proj1 (H6 G3)); simpl;
intro E; rewrite E;
apply (proj1 (A1 (h G3)));
trivial ] ]
| assert (H7 : img f d (f p'));
[ exists p'; auto
| generalize
(choice
(fun pH => G2 (exist _ _ H7)
(proj1_sig pH) (proj2_sig pH)));
intros (i, G3);
generalize
(dep_comp A3 (proj1 (H4 (exist _ _ H7)))
(sub_reflexive _)
(fun p H => proj2 (G3 (exist _ _ H))));
intros (d'', ([G4 | G4], G5));
[ exists d''; split;
[ refine (sub_transitive G5 _); clear G5;
intros q [(G5, G6) | (q', (H, G5))];
[ case (G6 G5)
| exact (proj1 (G3 (exist _ _ H)) _ G5) ]
| exact (proj2 (A1 p') _ G4) ]
| generalize
(always_sat_implies_internal_conflicts G4);
intros (q, (G6, G7));
generalize (G5 _ G6); clear G6;
intros [(G6, G8) | (q', (H, G6))];
[ case (G8 G6)
| generalize (proj1 (G3 _) _ G6);
clear G6; intros (H', E); subst q;
generalize (proj2 (H6 H'));
intros (q'', (G8, G9));
generalize (G7 _ G8); clear G7 G8; intro G7;
generalize (G5 _ G7); clear G7;
intros [(I1, I2) | (q1, (I1, I2))];
[ case (I2 I1)
| generalize (proj1 (G3 _) _ I2);
clear I2; intros (I3, E); subst q'';
rewrite <- (proj1 (H6 I3)) in G9;
revert I3 G9; simpl;
intros (q2, (H'', I4)) G9;
case (G9 H'');
exists q2; auto ] ] ] ] ]
| assert (G2' : exists f : (forall p, d p -> set package),
forall p (H : d p),
sub (f _ H) (fun p => exists H, p = h H) /\
depends c p (f _ H));
[ generalize
(choice (fun pH => G2 (proj1_sig pH) (proj2_sig pH)));
intros (i, G3);
exists (fun p H => i (exist _ _ H));
intros q H; exact (G3 (exist _ _ H))
| clear G2; revert G2'; intros (i, G2);
generalize
(dep_comp A3 H3 (@sub_reflexive _ _)
(fun p H => proj2 (G2 p H)));
intros (d'', ([G3 | G3], G4));
[ exists (img f d''); split;
[ intros q' (q, (G5, G6)); subst q';
generalize (G4 _ G5);
intros [(G6, G7) | (q', (H, G6))];
[ case (G7 G6)
| generalize (proj1 (G2 _ H) _ G6); clear G6;
intros (G6, G7); subst q;
rewrite <- (proj1 (H6 G6));
generalize G6; clear G5 G6;
intros (q1, ((q2, G5), G6));
exists q2; exists G5;
generalize
(proj2 (H4 (exist (fun p => img f d p) q2 G5)));
simpl; intro E; rewrite E; clear E;
exists q1; auto ]
| exists d''; auto ]
| case (fun H => G1 _ H G3);
intros q G5; generalize (G4 _ G5); clear G5;
intros [(G5, G6) | (q', (H, G5))];
[ case (G6 G5)
| exact (proj1 (G2 _ H) _ G5) ] ] ] ] ] ] ].
Qed.
(*************************************************************)
(* Reflexive transitive reduction (Section 10). *)
(* Lemma 19, and an immediate corollary. *)
Lemma remove_trans_healthy :
forall c p d i,
let c' := remove_dep c p d in
(dep_fun_compose (depends c') (depends c') p d) ->
healthy c' i -> healthy c i.
intros c p d i c' (d'', (H1, (f, (H2, E)))) (H3, H4); split; trivial;
intros p' d' H5 H6;
case (classic (p' = p /\ d' = d));
[ intros (E1, E2); subst p' d' c';
generalize (H3 _ _ H5 H1); intros (p', (H7, H8));
generalize (H3 _ _ H7 (H2 _ H8)); intros (q, (G1, G2));
exists q; split; trivial;
rewrite E; exists p'; exists H8; trivial
| intro H7; exact (H3 _ _ H5 (conj H6 H7)) ].
Qed.
Lemma remove_trans_co_installable :
forall c p d i,
let c' := remove_dep c p d in
(dep_fun_compose (depends c') (depends c') p d) ->
co_installable c' i -> co_installable c i.
intros c p d i c' H1 (s, (H2, H3)); exists s; split; trivial;
exact (remove_trans_healthy H1 H2).
Qed.
(* We define what it means to remove self-dependencies. *)
Definition no_self_dep c :=
Build_constraints (fun p d => depends c p d /\ ~ d p) (conflicts c).
(* Lemma 20. *)
Lemma no_self_dep_healthy :
forall c i, healthy (no_self_dep c) i -> healthy c i.
intros c i (H1, H2); split; trivial;
intros p d H3 H4; case (classic (d p)); intro H5;
[ exists p; split; trivial
| apply (H1 p); trivial;
split; trivial ].
Qed.
(*
Co-installability is left invariant when removing self-dependencies
(not explicitly in the paper).
*)
Lemma no_self_dep_smaller : forall c, sub (no_self_dep c) c.
intros c; split;
[ apply dsub_incl; intros p d (H1, H2); trivial
| intro p; apply sub_reflexive ].
Qed.
Lemma no_self_dep_co_installable :
forall c s, co_installable (no_self_dep c) s <-> co_installable c s.
intros c s; split;
[ intros (s', (H1, H2)); exists s'; split; trivial;
exact (no_self_dep_healthy H1)
| apply constraint_weakening_and_co_installability;
apply no_self_dep_smaller ].
Qed.
(*************************************************************)
(* Putting all together (Section 11). *)
(* First, some definition useful to specify an algorithm. *)
Definition seq A step1 step2 (c c'' : A) :=
exists c' : A, step1 c c' /\ step2 c' c''.
Inductive repeat A (step : A -> A -> Prop) : A -> A -> Prop :=
| rep_zero :
forall c, repeat step c c
| rep_succ :
forall c c' c'', repeat step c c' -> step c' c'' -> repeat step c c''.
Definition assert A P (c c' : A) := c' = c /\ P c.
Infix "++" := seq.
Lemma seq_elim :
forall A (P : Prop) (step1 step2 : A -> A -> Prop) c c',
seq step1 step2 c c' -> (forall c'', step1 c c'' -> step2 c'' c' -> P) -> P.
intros A P step1 step2 c c' (c'', (H1, H2)); eauto.
Qed.
Lemma repeat_elim :
forall A (P : A -> Prop) (step : A -> A -> Prop) c c',
repeat step c c' -> (forall c c', step c c' -> (P c <-> P c')) ->
(P c <-> P c').
intros A P step c c' H1 H2; induction H1;
[ reflexivity
| rewrite IHrepeat; auto ].
Qed.
(*
We now specify the algorithm. Note that we do not prove formally any
termination result when operations are repeated, but there are
simple arguments for that in each case. Thus, the specification just
states that some numbers of repetitions have been performed.
*)
Definition flatten c c' := c' = flattened c.
Definition canonise (c c' : constraints) := equiv c c'.
Definition remove_clearly_irrelevant_deps c c' := c' = simplified c.
Definition remove_clearly_broken c c' :=
exists p, clearly_broken c p /\ c' = strength_dep c p.
Definition remove_redundant_conflict c c' :=
exists p1, exists p2,
redundant_conflict c p1 p2 /\ c' = remove_confl c p1 p2.
Definition remove_conflict_covered_deps c c' :=
exists d, exists p, exists q,
conflict_covered c d q /\
let c'' := remove_dep c p d in
~ sub d (singleton p) /\
(forall d' : set package,
dep_fun_compose (depends c') (depends c') p d' -> ~ sub d d') /\
c' = c''.
Definition perform_quotient f c c' :=
representative c f /\ c' = quotient c f.
Definition phase1 :=
flatten ++ canonise ++ remove_clearly_irrelevant_deps ++
repeat remove_clearly_broken ++ repeat remove_redundant_conflict.
Definition simplification f :=
repeat phase1
++
flatten
++
assert no_dep_on_conflict
++
repeat remove_conflict_covered_deps
++
perform_quotient f.
(* We have two technical lemmas regarding phase 1. *)
Lemma phase1_and_co_installability :
forall c c' i, phase1 c c' -> (co_installable c i <-> co_installable c' i).
intros c1 c4 i H1;
apply (seq_elim H1); clear H1; unfold flatten; intros c2 E H2; subst c2;
apply (seq_elim H2); clear H2; unfold canonise; intros c2 H1 H2;
apply (seq_elim H2); clear H2; unfold remove_clearly_irrelevant_deps;
intros c3 E H2; subst c3;
apply (seq_elim H2); clear H2; intros c3 H2 H3;
transitivity (co_installable c2 i);
[ transitivity (co_installable (flattened c1) i);
[ split;
[ apply flatten_co_inst_prop_1
| intro H4; apply flatten_co_inst_prop_3;
apply flatten_co_inst_prop_5; trivial ]
| split; apply constraint_weakening_and_co_installability;
case H1;trivial ]
| transitivity (co_installable (simplified c2) i);
[ assert (H4 : flat c2);
[ apply strongly_flat_implies_flat;
apply (strongly_flat_preserved H1);
apply flattened_strongly_flat
| split; intro H5;
[ apply weakly_co_installable_implies_co_installable_3;
[ apply
removing_clearly_irrelevant_dependencies_preserves_flatness;
trivial
| rewrite <-
removing_clearly_irrelevant_dependencies_and_weak_co_installability;
apply co_installable_implies_weakly_co_installable;
trivial ]
| apply weakly_co_installable_implies_co_installable_3; trivial;
rewrite
removing_clearly_irrelevant_dependencies_and_weak_co_installability;
apply co_installable_implies_weakly_co_installable;
trivial ] ]
| transitivity (co_installable c3 i);
[ apply (repeat_elim (P := fun c => co_installable c i) H2);
intros c c' (p, (H4, E)); subst c';
assert (H5 := clearly_broken_not_installable H4);
split; intros (i', (H6, H7)); exists i'; split; trivial;
apply (strenghten_dependence_of_conflicting_package _ H5); trivial
| apply (repeat_elim (P := fun c => co_installable c i) H3);
intros c c' (p1, (p2, (H4, E))); subst c';
split; intros (i', (H6, H7)); exists i'; split; trivial;
[ apply constraint_weakening with (2 := H6); split;
[ apply sub_reflexive
| intros p p' (H8, H9); trivial ]
| apply
(redundant_conflict_removal_and_healthiness H4 H6) ] ] ] ].
Qed.
Lemma phase1_preserves_no_self_conflict :
forall c c', phase1 c c' -> no_self_conflict c -> no_self_conflict c'.
intros c1 c4 H1;
apply (seq_elim H1); clear H1; unfold flatten; intros c2 E H2; subst c2;
apply (seq_elim H2); clear H2; unfold canonise; intros c2 H1 H2;
apply (seq_elim H2); clear H2; unfold remove_clearly_irrelevant_deps;
intros c3 E H2; subst c3;
apply (seq_elim H2); clear H2; intros c3 H2 H3 H4;
assert (H5 : no_self_conflict c2);
[ assert (H5 : no_self_conflict (flattened c1));
[ exact H4
| intros p H6; apply (H5 p); apply (proj2 (proj2 H1)); trivial ]
| assert (H6 : no_self_conflict (simplified c2));
[ exact H5
| assert (H7 : no_self_conflict c3);
[ clear H3; induction H2; trivial;
revert H; intros (p, (H7, E)); subst c''; apply IHrepeat; auto
| induction H3; trivial;
revert H; intros (p1, (p2, (H8, E))); subst c'';
intros p (H9, _); revert p H9; apply IHrepeat; trivial ] ] ].
Qed.
(* We can finally prove Theorem 21. *)
Lemma simplification_and_co_installability :
forall f c c' i, no_self_conflict c -> simplification f c c' ->
(co_installable c i <-> co_installable c' (img f i)) /\ flat c'.
intros f c1 c4 i A1 H1;
apply (seq_elim H1); clear H1; intros c2 H1 H2;
apply (seq_elim H2); clear H2; unfold flatten; intros c' E H2; subst c';
apply (seq_elim H2); clear H2; intros c' (E, H2) H3; subst c';
apply (seq_elim H3); clear H3; intros c3 H3 (H4, E); subst c4;
assert (A2 : (co_installable c1 i <-> co_installable (flattened c2) i)
/\ flat (flattened c2) /\ no_self_conflict (flattened c2)
/\ no_dep_on_conflict (flattened c2));
[ assert (A2 : (co_installable c1 i <-> co_installable c2 i)
/\ no_self_conflict c2);
[ split;
[ apply (repeat_elim H1 (P := fun c => co_installable c i));
intros c c'; apply phase1_and_co_installability
| clear H2 H3; induction H1; trivial;
generalize (phase1_preserves_no_self_conflict H); auto ]
| rewrite (proj1 A2); split;
[ split;
[ apply flatten_co_inst_prop_1
| intro H5; apply flatten_co_inst_prop_3;
apply flatten_co_inst_prop_5; trivial ]
| split;
[ apply strongly_flat_implies_flat; apply flattened_strongly_flat
| split; trivial;
exact (proj2 A2) ] ] ]
| rewrite (proj1 A2); clear A1 H1;
assert (A1 : (co_installable (flattened c2) i <-> co_installable c3 i)
/\ flat c3 /\ no_self_conflict c3 /\ no_dep_on_conflict c3);
[ clear H2 H4;
induction H3;
[ tauto
| revert H; intros (d, (p, (q, (G1, (G2, (G3, G4))))));
subst c''; assert (G4 : flat (remove_dep c' p d));
[ apply (removal_preserves_flatness G2 G3); tauto
| split;
[ rewrite (proj1 (IHrepeat A2)); split;
[ intro G5;
apply weakly_co_installable_implies_co_installable_3;
trivial;
apply
constraint_weakening_config_and_co_installability
with
(2 :=
co_installable_implies_weakly_co_installable
G5);
split;
[ intros p' d' (G6, G7);
exists d'; split; trivial;
apply sub_reflexive
| intro p'; apply sub_reflexive ]
| intro G5;
assert (G6 := proj1 (proj2 (proj2 (IHrepeat A2))));
assert (G7 := proj1 (proj2 (IHrepeat A2)));
apply
weakly_co_installable_implies_co_installable_3;
trivial;
apply (remove_conflict_covered (p := p) G6 G7 G1);
apply co_installable_implies_weakly_co_installable;
trivial ]
| split; trivial;
split;
[ exact (proj1 (proj2 (proj2 (IHrepeat A2))))
| intros p' d' q' (G5, _); revert p' d' q' G5;
exact (proj2 (proj2 (proj2 (IHrepeat A2)))) ] ] ] ]
| clear A2; revert A1; intros (A1, (A2, (A3, A4))); rewrite A1; split;
[ split;
[ intro G1;
apply (weakly_co_installable_implies_co_installable_3
(quotient_flat A3 H4 A4 A2));
apply (quotient_and_co_installability i A3 A2 H4);
apply co_installable_implies_weakly_co_installable; trivial
| intro G1;
apply (weakly_co_installable_implies_co_installable_3 A2);
apply (quotient_and_co_installability i A3 A2 H4);
apply co_installable_implies_weakly_co_installable; trivial ]
| exact (quotient_flat A3 H4 A4 A2) ] ] ].
Qed.
(*
The repetition of phase 1 should terminate. The argument is that
the "remove clearly broken" phase either do nothing or stricly
increases the number of packages with empty dependencies. Other
steps in phase 1 preserves or increases this number of packages.
We prove below that this is the case for flattening.
*)
Lemma flatten_and_empty_dep :
forall c p d,
depends c p d -> sub d (fun _ => False) ->
exists d', depends (flattened c) p d' /\ sub d' (fun _ => False).
intros c p d H1 H2;
assert (f : forall q : package, d q -> below_conflicts c q);
[ intros H3 H4; case (H2 _ H4)
| pose (dep := higher_conflicts H1 f);
exists (flattened_dep dep); split;
[ exists dep; trivial
| simpl; intros q (q', (H3, H4)); exact (H2 _ H3) ] ].
Qed.
(*************************************************************)
(* Shapes of installations *)
(*
To prove that a package is weakly installable, one only needs to
consider the packages it depends on.
*)
Lemma installability_shape :
forall c p,
weakly_co_installable c (singleton p) ->
exists s, healthy_config c (singleton p) s /\
forall q, s q -> exists d, depends c p d /\ d q.
intros c p (s, (H1, H2));
exists (fun q => s q /\ exists d : set package, depends c p d /\ d q); split;
[ split;
[ intros p' d H3 H4; generalize (H1 _ _ H3 H4);
intros (q, (H5, H6)); exists q; repeat split; trivial;
rewrite <- H3; exists d; split; trivial
| intros p' p'' (H3, _) (H4, _); apply H2; trivial ]
| tauto ].
Qed.
(*
The following lemma can be used to prune down the number of pairs of
packages to consider when computing strong conflicts.
If two weakly installable packages p and p' are not weakly
co-installable, one can find two conflicting packages p' and q'
such that p depends on p' and q depends on q'
*)
Lemma strong_conflict_shape :
forall c p p',
weakly_co_installable c (singleton p) ->
weakly_co_installable c (singleton p') ->
~ weakly_co_installable c (fun q => q = p \/ q = p') ->
exists d, exists d', exists q, exists q',
depends c p d /\ depends c p' d' /\ d q /\ d' q' /\ in_conflict c q q'.
intros c p p' H1 H2 H3;
generalize (installability_shape H1); intros (s, (H4, H5));
generalize (installability_shape H2); intros (s', (H6, H7));
apply NNPP; intro H8; apply H3;
exists (fun q => s q \/ s' q); split;
[ intros q d [G1 | G1] G2;
[ generalize (abundance_config H4 G1 G2); subst q; intros (q, (G3, G4));
exists q; auto
| generalize (abundance_config H6 G1 G2); subst q; intros (q, (G3, G4));
exists q; auto ]
| intros q q' [G1 | G1] [G2 | G2] G3;
[ exact (peace_config H4 G1 G2 G3)
| apply H8;
generalize (H5 _ G1); intros (d, (G4, G5));
generalize (H7 _ G2); intros (d', (G6, G7));
exists d; exists d'; exists q; exists q'; repeat (split; trivial);
red; auto
| apply H8;
generalize (H5 _ G2); intros (d, (G4, G5));
generalize (H7 _ G1); intros (d', (G6, G7));
exists d; exists d'; exists q'; exists q; repeat (split; trivial);
red; auto
| exact (peace_config H6 G1 G2 G3) ] ].
Qed.
coinst-1.9.3/viewer/ 0000755 0001750 0001750 00000000000 12657630652 013276 5 ustar mehdi mehdi coinst-1.9.3/viewer/dot_lexer.mli 0000644 0001750 0001750 00000001625 12657630652 015772 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
val reset : unit -> unit
val token : Lexing.lexbuf -> Dot_parser.token
coinst-1.9.3/viewer/scene_json.ml 0000644 0001750 0001750 00000005675 12657630652 015773 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
open Scene
let array_stringify f ch l =
Format.fprintf ch "@[<1>[0";
Array.iter (fun e -> Format.fprintf ch ",@,%a" f e) l;
Format.fprintf ch "]@]"
let string_stringify ch s =
(*XXX Escape! *)
Format.fprintf ch "\"%s\"" s
let color_stringify ch c =
match c with
None ->
Format.fprintf ch "0"
| Some (r, g, b) ->
let h v = truncate (v *. 255.99) in
Format.fprintf ch "@[<1>[0,@,%a]@]"
string_stringify (Format.sprintf "#%02x%02x%02x" (h r) (h g) (h b))
let font_stringify ch (font, size) =
Format.fprintf ch "%a" string_stringify (Format.sprintf "%gpx %s" size font)
let command_stringify ch c =
match c with
Move_to (x, y) ->
Format.fprintf ch "@[<1>[0,@,%g,@,%g]@]" x y
| Curve_to (x1, y1, x2, y2, x3, y3) ->
Format.fprintf ch "@[<1>[1,@,%g,@,%g,@,%g,@,%g,@,%g,@,%g]@]"
x1 y1 x2 y2 x3 y3
let commands_stringify = array_stringify command_stringify
let point_stringify ch (x, y) = Format.fprintf ch "@[<1>[0,@,%g,@,%g]@]" x y
let points_stringify = array_stringify point_stringify
let rect_stringify ch (x1, y1, x2, y2) =
Format.fprintf ch "@[<1>[0,@,%g,@,%g,@,%g,@,%g]@]" x1 y1 x2 y2
let rect_array_stringify = array_stringify rect_stringify
let element_stringify ch e =
match e with
Path (cmds, fill, stroke, style) ->
Format.fprintf ch "@[<1>[0,@,%a,@,%a,@,%a,@,%a]@]"
commands_stringify cmds color_stringify fill color_stringify stroke
string_stringify style
| Polygon (l, fill, stroke, style) ->
Format.fprintf ch "@[<1>[1,@,%a,@,%a,@,%a,@,%a]@]"
points_stringify l color_stringify fill color_stringify stroke
string_stringify style
| Ellipse (cx, cy, rx, ry, fill, stroke, style) ->
Format.fprintf ch "@[<1>[2,@,%g,@,%g,@,%g,@,%g,@,%a,@,%a,@,%a]@]"
cx cy rx ry color_stringify fill color_stringify stroke
string_stringify style
| Text (x, y, txt, font, fill, stroke) ->
Format.fprintf ch "@[<1>[3,@,%g,@,%g,@,%a,@,%a,@,%a,@,%a]@]"
x y string_stringify txt font_stringify font
color_stringify fill color_stringify stroke
let stringify = array_stringify element_stringify
coinst-1.9.3/viewer/scene_extents.mli 0000644 0001750 0001750 00000001707 12657630652 016655 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
val compute :
Cairo.t -> ('color, string * float, string) Scene.element array ->
(float * float * float * float) array
coinst-1.9.3/viewer/viewer_common.ml 0000644 0001750 0001750 00000020752 12657630652 016507 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
open Scene
let pi = 4. *. atan 1.
(****)
module F (M : sig
type font
type color
type text
val white : color
type ctx
val save : ctx -> unit
val restore : ctx -> unit
val scale : ctx -> sx:float -> sy:float -> unit
val translate : ctx -> tx:float -> ty:float -> unit
val set_line_width : ctx -> float -> unit
val begin_path : ctx -> unit
val close_path : ctx -> unit
val move_to : ctx -> x:float -> y:float -> unit
val line_to : ctx -> x:float -> y:float -> unit
val curve_to :
ctx ->
x1:float -> y1:float -> x2:float -> y2:float -> x3:float -> y3:float ->
unit
val arc :
ctx ->
xc:float -> yc:float -> radius:float -> angle1:float -> angle2:float ->
unit
val rectangle :
ctx -> x:float -> y:float -> width:float -> height:float -> unit
val fill : ctx -> color -> unit
val stroke : ctx -> color -> unit
val clip : ctx -> unit
val draw_text :
ctx -> float -> float -> text ->
font -> color option -> color option -> unit
type window
type drawable
type pixmap
val get_drawable : window -> drawable
val make_pixmap : window -> int -> int -> pixmap
val drawable_of_pixmap : pixmap -> drawable
val get_context : pixmap -> ctx
val put_pixmap :
dst:drawable ->
x:int -> y:int -> xsrc:int -> ysrc:int -> width:int -> height:int ->
pixmap -> unit
(****)
type rectangle = {x : int; y : int; width : int; height: int}
val compute_extents :
ctx ->
(color, font, text) Scene.element array ->
(float * float * float * float) array
end) = struct
open M
let empty_rectangle = {x = 0; y = 0; width = 0; height = 0}
let rectangle_is_empty r = r.width = 0 || r.height = 0
(****)
type pixmap =
{ mutable pixmap : M.pixmap option;
mutable p_width : int; mutable p_height : int;
mutable valid_rect : rectangle }
let make_pixmap () =
{ pixmap = None; p_width = -1; p_height = -1;
valid_rect = empty_rectangle }
let invalidate_pixmap p = p.valid_rect <- empty_rectangle
let grow_pixmap pm window width height =
let width = max width pm.p_width in
let height = max height pm.p_height in
if width > pm.p_width || height > pm.p_height then begin
let old_p = pm.pixmap in
let p = M.make_pixmap window width height in
let r = pm.valid_rect in
begin match old_p with
Some old_p ->
put_pixmap ~dst:(drawable_of_pixmap p)
~x:0 ~y:0 ~xsrc:0 ~ysrc:0 ~width:r.width ~height:r.height old_p
| None ->
()
end;
pm.pixmap <- Some p;
pm.p_width <- width;
pm.p_height <- height
end
let get_pixmap pm = match pm.pixmap with Some p -> p | None -> assert false
(****)
type st =
{ mutable bboxes : (float * float * float * float) array;
scene : (color, font, text) Scene.element array;
mutable zoom_factor : float;
st_x : float; st_y : float; st_width : float; st_height : float;
st_pixmap : pixmap }
(****)
let perform_draw ctx fill stroke =
begin match fill with
Some c -> M.fill ctx c
| None -> ()
end;
begin match stroke with
Some c -> M.stroke ctx c
| None -> ()
end
let draw_element ctx e =
begin_path ctx;
match e with
Path (cmd, fill, stroke, _) ->
Array.iter
(fun c ->
match c with
Move_to (x, y) ->
move_to ctx x y
| Curve_to (x1, y1, x2, y2, x3, y3) ->
curve_to ctx x1 y1 x2 y2 x3 y3)
cmd;
perform_draw ctx fill stroke
| Ellipse (cx, cy, rx, ry, fill, stroke, _) ->
save ctx;
translate ctx cx cy;
scale ctx rx ry;
arc ctx 0. 0. 1. 0. (2. *. pi);
restore ctx;
perform_draw ctx fill stroke
| Polygon (points, fill, stroke, _) ->
Array.iteri
(fun i (x, y) ->
if i = 0 then move_to ctx x y else line_to ctx x y)
points;
close_path ctx;
perform_draw ctx fill stroke
| Text (x, y, txt, font, fill, stroke) ->
draw_text ctx x y txt font fill stroke
let intersects
((x1, y1, x2, y2) : float * float * float * float) (x3, y3, x4, y4) =
x1 <= x4 && y1 <= y4 && x3 <= x2 && y3 <= y2
let compute_scale st range =
st.zoom_factor ** range#adjustment#value /. st.zoom_factor
let redraw st scale x y x' y' w h =
(*
Format.eprintf "REDRAW %d %d %d %d@." x' y' w h;
*)
let ctx = get_context (get_pixmap st.st_pixmap) in
save ctx;
if Array.length st.bboxes = 0 && Array.length st.scene > 0 then
st.bboxes <- compute_extents ctx st.scene;
begin_path ctx;
rectangle ctx (float x') (float y') (float w) (float h);
M.fill ctx M.white;
clip ctx;
let x = float x /. scale in
let y = float y /. scale in
M.scale ctx scale scale;
M.set_line_width ctx (max 2. (0.5 /. scale));
translate ctx (-. st.st_x -. x) (-. st.st_y -. y);
let bbox =
let x = st.st_x +. x +. float x' /. scale in
let y = st.st_y +. y +. float y' /. scale in
(x, y,
x +. float st.st_pixmap.p_width /. scale,
y +. float st.st_pixmap.p_height /. scale)
in
for i = 0 to Array.length st.scene - 1 do
let box = st.bboxes.(i) in
let e = st.scene.(i) in
if intersects box bbox then draw_element ctx e
done;
restore ctx
let redraw st scale x0 y0 window a x y width height =
let pm = st.st_pixmap in
grow_pixmap pm window a.width a.height;
let round x = truncate (x *. scale +. 0.5) in
let x0 = round x0 in
let x0' = round ((float a.width /. scale -. st.st_width) /. 2.) in
let x0 = if x0' > 0 then - x0' else x0 in
let y0 = round y0 in
let y0' = round ((float a.height /. scale -. st.st_height) /. 2.) in
let y0 = if y0' > 0 then - y0' else y0 in
let dx = pm.valid_rect.x - x0 in
let dy = pm.valid_rect.y - y0 in
(*
Firebug.console##log_6 (dx, pm.valid_rect.width, a.width,
dy, pm.valid_rect.height, a.height);
*)
if
(dx > 0 && pm.valid_rect.width + dx < a.width) ||
(dy > 0 && pm.valid_rect.height + dy < a.height)
then begin
pm.valid_rect <- empty_rectangle
end else if not (rectangle_is_empty pm.valid_rect) then begin
(*XXX FIX: should redraw up to four rectangles here *)
(*XXX FIX: does not change pm.valid_rect when it is large enough already and valid *)
let p = get_pixmap pm in
let r = pm.valid_rect in
(*
Format.eprintf "Translation: %d %d@." dx dy;
*)
if (dx <> 0 || dy <> 0) then
put_pixmap ~dst:(drawable_of_pixmap p) ~x:dx ~y:dy
~xsrc:0 ~ysrc:0 ~width:r.width ~height:r.height p;
let offset p l d m = (* 0 <= p; 0 <= l; p + l <= m *)
if p + d + l <= 0 then
(0, 0)
else if p + d < 0 then
(0, l + p + d)
else if p + d >= m then
(m, 0)
else if p + d + l > m then
(p + d, m - p - d)
else
(p + d, l)
in
let (x, width) = offset 0 r.width dx pm.p_width in
let (y, height) = offset 0 r.height dy pm.p_height in
if height > 0 then begin
if x > 0 then begin
assert (x + width >= a.width);
redraw st scale x0 y0 0 y x height
end else begin
assert (x = 0);
if a.width > width then
redraw st scale x0 y0 width y (a.width - width) height
end
end;
if y > 0 then begin
assert (y + height >= a.height);
redraw st scale x0 y0 0 0 a.width y;
end else begin
assert (y = 0);
if a.height > height then
redraw st scale x0 y0 0 height a.width (a.height - height)
end;
pm.valid_rect <- { x = x0; y = y0; width = a.width; height = a.height }
end;
let r = pm.valid_rect in
if
x < 0 || y < 0 ||
x + width > r.width || y + height > r.height
then begin
redraw st scale x0 y0 0 0 a.width a.height;
pm.valid_rect <- {x = x0; y = y0; width = a.width; height = a.height };
end;
put_pixmap
~dst:(get_drawable window) ~x ~y ~xsrc:x ~ysrc:y ~width ~height
(get_pixmap pm)
end
coinst-1.9.3/viewer/svg.ml 0000644 0001750 0001750 00000043267 12657630652 014443 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
type command =
Move_to of float * float
| Curve_to of float * float * float * float * float * float
type color = float * float * float
type element =
Path of command list * color option * color option
| Ellipse of float * float * float * float * color option * color option
| Polygon of (float * float) list * color option * color option
| Text of
float * float * string * string * float * color option * color option
(****)
let width = 16499.
let height = 22807.
let h = (*8192*)2000
let w = truncate (width *. float h /. height +. 0.5)
let s = Cairo.image_surface_create Cairo.FORMAT_ARGB32 w h
let perform_draw ctx fill stroke =
(*
print_extent ctx fill stroke;
*)
begin match fill with
Some (r, g, b) ->
Cairo.set_source_rgb ctx r g b;
if stroke <> None then Cairo.fill_preserve ctx
else Cairo.fill ctx
| None ->
()
end;
begin match stroke with
Some (r, g, b) ->
Cairo.set_source_rgb ctx r g b;
Cairo.stroke ctx
| None ->
()
end
let pi = 4. *. atan 1.
let draw_element ctx e =
match e with
Path (cmd, fill, stroke) ->
List.iter
(fun c ->
match c with
Move_to (x, y) ->
Cairo.move_to ctx x y
| Curve_to (x1, y1, x2, y2, x3, y3) ->
Cairo.curve_to ctx x1 y1 x2 y2 x3 y3)
cmd;
perform_draw ctx fill stroke
| Ellipse (cx, cy, rx, ry, fill, stroke) ->
Cairo.save ctx;
Cairo.translate ctx cx cy;
Cairo.scale ctx rx ry;
Cairo.arc ctx 0. 0. 1. 0. (2. *. pi);
Cairo.restore ctx;
perform_draw ctx fill stroke
| Polygon (points, fill, stroke) ->
begin match points with
(x, y) :: rem ->
Cairo.move_to ctx x y;
List.iter (fun (x, y) -> Cairo.line_to ctx x y) rem;
Cairo.close_path ctx;
perform_draw ctx fill stroke
| [] ->
()
end
| Text (x, y, txt, font, font_size, fill, stroke) ->
let ext = Cairo.text_extents ctx txt in
Cairo.move_to ctx
(x -. ext.Cairo.x_bearing -. ext.Cairo.text_width /. 2.) y;
Cairo.select_font_face ctx font
Cairo.FONT_SLANT_NORMAL Cairo.FONT_WEIGHT_NORMAL;
Cairo.set_font_size ctx font_size;
Cairo.show_text ctx txt;
perform_draw ctx fill stroke
let path_extent ctx fill stroke =
if stroke <> None then Cairo.stroke_extents ctx
else Cairo.fill_extents ctx
let compute_extent ctx e =
Cairo.new_path ctx;
match e with
Path (cmd, fill, stroke) ->
List.iter
(fun c ->
match c with
Move_to (x, y) ->
Cairo.move_to ctx x y
| Curve_to (x1, y1, x2, y2, x3, y3) ->
Cairo.curve_to ctx x1 y1 x2 y2 x3 y3)
cmd;
path_extent ctx fill stroke
| Ellipse (cx, cy, rx, ry, fill, stroke) ->
Cairo.save ctx;
Cairo.translate ctx cx cy;
Cairo.scale ctx rx ry;
Cairo.arc ctx 0. 0. 1. 0. (2. *. pi);
Cairo.restore ctx;
path_extent ctx fill stroke
| Polygon (points, fill, stroke) ->
begin match points with
(x, y) :: rem ->
Cairo.move_to ctx x y;
List.iter (fun (x, y) -> Cairo.line_to ctx x y) rem;
Cairo.close_path ctx;
path_extent ctx fill stroke
| [] ->
assert false
end
| Text (x, y, txt, font, font_size, fill, stroke) ->
let ext = Cairo.text_extents ctx txt in
(x -. ext.Cairo.text_width /. 2.,
y +. ext.Cairo.y_bearing,
x +. ext.Cairo.text_width /. 2.,
y +. ext.Cairo.y_bearing +. ext.Cairo.text_height)
let ctx = Cairo.create s
let scale = float h /. height
let _ = Cairo.scale ctx scale scale; Cairo.translate ctx 364. 22443.
(****)
let convert (r, g, b) =
let c i = float i /. 255.99 in
(c r, c g, c b)
let named_colors =
let colors = Hashtbl.create 101 in
List.iter (fun (nm, v) -> Hashtbl.add colors nm (convert v))
["aliceblue", (240, 248, 255);
"antiquewhite", (250, 235, 215);
"aqua", ( 0, 255, 255);
"aquamarine", (127, 255, 212);
"azure", (240, 255, 255);
"beige", (245, 245, 220);
"bisque", (255, 228, 196);
"black", ( 0, 0, 0);
"blanchedalmond", (255, 235, 205);
"blue", ( 0, 0, 255);
"blueviolet", (138, 43, 226);
"brown", (165, 42, 42);
"burlywood", (222, 184, 135);
"cadetblue", ( 95, 158, 160);
"chartreuse", (127, 255, 0);
"chocolate", (210, 105, 30);
"coral", (255, 127, 80);
"cornflowerblue", (100, 149, 237);
"cornsilk", (255, 248, 220);
"crimson", (220, 20, 60);
"cyan", ( 0, 255, 255);
"darkblue", ( 0, 0, 139);
"darkcyan", ( 0, 139, 139);
"darkgoldenrod", (184, 134, 11);
"darkgray", (169, 169, 169);
"darkgreen", ( 0, 100, 0);
"darkgrey", (169, 169, 169);
"darkkhaki", (189, 183, 107);
"darkmagenta", (139, 0, 139);
"darkolivegreen", ( 85, 107, 47);
"darkorange", (255, 140, 0);
"darkorchid", (153, 50, 204);
"darkred", (139, 0, 0);
"darksalmon", (233, 150, 122);
"darkseagreen", (143, 188, 143);
"darkslateblue", ( 72, 61, 139);
"darkslategray", ( 47, 79, 79);
"darkslategrey", ( 47, 79, 79);
"darkturquoise", ( 0, 206, 209);
"darkviolet", (148, 0, 211);
"deeppink", (255, 20, 147);
"deepskyblue", ( 0, 191, 255);
"dimgray", (105, 105, 105);
"dimgrey", (105, 105, 105);
"dodgerblue", ( 30, 144, 255);
"firebrick", (178, 34, 34);
"floralwhite", (255, 250, 240);
"forestgreen", ( 34, 139, 34);
"fuchsia", (255, 0, 255);
"gainsboro", (220, 220, 220);
"ghostwhite", (248, 248, 255);
"gold", (255, 215, 0);
"goldenrod", (218, 165, 32);
"gray", (128, 128, 128);
"grey", (128, 128, 128);
"green", ( 0, 128, 0);
"greenyellow", (173, 255, 47);
"honeydew", (240, 255, 240);
"hotpink", (255, 105, 180);
"indianred", (205, 92, 92);
"indigo", ( 75, 0, 130);
"ivory", (255, 255, 240);
"khaki", (240, 230, 140);
"lavender", (230, 230, 250);
"lavenderblush", (255, 240, 245);
"lawngreen", (124, 252, 0);
"lemonchiffon", (255, 250, 205);
"lightblue", (173, 216, 230);
"lightcoral", (240, 128, 128);
"lightcyan", (224, 255, 255);
"lightgoldenrodyellow", (250, 250, 210);
"lightgray", (211, 211, 211);
"lightgreen", (144, 238, 144);
"lightgrey", (211, 211, 211);
"lightpink", (255, 182, 193);
"lightsalmon", (255, 160, 122);
"lightseagreen", ( 32, 178, 170);
"lightskyblue", (135, 206, 250);
"lightslategray", (119, 136, 153);
"lightslategrey", (119, 136, 153);
"lightsteelblue", (176, 196, 222);
"lightyellow", (255, 255, 224);
"lime", ( 0, 255, 0);
"limegreen", ( 50, 205, 50);
"linen", (250, 240, 230);
"magenta", (255, 0, 255);
"maroon", (128, 0, 0);
"mediumaquamarine", (102, 205, 170);
"mediumblue", ( 0, 0, 205);
"mediumorchid", (186, 85, 211);
"mediumpurple", (147, 112, 219);
"mediumseagreen", ( 60, 179, 113);
"mediumslateblue", (123, 104, 238);
"mediumspringgreen", ( 0, 250, 154);
"mediumturquoise", ( 72, 209, 204);
"mediumvioletred", (199, 21, 133);
"midnightblue", ( 25, 25, 112);
"mintcream", (245, 255, 250);
"mistyrose", (255, 228, 225);
"moccasin", (255, 228, 181);
"navajowhite", (255, 222, 173);
"navy", ( 0, 0, 128);
"oldlace", (253, 245, 230);
"olive", (128, 128, 0);
"olivedrab", (107, 142, 35);
"orange", (255, 165, 0);
"orangered", (255, 69, 0);
"orchid", (218, 112, 214);
"palegoldenrod", (238, 232, 170);
"palegreen", (152, 251, 152);
"paleturquoise", (175, 238, 238);
"palevioletred", (219, 112, 147);
"papayawhip", (255, 239, 213);
"peachpuff", (255, 218, 185);
"peru", (205, 133, 63);
"pink", (255, 192, 203);
"plum", (221, 160, 221);
"powderblue", (176, 224, 230);
"purple", (128, 0, 128);
"red", (255, 0, 0);
"rosybrown", (188, 143, 143);
"royalblue", ( 65, 105, 225);
"saddlebrown", (139, 69, 19);
"salmon", (250, 128, 114);
"sandybrown", (244, 164, 96);
"seagreen", ( 46, 139, 87);
"seashell", (255, 245, 238);
"sienna", (160, 82, 45);
"silver", (192, 192, 192);
"skyblue", (135, 206, 235);
"slateblue", (106, 90, 205);
"slategray", (112, 128, 144);
"slategrey", (112, 128, 144);
"snow", (255, 250, 250);
"springgreen", ( 0, 255, 127);
"steelblue", ( 70, 130, 180);
"tan", (210, 180, 140);
"teal", ( 0, 128, 128);
"thistle", (216, 191, 216);
"tomato", (255, 99, 71);
"turquoise", ( 64, 224, 208);
"violet", (238, 130, 238);
"wheat", (245, 222, 179);
"white", (255, 255, 255);
"whitesmoke", (245, 245, 245);
"yellow", (255, 255, 0);
"yellowgreen", (154, 205, 50)];
colors
let svg_name nm = ("http://www.w3.org/2000/svg", nm)
let d_attr = ("", "d")
let x_attr = ("", "x")
let y_attr = ("", "y")
let cx_attr = ("", "cx")
let cy_attr = ("", "cy")
let rx_attr = ("", "rx")
let ry_attr = ("", "ry")
let points_attr = ("", "points")
let taxt_anchor_attr = ("", "text-anchor")
let font_family_attr = ("", "font-family")
let font_size_attr = ("", "font-size")
let fill_attr = ("", "fill")
let stroke_attr = ("", "stroke")
let stack = ref []
let push e = stack := e :: !stack
let skip_whitespace i =
(* XXX Check white-space only *)
match Xmlm.peek i with
`Data s -> ignore (Xmlm.input i)
| _ -> ()
let end_tag i =
let e = Xmlm.input i in
assert (e = `El_end)
let rec empty_tag i =
match Xmlm.input i with
`Data s -> (*Whitespace*) empty_tag i
| `El_end -> ()
| _ -> assert false
let rec text_tag i =
match Xmlm.input i with
`Data s -> empty_tag i; s
| `El_end -> ""
| _ -> assert false
let comma_wsp = Str.regexp "[\x20\x09\x0D\x0A,]+"
let cmd = Str.regexp "[a-zA-Z]"
let rec parse_curve_to args rem =
match args with
[] ->
rem
| x1 :: y1 :: x2 :: y2 :: x3 :: z3 :: r ->
Curve_to (x1, y1, x2, y2, x3, z3) :: parse_curve_to r rem
| _ ->
assert false
let rec parse_cmds l =
match l with
Str.Delim cmd :: Str.Text args :: rem ->
let args = List.map float_of_string (Str.split comma_wsp args) in
let rem = parse_cmds rem in
begin match cmd, args with
"M", [x; y] ->
Move_to (x, y) :: rem
| "C", (_ :: _ as args) ->
parse_curve_to args rem
| _ ->
assert false
end
| [] ->
[]
| _ ->
assert false
let parse_path s =
let l = Str.full_split cmd s in
parse_cmds l
let parse_color c =
if c = "none" then None else
if String.length c = 7 && c.[0] = '#' then begin
let conv s = int_of_string ("0x" ^ s) in
let c =
(conv (String.sub c 1 2),
conv (String.sub c 3 2),
conv (String.sub c 5 2))
in
Some (convert c)
end else
Some (try Hashtbl.find named_colors c
with Not_found -> Format.eprintf "%s@." c; assert false)
let read_path attrs i =
let d = List.assoc d_attr attrs in
(*Format.eprintf "d=%s@." d;*)
let cmd = parse_path d in
let fill = parse_color (List.assoc fill_attr attrs) in
let stroke = parse_color (List.assoc stroke_attr attrs) in
let e = Path (cmd, fill, stroke) in
push e;
empty_tag i
let read_ellipse attrs i =
let cx = float_of_string (List.assoc cx_attr attrs) in
let cy = float_of_string (List.assoc cy_attr attrs) in
let rx = float_of_string (List.assoc rx_attr attrs) in
let ry = float_of_string (List.assoc ry_attr attrs) in
let fill = parse_color (List.assoc fill_attr attrs) in
let stroke = parse_color (List.assoc stroke_attr attrs) in
let e = Ellipse (cx, cy, rx, ry, fill, stroke) in
push e;
empty_tag i
let rec group l =
match l with
x :: y :: r -> (x, y) :: group r
| [] -> []
| _ -> assert false
let read_polygon attrs i =
let points = List.assoc points_attr attrs in
let points = group (List.map float_of_string (Str.split comma_wsp points)) in
let fill = parse_color (List.assoc fill_attr attrs) in
let stroke = parse_color (List.assoc stroke_attr attrs) in
let e = Polygon (points, fill, stroke) in
push e;
empty_tag i
let read_text attrs i =
let fill = parse_color (try List.assoc fill_attr attrs with Not_found -> "black") in
let stroke = parse_color (try List.assoc stroke_attr attrs with Not_found -> "none") in
let x = float_of_string (List.assoc x_attr attrs) in
let y = float_of_string (List.assoc y_attr attrs) in
let font = List.assoc font_family_attr attrs in
let font_size = float_of_string (List.assoc font_size_attr attrs) in
let txt = text_tag i in
let e = Text (x, y, txt, font, font_size, fill, stroke) in
push e
let rec read_element nm attrs i =
skip_whitespace i;
match Xmlm.input i with
`El_end ->
()
| `Data d ->
begin match Xmlm.input i with
`El_end ->
()
| _ ->
assert false
end
| `El_start ((_, nm'), attrs') ->
(*
Format.eprintf "%s" nm';
List.iter (fun ((_, nm), _) -> Format.eprintf " %s" nm) attrs';
Format.eprintf "@.";
*)
begin match nm' with
"path" ->
ignore (read_path attrs' i)
| "ellipse" ->
ignore (read_ellipse attrs' i)
| "polygon" ->
ignore (read_polygon attrs' i)
| "text" ->
ignore (read_text attrs' i)
| _ ->
read_element nm' attrs' i
end;
read_element nm attrs i
| _ ->
assert false
let _ =
let ch = open_in "/tmp/foo.svg" in
let i = Xmlm.make_input (`Channel ch) in
begin match Xmlm.input i with
`Dtd (Some nm) -> ()
| _ ->
assert false
end;
begin match Xmlm.input i with
`El_start ((_, nm), attrs) -> assert (nm = "svg"); read_element nm attrs i
| _ -> assert false
end
let l = List.rev !stack
let bboxes = ref []
let intersects (x1, y1, x2, y2) (x3, y3, x4, y4) =
x1 <= x4 && y1 <= y4 && x3 <= x2 && y3 <= y4
let redraw w range ev =
(*
let t1 = Unix.gettimeofday () in
*)
let ctx = Cairo_lablgtk.create w#misc#window in
Cairo.save ctx;
if !bboxes = [] then bboxes := List.map (fun e -> compute_extent ctx e) l;
Cairo.new_path ctx;
Cairo_lablgtk.region ctx (GdkEvent.Expose.region ev);
let rect = Gdk.Rectangle.create 0 0 0 0 in
Gdk.Region.get_clipbox (GdkEvent.Expose.region ev) rect;
Cairo.clip ctx;
let scale = scale *. (1. /. scale) ** range#adjustment#value in
Cairo.scale ctx scale scale; Cairo.translate ctx 364. 22443.;
let bbox =
let x = float (Gdk.Rectangle.x rect) /. scale -. 364. in
let y = float (Gdk.Rectangle.y rect) /. scale -. 22443. in
(x, y,
x +. float (Gdk.Rectangle.width rect) /. scale,
y +. float (Gdk.Rectangle.height rect) /. scale)
in
(*
let (x1, y1, x2, y2) = bbox in
Format.eprintf "%f %f %f %f (%f)@." x1 y1 x2 y2 scale;
*)
List.iter2
(fun box e -> if intersects box bbox then draw_element ctx e) !bboxes l;
Cairo.restore ctx;
(*
let t2 = Unix.gettimeofday () in
Format.eprintf "%f@." (t2 -. t1);
*)
true
let slider_changed (area : GMisc.drawing_area) range () =
let scale = scale *. (1. /. scale) ** range#adjustment#value in
area#misc#set_size_request
~width:(truncate (width *. scale))
~height:(truncate (height *. scale))
();
GtkBase.Widget.queue_draw area#as_widget
let _ =
ignore (GMain.Main.init ());
let initial_size = 600 in
let w = GWindow.window () in
ignore (w#connect#destroy GMain.quit);
let b = GPack.vbox ~spacing:6 ~border_width:12
~packing:w#add () in
(*
let f = GBin.frame ~shadow_type:`IN
~packing:(b#pack ~expand:true ~fill:true) () in
*)
let f =
GBin.scrolled_window ~packing:(b#pack ~expand:true)
(* ~hpolicy:`AUTOMATIC ~vpolicy:`AUTOMATIC *) ()
in
let area = GMisc.drawing_area
~width:initial_size ~height:initial_size
~packing:f#add_with_viewport () in
area#misc#set_size_request
~width:(truncate (width *. scale))
~height:(truncate (height *. scale))
();
let slider = GRange.scale `HORIZONTAL
~draw_value:false ~packing:b#pack () in
slider#adjustment#set_bounds
~lower:0. ~upper:1.
~step_incr:0.1 () ;
(*
let button = GButton.check_button ~label:"Animate"
~packing:b#pack () in
ignore (area#event#connect#expose
(redraw area slider)) ;
ignore (slider#connect#value_changed
(slider_changed area)) ;
ignore (button#connect#toggled
(animate_toggled button slider)) ;
*)
ignore (area#event#connect#expose
(redraw area slider));
ignore (slider#connect#value_changed
(slider_changed area slider)) ;
w#show () ;
GMain.main ()
(*
let _ =
let l = List.rev !stack in
Format.eprintf "len: %d@." (List.length l);
let t1 = Unix.gettimeofday () in
List.iter (fun e -> draw_element ctx e) l;
let t2 = Unix.gettimeofday () in
Format.eprintf "%f@." (t2 -. t1);
(*
let ch = open_out "/tmp/foo.mar" in
Marshal.to_channel ch l [];
close_out ch;
*)
Cairo_png.surface_write_to_file s "/tmp/foo.png"
*)
coinst-1.9.3/viewer/dot_render.mli 0000644 0001750 0001750 00000001627 12657630652 016134 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
val f : Dot_graph.graph -> (float * float * float * float) * Scene.cairo_t
coinst-1.9.3/viewer/scene_extents.ml 0000644 0001750 0001750 00000004450 12657630652 016502 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
open Scene
let pi = 4. *. atan 1.
let path_extent ctx fill stroke =
if stroke <> None then Cairo.stroke_extents ctx
else Cairo.fill_extents ctx
let compute_extent ctx e =
Cairo.new_path ctx;
match e with
Path (cmd, fill, stroke, _) ->
Array.iter
(fun c ->
match c with
Move_to (x, y) ->
Cairo.move_to ctx x y
| Curve_to (x1, y1, x2, y2, x3, y3) ->
Cairo.curve_to ctx x1 y1 x2 y2 x3 y3)
cmd;
path_extent ctx fill stroke
| Ellipse (cx, cy, rx, ry, fill, stroke, _) ->
Cairo.save ctx;
Cairo.translate ctx cx cy;
Cairo.scale ctx rx ry;
Cairo.arc ctx 0. 0. 1. 0. (2. *. pi);
Cairo.restore ctx;
path_extent ctx fill stroke
| Polygon (points, fill, stroke, _) ->
Array.iteri
(fun i (x, y) ->
if i = 0 then Cairo.move_to ctx x y else Cairo.line_to ctx x y)
points;
Cairo.close_path ctx;
path_extent ctx fill stroke
| Text (x, y, txt, (font, font_size), fill, stroke) ->
Cairo.select_font_face ctx font
Cairo.FONT_SLANT_NORMAL Cairo.FONT_WEIGHT_NORMAL;
Cairo.set_font_size ctx font_size;
let ext = Cairo.text_extents ctx txt in
(x -. ext.Cairo.text_width /. 2. -. 5.,
y +. ext.Cairo.y_bearing -. 5.,
x +. ext.Cairo.text_width /. 2. +. 5.,
y +. ext.Cairo.y_bearing +. ext.Cairo.text_height +. 5.)
let compute ctx l = Array.map (fun e -> compute_extent ctx e) l
coinst-1.9.3/viewer/scene.js 0000644 0001750 0001750 00001716466 12657630652 014756 0 ustar mehdi mehdi scene =
[0,[0,0,0,17706,24785],
[0,[0,12668,17970.5,13016,18009.5],[0,12721.5,17977.7,12962.5,18001.7],
[0,15002,17970.5,15212,18009.5],[0,15035.5,17977.7,15178.5,17998.7],
[0,8024.4,17410.5,8128.4,17449.5],[0,8042.4,17417.7,8110.4,17441.7],
[0,10344,17970.5,10654,18009.5],[0,10394.5,17977.7,10603.5,18001.7],
[0,2895.4,21701.5,3049.4,21740.5],[0,2921.4,21708.7,3023.4,21732.7],
[0,5396.4,21778.5,5566.4,21817.5],[0,5425.9,21785.7,5536.9,21809.7],
[0,10406,17387.5,10592,17426.5],[0,10437,17394.7,10561,17418.7],
[0,12756,17387.5,12928,17426.5],[0,12786.5,17394.7,12897.5,17418.7],
[0,725.43,1621.5,937.43,1660.5],[0,759.43,1628.7,903.43,1652.7],
[0,2891.4,1594.5,3053.4,1633.5],[0,2918.9,1601.7,3025.9,1625.7],
[0,2882.4,1648.5,3062.4,1687.5],[0,2912.4,1655.7,3032.4,1679.7],
[0,5417.4,1648.5,5545.4,1687.5],[0,5440.4,1655.7,5522.4,1679.7],
[0,5417.4,21229.5,5545.4,21268.5],[0,5439.9,21236.7,5522.9,21260.7],
[0,8021.4,21218.5,8131.4,21257.5],[0,8041.9,21225.7,8110.9,21249.7],
[0,7966.4,9680.5,8186.4,9719.5],[0,8001.9,9687.7,8150.9,9710.7],
[0,10382,10092.5,10616,10131.5],[0,10420,10099.7,10578,10122.7],
[0,5429.4,22049.5,5533.4,22088.5],[0,5447.9,22056.7,5514.9,22077.7],
[0,8015.4,22030.5,8137.4,22069.5],[0,8035.9,22037.7,8116.9,22058.7],
[0,10430,23386.5,10568,23425.5],[0,10455.5,23393.7,10542.5,23414.7],
[0,12773,23386.5,12911,23425.5],[0,12798.5,23393.7,12885.5,23414.7],
[0,781.43,1471.5,881.43,1510.5],[0,800.93,1478.7,861.93,1499.7],
[0,2944.4,1448.5,3000.4,1487.5],[0,2959.9,1455.7,2984.9,1476.7],
[0,2889.4,3176.5,3055.4,3215.5],[0,2917.9,3183.7,3026.9,3204.7],
[0,5399.4,3199.5,5563.4,3238.5],[0,5427.4,3206.7,5535.4,3227.7],
[0,10402,23332.5,10596,23371.5],[0,10434.5,23339.7,10563.5,23363.7],
[0,12793,23332.5,12891,23371.5],[0,12811.5,23339.7,12872.5,23360.7],
[0,10397,10601.5,10601,10640.5],[0,10432.5,10608.7,10565.5,10632.7],
[0,12740,10601.5,12944,10640.5],[0,12775.5,10608.7,12908.5,10632.7],
[0,8005.4,22198.5,8147.4,22237.5],[0,8029.9,22205.7,8122.9,22226.7],
[0,10435,22198.5,10563,22237.5],[0,10459.5,22205.7,10538.5,22228.7],
[0,8026.4,2710.5,8126.4,2749.5],[0,8045.4,2717.7,8107.4,2741.7],
[0,10451,2678.5,10547,2717.5],[0,10468.5,2686.7,10529.5,2709.7],
[0,5351.4,16750.5,5611.4,16789.5],[0,5392.4,16757.7,5570.4,16781.7],
[0,7946.4,16528.5,8206.4,16567.5],[0,7987.4,16535.7,8165.4,16559.7],
[0,5352.4,16582.5,5610.4,16621.5],[0,5392.9,16589.7,5569.9,16613.7],
[0,7947.4,16582.5,8205.4,16621.5],[0,7987.9,16589.7,8164.9,16613.7],
[0,5337.4,16528.5,5625.4,16567.5],[0,5383.4,16535.7,5579.4,16559.7],
[0,7932.4,16474.5,8220.4,16513.5],[0,7978.4,16481.7,8174.4,16505.7],
[0,15079,15324,15135,15362],[0,15097,15331.6,15117,15351.6],
[0,10370,15572.5,10628,15611.5],[0,10412.5,15579.7,10585.5,15603.7],
[0,12713,15251.5,12971,15290.5],[0,12755.5,15258.7,12928.5,15282.7],
[0,12713,15323.5,12971,15362.5],[0,12755.5,15330.7,12928.5,15354.7],
[0,12814,14107,12870,14145],[0,12832,14114.6,12852,14134.6],
[0,10391,14160.5,10607,14199.5],[0,10427,14167.7,10571,14191.7],
[0,10391,14052.5,10607,14091.5],[0,10427,14059.7,10571,14083.7],
[0,10391,14106.5,10607,14145.5],[0,10427,14113.7,10571,14137.7],
[0,7990.4,22252.5,8162.4,22291.5],[0,8017.9,22259.7,8134.9,22283.7],
[0,10430,22252.5,10568,22291.5],[0,10452.5,22259.7,10545.5,22283.7],
[0,10471,13647,10527,13685],[0,10489,13654.6,10509,13674.6],
[0,8004.4,13646.5,8148.4,13685.5],[0,8028.4,13653.7,8124.4,13677.7],
[0,7997.4,12742.5,8155.4,12781.5],[0,8024.4,12749.7,8128.4,12773.7],
[0,7999.4,15734.5,8153.4,15773.5],[0,8027.4,15741.7,8125.4,15764.7],
[0,7995.4,22306.5,8157.4,22345.5],[0,8022.9,22313.7,8129.9,22334.7],
[0,10416,22306.5,10582,22345.5],[0,10444.5,22313.7,10553.5,22336.7],
[0,5439.4,15950.5,5523.4,15989.5],[0,5454.4,15957.7,5508.4,15981.7],
[0,8047.4,15950.5,8105.4,15989.5],[0,8059.4,15957.7,8093.4,15978.7],
[0,12814,10836,12870,10874],[0,12832,10843.6,12852,10863.6],
[0,10413,11147.5,10585,11186.5],[0,10444.5,11154.7,10553.5,11177.7],
[0,10414,10693.5,10584,10732.5],[0,10443.5,10700.7,10554.5,10721.7],
[0,10471,10893.5,10527,10932.5],[0,10485,10900.7,10513,10921.7],
[0,12814,10890,12870,10928],[0,12832,10897.6,12852,10917.6],
[0,10420,10747.5,10578,10786.5],[0,10448,10754.7,10550,10775.7],
[0,5446.4,1494.5,5516.4,1533.5],[0,5460.4,1501.7,5502.4,1522.7],
[0,8023.4,1494.5,8129.4,1533.5],[0,8043.4,1501.7,8109.4,1524.7],
[0,5363.4,11214.5,5599.4,11253.5],[0,5398.9,11221.7,5563.9,11245.7],
[0,7989.4,11216.5,8163.4,11255.5],[0,8016.9,11223.7,8135.9,11247.7],
[0,5379.4,11268.5,5583.4,11307.5],[0,5410.9,11275.7,5551.9,11296.7],
[0,2914.4,21570.5,3030.4,21609.5],[0,2935.4,21577.7,3009.4,21598.7],
[0,5448.4,20918.5,5514.4,20957.5],[0,5462.4,20926.7,5500.4,20946.7],
[0,5433.4,21670.5,5529.4,21709.5],[0,5450.9,21677.7,5511.9,21698.7],
[0,10397,23560.5,10601,23599.5],[0,10431.5,23567.7,10566.5,23591.7],
[0,12756,23802.5,12928,23841.5],[0,12785,23809.7,12899,23833.7],
[0,2855.4,15397.5,3089.4,15436.5],[0,2894.4,15404.7,3050.4,15427.7],
[0,10376,15047.5,10622,15086.5],[0,10416.5,15054.7,10581.5,15077.7],
[0,10397,12461.5,10601,12500.5],[0,10431.5,12468.7,10566.5,12492.7],
[0,12768,12301.5,12916,12340.5],[0,12793.5,12308.7,12890.5,12332.7],
[0,2924.4,20248.5,3020.4,20287.5],[0,2941.9,20258.7,3002.9,20279.7],
[0,5389.4,20260.5,5573.4,20299.5],[0,5420.9,20267.7,5541.9,20290.7],
[0,7945.4,12272.5,8207.4,12311.5],[0,7986.4,12279.7,8166.4,12303.7],
[0,10396,12326.5,10602,12365.5],[0,10431.5,12333.7,10566.5,12357.7],
[0,7987.4,12018.5,8165.4,12057.5],[0,8016.4,12025.7,8136.4,12049.7],
[0,10412,12203.5,10586,12242.5],[0,10441,12210.7,10557,12234.7],
[0,5431.4,21832.5,5531.4,21871.5],[0,5449.4,21839.7,5513.4,21863.7],
[0,7983.4,21792.5,8169.4,21831.5],[0,8014.4,21799.7,8138.4,21823.7],
[0,7946.4,14198.5,8206.4,14237.5],[0,7989.4,14205.7,8163.4,14229.7],
[0,10390,14214.5,10608,14253.5],[0,10427,14221.7,10571,14245.7],
[0,10389,23008.5,10609,23047.5],[0,10424,23015.7,10574,23039.7],
[0,12727,23008.5,12957,23047.5],[0,12763,23015.7,12921,23039.7],
[0,10471,16417,10527,16455],[0,10489,16424.6,10509,16444.6],
[0,7970.4,18162.5,8182.4,18201.5],[0,8006.4,18169.7,8146.4,18193.7],
[0,8021.4,17610.5,8131.4,17649.5],[0,8040.9,17617.7,8111.9,17641.7],
[0,7953.4,18070.5,8199.4,18109.5],[0,7994.9,18077.7,8157.9,18101.7],
[0,5390.4,21324.5,5572.4,21363.5],[0,5419.4,21331.7,5543.4,21355.7],
[0,7957.4,21348.5,8195.4,21387.5],[0,7996.9,21355.7,8155.9,21379.7],
[0,5334.4,17014.5,5628.4,17053.5],[0,5382.4,17021.7,5580.4,17045.7],
[0,7883.4,17118.5,8269.4,17157.5],[0,7943.4,17125.7,8209.4,17149.7],
[0,7933.4,2136.5,8219.4,2175.5],[0,7978.4,2143.7,8174.4,2167.7],
[0,10359,2174.5,10639,2213.5],[0,10401,2181.7,10597,2205.7],
[0,5366.4,12926.5,5596.4,12965.5],[0,5403.4,12933.7,5559.4,12957.7],
[0,7959.4,13846.5,8193.4,13885.5],[0,7996.9,13853.7,8155.9,13877.7],
[0,2800.4,12926.5,3144.4,12965.5],[0,2853.4,12933.7,3091.4,12957.7],
[0,10400,12937.5,10598,12976.5],[0,10434,12944.7,10564,12968.7],
[0,12761,12937.5,12923,12976.5],[0,12788.5,12944.7,12895.5,12968.7],
[0,12797,2603.5,12887,2642.5],[0,12814,2610.7,12870,2634.7],
[0,15056,2603.5,15158,2642.5],[0,15075,2610.7,15139,2634.7],
[0,12770,2786.5,12914,2825.5],[0,12794.5,2793.7,12889.5,2817.7],
[0,5416.4,17610.5,5546.4,17649.5],[0,5438.9,17617.7,5523.9,17641.7],
[0,10380,11239.5,10618,11278.5],[0,10419,11246.7,10579,11270.7],
[0,5359.4,23975.5,5603.4,24014.5],[0,5400.4,23982.7,5562.4,24005.7],
[0,8000.4,24110.5,8152.4,24149.5],[0,8025.9,24117.7,8126.9,24138.7],
[0,10471,24473,10527,24511],[0,10489,24480.6,10509,24500.6],
[0,7943.4,24472.5,8209.4,24511.5],[0,7984.9,24479.7,8167.9,24500.7],
[0,8015.4,24526.5,8137.4,24565.5],[0,8037.4,24533.7,8115.4,24557.7],
[0,8000.4,24418.5,8152.4,24457.5],[0,8025.4,24425.7,8127.4,24449.7],
[0,10471,24419,10527,24457],[0,10489,24426.6,10509,24446.6],
[0,7966.4,23894.5,8186.4,23933.5],[0,8001.9,23901.7,8150.9,23922.7],
[0,10403,7688.5,10595,7727.5],[0,10434.5,7695.7,10563.5,7716.7],
[0,12802,7656.5,12882,7695.5],[0,12818.5,7663.7,12865.5,7684.7],
[0,7961.4,2656.5,8191.4,2695.5],[0,7997.9,2663.7,8154.9,2687.7],
[0,10372,17010.5,10626,17049.5],[0,10415,17017.7,10583,17041.7],
[0,777.43,1340.5,885.43,1379.5],[0,796.93,1347.7,865.93,1371.7],
[0,2917.4,1340.5,3027.4,1379.5],[0,2935.9,1347.7,3008.9,1368.7],
[0,8019.4,6758.5,8133.4,6797.5],[0,8039.9,6765.7,8112.9,6786.7],
[0,10431,6742.5,10567,6781.5],[0,10457,6749.7,10541,6772.7],
[0,5399.4,7877.5,5563.4,7916.5],[0,5427.4,7884.7,5535.4,7905.7],
[0,7960.4,7896.5,8192.4,7935.5],[0,7997.9,7903.7,8154.9,7927.7],
[0,8017.4,14252.5,8135.4,14291.5],[0,8038.9,14259.7,8113.9,14283.7],
[0,10425,14268.5,10573,14307.5],[0,10451,14275.7,10547,14299.7],
[0,7983.4,22360.5,8169.4,22399.5],[0,8013.4,22367.7,8139.4,22391.7],
[0,10426,22360.5,10572,22399.5],[0,10450.5,22367.7,10547.5,22391.7],
[0,5395.4,20864.5,5567.4,20903.5],[0,5422.9,20871.7,5539.9,20892.7],
[0,8008.4,20904.5,8144.4,20943.5],[0,8032.4,20911.7,8120.4,20934.7],
[0,10418,23228.5,10580,23267.5],[0,10446.5,23235.7,10551.5,23256.7],
[0,12787,23253.5,12897,23292.5],[0,12807.5,23260.7,12876.5,23281.7],
[0,10370,16956.5,10628,16995.5],[0,10412.5,16963.7,10585.5,16987.7],
[0,7958.4,16956.5,8194.4,16995.5],[0,7996.9,16963.7,8155.9,16987.7],
[0,10471,8181,10527,8219],[0,10489,8188.6,10509,8208.6],
[0,7959.4,8940.5,8193.4,8979.5],[0,7995.9,8947.7,8156.9,8971.7],
[0,8005.4,8508.5,8147.4,8547.5],[0,8028.9,8515.7,8123.9,8539.7],
[0,7983.4,8562.5,8169.4,8601.5],[0,8012.9,8569.7,8139.9,8593.7],
[0,10471,8235,10527,8273],[0,10489,8242.6,10509,8262.6],
[0,7972.4,9318.5,8180.4,9357.5],[0,8004.4,9325.7,8148.4,9349.7],
[0,10344,23170.5,10654,23209.5],[0,10391.5,23177.7,10606.5,23201.7],
[0,12676,23170.5,13008,23209.5],[0,12727,23177.7,12957,23201.7],
[0,7966.4,13446.5,8186.4,13485.5],[0,8003.4,13453.7,8149.4,13476.7],
[0,10341,13519.5,10657,13558.5],[0,10390,13526.7,10608,13550.7],
[0,5373.4,13446.5,5589.4,13485.5],[0,5408.9,13453.7,5553.9,13474.7],
[0,10471,24581,10527,24619],[0,10489,24588.6,10509,24608.6],
[0,7976.4,24056.5,8176.4,24095.5],[0,8008.4,24063.7,8144.4,24084.7],
[0,7968.4,23948.5,8184.4,23987.5],[0,8002.9,23955.7,8149.9,23976.7],
[0,7968.4,24742.5,8184.4,24781.5],[0,8002.4,24749.7,8150.4,24770.7],
[0,7971.4,24002.5,8181.4,24041.5],[0,8004.4,24009.7,8148.4,24030.7],
[0,7970.4,24688.5,8182.4,24727.5],[0,8004.4,24695.7,8148.4,24716.7],
[0,7972.4,24580.5,8180.4,24619.5],[0,8005.4,24587.7,8147.4,24608.7],
[0,7935.4,24634.5,8217.4,24673.5],[0,7978.9,24641.7,8173.9,24665.7],
[0,5417.4,18762.5,5545.4,18801.5],[0,5440.4,18769.7,5522.4,18793.7],
[0,7985.4,18644.5,8167.4,18683.5],[0,8016.4,18651.7,8136.4,18675.7],
[0,5413.4,8283.5,5549.4,8322.5],[0,5436.4,8290.7,5526.4,8314.7],
[0,8002.4,8264.5,8150.4,8303.5],[0,8026.9,8271.7,8125.9,8295.7],
[0,8022.4,10816.5,8130.4,10855.5],[0,8041.9,10823.7,8110.9,10844.7],
[0,10413,11093.5,10585,11132.5],[0,10443,11100.7,10555,11123.7],
[0,10389,18024.5,10609,18063.5],[0,10425.5,18031.7,10572.5,18055.7],
[0,12771,18024.5,12913,18063.5],[0,12794.5,18031.7,12889.5,18055.7],
[0,8000.4,9772.5,8152.4,9811.5],[0,8024.9,9779.7,8127.9,9800.7],
[0,10396,10146.5,10602,10185.5],[0,10430.5,10153.7,10567.5,10176.7],
[0,5398.4,18162.5,5564.4,18201.5],[0,5425.9,18169.7,5536.9,18190.7],
[0,7983.4,18216.5,8169.4,18255.5],[0,8015.4,18223.7,8137.4,18246.7],
[0,7965.4,24364.5,8187.4,24403.5],[0,8001.9,24371.7,8150.9,24395.7],
[0,10420,24129.5,10578,24168.5],[0,10447,24136.7,10551,24160.7],
[0,10380,21850.5,10618,21889.5],[0,10415.5,21857.7,10582.5,21881.7],
[0,12735,21874.5,12949,21913.5],[0,12767,21881.7,12917,21905.7],
[0,5402.4,3291.5,5560.4,3330.5],[0,5428.4,3298.7,5534.4,3322.7],
[0,7978.4,3161.5,8174.4,3200.5],[0,8010.4,3168.7,8142.4,3192.7],
[0,2856.4,3077.5,3088.4,3116.5],[0,2891.4,3084.7,3053.4,3108.7],
[0,5376.4,3069.5,5586.4,3108.5],[0,5409.9,3076.7,5552.9,3100.7],
[0,7964.4,6212.5,8188.4,6251.5],[0,8002.4,6219.7,8150.4,6243.7],
[0,10420,6418.5,10578,6457.5],[0,10447,6425.7,10551,6449.7],
[0,7959.4,24256.5,8193.4,24295.5],[0,7996.4,24263.7,8156.4,24287.7],
[0,10417,23845.5,10581,23884.5],[0,10446.5,23852.7,10551.5,23875.7],
[0,2880.4,1232.5,3064.4,1271.5],[0,2910.9,1239.7,3033.9,1260.7],
[0,5423.4,1232.5,5539.4,1271.5],[0,5443.9,1239.7,5518.9,1260.7],
[0,724.43,1259.5,938.43,1298.5],[0,758.93,1266.7,903.93,1287.7],
[0,2893.4,1286.5,3051.4,1325.5],[0,2919.9,1293.7,3024.9,1314.7],
[0,12814,7419,12870,7457],[0,12832,7426.6,12852,7446.6],
[0,10471,7358.5,10527,7397.5],[0,10484.5,7365.7,10513.5,7386.7],
[0,10438,7158.5,10560,7197.5],[0,10459,7165.7,10539,7186.7],
[0,10461,4774.5,10537,4813.5],[0,10475,4781.7,10523,4802.7],
[0,10471,13258.5,10527,13297.5],[0,10484.5,13265.7,10513.5,13289.7],
[0,12778,13362.5,12906,13401.5],[0,12801.5,13369.7,12882.5,13393.7],
[0,15013,16135.5,15201,16174.5],[0,15045.5,16142.7,15168.5,16165.7],
[0,16641,16189.5,16779,16228.5],[0,16663.5,16196.7,16756.5,16217.7],
[0,15047,16189.5,15167,16228.5],[0,15067,16196.7,15147,16217.7],
[0,15048,16243.5,15166,16282.5],[0,15068.5,16250.7,15145.5,16271.7],
[0,16638,16243.5,16782,16282.5],[0,16661.5,16250.7,16758.5,16271.7],
[0,12814,9664,12870,9702],[0,12832,9671.6,12852,9691.6],
[0,10442,9822.5,10556,9861.5],[0,10462,9829.7,10536,9850.7],
[0,10449,9676.5,10549,9715.5],[0,10466,9683.7,10532,9707.7],
[0,10431,9568.5,10567,9607.5],[0,10453,9575.7,10545,9599.7],
[0,10425,9622.5,10573,9661.5],[0,10449,9629.7,10549,9653.7],
[0,12814,9583,12870,9621],[0,12832,9590.6,12852,9610.6],
[0,10431,9514.5,10567,9553.5],[0,10453,9521.7,10545,9545.7],
[0,12814,10694,12870,10732],[0,12832,10701.6,12852,10721.6],
[0,8019.4,10670.5,8133.4,10709.5],[0,8039.4,10677.7,8113.4,10698.7],
[0,12814,10748,12870,10786],[0,12832,10755.6,12852,10775.6],
[0,8043.4,12380.5,8109.4,12419.5],[0,8057.4,12387.7,8095.4,12411.7],
[0,10393,9930.5,10605,9969.5],[0,10428.5,9937.7,10569.5,9961.7],
[0,5428.4,14890.5,5534.4,14929.5],[0,5446.9,14897.7,5515.9,14921.7],
[0,8036.4,14890.5,8116.4,14929.5],[0,8052.4,14897.7,8100.4,14918.7],
[0,7973.4,12596.5,8179.4,12635.5],[0,8006.9,12603.7,8145.9,12627.7],
[0,10396,12623.5,10602,12662.5],[0,10429.5,12630.7,10568.5,12654.7],
[0,5340.4,16004.5,5622.4,16043.5],[0,5384.4,16011.7,5578.4,16035.7],
[0,8003.4,16004.5,8149.4,16043.5],[0,8029.4,16011.7,8123.4,16035.7],
[0,5375.4,18438.5,5587.4,18477.5],[0,5411.4,18445.7,5551.4,18468.7],
[0,7976.4,17464.5,8176.4,17503.5],[0,8010.9,17471.7,8141.9,17494.7],
[0,10418,13946.5,10580,13985.5],[0,10446,13953.7,10552,13977.7],
[0,12728,15174.5,12956,15213.5],[0,12765.5,15181.7,12918.5,15205.7],
[0,12814,9299,12870,9337],[0,12832,9306.6,12852,9326.6],
[0,10454,9352.5,10544,9391.5],[0,10470.5,9362.7,10527.5,9380.7],
[0,10411,9298.5,10587,9337.5],[0,10443,9305.7,10555,9329.7],
[0,10374,9244.5,10624,9283.5],[0,10416,9251.7,10582,9275.7],
[0,12814,9245,12870,9283],[0,12832,9252.6,12852,9272.6],
[0,10399,9152.5,10599,9191.5],[0,10434,9159.7,10564,9183.7],
[0,12814,9353,12870,9391],[0,12832,9360.6,12852,9380.6],
[0,10447,9406.5,10551,9445.5],[0,10465,9413.7,10533,9437.7],
[0,10445,7412.5,10553,7451.5],[0,10466.5,7419.7,10531.5,7442.7],
[0,12775,7564.5,12909,7603.5],[0,12800,7571.7,12884,7592.7],
[0,12787,7202.5,12897,7241.5],[0,12807,7209.7,12877,7230.7],
[0,12814,4008,12870,4046],[0,12832,4015.6,12852,4035.6],
[0,10408,4034.5,10590,4073.5],[0,10438.5,4041.7,10559.5,4062.7],
[0,8002.4,3938.5,8150.4,3977.5],[0,8027.9,3945.7,8124.9,3966.7],
[0,10435,3980.5,10563,4019.5],[0,10458,3987.7,10540,4008.7],
[0,10452,4088.5,10546,4127.5],[0,10469.5,4095.7,10528.5,4116.7],
[0,8000.4,10762.5,8152.4,10801.5],[0,8025.4,10769.7,8127.4,10793.7],
[0,10401,11039.5,10597,11078.5],[0,10433.5,11046.7,10564.5,11070.7],
[0,12814,16417,12870,16455],[0,12832,16424.6,12852,16444.6],
[0,10418,16362.5,10580,16401.5],[0,10445.5,16369.7,10552.5,16390.7],
[0,10391,16742.5,10607,16781.5],[0,10427.5,16749.7,10570.5,16773.7],
[0,10454,16470.5,10544,16509.5],[0,10471,16477.7,10527,16498.7],
[0,10430,16308.5,10568,16347.5],[0,10455,16315.7,10543,16338.7],
[0,12814,9407,12870,9445],[0,12832,9414.6,12852,9434.6],
[0,10447,9460.5,10551,9499.5],[0,10467.5,9467.7,10530.5,9490.7],
[0,8048.4,1125,8104.4,1163],[0,8066.4,1132.6,8086.4,1152.6],
[0,5398.4,1070.5,5564.4,1109.5],[0,5425.4,1077.7,5537.4,1101.7],
[0,5402.4,1124.5,5560.4,1163.5],[0,5427.9,1131.7,5534.9,1155.7],
[0,5369.4,1178.5,5593.4,1217.5],[0,5403.9,1185.7,5558.9,1209.7],
[0,8048.4,747,8104.4,785],[0,8066.4,754.6,8086.4,774.6],
[0,5398.4,800.5,5564.4,839.5],[0,5426.9,807.7,5535.9,831.7],
[0,5402.4,692.5,5560.4,731.5],[0,5429.4,699.7,5533.4,723.7],
[0,5370.4,746.5,5592.4,785.5],[0,5405.4,753.7,5557.4,777.7],
[0,10471,2267,10527,2305],[0,10489,2274.6,10509,2294.6],
[0,7993.4,2282.5,8159.4,2321.5],[0,8022.9,2289.7,8129.9,2313.7],
[0,8001.4,2228.5,8151.4,2267.5],[0,8026.9,2235.7,8125.9,2259.7],
[0,10395,15464.5,10603,15503.5],[0,10430.5,15471.7,10567.5,15495.7],
[0,12776,15399.5,12908,15438.5],[0,12799,15406.7,12885,15430.7],
[0,8048.4,936,8104.4,974],[0,8066.4,943.6,8086.4,963.6],
[0,5361.4,854.5,5601.4,893.5],[0,5398.9,861.7,5563.9,885.7],
[0,5397.4,1016.5,5565.4,1055.5],[0,5425.4,1023.7,5537.4,1047.7],
[0,5401.4,908.5,5561.4,947.5],[0,5427.9,915.7,5534.9,939.7],
[0,5369.4,962.5,5593.4,1001.5],[0,5403.9,969.7,5558.9,993.7],
[0,12814,4076,12870,4114],[0,12832,4083.6,12852,4103.6],
[0,10383,4288.5,10615,4327.5],[0,10421,4295.7,10577,4318.7],
[0,12814,3327,12870,3365],[0,12832,3334.6,12852,3354.6],
[0,10424,2948.5,10574,2987.5],[0,10449,2955.7,10549,2979.7],
[0,10442,3002.5,10556,3041.5],[0,10461,3009.7,10537,3033.7],
[0,10452,3218.5,10546,3257.5],[0,10468.5,3225.7,10529.5,3249.7],
[0,10467,3434.5,10531,3473.5],[0,10480,3441.7,10518,3465.7],
[0,10432,3542.5,10566,3581.5],[0,10453.5,3549.7,10544.5,3573.7],
[0,10391,3164.5,10607,3203.5],[0,10426,3171.7,10572,3195.7],
[0,10418,3326.5,10580,3365.5],[0,10443.5,3333.7,10554.5,3357.7],
[0,10410,2840.5,10588,2879.5],[0,10437.5,2847.7,10560.5,2871.7],
[0,10388,3272.5,10610,3311.5],[0,10421.5,3279.7,10576.5,3303.7],
[0,10442,3380.5,10556,3419.5],[0,10461,3387.7,10537,3411.7],
[0,10428,3650.5,10570,3689.5],[0,10452.5,3657.7,10545.5,3681.7],
[0,10457,3488.5,10541,3527.5],[0,10472,3495.7,10526,3519.7],
[0,10448,3596.5,10550,3635.5],[0,10467,3603.7,10531,3627.7],
[0,10420,3110.5,10578,3149.5],[0,10449,3117.7,10549,3141.7],
[0,8004.4,7950.5,8148.4,7989.5],[0,8028.9,7957.7,8123.9,7978.7],
[0,10399,8126.5,10599,8165.5],[0,10433,8133.7,10565,8156.7],
[0,7964.4,8616.5,8188.4,8655.5],[0,8001.4,8623.7,8151.4,8646.7],
[0,10471,8288.5,10527,8327.5],[0,10483,8296.7,10515,8319.7],
[0,10471,8451,10527,8489],[0,10489,8458.6,10509,8478.6],
[0,7990.4,8724.5,8162.4,8763.5],[0,8020.4,8731.7,8132.4,8754.7],
[0,7980.4,9372.5,8172.4,9411.5],[0,8012.9,9379.7,8139.9,9403.7],
[0,10429,8342.5,10569,8381.5],[0,10452.5,8349.7,10545.5,8370.7],
[0,12814,9931,12870,9969],[0,12832,9938.6,12852,9958.6],
[0,10403,9984.5,10595,10023.5],[0,10435,9991.7,10563,10012.7],
[0,10366,9876.5,10632,9915.5],[0,10408.5,9883.7,10589.5,9907.7],
[0,10347,9768.5,10651,9807.5],[0,10395.5,9775.7,10602.5,9799.7],
[0,10395,10038.5,10603,10077.5],[0,10429,10045.7,10569,10066.7],
[0,7964.4,7290.5,8188.4,7329.5],[0,8001.4,7297.7,8151.4,7320.7],
[0,10438,5704.5,10560,5743.5],[0,10460,5711.7,10538,5735.7],
[0,10399,7104.5,10599,7143.5],[0,10432.5,7111.7,10565.5,7134.7],
[0,10456,7504.5,10542,7543.5],[0,10471.5,7511.7,10526.5,7535.7],
[0,17508,7657,17564,7695],[0,17526,7664.6,17546,7684.6],
[0,16657,7656.5,16763,7695.5],[0,16675,7664.7,16745,7687.7],
[0,16662,7602.5,16758,7641.5],[0,16678,7609.7,16742,7633.7],
[0,12814,4243,12870,4281],[0,12832,4250.6,12852,4270.6],
[0,12800,7856.5,12884,7895.5],[0,12816,7863.7,12868,7884.7],
[0,12793,7802.5,12891,7841.5],[0,12810.5,7809.7,12873.5,7830.7],
[0,12814,7511,12870,7549],[0,12832,7518.6,12852,7538.6],
[0,10437,7596.5,10561,7635.5],[0,10458,7603.7,10540,7624.7],
[0,10399,6634.5,10599,6673.5],[0,10431,6641.7,10567,6662.7],
[0,10471,8397,10527,8435],[0,10489,8404.6,10509,8424.6],
[0,8024.4,8670.5,8128.4,8709.5],[0,8042.4,8677.7,8110.4,8698.7],
[0,8001.4,8778.5,8151.4,8817.5],[0,8027.9,8785.7,8124.9,8809.7],
[0,12814,3570,12870,3608],[0,12832,3577.6,12852,3597.6],
[0,12814,5241,12870,5279],[0,12832,5248.6,12852,5268.6],
[0,10411,5072.5,10587,5111.5],[0,10439,5079.7,10559,5100.7],
[0,7994.4,6904.5,8158.4,6943.5],[0,8021.4,6911.7,8131.4,6932.7],
[0,10457,7212.5,10541,7251.5],[0,10473,7220.7,10525,7240.7],
[0,5405.4,14982.5,5557.4,15021.5],[0,5431.4,14989.7,5531.4,15013.7],
[0,7973.4,15020.5,8179.4,15059.5],[0,8009.4,15027.7,8143.4,15051.7],
[0,8019.4,11054.5,8133.4,11093.5],[0,8039.4,11061.7,8113.4,11085.7],
[0,8018.4,10962.5,8134.4,11001.5],[0,8037.9,10969.7,8114.9,10993.7],
[0,10471,17238,10527,17276],[0,10489,17245.6,10509,17265.6],
[0,8013.4,17210.5,8139.4,17249.5],[0,8037.4,17217.7,8115.4,17241.7],
[0,7995.4,17264.5,8157.4,17303.5],[0,8023.4,17271.7,8129.4,17292.7],
[0,8039.4,17318.5,8113.4,17357.5],[0,8054.4,17325.7,8098.4,17346.7],
[0,696.43,23640.5,966.43,23679.5],[0,737.93,23647.7,924.93,23671.7],
[0,2792.4,23640.5,3152.4,23679.5],[0,2849.4,23647.7,3095.4,23671.7],
[0,5428.4,7950.5,5534.4,7989.5],[0,5447.4,7960.7,5515.4,7981.7],
[0,15079,23614,15135,23652],[0,15097,23621.6,15117,23641.6],
[0,12773,23748.5,12911,23787.5],[0,12795.5,23755.7,12888.5,23779.7],
[0,12735,23640.5,12949,23679.5],[0,12770,23647.7,12914,23671.7],
[0,12729,23694.5,12955,23733.5],[0,12765.5,23701.7,12918.5,23725.7],
[0,12767,23532.5,12917,23571.5],[0,12792.5,23539.7,12891.5,23563.7],
[0,12758,23586.5,12926,23625.5],[0,12786.5,23593.7,12897.5,23617.7],
[0,12767,23478.5,12917,23517.5],[0,12792.5,23485.7,12891.5,23509.7],
[0,5285.4,18384.5,5677.4,18423.5],[0,5340.4,18391.7,5622.4,18415.7],
[0,7985.4,1968.5,8167.4,2007.5],[0,8015.4,1975.7,8137.4,1999.7],
[0,7951.4,18806.5,8201.4,18845.5],[0,7990.4,18813.7,8162.4,18837.7],
[0,5288.4,1702.5,5674.4,1741.5],[0,5342.4,1709.7,5620.4,1733.7],
[0,7998.4,1692.5,8154.4,1731.5],[0,8024.9,1699.7,8127.9,1723.7],
[0,7974.4,1746.5,8178.4,1785.5],[0,8007.9,1753.7,8144.9,1777.7],
[0,7999.4,19028.5,8153.4,19067.5],[0,8024.4,19035.7,8128.4,19059.7],
[0,10443,19028.5,10555,19067.5],[0,10463,19035.7,10535,19059.7],
[0,5427.4,21064.5,5535.4,21103.5],[0,5445.9,21071.7,5516.9,21095.7],
[0,8043.4,21034.5,8109.4,21073.5],[0,8056.9,21041.7,8095.9,21065.7],
[0,5424.4,20487.5,5538.4,20526.5],[0,5444.4,20494.7,5518.4,20518.7],
[0,8043.4,20460.5,8109.4,20499.5],[0,8055.9,20467.7,8096.9,20488.7],
[0,8040.4,20514.5,8112.4,20553.5],[0,8054.4,20521.7,8098.4,20542.7],
[0,8044.4,20406.5,8108.4,20445.5],[0,8057.4,20413.7,8095.4,20434.7],
[0,8017.4,15518.5,8135.4,15557.5],[0,8039.4,15525.7,8113.4,15548.7],
[0,2910.4,1540.5,3034.4,1579.5],[0,2933.9,1547.7,3010.9,1571.7],
[0,5405.4,16204.5,5557.4,16243.5],[0,5429.4,16211.7,5533.4,16232.7],
[0,8000.4,16204.5,8152.4,16243.5],[0,8024.9,16211.7,8127.9,16232.7],
[0,10471,23733,10527,23771],[0,10489,23740.6,10509,23760.6],
[0,8010.4,23732.5,8142.4,23771.5],[0,8034.4,23739.7,8118.4,23763.7],
[0,8036.4,23624.5,8116.4,23663.5],[0,8051.9,23631.7,8100.9,23655.7],
[0,2845.4,21018.5,3099.4,21057.5],[0,2884.4,21025.7,3060.4,21049.7],
[0,10471,23625,10527,23663],[0,10489,23632.6,10509,23652.6],
[0,8004.4,11850.5,8148.4,11889.5],[0,8027.4,11857.7,8125.4,11881.7],
[0,10437,11995.5,10561,12034.5],[0,10459.5,12002.7,10538.5,12026.7],
[0,8048.4,2413,8104.4,2451],[0,8066.4,2420.6,8086.4,2440.6],
[0,5396.4,2869.5,5566.4,2908.5],[0,5423.9,2876.7,5538.9,2900.7],
[0,5373.4,2228.5,5589.4,2267.5],[0,5406.4,2235.7,5556.4,2259.7],
[0,5342.4,2923.5,5620.4,2962.5],[0,5386.4,2930.7,5576.4,2954.7],
[0,5419.4,6904.5,5543.4,6943.5],[0,5440.9,6911.7,5521.9,6935.7],
[0,10397,11620.5,10601,11659.5],[0,10429,11627.7,10569,11651.7],
[0,12757,11620.5,12927,11659.5],[0,12784.5,11627.7,12899.5,11651.7],
[0,5429.4,11609.5,5533.4,11648.5],[0,5447.4,11616.7,5515.4,11640.7],
[0,10414,11468.5,10584,11507.5],[0,10443,11475.7,10555,11499.7],
[0,7961.4,11796.5,8191.4,11835.5],[0,7999.9,11803.7,8152.9,11826.7],
[0,10389,11796.5,10609,11835.5],[0,10425.5,11803.7,10572.5,11827.7],
[0,8048.4,12797,8104.4,12835],[0,8066.4,12804.6,8086.4,12824.6],
[0,5382.4,11850.5,5580.4,11889.5],[0,5413.9,11857.7,5548.9,11881.7],
[0,5390.4,11796.5,5572.4,11835.5],[0,5420.9,11803.7,5541.9,11827.7],
[0,5390.4,11742.5,5572.4,11781.5],[0,5420.4,11749.7,5542.4,11773.7],
[0,7925.4,1838.5,8227.4,1877.5],[0,7973.9,1845.7,8178.9,1869.7],
[0,10379,1857.5,10619,1896.5],[0,10419.5,1864.7,10578.5,1888.7],
[0,7997.4,24310.5,8155.4,24349.5],[0,8024.4,24317.7,8128.4,24341.7],
[0,10442,24016.5,10556,24055.5],[0,10462,24023.7,10536,24047.7],
[0,5433.4,10362.5,5529.4,10401.5],[0,5451.4,10369.7,5511.4,10390.7],
[0,8046.4,10162.5,8106.4,10201.5],[0,8059.4,10169.7,8093.4,10190.7],
[0,734.43,504.5,928.43,543.5],[0,763.93,511.7,898.93,532.7],
[0,2848.4,504.5,3096.4,543.5],[0,2884.9,511.7,3059.9,535.7],
[0,5340.4,462.5,5622.4,501.5],[0,5380.9,469.7,5581.9,490.7],
[0,7983.4,428.5,8169.4,467.5],[0,8011.9,435.7,8140.9,459.7],
[0,7908.4,596.5,8244.4,635.5],[0,7959.4,603.7,8193.4,626.7],
[0,10331,512.5,10667,551.5],[0,10382,519.7,10616,542.7],
[0,2875.4,619.5,3069.4,658.5],[0,2904.9,626.7,3039.9,647.7],
[0,5388.4,638.5,5574.4,677.5],[0,5416.9,645.7,5545.9,669.7],
[0,8023.4,10562.5,8129.4,10601.5],[0,8041.9,10569.7,8110.9,10593.7],
[0,10459,2732.5,10539,2771.5],[0,10474,2739.7,10524,2760.7],
[0,12770,2732.5,12914,2771.5],[0,12795.5,2739.7,12888.5,2763.7],
[0,12814,10998,12870,11036],[0,12832,11005.6,12852,11025.6],
[0,10469,10985.5,10529,11024.5],[0,10481,10992.7,10517,11013.7],
[0,12814,10944,12870,10982],[0,12832,10951.6,12852,10971.6],
[0,5385.4,21172.5,5577.4,21211.5],[0,5416.9,21179.7,5545.9,21203.7],
[0,7987.4,21126.5,8165.4,21165.5],[0,8016.4,21133.7,8136.4,21157.7],
[0,5383.4,21616.5,5579.4,21655.5],[0,5415.4,21623.7,5547.4,21647.7],
[0,7985.4,21570.5,8167.4,21609.5],[0,8014.9,21577.7,8137.9,21601.7],
[0,8041.4,10454.5,8111.4,10493.5],[0,8054.9,10461.7,8097.9,10482.7],
[0,12768,7256.5,12916,7295.5],[0,12794,7263.7,12890,7286.7],
[0,15039,7300.5,15175,7339.5],[0,15063.5,7307.7,15150.5,7331.7],
[0,12812,7310.5,12872,7349.5],[0,12824,7317.7,12860,7338.7],
[0,12814,6289,12870,6327],[0,12832,6296.6,12852,6316.6],
[0,10355,6288.5,10643,6327.5],[0,10402.5,6295.7,10595.5,6319.7],
[0,10363,6234.5,10635,6273.5],[0,10407,6241.7,10591,6265.7],
[0,10462,6472.5,10536,6511.5],[0,10476,6479.7,10522,6500.7],
[0,2908.4,23921.5,3036.4,23960.5],[0,2930.9,23928.7,3013.9,23952.7],
[0,5411.4,23921.5,5551.4,23960.5],[0,5437.4,23928.7,5525.4,23951.7],
[0,5434.4,21118.5,5528.4,21157.5],[0,5451.9,21125.7,5510.9,21146.7],
[0,7908.4,20222.5,8244.4,20261.5],[0,7960.9,20229.7,8191.9,20253.7],
[0,10471,22469,10527,22507],[0,10489,22476.6,10509,22496.6],
[0,7995.4,22414.5,8157.4,22453.5],[0,8020.9,22421.7,8131.9,22442.7],
[0,7999.4,22522.5,8153.4,22561.5],[0,8025.4,22530.7,8127.4,22550.7],
[0,8021.4,22468.5,8131.4,22507.5],[0,8040.9,22476.7,8111.9,22496.7],
[0,5425.4,300.5,5537.4,339.5],[0,5444.9,307.7,5517.9,328.7],
[0,7981.4,300.5,8171.4,339.5],[0,8013.9,307.7,8138.9,331.7],
[0,2908.4,354.5,3036.4,393.5],[0,2929.9,361.7,3014.9,382.7],
[0,5407.4,354.5,5555.4,393.5],[0,5432.4,361.7,5530.4,382.7],
[0,5410.4,408.5,5552.4,447.5],[0,5434.4,415.7,5528.4,436.7],
[0,759.43,300.5,903.43,339.5],[0,783.43,307.7,879.43,328.7],
[0,2913.4,300.5,3031.4,339.5],[0,2934.4,307.7,3010.4,328.7],
[0,8048.4,3993,8104.4,4031],[0,8066.4,4000.6,8086.4,4020.6],
[0,5429.4,2815.5,5533.4,2854.5],[0,5447.4,2822.7,5515.4,2843.7],
[0,5424.4,4142.5,5538.4,4181.5],[0,5443.4,4149.7,5519.4,4173.7],
[0,5354.4,3838.5,5608.4,3877.5],[0,5394.4,3845.7,5568.4,3869.7],
[0,12814,4451,12870,4489],[0,12832,4458.6,12852,4478.6],
[0,10394,5126.5,10604,5165.5],[0,10429,5133.7,10569,5156.7],
[0,10406,4612.5,10592,4651.5],[0,10436.5,4619.7,10561.5,4643.7],
[0,10415,4196.5,10583,4235.5],[0,10442.5,4203.7,10555.5,4227.7],
[0,10398,4142.5,10600,4181.5],[0,10429.5,4149.7,10568.5,4173.7],
[0,10412,4504.5,10586,4543.5],[0,10440,4511.7,10558,4535.7],
[0,10451,4450.5,10547,4489.5],[0,10468.5,4457.7,10529.5,4481.7],
[0,10423,4396.5,10575,4435.5],[0,10446.5,4403.7,10551.5,4427.7],
[0,10447,4558.5,10551,4597.5],[0,10465,4568.7,10533,4589.7],
[0,10431,4666.5,10567,4705.5],[0,10454,4673.7,10544,4697.7],
[0,10461,4342.5,10537,4381.5],[0,10475,4349.7,10523,4373.7],
[0,12814,5516,12870,5554],[0,12832,5523.6,12852,5543.6],
[0,10423,5380.5,10575,5419.5],[0,10447,5387.7,10551,5411.7],
[0,10400,5488.5,10598,5527.5],[0,10432,5495.7,10566,5519.7],
[0,10389,5542.5,10609,5581.5],[0,10425.5,5549.7,10572.5,5573.7],
[0,10399,5596.5,10599,5635.5],[0,10429.5,5603.7,10568.5,5627.7],
[0,10406,5434.5,10592,5473.5],[0,10435.5,5441.7,10562.5,5465.7],
[0,12814,6851,12870,6889],[0,12832,6858.6,12852,6878.6],
[0,10404,6526.5,10594,6565.5],[0,10435.5,6533.7,10562.5,6556.7],
[0,10466,6850.5,10532,6889.5],[0,10479,6857.7,10519,6878.7],
[0,10436,6904.5,10562,6943.5],[0,10457.5,6912.7,10540.5,6935.7],
[0,10441,6996.5,10557,7035.5],[0,10460.5,7003.7,10537.5,7027.7],
[0,10431,6796.5,10567,6835.5],[0,10453,6804.7,10545,6827.7],
[0,10422,6580.5,10576,6619.5],[0,10449.5,6587.7,10548.5,6611.7],
[0,10458,7050.5,10540,7089.5],[0,10473,7058.7,10525,7081.7],
[0,8006.4,5823.5,8146.4,5862.5],[0,8029.4,5830.7,8123.4,5854.7],
[0,10397,5796.5,10601,5835.5],[0,10430.5,5803.7,10567.5,5827.7],
[0,10429,5850.5,10569,5889.5],[0,10452.5,5857.7,10545.5,5881.7],
[0,12814,4559,12870,4597],[0,12832,4566.6,12852,4586.6],
[0,10429,5180.5,10569,5219.5],[0,10453.5,5187.7,10544.5,5210.7],
[0,12814,5408,12870,5446],[0,12832,5415.6,12852,5435.6],
[0,12814,22874,12870,22912],[0,12832,22881.6,12852,22901.6],
[0,10398,22846.5,10600,22885.5],[0,10432.5,22853.7,10565.5,22877.7],
[0,10398,22900.5,10600,22939.5],[0,10432.5,22907.7,10565.5,22931.7],
[0,10398,22954.5,10600,22993.5],[0,10432.5,22961.7,10565.5,22985.7],
[0,10398,22792.5,10600,22831.5],[0,10432.5,22799.7,10565.5,22823.7],
[0,12814,7911,12870,7949],[0,12832,7918.6,12852,7938.6],
[0,10401,7964.5,10597,8003.5],[0,10434,7971.7,10564,7994.7],
[0,10401,7910.5,10597,7949.5],[0,10434,7917.7,10564,7940.7],
[0,10401,7818.5,10597,7857.5],[0,10434,7825.7,10564,7848.7],
[0,5383.4,7440.5,5579.4,7479.5],[0,5416.4,7447.7,5546.4,7470.7],
[0,8004.4,22576.5,8148.4,22615.5],[0,8028.9,22583.7,8123.9,22604.7],
[0,10460,22576.5,10538,22615.5],[0,10475.5,22583.7,10522.5,22604.7],
[0,10403,3780.5,10595,3819.5],[0,10435,3787.7,10563,3808.7],
[0,12780,3757.5,12904,3796.5],[0,12803,3764.7,12881,3787.7],
[0,2804.4,192.5,3140.4,231.5],[0,2854.9,199.7,3089.9,223.7],
[0,5336.4,192.5,5626.4,231.5],[0,5379.9,199.7,5582.9,223.7],
[0,702.43,246.5,960.43,285.5],[0,740.93,253.7,921.93,277.7],
[0,2884.4,246.5,3060.4,285.5],[0,2912.4,253.7,3032.4,277.7],
[0,12704,5153.5,12980,5192.5],[0,12747,5160.7,12937,5184.7],
[0,14953,5452.5,15261,5491.5],[0,15000,5459.7,15214,5483.7],
[0,12814,4505,12870,4543],[0,12832,4512.6,12852,4532.6],
[0,10408,4720.5,10590,4759.5],[0,10437.5,4727.7,10560.5,4751.7],
[0,12814,4613,12870,4651],[0,12832,4620.6,12852,4640.6],
[0,12814,8397,12870,8435],[0,12832,8404.6,12852,8424.6],
[0,10408,8018.5,10590,8057.5],[0,10438.5,8025.7,10559.5,8049.7],
[0,10465,8072.5,10533,8111.5],[0,10479.5,8079.7,10518.5,8100.7],
[0,10445,8504.5,10553,8543.5],[0,10465,8511.7,10533,8532.7],
[0,10471,8558.5,10527,8597.5],[0,10486.5,8568.7,10511.5,8586.7],
[0,12814,8127,12870,8165],[0,12832,8134.6,12852,8154.6],
[0,12814,5462,12870,5500],[0,12832,5469.6,12852,5489.6],
[0,10408,5234.5,10590,5273.5],[0,10437.5,5241.7,10560.5,5265.7],
[0,12814,5354,12870,5392],[0,12832,5361.6,12852,5381.6],
[0,12713,4980.5,12971,5019.5],[0,12754.5,4987.7,12929.5,5011.7],
[0,14995,4896.5,15219,4935.5],[0,15029,4903.7,15185,4927.7],
[0,5388.4,6666.5,5574.4,6705.5],[0,5418.9,6673.7,5543.9,6697.7],
[0,7973.4,6666.5,8179.4,6705.5],[0,8005.9,6673.7,8146.9,6697.7],
[0,5345.4,8080.5,5617.4,8119.5],[0,5388.9,8087.7,5573.9,8111.7],
[0,7941.4,8042.5,8211.4,8081.5],[0,7984.4,8049.7,8168.4,8073.7],
[0,10402,13362.5,10596,13401.5],[0,10434.5,13369.7,10563.5,13393.7],
[0,8022.4,13208.5,8130.4,13247.5],[0,8040.4,13215.7,8112.4,13239.7],
[0,12814,6573,12870,6611],[0,12832,6580.6,12852,6600.6],
[0,15079,6897,15135,6935],[0,15097,6904.6,15117,6924.6],
[0,12742,6234.5,12942,6273.5],[0,12775,6241.7,12909,6265.7],
[0,7959.4,3326.5,8193.4,3365.5],[0,7995.4,3333.7,8157.4,3357.7],
[0,10445,3056.5,10553,3095.5],[0,10463,3063.7,10535,3087.7],
[0,5414.4,20390.5,5548.4,20429.5],[0,5437.4,20397.7,5525.4,20418.7],
[0,7988.4,20314.5,8164.4,20353.5],[0,8016.9,20321.7,8135.9,20345.7],
[0,5330.4,20810.5,5632.4,20849.5],[0,5378.4,20817.7,5584.4,20841.7],
[0,7996.4,20736.5,8156.4,20775.5],[0,8024.4,20743.7,8128.4,20767.7],
[0,7974.4,6012.5,8178.4,6051.5],[0,8009.9,6019.7,8142.9,6042.7],
[0,10469,6012.5,10529,6051.5],[0,10481.5,6019.7,10516.5,6040.7],
[0,5377.4,14306.5,5585.4,14345.5],[0,5410.9,14313.7,5551.9,14337.7],
[0,7954.4,14306.5,8198.4,14345.5],[0,7994.4,14313.7,8158.4,14336.7],
[0,10423,16112.5,10575,16151.5],[0,10447.5,16119.7,10550.5,16140.7],
[0,12768,16112.5,12916,16151.5],[0,12793,16119.7,12891,16140.7],
[0,10422,16058.5,10576,16097.5],[0,10447.5,16065.7,10550.5,16086.7],
[0,5409.4,5488.5,5553.4,5527.5],[0,5433.9,5495.7,5528.9,5516.7],
[0,7953.4,5534.5,8199.4,5573.5],[0,7992.4,5541.7,8160.4,5564.7],
[0,12814,6343,12870,6381],[0,12832,6350.6,12852,6370.6],
[0,7983.4,6158.5,8169.4,6197.5],[0,8014.9,6165.7,8137.9,6188.7],
[0,12814,6943,12870,6981],[0,12832,6950.6,12852,6970.6],
[0,785.43,1394.5,877.43,1433.5],[0,802.43,1401.7,860.43,1425.7],
[0,2917.4,1394.5,3027.4,1433.5],[0,2938.9,1401.7,3005.9,1425.7],
[0,8025.4,4826.5,8127.4,4865.5],[0,8042.4,4833.7,8110.4,4857.7],
[0,10471,5289,10527,5327],[0,10489,5296.6,10509,5316.6],
[0,8024.4,5264.5,8128.4,5303.5],[0,8042.4,5271.7,8110.4,5295.7],
[0,8024.4,5426.5,8128.4,5465.5],[0,8041.9,5433.7,8110.9,5457.7],
[0,5401.4,7290.5,5561.4,7329.5],[0,5430.9,7297.7,5531.9,7321.7],
[0,2855.4,17318.5,3089.4,17357.5],[0,2893.4,17325.7,3051.4,17349.7],
[0,10428,17916.5,10570,17955.5],[0,10453,17923.7,10545,17946.7],
[0,12662,17916.5,13022,17955.5],[0,12717,17923.7,12967,17947.7],
[0,5381.4,21524.5,5581.4,21563.5],[0,5416.4,21531.7,5546.4,21554.7],
[0,7990.4,21516.5,8162.4,21555.5],[0,8020.9,21523.7,8131.9,21546.7],
[0,5434.4,5823.5,5528.4,5862.5],[0,5450.4,5830.7,5512.4,5854.7],
[0,12814,8775,12870,8813],[0,12832,8782.6,12852,8802.6],
[0,10407,8720.5,10591,8759.5],[0,10437,8727.7,10561,8751.7],
[0,10425,8936.5,10573,8975.5],[0,10451.5,8943.7,10546.5,8967.7],
[0,10408,8882.5,10590,8921.5],[0,10437.5,8889.7,10560.5,8913.7],
[0,10427,8774.5,10571,8813.5],[0,10452.5,8781.7,10545.5,8805.7],
[0,10430,8666.5,10568,8705.5],[0,10453.5,8673.7,10544.5,8697.7],
[0,10445,8612.5,10553,8651.5],[0,10464.5,8619.7,10533.5,8643.7],
[0,10441,8828.5,10557,8867.5],[0,10461.5,8835.7,10536.5,8859.7],
[0,12814,8829,12870,8867],[0,12832,8836.6,12852,8856.6],
[0,10461,9044.5,10537,9083.5],[0,10475.5,9051.7,10522.5,9075.7],
[0,10471,5651,10527,5689],[0,10489,5658.6,10509,5678.6],
[0,8029.4,5480.5,8123.4,5519.5],[0,8046.4,5487.7,8106.4,5511.7],
[0,7950.4,15896.5,8202.4,15935.5],[0,7992.4,15903.7,8160.4,15926.7],
[0,10373,16524.5,10625,16563.5],[0,10415,16531.7,10583,16554.7],
[0,7935.4,10616.5,8217.4,10655.5],[0,7979.9,10623.7,8172.9,10647.7],
[0,10358,10801.5,10640,10840.5],[0,10402.5,10808.7,10595.5,10832.7],
[0,5426.4,10092.5,5536.4,10131.5],[0,5447.4,10099.7,5515.4,10120.7],
[0,8018.4,10054.5,8134.4,10093.5],[0,8038.4,10061.7,8114.4,10082.7],
[0,8012.4,10108.5,8140.4,10147.5],[0,8036.4,10115.7,8116.4,10138.7],
[0,10471,9099,10527,9137],[0,10489,9106.6,10509,9126.6],
[0,8027.4,8886.5,8125.4,8925.5],[0,8044.9,8893.7,8107.9,8914.7],
[0,8032.4,8832.5,8120.4,8871.5],[0,8049.9,8839.7,8102.9,8860.7],
[0,8014.4,9048.5,8138.4,9087.5],[0,8036.4,9055.7,8116.4,9076.7],
[0,8027.4,8994.5,8125.4,9033.5],[0,8045.4,9001.7,8107.4,9022.7],
[0,8025.4,9102.5,8127.4,9141.5],[0,8043.9,9109.7,8108.9,9130.7],
[0,10471,8991,10527,9029],[0,10489,8998.6,10509,9018.6],
[0,8016.4,3761.5,8136.4,3800.5],[0,8036.4,3768.7,8116.4,3789.7],
[0,10440,3834.5,10558,3873.5],[0,10461.5,3841.7,10536.5,3864.7],
[0,5382.4,3345.5,5580.4,3384.5],[0,5413.9,3352.7,5548.9,3376.7],
[0,8006.4,3272.5,8146.4,3311.5],[0,8030.4,3279.7,8122.4,3300.7],
[0,8008.4,22630.5,8144.4,22669.5],[0,8033.4,22637.7,8119.4,22658.7],
[0,10411,22630.5,10587,22669.5],[0,10441.5,22637.7,10556.5,22661.7],
[0,8048.4,85,8104.4,123],[0,8066.4,92.6,8086.4,112.6],
[0,5419.4,30.5,5543.4,69.5],[0,5440.9,37.7,5521.9,61.7],
[0,5439.4,84.5,5523.4,123.5],[0,5455.4,91.7,5507.4,112.7],
[0,5407.4,138.5,5555.4,177.5],[0,5432.4,148.7,5530.4,169.7],
[0,12814,5959,12870,5997],[0,12832,5966.6,12852,5986.6],
[0,10457,5904.5,10541,5943.5],[0,10473,5911.7,10525,5935.7],
[0,10463,5958.5,10535,5997.5],[0,10477,5965.7,10521,5989.7],
[0,10442,6142.5,10556,6181.5],[0,10461.5,6149.7,10536.5,6173.7],
[0,5363.4,21724.5,5599.4,21763.5],[0,5399.9,21731.7,5562.9,21755.7],
[0,7972.4,21700.5,8180.4,21739.5],[0,8005.4,21707.7,8147.4,21731.7],
[0,8033.4,6612.5,8119.4,6651.5],[0,8048.9,6619.7,8103.9,6643.7],
[0,10397,6688.5,10601,6727.5],[0,10430.5,6695.7,10567.5,6719.7],
[0,15079,15546,15135,15584],[0,15097,15553.6,15117,15573.6],
[0,12790,15491.5,12894,15530.5],[0,12808.5,15498.7,12875.5,15522.7],
[0,12778,15545.5,12906,15584.5],[0,12799,15552.7,12885,15576.7],
[0,12757,15599.5,12927,15638.5],[0,12783.5,15606.7,12900.5,15630.7],
[0,5368.4,7586.5,5594.4,7625.5],[0,5403.9,7593.7,5558.9,7617.7],
[0,7954.4,7582.5,8198.4,7621.5],[0,7992.9,7589.7,8159.9,7613.7],
[0,16682,2490,16738,2528],[0,16700,2497.6,16720,2517.6],
[0,14995,2435.5,15219,2474.5],[0,15030,2442.7,15184,2466.7],
[0,14988,2489.5,15226,2528.5],[0,15025,2496.7,15189,2520.7],
[0,14995,2657.5,15219,2696.5],[0,15031.5,2664.7,15182.5,2688.7],
[0,16682,2409,16738,2447],[0,16700,2416.6,16720,2436.6],
[0,15009,2381.5,15205,2420.5],[0,15040,2388.7,15174,2412.7],
[0,14961,2327.5,15253,2366.5],[0,15006.5,2334.7,15207.5,2358.7],
[0,8021.4,17702.5,8131.4,17741.5],[0,8043.4,17709.7,8109.4,17732.7],
[0,10428,17862.5,10570,17901.5],[0,10455,17869.7,10543,17892.7],
[0,5392.4,19644.5,5570.4,19683.5],[0,5422.4,19651.7,5540.4,19675.7],
[0,7971.4,18752.5,8181.4,18791.5],[0,8006.4,18759.7,8146.4,18783.7],
[0,5435.4,19074.5,5527.4,19113.5],[0,5452.9,19081.7,5509.9,19105.7],
[0,8014.4,18698.5,8138.4,18737.5],[0,8036.9,18705.7,8115.9,18729.7],
[0,10447,23116.5,10551,23155.5],[0,10466,23126.7,10532,23144.7],
[0,12805,23116.5,12879,23155.5],[0,12819,23123.7,12865,23144.7],
[0,7973.4,3884.5,8179.4,3923.5],[0,8009.4,3891.7,8143.4,3914.7],
[0,10389,3888.5,10609,3927.5],[0,10423,3895.7,10575,3919.7],
[0,10389,19815.5,10609,19854.5],[0,10426,19822.7,10572,19845.7],
[0,12730,19815.5,12954,19854.5],[0,12767,19822.7,12917,19843.7],
[0,5381.4,20586.5,5581.4,20625.5],[0,5413.4,20593.7,5549.4,20617.7],
[0,7983.4,20606.5,8169.4,20645.5],[0,8012.9,20613.7,8139.9,20637.7],
[0,10471,22739,10527,22777],[0,10489,22746.6,10509,22766.6],
[0,7995.4,22684.5,8157.4,22723.5],[0,8023.9,22691.7,8128.9,22715.7],
[0,8022.4,23062.5,8130.4,23101.5],[0,8040.9,23069.7,8111.9,23093.7],
[0,8017.4,22738.5,8135.4,22777.5],[0,8037.9,22745.7,8114.9,22769.7],
[0,8025.4,16788.5,8127.4,16827.5],[0,8044.4,16795.7,8108.4,16816.7],
[0,5432.4,21378.5,5530.4,21417.5],[0,5450.4,21385.7,5512.4,21406.7],
[0,752.43,3.5,910.43,42.5],[0,780.43,10.7,882.43,34.7],
[0,2916.4,4,3028.4,42],[0,2918.4,11.6,3026.4,31.6],
[0,7950.4,15788.5,8202.4,15827.5],[0,7991.4,15795.7,8161.4,15819.7],
[0,5341.4,17779.5,5621.4,17818.5],[0,5385.4,17786.7,5577.4,17809.7],
[0,7997.4,15572.5,8155.4,15611.5],[0,8025.9,15579.7,8126.9,15603.7],
[0,12764,7748.5,12920,7787.5],[0,12792,7755.7,12892,7778.7],
[0,15079,7657,15135,7695],[0,15087.5,7664.6,15126.5,7684.6],
[0,7967.4,7636.5,8185.4,7675.5],[0,8003.4,7643.7,8149.4,7667.7],
[0,8006.4,17794.5,8146.4,17833.5],[0,8029.9,17801.7,8122.9,17822.7],
[0,5349.4,2082.5,5613.4,2121.5],[0,5392.9,2089.7,5569.9,2112.7],
[0,12814,2267,12870,2305],[0,12822.5,2274.6,12861.5,2294.6],
[0,10400,7266.5,10598,7305.5],[0,10432.5,7273.7,10565.5,7297.7],
[0,12814,7149,12870,7187],[0,12822.5,7156.6,12861.5,7176.6],
[0,7964.4,14360.5,8188.4,14399.5],[0,8001.9,14367.7,8150.9,14390.7],
[0,5302.4,10862.5,5660.4,10901.5],[0,5358.9,10869.7,5603.9,10893.7],
[0,5366.4,11515.5,5596.4,11554.5],[0,5402.9,11522.7,5559.9,11546.7],
[0,7897.4,11108.5,8255.4,11147.5],[0,7953.9,11115.7,8198.9,11139.7],
[0,7980.4,13316.5,8172.4,13355.5],[0,8011.4,13323.7,8141.4,13347.7],
[0,714.43,16990.5,948.43,17029.5],[0,752.43,16997.7,910.43,17020.7],
[0,7987.4,9210.5,8165.4,9249.5],[0,8016.9,9217.7,8135.9,9241.7],
[0,5427.4,10146.5,5535.4,10185.5],[0,5445.9,10153.7,5516.9,10177.7],
[0,8048.4,7491,8104.4,7529],[0,8056.9,7498.6,8095.9,7518.6],
[0,7991.4,7766.5,8161.4,7805.5],[0,8018.4,7773.7,8134.4,7794.7],
[0,10420,5018.5,10578,5057.5],[0,10447,5025.7,10551,5049.7],
[0,7984.4,22846.5,8168.4,22885.5],[0,8014.4,22853.7,8138.4,22877.7],
[0,7984.4,22900.5,8168.4,22939.5],[0,8014.4,22907.7,8138.4,22931.7],
[0,7984.4,22954.5,8168.4,22993.5],[0,8014.4,22961.7,8138.4,22985.7],
[0,7984.4,22792.5,8168.4,22831.5],[0,8014.4,22799.7,8138.4,22823.7],
[0,2898.4,11264.5,3046.4,11303.5],[0,2923.9,11271.7,3020.9,11292.7],
[0,2901.4,12784.5,3043.4,12823.5],[0,2923.9,12791.7,3020.9,12815.7],
[0,2896.4,16004.5,3048.4,16043.5],[0,2922.9,16011.7,3021.9,16035.7],
[0,5360.4,2977.5,5602.4,3016.5],[0,5397.4,2984.7,5565.4,3008.7],
[0,12751,7364.5,12933,7403.5],[0,12781.5,7371.7,12902.5,7395.7],
[0,5349.4,10200.5,5613.4,10239.5],[0,5392.4,10207.7,5570.4,10230.7],
[0,5429.4,16112.5,5533.4,16151.5],[0,5448.4,16119.7,5514.4,16140.7],
[0,8048.4,16113,8104.4,16151],[0,8056.9,16120.6,8095.9,16140.6],
[0,5383.4,2282.5,5579.4,2321.5],[0,5415.4,2289.7,5547.4,2312.7],
[0,8048.4,3108,8104.4,3146],[0,8056.9,3115.6,8095.9,3135.6],
[0,8048.4,5096,8104.4,5134],[0,8056.9,5103.6,8095.9,5123.6],
[0,8048.4,4235,8104.4,4273],[0,8056.9,4242.6,8095.9,4262.6],
[0,8048.4,4665,8104.4,4703],[0,8056.9,4672.6,8095.9,4692.6],
[0,8048.4,4143,8104.4,4181],[0,8056.9,4150.6,8095.9,4170.6],
[0,8048.4,4973,8104.4,5011],[0,8056.9,4980.6,8095.9,5000.6],
[0,8048.4,4773,8104.4,4811],[0,8056.9,4780.6,8095.9,4800.6],
[0,2867.4,3391.5,3077.4,3430.5],[0,2900.4,3398.7,3044.4,3422.7],
[0,7970.4,16312.5,8182.4,16351.5],[0,8004.4,16319.7,8148.4,16340.7],
[0,5333.4,18708.5,5629.4,18747.5],[0,5379.9,18715.7,5582.9,18739.7],
[0,8004.4,10400.5,8148.4,10439.5],[0,8027.9,10407.7,8124.9,10428.7],
[0,5413.4,6062.5,5549.4,6101.5],[0,5438.4,6069.7,5524.4,6092.7],
[0,8048.4,6105,8104.4,6143],[0,8056.9,6112.6,8095.9,6132.6],
[0,8000.4,7143.5,8152.4,7182.5],[0,8024.9,7150.7,8127.9,7174.7],
[0,2848.4,20810.5,3096.4,20849.5],[0,2887.4,20817.7,3057.4,20841.7],
[0,2910.4,8126.5,3034.4,8165.5],[0,2932.9,8133.7,3011.9,8154.7],
[0,7986.4,18974.5,8166.4,19013.5],[0,8018.4,18981.7,8134.4,19004.7],
[0,7983.4,15074.5,8169.4,15113.5],[0,8013.4,15081.7,8139.4,15105.7],
[0,5342.4,1838.5,5620.4,1877.5],[0,5388.4,1845.7,5574.4,1869.7],
[0,5400.4,1922.5,5562.4,1961.5],[0,5428.4,1929.7,5534.4,1953.7],
[0,7989.4,14144.5,8163.4,14183.5],[0,8018.9,14151.7,8133.9,14174.7],
[0,7968.4,16058.5,8184.4,16097.5],[0,8005.9,16065.7,8146.9,16089.7],
[0,8048.4,6267,8104.4,6305],[0,8056.9,6274.6,8095.9,6294.6],
[0,8048.4,6321,8104.4,6359],[0,8056.9,6328.6,8095.9,6348.6],
[0,5370.4,6293.5,5592.4,6332.5],[0,5404.4,6300.7,5558.4,6324.7],
[0,7975.4,5318.5,8177.4,5357.5],[0,8009.4,5325.7,8143.4,5349.7],
[0,7942.4,13262.5,8210.4,13301.5],[0,7985.9,13269.7,8166.9,13293.7],
[0,2874.4,9978.5,3070.4,10017.5],[0,2907.9,9985.7,3036.9,10009.7],
[0,7997.4,18552.5,8155.4,18591.5],[0,8023.4,18559.7,8129.4,18583.7],
[0,5413.4,20972.5,5549.4,21011.5],[0,5436.4,20979.7,5526.4,21003.7],
[0,8021.4,10508.5,8131.4,10547.5],[0,8040.4,10515.7,8112.4,10539.7],
[0,7985.4,23008.5,8167.4,23047.5],[0,8016.4,23015.7,8136.4,23039.7],
[0,7985.4,23116.5,8167.4,23155.5],[0,8014.4,23123.7,8138.4,23147.7],
[0,2872.4,23975.5,3072.4,24014.5],[0,2903.9,23982.7,3040.9,24006.7],
[0,5388.4,5983.5,5574.4,6022.5],[0,5418.4,5990.7,5544.4,6014.7],
[0,8048.4,5959,8104.4,5997],[0,8056.9,5966.6,8095.9,5986.6],
[0,2942.4,20707.5,3002.4,20746.5],[0,2954.9,20717.7,2989.9,20738.7],
[0,5443.4,6531.5,5519.4,6570.5],[0,5457.9,6541.7,5504.9,6562.7],
[0,8048.4,6559,8104.4,6597],[0,8056.9,6566.6,8095.9,6586.6],
[0,8048.4,6505,8104.4,6543],[0,8056.9,6512.6,8095.9,6532.6],
[0,7966.4,24164.5,8186.4,24203.5],[0,8001.4,24171.7,8151.4,24195.7],
[0,10471,23488,10527,23526],[0,10479.5,23495.6,10518.5,23515.6],
[0,5398.4,18654.5,5564.4,18693.5],[0,5425.4,18661.7,5537.4,18685.7],
[0,7988.4,9534.5,8164.4,9573.5],[0,8016.9,9541.7,8135.9,9562.7],
[0,7962.4,11270.5,8190.4,11309.5],[0,7999.4,11277.7,8153.4,11301.7],
[0,7977.4,13002.5,8175.4,13041.5],[0,8007.9,13009.7,8144.9,13033.7],
[0,7944.4,23170.5,8208.4,23209.5],[0,7987.4,23177.7,8165.4,23201.7],
[0,8021.4,14414.5,8131.4,14453.5],[0,8041.9,14421.7,8110.9,14444.7],
[0,7988.4,14522.5,8164.4,14561.5],[0,8017.4,14529.7,8135.4,14550.7],
[0,5384.4,1765.5,5578.4,1804.5],[0,5413.9,1772.7,5548.9,1796.7],
[0,7965.4,16366.5,8187.4,16405.5],[0,8001.4,16373.7,8151.4,16397.7],
[0,7954.4,13900.5,8198.4,13939.5],[0,7995.9,13907.7,8156.9,13930.7],
[0,8004.4,13500.5,8148.4,13539.5],[0,8028.4,13507.7,8124.4,13531.7],
[0,5371.4,9680.5,5591.4,9719.5],[0,5408.9,9687.7,5553.9,9711.7],
[0,7935.4,12488.5,8217.4,12527.5],[0,7979.4,12495.7,8173.4,12519.7],
[0,7974.4,12434.5,8178.4,12473.5],[0,8010.4,12441.7,8142.4,12464.7],
[0,2866.4,17264.5,3078.4,17303.5],[0,2901.9,17271.7,3042.9,17294.7],
[0,5414.4,12834.5,5548.4,12873.5],[0,5436.4,12841.7,5526.4,12865.7],
[0,7981.4,12218.5,8171.4,12257.5],[0,8012.9,12225.7,8139.9,12249.7],
[0,7953.4,12164.5,8199.4,12203.5],[0,7990.9,12171.7,8161.9,12195.7],
[0,7982.4,12650.5,8170.4,12689.5],[0,8014.4,12657.7,8138.4,12681.7],
[0,8004.4,8210.5,8148.4,8249.5],[0,8028.9,8217.7,8123.9,8241.7],
[0,5437.4,5596.5,5525.4,5635.5],[0,5453.9,5603.7,5508.9,5624.7],
[0,8027.4,13792.5,8125.4,13831.5],[0,8045.4,13799.7,8107.4,13820.7],
[0,2887.4,11318.5,3057.4,11357.5],[0,2915.9,11325.7,3028.9,11349.7],
[0,10459,15518.5,10539,15557.5],[0,10474,15525.7,10524,15549.7],
[0,5421.4,13992.5,5541.4,14031.5],[0,5441.9,13999.7,5520.9,14023.7],
[0,7955.4,10216.5,8197.4,10255.5],[0,7993.4,10223.7,8159.4,10247.7],
[0,7995.4,15680.5,8157.4,15719.5],[0,8022.4,15687.7,8130.4,15708.7],
[0,7993.4,23678.5,8159.4,23717.5],[0,8022.4,23685.7,8130.4,23708.7],
[0,7966.4,7344.5,8186.4,7383.5],[0,8002.4,7351.7,8150.4,7375.7],
[0,10331,1746.5,10667,1785.5],[0,10382.5,1753.7,10615.5,1777.7],
[0,2899.4,7712.5,3045.4,7751.5],[0,2924.4,7719.7,3020.4,7743.7],
[0,7938.4,14468.5,8214.4,14507.5],[0,7983.4,14475.7,8169.4,14498.7],
[0,2872.4,7766.5,3072.4,7805.5],[0,2904.4,7773.7,3040.4,7797.7],
[0,7936.4,21846.5,8216.4,21885.5],[0,7977.9,21853.7,8174.9,21877.7],
[0,7948.4,21900.5,8204.4,21939.5],[0,7986.4,21907.7,8166.4,21931.7],
[0,5419.4,23532.5,5543.4,23571.5],[0,5440.9,23539.7,5521.9,23563.7],
[0,8048.4,23533,8104.4,23571],[0,8056.9,23540.6,8095.9,23560.6],
[0,7908.4,14576.5,8244.4,14615.5],[0,7961.4,14583.7,8191.4,14607.7],
[0,7988.4,11704.5,8164.4,11743.5],[0,8017.9,11711.7,8134.9,11735.7],
[0,5403.4,18600.5,5559.4,18639.5],[0,5429.4,18607.7,5533.4,18631.7],
[0,2891.4,9894.5,3053.4,9933.5],[0,2918.4,9901.7,3026.4,9925.7],
[0,738.43,1016.5,924.43,1055.5],[0,768.43,1023.7,894.43,1047.7],
[0,2944.4,1017,3000.4,1055],[0,2952.9,1024.6,2991.9,1044.6],
[0,2905.4,21278.5,3039.4,21317.5],[0,2927.9,21285.7,3016.9,21309.7],
[0,5453.4,23641,5509.4,23679],[0,5461.9,23648.6,5500.9,23668.6],
[0,2898.4,13946.5,3046.4,13985.5],[0,2924.9,13953.7,3019.9,13976.7],
[0,8014.4,23224.5,8138.4,23263.5],[0,8037.4,23231.7,8115.4,23252.7],
[0,8040.4,23278.5,8112.4,23317.5],[0,8055.4,23288.7,8097.4,23306.7],
[0,768.43,15726.5,894.43,15765.5],[0,790.43,15733.7,872.43,15754.7],
[0,7929.4,14668.5,8223.4,14707.5],[0,7972.9,14675.7,8179.9,14699.7],
[0,767.43,57.5,895.43,96.5],[0,788.93,64.7,873.93,88.7],
[0,2944.4,58,3000.4,96],[0,2952.9,65.6,2991.9,85.6],
[0,5352.4,4880.5,5610.4,4919.5],[0,5389.9,4887.7,5572.9,4911.7],
[0,8048.4,4881,8104.4,4919],[0,8056.9,4888.6,8095.9,4908.6],
[0,7942.4,4718.5,8210.4,4757.5],[0,7982.9,4725.7,8169.9,4749.7],
[0,5340.4,3437.5,5622.4,3476.5],[0,5381.9,3444.7,5580.9,3468.7],
[0,8048.4,3381,8104.4,3419],[0,8056.9,3388.6,8095.9,3408.6],
[0,2890.4,3023.5,3054.4,3062.5],[0,2916.9,3030.7,3027.9,3054.7],
[0,7915.4,17010.5,8237.4,17049.5],[0,7966.4,17017.7,8186.4,17041.7],
[0,5368.4,10254.5,5594.4,10293.5],[0,5406.4,10261.7,5556.4,10285.7],
[0,8048.4,9427,8104.4,9465],[0,8056.9,9434.6,8095.9,9454.6],
[0,8048.4,9481,8104.4,9519],[0,8056.9,9488.6,8095.9,9508.6],
[0,8048.4,9589,8104.4,9627],[0,8056.9,9596.6,8095.9,9616.6],
[0,5416.4,7494.5,5546.4,7533.5],[0,5438.9,7501.7,5523.9,7525.7],
[0,7947.4,23786.5,8205.4,23825.5],[0,7988.4,23793.7,8164.4,23817.7],
[0,5332.4,10308.5,5630.4,10347.5],[0,5379.4,10315.7,5583.4,10339.7],
[0,7978.4,15626.5,8174.4,15665.5],[0,8009.4,15633.7,8143.4,15657.7],
[0,7974.4,13592.5,8178.4,13631.5],[0,8006.9,13599.7,8145.9,13623.7],
[0,5381.4,8026.5,5581.4,8065.5],[0,5415.4,8033.7,5547.4,8056.7],
[0,8037.4,13700.5,8115.4,13739.5],[0,8053.4,13707.7,8099.4,13728.7],
[0,10357,2586.5,10641,2625.5],[0,10400,2593.7,10598,2617.7],
[0,12814,2436,12870,2474],[0,12822.5,2443.6,12861.5,2463.6],
[0,10425,2786.5,10573,2825.5],[0,10451,2793.7,10547,2817.7],
[0,5382.4,6450.5,5580.4,6489.5],[0,5415.4,6457.7,5547.4,6481.7],
[0,8048.4,6451,8104.4,6489],[0,8056.9,6458.6,8095.9,6478.6],
[0,728.43,20528.5,934.43,20567.5],[0,761.93,20535.7,900.93,20559.7],
[0,2944.4,20529,3000.4,20567],[0,2952.9,20536.6,2991.9,20556.6],
[0,2944.4,20303,3000.4,20341],[0,2952.9,20310.6,2991.9,20330.6],
[0,5364.4,18492.5,5598.4,18531.5],[0,5400.4,18499.7,5562.4,18523.7],
[0,8000.4,17064.5,8152.4,17103.5],[0,8025.4,17071.7,8127.4,17092.7],
[0,2908.4,10446.5,3036.4,10485.5],[0,2929.9,10453.7,3014.9,10477.7],
[0,8034.4,12326.5,8118.4,12365.5],[0,8049.4,12333.7,8103.4,12357.7],
[0,7944.4,12542.5,8208.4,12581.5],[0,7987.4,12549.7,8165.4,12573.7],
[0,7971.4,12110.5,8181.4,12149.5],[0,8006.9,12117.7,8145.9,12141.7],
[0,7962.4,16258.5,8190.4,16297.5],[0,7998.9,16265.7,8153.9,16289.7],
[0,7942.4,7398.5,8210.4,7437.5],[0,7984.9,7405.7,8167.9,7428.7],
[0,2881.4,7820.5,3063.4,7859.5],[0,2912.4,7827.7,3032.4,7850.7],
[0,7897.4,23840.5,8255.4,23879.5],[0,7952.4,23847.7,8200.4,23871.7],
[0,10442,2894.5,10556,2933.5],[0,10462,2901.7,10536,2922.7],
[0,5400.4,4972.5,5562.4,5011.5],[0,5426.9,4979.7,5535.9,5003.7],
[0,5428.4,22819.5,5534.4,22858.5],[0,5448.4,22826.7,5514.4,22850.7],
[0,8038.4,23332.5,8114.4,23371.5],[0,8053.9,23339.7,8098.9,23363.7],
[0,8004.4,17518.5,8148.4,17557.5],[0,8028.9,17525.7,8123.9,17549.7],
[0,8004.4,15464.5,8148.4,15503.5],[0,8028.9,15471.7,8123.9,15495.7],
[0,5411.4,8840.5,5551.4,8879.5],[0,5435.4,8847.7,5527.4,8871.7],
[0,7985.4,23478.5,8167.4,23517.5],[0,8014.4,23486.7,8138.4,23509.7],
[0,5374.4,9264.5,5588.4,9303.5],[0,5409.4,9272.7,5553.4,9295.7],
[0,8048.4,9265,8104.4,9303],[0,8056.9,9272.6,8095.9,9292.6],
[0,8006.4,9156.5,8146.4,9195.5],[0,8031.4,9164.7,8121.4,9187.7],
[0,7943.4,17940.5,8209.4,17979.5],[0,7987.9,17947.7,8164.9,17971.7],
[0,2897.4,16528.5,3047.4,16567.5],[0,2923.4,16536.7,3021.4,16556.7],
[0,7938.4,15842.5,8214.4,15881.5],[0,7982.4,15849.7,8170.4,15873.7],
[0,7943.4,16420.5,8209.4,16459.5],[0,7987.9,16427.7,8164.9,16451.7],
[0,5406.4,16420.5,5556.4,16459.5],[0,5432.4,16428.7,5530.4,16448.7],
[0,7938.4,14722.5,8214.4,14761.5],[0,7982.4,14729.7,8170.4,14753.7],
[0,7943.4,17848.5,8209.4,17887.5],[0,7987.9,17855.7,8164.9,17879.7],
[0,5406.4,16474.5,5556.4,16513.5],[0,5432.4,16482.7,5530.4,16502.7],
[0,7938.4,15166.5,8214.4,15205.5],[0,7982.4,15173.7,8170.4,15197.7],
[0,10471,15373,10527,15411],[0,10479.5,15380.6,10518.5,15400.6],
[0,5356.4,18546.5,5606.4,18585.5],[0,5394.4,18553.7,5568.4,18577.7],
[0,8048.4,15373,8104.4,15411],[0,8056.9,15380.6,8095.9,15400.6],
[0,8012.4,23386.5,8140.4,23425.5],[0,8033.4,23393.7,8119.4,23417.7],
[0,8017.4,5372.5,8135.4,5411.5],[0,8037.9,5379.7,8114.9,5403.7],
[0,7989.4,10908.5,8163.4,10947.5],[0,8018.4,10915.7,8134.4,10939.7],
[0,7989.4,11162.5,8163.4,11201.5],[0,8018.4,11169.7,8134.4,11193.7],
[0,7959.4,10308.5,8193.4,10347.5],[0,7996.4,10315.7,8156.4,10339.7],
[0,2935.4,17210.5,3009.4,17249.5],[0,2949.9,17217.7,2994.9,17241.7],
[0,5453.4,17211,5509.4,17249],[0,5461.9,17218.6,5500.9,17238.6],
[0,5453.4,17265,5509.4,17303],[0,5461.9,17272.6,5500.9,17292.6],
[0,2869.4,20356.5,3075.4,20395.5],[0,2904.4,20363.7,3040.4,20387.7],
[0,5411.4,2136.5,5551.4,2175.5],[0,5435.4,2143.7,5527.4,2164.7],
[0,7977.4,18346.5,8175.4,18385.5],[0,8009.9,18353.7,8142.9,18377.7],
[0,5328.4,21470.5,5634.4,21509.5],[0,5376.9,21477.7,5585.9,21501.7],
[0,13015,17989,15003,17991],[0,8125.68,17434.5,10403.2,17976.8],
[0,3048.47,21722.3,5398.03,21796.4],[0,10592,17406,12757,17408],
[0,936.859,1614,2892.41,1641],[0,3061.7,1667,5418.3,1669],
[0,5544.89,21237.2,8021.7,21249.7],[0,8151.73,9712.01,10418.2,10100],
[0,5532.69,22049.4,8016.41,22069.6],[0,10568,23405,12774,23407],
[0,880.418,1467,2945.21,1491],[0,3054.49,3196,5399.71,3219],
[0,10596,23351,12794,23353],[0,10600,10620,12741,10622],
[0,8147,22217,10436,22219],[0,8125.69,2698,10451,2730],
[0,5592.02,16556.5,7965.98,16761.5],[0,5610.1,16601,7947.7,16603],
[0,5623.28,16496,7934.62,16546],[0,10618.9,15343.5,15080.1,15586.5],
[0,12968,15274,15080,15343.1],[0,12971,15342,15080,15344],
[0,10606,14126,12815,14179],[0,10606,14073,12815,14126],
[0,10607,14125,12815,14127],[0,8161.6,22271,10431,22273],
[0,8148,13665,10472,13667],[0,8149.99,12767,10472.4,13652.9],
[0,8153.12,13683.4,10487.8,15754.8],[0,8156.7,22325,10417,22327],
[0,5523,15969,8047.8,15971],[0,10570.9,10858,12815.1,11158],
[0,10579.9,10717,12815.1,10854],[0,10527,10855,12815,10913],
[0,10574.9,10771,12815.1,10908],[0,10574.9,10911,12815.1,11160],
[0,10527,10908,12815,10914],[0,5515.7,1513,8023.8,1515],
[0,5599.2,11233,7989.8,11237],[0,5581.98,11237,7990.12,11287],
[0,3012.39,20940.1,5449.91,21578.1],[0,3029.46,21591.3,5433.84,21689.1],
[0,10586.9,23588,12766.1,23815.1],[0,3023.1,14801.5,10402,15401.7],
[0,10593.9,12325,12772.1,12476],[0,3020,20267.2,5390.2,20280.6],
[0,8204.98,12294,10398,12345],[0,8159.42,12043,10418.1,12218],
[0,5530.88,21812.4,7983.91,21852.2],[0,8205.79,14218,10391,14234],
[0,10609,23027,12728,23029],[0,8137.54,16435.2,10472,18168.3],
[0,8117.52,16436.6,10472.1,17619.2],[0,8112.06,16435.5,10472,18073.6],
[0,5571.89,21343.8,7958.41,21367.9],[0,5620.86,17038.6,7899.14,17131.9],
[0,8217.59,2157,10361,2193],[0,5517.78,12962.1,7978.03,13857],
[0,3143.9,12945,5367.2,12947],[0,10598,12956,12762,12958],
[0,12887,2622,15057,2624],[0,12910.9,2626,15058.1,2801],
[0,5492.98,11196.3,10416.1,17612.9],[0,5595.85,23999.9,8002.65,24127.2],
[0,8208.9,24491,10472,24493],[0,8136.28,24491.6,10472,24545.7],
[0,8151.58,24438.7,10472,24492.4],[0,8207.08,24437.6,10472,24490.1],
[0,8163.97,23923.8,10472.2,24432],[0,8151.9,24437,10472,24439],
[0,10595,7676,12803,7708],[0,8175.81,2666,10374.3,17028.8],
[0,884.621,1359,2917.5,1361],[0,8132.99,6761,10432,6779],
[0,5562.99,7897,7960.71,7916],[0,8135.09,14271,10426,14289],
[0,8169.2,22379,10427,22381],[0,5566.29,20884.3,8009.32,20924],
[0,10579,23247.9,12788,23273.4],[0,10584.8,16988.5,12780.2,17395.8],
[0,8194.1,16975,10371,16977],[0,8173.67,8202.01,10472.1,8950.99],
[0,8138.67,8203.01,10472.1,8520.99],[0,8151.96,8203.01,10472.2,8572.99],
[0,8171.38,8255,10472.1,9331.99],[0,8140.79,8256.01,10472.1,8521.99],
[0,8152.16,8257.01,10472.1,8572.99],[0,10654,23189,12677,23191],
[0,8184.47,13468,10348,13535],[0,5589.2,13465,7966.6,13467],
[0,8158.67,24085.1,10472.2,24594],[0,8165.57,23977.1,10472.3,24592.2],
[0,8176.23,24600.8,10472.1,24756.3],[0,8163.07,24031.2,10472.3,24593.1],
[0,8178.56,24600.2,10472,24704.4],[0,8179.8,24599,10472,24601],
[0,8214.48,24599.6,10472,24651.9],[0,5543.65,18667,7988.65,18780.2],
[0,5548.49,8284,8002.91,8304],[0,8126.69,10841,10424.1,11105],
[0,10609,18043,12772,18045],[0,8139.85,9801.01,10422.2,10155],
[0,5563.38,18182.7,7984.82,18235.1],[0,8171.3,24155,10427.1,24375.8],
[0,10617,21870.2,12736,21893.9],[0,5557.65,3185,7982.05,3308],
[0,3088,3088,5376.8,3098],[0,8174.71,6239,10426.1,6433],
[0,8156.14,23875.1,10435.2,24263.8],[0,3063.6,1251,5423.7,1253],
[0,937.227,1279,2893.81,1306],[0,10527,7378,12815,7438],
[0,10555.9,7183.01,12815.1,7435.99],[0,10512.2,4810.38,12815,7441.15],
[0,10527,13278,12780,13380],[0,15200,16157.1,16642,16207.7],
[0,15167,16208,16642,16210],[0,15166,16262,16639,16264],
[0,15165,16210.3,16642,16262],[0,10554.9,9684,12815.1,9839],
[0,10549,9682,12815,9697],[0,10566,9590,12815,9683],
[0,10573,9642,12815,9684],[0,10566,9535,12815,9602],
[0,10549,9602,12815,9695],[0,10567,9587,12815,9603],
[0,10573,9601,12815,9642],[0,8131.02,10588,12815,10712],
[0,10584,10712,12815,10714],[0,10526.9,10714,12815.1,10912],
[0,8132.88,10676.5,12815.1,10767],[0,10578,10766,12815,10768],
[0,10526.9,10768,12815.1,10912],[0,8108.28,9954.02,10398.2,12403.2],
[0,5534.1,14909,8037.1,14911],[0,8178.59,12616,10397,12643],
[0,5622.3,16023,8004.4,16025],[0,5575.98,17490.7,7986.73,18450.8],
[0,10534.6,13981.1,12811.5,15177.5],[0,10544,9318,12815,9372],
[0,10587,9317,12815,9319],[0,10623,9266,12815,9318],
[0,10544,9264,12815,9371],[0,10587,9264,12815,9317],
[0,10596,9175,12815,9264],[0,10544,9371,12815,9373],
[0,10551,9372,12815,9426],[0,10587,9319,12815,9372],
[0,10551.9,7434,12778.1,7581],[0,10550.9,7226,12790.1,7428],
[0,10590,4026,12815,4054],[0,8149.59,3957,12815,4027],
[0,10562,4000,12815,4028],[0,10546,4027,12815,4107],
[0,8144.59,10789,10416.1,11050],[0,10579,16382.8,12815,16436.4],
[0,10581.9,16438.8,12815.1,16751.5],[0,10543,16435.6,12815,16490],
[0,10567,16330.1,12815,16435.7],[0,10551,9426,12815,9480],
[0,10544,9372,12815,9426],[0,10585,9321,12815,9426],
[0,5563.68,1091,8049.42,1144],[0,5560.2,1143,8049.2,1145],
[0,5592.08,1144,8049.32,1197],[0,5563.38,766,8049.32,819],
[0,5559.38,713,8049.22,766],[0,5592.1,765,8049.3,767],
[0,8159.09,2285,10472,2302],[0,8156.24,2289.01,10472.2,2663.99],
[0,8150.59,2248,10472,2287],[0,10601,15419.8,12777,15482.2],
[0,5598.37,877,8049.13,955],[0,5564.07,955,8049.43,1034],
[0,5560.49,928,8049.21,956],[0,5592.89,954,8049.31,982],
[0,10598.9,4096,12815.1,4300],[0,10590,4055,12815,4096],
[0,10562,4002,12815,4095],[0,10546,4094,12815,4109],
[0,10542.6,3356.08,12815.4,4291.93],[0,10560.8,2977.01,12815.2,3342.99],
[0,10550.9,3028.01,12815.1,3342.99],[0,10546,3239,12815,3346],
[0,10530,3346,12815,3454],[0,10561.9,3347,12815.1,3557],
[0,10598.9,3190,12815.1,3345],[0,10580,3345,12815,3347],
[0,10570.9,2870.01,12815.2,3340.98],[0,10609,3294,12815,3346],
[0,10556,3346,12815,3400],[0,10560.9,3349.01,12815.1,3661.99],
[0,10540.9,3347,12815.1,3506],[0,10546.9,3348.01,12815.1,3610.99],
[0,10571.9,3136,12815.1,3345],[0,8145.32,7974,10407.1,8140],
[0,8161.87,8311.01,10472.1,8624.99],[0,8178.93,8471,10472.1,8630],
[0,8151.49,8472.01,10472.1,8735.99],[0,8163.28,8471.01,10472.1,9385.99],
[0,8167.59,8368.01,10436.1,8626.99],[0,10594,9950,12815,10003],
[0,10630,9898,12815,9950],[0,10629.9,9796,12815.1,9949],
[0,10599,9950,12815,10054],[0,8104.88,5736.06,10458.3,7292.86],
[0,8177.43,7130,10408.1,7303],[0,8174.31,7318,10457.1,7521],
[0,8187.26,7311.01,17527.9,9755.81],[0,16763,7675,17509,7677],
[0,16757.9,7624,17509.1,7675],[0,8162.38,7321.01,10430.2,7696.99],
[0,8112.35,4245.66,12815,7293.89],[0,10614,4262,12815,4307],
[0,10544.9,4110,12815.1,4261],[0,8164.35,7320.01,12801,7879.49],
[0,8163.85,7320.01,12794,7828.36],[0,8165.68,7320.01,12815,7555.78],
[0,10610.8,4312.02,12815.2,7526.98],[0,10561,7530,12815,7615],
[0,10582.9,6663.01,12815.3,7520.94],[0,8177.37,7317.01,10472.1,8415],
[0,8125.59,8418.01,10472.1,8684.99],[0,8141.07,8419.01,10472.2,8789.99],
[0,8114.07,3588,12815,7293.9],[0,10551.7,3596.04,12815.3,4292.96],
[0,10529.9,3455,12815.1,3588],[0,10566,3562,12815,3590],
[0,10541,3508,12815,3589],[0,10549,3588,12815,3616],
[0,8107.41,5260,12815,7293.87],[0,10591.8,4318.01,12815.3,5252.95],
[0,10581.9,5097,12815.1,5259],[0,10588.8,5271.08,12815.4,6646.99],
[0,8147.17,6932.01,10460.1,7227.99],[0,8154.54,6765,10434.1,6920],
[0,5556.98,15002.1,7974.52,15039.5],[0,8127.15,10722,10430.1,11067],
[0,8128.57,10775,10431.1,11068],[0,8130.59,10720,10425.1,10977],
[0,8131.81,10772,10427.1,10978],[0,8138.49,17229.7,10472,17257.7],
[0,8176.91,7301,10479.7,17239.6],[0,8156.39,17256.3,10472,17284.1],
[0,8112.57,17256.9,10472,17337.8],[0,966.172,23659,2793.3,23661],
[0,5534.1,7969,8004.9,7971],[0,12908.9,23633.6,15080.1,23765],
[0,12948,23632.3,15080,23659.7],[0,12952,23633,15080,23711.1],
[0,12916,23553.6,15080,23633],[0,12926,23606,15080,23633.7],
[0,12914.9,23501.3,15080.1,23632.4],[0,5507.73,2003.1,8038.84,18386.9],
[0,5592.26,18417.8,7985.24,18814.7],[0,5673.8,1711,7999.3,1722],
[0,5670.88,1724,7975.62,1765],[0,8152.9,19047,10444,19049],
[0,5534.39,21053.4,8044.31,21084.4],[0,5537.99,20479.3,8043.71,20507.4],
[0,5537.99,20506.6,8040.61,20534.6],[0,5537.67,20426,8045.33,20506.2],
[0,5533.41,15531,8020.83,20500.7],[0,3033.48,1514,5447.22,1560],
[0,5557,16223,8000.7,16225],[0,8141.6,23751,10472,23753],
[0,8115.46,23644.7,10472,23751.8],[0,2985.51,21055.4,10472.3,24223.7],
[0,8140.56,23644.2,10472,23750.1],[0,8115.5,23643,10472,23645],
[0,5529.46,20515.6,10472,23645],[0,8145.94,11873,10439.1,12012],
[0,5553.66,2435.01,8049.36,2880.99],[0,5580.73,2254,8049.27,2431],
[0,5580.64,2437.02,8049.52,2930.99],[0,5542.7,6923,7994.8,6925],
[0,10600,11639,12758,11641],[0,5532.45,11488,10415,11628],
[0,8190.4,11815,10390,11817],[0,5515.97,11886.1,8049.28,12815],
[0,5565.79,11822,8049.16,12815],[0,5566.39,11767,8049.48,12816],
[0,8226.59,1858,10381,1877],[0,8145.58,24041.4,10446.1,24322.6],
[0,5528.02,10183,8047.38,10379],[0,927.578,523,2849.1,525],
[0,5621.39,448,7984.11,481],[0,8235.36,537,10340,611],
[0,3068.49,639,5388.81,658],[0,8128.34,10584,10418.1,10710],
[0,8127.82,10585,10425.1,10762],[0,10539,2751,12771,2753],
[0,10529,11004,12815,11018],[0,10580.9,11018,12815.1,11163],
[0,10527,10913,12815,11017],[0,10529,10962,12815,11005],
[0,8127.75,10697,12815,10977.8],[0,10527,10913,12815,10963],
[0,5576.08,21146.6,7988.12,21191.3],[0,5577.98,21590.6,7986.02,21635.3],
[0,8110.1,10476,10423.1,10706],[0,8109.68,10477,10430.1,10760],
[0,12916,7276,15041,7320],[0,12872,7319,15040,7331],
[0,10643,6307,12815,6309],[0,10633,6256,12815,6308],
[0,10534.9,6309,12815.1,6490],[0,3035.7,23940,5411.9,23942],
[0,5527.21,20258.3,8024.63,21135.4],[0,8156.68,22434.8,10472,22488.4],
[0,8152.58,22487.6,10472,22541.3],[0,8131,22487,10472,22489],
[0,5536.5,319,7982.3,321],[0,3036,373,5407.7,375],
[0,3035.98,374,5411.62,427],[0,902.969,319,2913.5,321],
[0,5532.03,2836,8049.35,4012],[0,5537.04,4013,8049.46,4160],
[0,5598.34,3864,8049.16,4011],[0,10581.9,4472.01,12815.1,5135.99],
[0,10586.9,4471,12815.1,4627],[0,10573.9,4223,12815.1,4468],
[0,10604.9,4314,12815.1,4469],[0,10580.9,4172.01,12815.1,4466.99],
[0,10586,4470,12815,4523],[0,10547,4469,12815,4471],
[0,10574,4417,12815,4470],[0,10550,4470,12815,4577],
[0,10562.9,4471,12815.1,4681],[0,10537,4363,12815,4470],
[0,10535.9,4473.01,12815.1,4789.99],[0,10572.9,5403,12815.1,5534],
[0,10575.8,5157.02,12815.2,5531.99],[0,10598,5508,12815,5536],
[0,10609,5534,12815,5562],[0,10597,5535,12815,5614],
[0,10590,5456,12815,5535],[0,10557.9,5536,12815.1,5720],
[0,10575.9,6556.01,12815.1,6866.99],[0,10532,6869,12815,6871],
[0,10561,6870,12815,6924],[0,10555.9,6871,12815.1,7013],
[0,10566,6817,12815,6870],[0,10553.9,6873.01,12815.1,7171.99],
[0,10567.9,6607.01,12815.1,6867.99],[0,10584.9,6872.01,12815.1,7115.99],
[0,10539.9,6871,12815.1,7068],[0,10517.3,4809.25,12822.7,6852.75],
[0,8145.99,5816,10398,5843],[0,8145.99,5843,10430,5870],
[0,10579.8,4580.02,12815.2,5135.98],[0,10592,4578,12815,4631],
[0,10561.8,4580.01,12815.1,5192.99],[0,10591.9,4318.01,12815.1,4575.99],
[0,10574.8,4173.02,12815.2,4574.99],[0,10586,4525,12815,4578],
[0,10547,4471,12815,4578],[0,10571.9,4420,12815.1,4577],
[0,10551,4577,12815,4579],[0,10565,4578,12815,4684],
[0,10536.9,4364,12815.1,4576],[0,10536.9,4580,12815.1,4792],
[0,10575,5400,12815,5428],[0,10584.9,5155.01,12815.1,5424.99],
[0,10596,5427,12815,5506],[0,10564.9,5205,12815.1,5425],
[0,10590.9,5428,12815.1,5610],[0,10591,5426,12815,5454],
[0,10554.9,5429.01,12815.1,5717.99],[0,10600,22866.2,12815,22893.7],
[0,10600,22892.3,12815,22919.8],[0,10598,22892.9,12815,22971.6],
[0,10598,22814.4,12815,22893.1],[0,10596,7930,12815,7983],
[0,10597,7929,12815,7931],[0,10595,7841,12815,7930],
[0,5574.95,7422.85,12815,7942.2],[0,8148,22595,10461,22597],
[0,10595,3777,12781,3800],[0,3139.5,211,5337.3,213],
[0,957.75,268,2886.41,273.75],[0,12938.9,5185.01,15005.1,5459.99],
[0,10580.9,4526.01,12815.1,5135.99],[0,10589,4524,12815,4629],
[0,10581.9,4526,12815.1,4733],[0,10570.9,4224.01,12815.1,4520.99],
[0,10598.9,4316,12815.1,4522],[0,10586,4523,12815,4525],
[0,10547,4470,12815,4524],[0,10573,4418,12815,4524],
[0,10551,4524,12815,4578],[0,10564.9,4525,12815.1,4682],
[0,10536.9,4364,12815.1,4523],[0,10535.9,4526.01,12815.1,4790.99],
[0,10578.8,4638.03,12815.2,5134.98],[0,10592,4631,12815,4633],
[0,10588,4632,12815,4737],[0,10560.9,4639.04,12815.3,5191.99],
[0,10585.9,4319.01,12815.1,4628.99],[0,10584,4527,12815,4632],
[0,10545.9,4472,12815.1,4631],[0,10569.9,4421,12815.1,4630],
[0,10551,4578,12815,4632],[0,10566,4632,12815,4685],
[0,10535.9,4365.01,12815.1,4629.99],[0,10536.9,4633,12815.1,4792],
[0,10569.8,8048.01,12815.2,8412.99],[0,10531.9,8095.01,12815.1,8412.99],
[0,10552,8416,12815,8523],[0,10526.9,8417,12815.1,8577],
[0,10587,8041,12815,8146],[0,10538.7,7443.04,12815.3,8138.96],
[0,10547.8,8149.01,12815.2,8516.99],[0,10525.8,8150.02,12815.2,8574.98],
[0,10574,5402,12815,5481],[0,10579.9,5156.01,12815.1,5477.99],
[0,10598,5480,12815,5508],[0,10580.9,5261,12815.1,5479],
[0,10606,5481,12815,5559],[0,10591,5454,12815,5482],
[0,10555.9,5483,12815.1,5719],[0,10575,5372,12815,5400],
[0,10589.9,5154,12815.1,5371],[0,10592.9,5374,12815.1,5504],
[0,10586.9,5257,12815.1,5373],[0,10565.9,5204,12815.1,5372],
[0,10590,5373,12815,5452],[0,10552.9,5376.01,12815.1,5716.99],
[0,12966,4919,14998,4996],[0,5574.2,6685,7974.2,6687],
[0,5615.88,8063,7942.52,8099],[0,10596,13381,12779,13383],
[0,8129.88,13228,10472,13278],[0,10593,6547,12815,6592],
[0,10576,6591,12815,6601],[0,10536,6493,12815,6592],
[0,10590,6514.92,15080.2,6910.97],[0,10562,6915,15080,6925],
[0,12925.9,6263.01,15080.3,6906.94],[0,10557,6916,15080,7017],
[0,10558.9,6917,15080.1,7176],[0,10572.9,6604,15080.1,6915],
[0,10596,6916,15080.1,7121],[0,10540,6916,15080,7070],
[0,10534.8,4712.62,15096.8,6898.55],[0,8170.89,3081.01,10448.1,3335.99],
[0,5547.87,20335.5,7989.53,20409.1],[0,5627.37,20757.2,7998.03,20826.8],
[0,8177.5,6031,10470,6033],[0,5584.8,14325,7955.2,14327],
[0,10575,16131,12769,16133],[0,10576,16078.8,12769,16131.3],
[0,5552.88,5508,7954.72,5553],[0,8160.21,6185,12815,6366.14],
[0,10530.9,6368.03,12815.2,6865.99],[0,10641,6310,12815,6362],
[0,10627,6259,12815,6362],[0,10557.8,6367.02,12815.2,6807.99],
[0,8159.68,6185.01,12815,6998.42],[0,10571.8,6556.01,12815.2,6957.98],
[0,10532,6870,12815,6962],[0,10561,6924,12815,6963],
[0,10557,6962,12815,7016],[0,10564.9,6819,12815.1,6961],
[0,10556.9,6964,12815.1,7174],[0,10563.8,6609.01,12815.2,6958.99],
[0,10591.9,6963,12815.1,7119],[0,10540,6962,12815,7069],
[0,877.141,1413,2917.7,1415],[0,8126.48,4794,10462,4846],
[0,8123.54,4851.01,10472.2,5304.98],[0,8128.19,5284,10472,5309],
[0,8107.41,5308,10472.1,7293.87],[0,8127.25,5309,10472.1,5444],
[0,5560.5,7309,7964.8,7311],[0,2979.39,17355.7,5390.51,20279.8],
[0,10570,17935,12663,17937],[0,10569,17936.6,12673,17987.1],
[0,5580.8,21535.3,7991.3,21544.7],[0,5528.1,5842,8006.9,5844],
[0,10590,8741,12815,8794],[0,10569.9,8795,12815.1,8952],
[0,10588,8794,12815,8899],[0,10571,8793,12815,8795],
[0,10567,8688,12815,8794],[0,10550.9,8635,12815.1,8793],
[0,10557,8794,12815,8848],[0,10588,8743,12815,8848],
[0,10572,8848,12815,8954],[0,10589,8848,12815,8901],
[0,10571,8795,12815,8848],[0,10564.9,8690,12815.1,8847],
[0,10536.9,8850,12815.1,9062],[0,10557,8847,12815,8849],
[0,8121.83,5502,10472.1,5669],[0,8124.75,5289.01,10472.2,5666.99],
[0,8105.34,5670,10472,7293.83],[0,8126.41,5450,10472.1,5668],
[0,8174.47,15926.2,10410.2,16532.4],[0,8197.32,10644,10379.1,10813],
[0,5535.88,10074,8019.02,10112],[0,5535.89,10111,8013.21,10129],
[0,8123.11,8909,10472.1,9117],[0,8118.09,8856,10472.1,9116],
[0,8137.48,9068,10472,9118],[0,8124.25,9015,10472,9118],
[0,8141.47,8806.01,10472.1,9114.99],[0,8126.5,9117,10472,9123],
[0,8124.25,8907,10472,9010],[0,8183.96,7314.01,10472,9011],
[0,8118.93,8854,10472.1,9009],[0,8124.6,9009,10472,9015],
[0,8146.21,8803,10472.1,9009],[0,8135.67,3782,10441,3853],
[0,5578.77,3293,8007.23,3363],[0,8143.4,22649,10412,22651],
[0,5542.38,50,8049.22,104],[0,5523,103,8049.1,105],
[0,5554.88,104,8049.42,157],[0,10541,5924,12815,5978],
[0,10535,5977,12815,5979],[0,10553.9,5979,12815.1,6159],
[0,5598.79,21720,7973.31,21743.9],[0,8118.97,6632,10400,6706],
[0,12893,15511.2,15080,15565.4],[0,12906,15564,15080,15566],
[0,12926,15564.7,15080,15618],[0,5594.2,7601,7954.8,7607],
[0,15217,2458,16683,2509],[0,15226,2508,16683,2510],
[0,15200.9,2511,16683.1,2668],[0,15219,2427,16683,2454],
[0,15204,2402,16683,2429],[0,15241.9,2353,16683.1,2428],
[0,15219.9,2428,16683.1,2504],[0,8130.04,17724.5,10431.1,17878.5],
[0,5517.49,18779.8,7985.53,19648.5],[0,5523.96,18724.7,8021.24,19088.7],
[0,10551,23135,12806,23137],[0,8179,3903,10390,3909],
[0,10609,19834,12731,19836],[0,5580.39,20605.8,7984.01,20626.3],
[0,8156.68,22704.8,10472,22758.4],[0,8126.07,22760.6,10472.1,23076.3],
[0,8135.1,22757,10472,22759],[0,8125.63,16810.4,10384.1,16969],
[0,10483.1,19850.4,10493.1,19865.3],[0,8156.34,19862,10488.9,22707.1],
[0,10483.1,19850.5,10493.1,19865.3],[0,8134.19,19862.1,10488.9,22762.1],
[0,7982.55,21526.1,7996.81,21536],[0,5528.95,21399.5,7983.86,21532.1],
[0,10471.7,19850.9,10485,19864.5],[0,5529.36,19859.7,10476.7,21438.2],
[0,10445.6,13980.6,10460.5,13990],[0,5526.52,13984.1,10448.3,21406.5],
[0,10450,19850.6,10464.8,19861.1],[0,5579.68,19855.3,10453.4,20622.9],
[0,10446.1,19850.5,10461,19860.6],[0,8153.85,19854.8,10449.4,20617.1],
[0,2905.3,18.0898,2919.33,27.9102],[0,909.531,22,2906.3,24],
[0,10489,19804.7,10498.6,19819.4],[0,8201.41,15807.6,10495,19806.8],
[0,10447.5,13980.7,10462.4,13990],[0,8194.54,13984.1,10450.4,15803.1],
[0,10383.8,18033.2,10398,18043.1],[0,5612.35,17804.2,10385.1,18039.2],
[0,7967.24,16982.8,7981.81,16992.5],[0,5523.23,16986.5,7969.04,17782.7],
[0,10476.5,12972.6,10488.8,12986.8],[0,8154.14,12982.4,10481.8,15594.6],
[0,10490,19805.5,10499.8,19820],[0,8151.47,15586,10496,19807.2],
[0,16647,7671.09,16661,7680.91],[0,15135,7675,16648,7677],
[0,16652,7619.09,16666,7628.91],[0,15135,7623,16653,7676],
[0,15068.5,7673.21,15083,7682.99],[0,12918,7677,15070,7766],
[0,10384.8,19836.6,10399,19846.5],[0,5510.99,19106.7,10386.1,19902],
[0,10381.8,19835.1,10396,19844.9],[0,5554.77,19673.1,10383,19911.5],
[0,10460.4,19807.4,10474.7,19819.4],[0,8136.51,18720.5,10464.5,19812.8],
[0,10423.3,17886,10437.9,17895.7],[0,8135.3,17889.7,10425.1,18714.2],
[0,10458.6,19807.5,10473.2,19818.8],[0,8170.77,18778.6,10462.5,19813.1],
[0,10423.3,17885.7,10437.9,17895.4],[0,8168.98,17889.4,10425.1,18764.7],
[0,10413.5,7966.01,10428,7975.79],[0,5580.72,7530.63,10415.2,7971.98],
[0,10412.5,8128.01,10427,8137.79],[0,5593.8,7603.7,10414.2,8133.98],
[0,10414.1,7964.99,10428.8,7974.62],[0,8166.15,7613.01,10416.2,7970.99],
[0,10410.1,8127.99,10424.8,8137.62],[0,8170.82,7612.02,10412.2,8133.99],
[0,10409.5,7967.01,10424,7976.79],[0,8160.36,7666.01,10411.1,7972.99],
[0,10411.5,8128.01,10426,8137.79],[0,8155.21,7667.02,10413.2,8133.98],
[0,10438.1,13978.7,10452.9,13988.9],[0,8137.1,13983.1,10441.3,17806.3],
[0,10475.5,19805.2,10487.8,19819.4],[0,8146.14,17813,10480.8,19809.5],
[0,10392.5,18029,10407,18038.8],[0,8141.8,17819.2,10394.1,18035],
[0,10474.6,19851.3,10487.5,19865.2],[0,5598.69,19860.6,10479.8,21743.6],
[0,7925,2148.09,7939.03,2157.91],[0,5610.98,2104,7926.02,2154],
[0,7974.73,3168.02,7989.16,3177.79],[0,5592.36,2111.01,7976.33,3173.99],
[0,15002,2391.09,15016,2400.91],[0,12868.9,2286,15003.1,2397],
[0,14954,2338.09,14968,2347.91],[0,12869,2286,14955,2344],
[0,12803.5,2277.01,12818,2286.79],[0,5609.27,2058.77,12805,2283],
[0,10483.1,19850.3,10493.2,19865.1],[0,8142.87,19861.8,10488.9,22653.6],
[0,7973.43,3183.21,7987.86,3192.98],[0,5573.33,3187,7974.97,3359],
[0,15030.5,7310.01,15045,7319.79],[0,12868.9,7169,15032.1,7316],
[0,16661.5,7655.03,16676.4,7664.34],[0,12870,7162.62,16664.3,7660.95],
[0,16662.6,7602.01,16677.5,7611.41],[0,12869,7150.8,16665.3,7607.95],
[0,12803.5,7165.21,12818,7174.99],[0,10594.9,7169,12805.1,7282],
[0,12769,3772.09,12783,3781.91],[0,8136.19,3771.9,12770,3782],
[0,12810.8,3791.79,12824.2,3805.18],[0,10544.7,3800.24,12815.7,5386.95],
[0,10374.9,16528.6,10389.7,16538.2],[0,8186.46,14382,10377.3,16534.6],
[0,10472.6,11275.2,10485.6,11289],[0,8187.96,11284.3,10477.8,14381],
[0,7939.4,15909.5,7954.15,15919.1],[0,5492.46,10899.5,7941.63,15915.5],
[0,10411.1,11238,10425.8,11247.6],[0,5643.66,10848.5,10413.2,11244],
[0,7951.62,10643.2,7966.06,10653],[0,5611.3,10647,7953.2,10871],
[0,7939.46,15908.9,7954.22,15918.5],[0,5560.75,11547,7941.73,15914.9],
[0,10376.5,11261.2,10391,11271],[0,5589.05,11265,10378.1,11530],
[0,10365.5,16531.4,10380.4,16540.7],[0,8235.62,11135.1,10368.3,16537.3],
[0,10376.5,11247,10391,11256.8],[0,8233.45,11135,10378.1,11253],
[0,10387.5,10830.2,10402,10840],[0,8187.48,10834,10389.1,11115],
[0,10377.8,18034.5,10392.6,18044],[0,8124.55,13351.1,10380.3,18040.5],
[0,10376.1,10114.4,10390.8,10124],[0,8170.68,10118,10378.3,13340],
[0,2877.38,17319,2891.98,17328.7],[0,913.977,17021.8,2879.25,17325],
[0,15002.9,16151,15017,16160.8],[0,882.129,16154.9,15004,16994.8],
[0,2906.03,1357.21,2920.47,1366.98],[0,877.113,1361,2907.53,1414],
[0,10399.5,5152.21,10414,5161.99],[0,8162.98,5156.02,10401.2,6172.99],
[0,10401.5,10150,10416,10159.8],[0,8158.99,9236.01,10403.2,10156],
[0,10401.1,8152.38,10415.8,8162.01],[0,8160.28,8156.01,10403.1,9224.99],
[0,10393.4,15049.3,10407.9,15059.1],[0,5532.65,10159.6,10395.1,15055.3],
[0,10412.5,7966.01,10427,7975.79],[0,8103.42,7513.02,10414.2,7971.98],
[0,10417.5,7911.01,10432,7920.79],[0,8103.42,7513.02,10419.2,7916.98],
[0,8037.34,7511.39,8052.07,7521.01],[0,5534.68,7515.02,8039.52,10170],
[0,8002.3,10124.1,8016.33,10133.9],[0,5534.98,10128,8003.32,10166],
[0,10459.6,19851.2,10474.2,19862.6],[0,5620.45,19857.1,10463.5,20878.1],
[0,10436.6,19849.9,10451.4,19859.3],[0,5548.09,19853.3,10439.3,20415.9],
[0,10399,13384.1,10413,13393.9],[0,5526.98,13388,10400.1,20397.8],
[0,10423,19847.2,10437.7,19856.8],[0,8146.54,19850.8,10425.2,20324.1],
[0,12767.2,15408.1,12781.8,15417.8],[0,8119.54,7801.07,12769.2,15414.1],
[0,10403.1,6551.38,10417.8,6561.01],[0,8107.43,6555.01,10405.2,7769.89],
[0,10397,13371.1,10411,13380.9],[0,8128.93,13230,10398.1,13377],
[0,10389,8140.09,10403,8149.91],[0,5616.29,8100,10390,8146],
[0,10390.5,8137.01,10405,8146.79],[0,8206.67,8066,10392,8143],
[0,12705.5,5160.01,12720,5169.79],[0,10575.9,5041,12707.1,5166],
[0,12704,4997.09,12718,5006.91],[0,10578,5001,12705,5038],
[0,12729.5,5007.21,12744,5016.99],[0,10578.9,5011,12731.1,5246],
[0,12804.2,5016.18,12818.4,5028.53],[0,10588.9,5023.18,12808.6,8037.99],
[0,12730.5,4983.01,12745,4992.79],[0,10578.9,4748.01,12732.1,4988.99],
[0,2875.2,258.09,2889.23,267.91],[0,957.75,258.25,2876.21,264],
[0,2798.8,211.09,2812.83,220.91],[0,958.121,215,2799.83,264],
[0,10482.1,19850.4,10492.1,19865.2],[0,8147.36,19862,10487.9,22599.3],
[0,10387,22861.1,10401,22870.9],[0,8167.7,22865,10388,22867],
[0,10484.1,19850.7,10494,19865.5],[0,8167.21,19862.3,10489.9,22868.8],
[0,10387,22915.1,10401,22924.9],[0,8167.7,22919,10388,22921],
[0,10484.1,19850.8,10494,19865.6],[0,8167.21,19862.4,10489.9,22922.9],
[0,10387,22969.1,10401,22978.9],[0,8167.7,22973,10388,22975],
[0,10484.1,19850.8,10493.9,19865.7],[0,8166.81,19862.6,10489.9,22977.1],
[0,10387,22807.1,10401,22816.9],[0,8167.7,22811,10388,22813],
[0,10484,19850.2,10493.4,19865],[0,8167.11,19862.2,10489.9,22814.6],
[0,10397.5,11241,10412,11250.8],[0,3038.89,11023.9,10399.1,11277],
[0,10375.6,16548,10390,16557.8],[0,3042.57,11278,10377,16705.3],
[0,5368.8,11283.1,5382.83,11292.9],[0,3045.5,11283,5369.8,11289],
[0,10408.5,12940,10423,12949.8],[0,3041.14,12695.6,10410.1,12946],
[0,10428.6,12202,10443.5,12211.4],[0,2992.46,11485.3,10431.2,12787.8],
[0,10397.5,19841.5,10411.9,19851.3],[0,3010.6,12818.1,10399,20066.5],
[0,5332.51,16012.2,5347.31,16021.7],[0,3004.73,12819.1,5334.96,16018.2],
[0,5329.8,16019.1,5343.83,16028.9],[0,3048.2,16023,5330.8,16025],
[0,10414.1,19845.7,10428.8,19855.3],[0,2978.67,16041.6,10416.2,20174.7],
[0,10390,12951.1,10404,12960.9],[0,2978.27,12951.9,10391,16006.4],
[0,8013.72,2171.59,8028.57,2180.99],[0,5580.97,2175.05,8016.42,2987.99],
[0,10337.5,13528,10352,13537.8],[0,5575.36,3007.03,10339,13534],
[0,7973.53,3169.02,7987.97,3178.79],[0,5589.93,3004,7975.07,3175],
[0,12803.5,2283.21,12818,2292.99],[0,5572.18,2287,12805,2985.99],
[0,15030,7317.09,15044,7326.91],[0,12932,7321,15031,7382],
[0,15068.5,7666.01,15083,7675.79],[0,12917.9,7393.01,15070.1,7671.99],
[0,10384.6,15051.3,10399,15061.1],[0,5612.39,10219,10386.1,15057.3],
[0,8037.63,7511.39,8052.37,7521.01],[0,5609.09,7515.02,8039.79,10217],
[0,10486,19804.9,10495.4,19819.7],[0,8103.36,16134.2,10492,19807.6],
[0,12729.6,15180.3,12744,15190.1],[0,8103.62,15156.5,12731.1,16131.2],
[0,8037.8,16127.1,8051.83,16136.9],[0,5532.7,16131,8038.8,16133],
[0,7934.82,2159.21,7949.27,2168.98],[0,5574.55,2163,7936.36,2298],
[0,7977.84,3165.99,7992.57,3175.61],[0,5518.6,2318.09,7979.93,3171.99],
[0,12804,2280.09,12818,2289.91],[0,5575.75,2211.77,12805,2299],
[0,10381.5,3176.01,10396,3185.79],[0,8103.58,3127,10383,3182],
[0,10409.5,2865.21,10424,2874.99],[0,8103.49,2869,10411.1,3125],
[0,8037.07,3110.02,8051.92,3119.38],[0,5530.09,2317.05,8039.8,3115.95],
[0,8002.02,2170.59,8016.87,2179.99],[0,5522.25,2174.03,8004.65,2824.97],
[0,7985.53,3164.02,7999.97,3173.79],[0,5529.07,2840.01,7987.13,3169.99],
[0,12804,2282.09,12818,2291.91],[0,5523.46,2286,12805,2825.97],
[0,8038.01,3118.02,8052.46,3127.78],[0,5529.99,2839.01,8039.61,3123.99],
[0,10400.5,5243.01,10415,5252.79],[0,8103.54,5116,10402.1,5249],
[0,10411.5,5598.01,10426,5607.79],[0,8103.21,5120.02,10413.2,5603.99],
[0,8036.7,5096.08,8051.55,5105.97],[0,5518.26,4175.06,8039.84,5101.94],
[0,7954.77,5538.99,7969.48,5548.62],[0,5502.59,4178.21,7956.86,5544.99],
[0,8021.09,3195.98,8035.92,3205.91],[0,5517.75,3200.06,8024.25,4148.94],
[0,7998.09,2170.61,8012.93,2179.98],[0,5497.19,2174.04,8000.79,4145.71],
[0,12703,4994.09,12717,5003.91],[0,8103.2,4262.05,12704,5000],
[0,10390,4161.09,10404,4170.91],[0,8103.56,4165,10391,4254],
[0,8038.1,4248.09,8052.13,4257.91],[0,5537.66,4163,8039.14,4254],
[0,10398,4733.09,10412,4742.91],[0,8103.58,4684,10399,4739],
[0,14985,4909.09,14999,4918.91],[0,8103.46,4685,14986,4915],
[0,8037.46,4671.99,8052.18,4681.62],[0,5529,4171.02,8039.6,4677.98],
[0,10414.5,4723.01,10429,4732.79],[0,8103.44,4169.04,10416.2,4728.98],
[0,10387,4157.09,10401,4166.91],[0,8103.6,4161,10388,4163],
[0,8038.1,4157.09,8052.13,4166.91],[0,5538,4161,8039.1,4163],
[0,8037.9,3124.09,8051.93,3133.91],[0,5509.73,3128,8039,4146.88],
[0,12803.5,2284.21,12818,2293.99],[0,5499.59,2288,12805.1,4145.71],
[0,7975.33,3909.21,7989.77,3918.98],[0,5535.5,3913,7976.9,4158],
[0,12703,4995.09,12717,5004.91],[0,8103.5,4991,12704,5001],
[0,10409.1,5597.99,10423.8,5607.62],[0,8103.31,4999.04,10411.2,5603.99],
[0,8037.72,4983.02,8052.16,4992.79],[0,5516.43,4175.07,8039.32,4988.99],
[0,10416.1,5235.99,10430.8,5245.62],[0,8103.57,4794.01,10418.2,5241.98],
[0,14985,4910.09,14999,4919.91],[0,8103.47,4792,14986,4916],
[0,8037.63,4783.02,8052.07,4792.79],[0,5523.02,4173.04,8039.23,4788.99],
[0,10409.5,4616.01,10424,4625.79],[0,5581.2,3776.19,10411.2,4621.99],
[0,7974.46,3354.38,7989.18,3364.01],[0,5549.28,3358.01,7976.56,3843.98],
[0,7963.2,3897.09,7977.23,3906.91],[0,5606.98,3859,7964.22,3903],
[0,12804,2283.09,12818,2292.91],[0,5505.21,2287,12805.1,3840.81],
[0,8037.53,3126.21,8051.96,3135.98],[0,5528.67,3130,8039.1,3841.95],
[0,8002.19,2170.61,8017.05,2179.99],[0,5501.86,2174.04,8004.89,3840.77],
[0,8008.04,3193.39,8022.77,3203.01],[0,5541.85,3197.03,8010.25,3842.97],
[0,7951.62,5541.02,7966.06,5550.79],[0,5499,3875.29,7953.31,5546.98],
[0,10410.1,5489.99,10424.8,5499.62],[0,5510.39,3875.14,10412.2,5495.99],
[0,10415.5,6588.01,10430,6597.79],[0,5495.02,3875.38,10417.1,6594],
[0,10406,4208.09,10420,4217.91],[0,3026.63,3425.04,10407,4214],
[0,7922.8,2151.09,7936.83,2160.91],[0,2995.51,2154.84,7923.8,3393.8],
[0,7968.9,3179.09,7982.93,3188.91],[0,3071.04,3183,7969.95,3406],
[0,7945.62,5554.21,7960.06,5563.98],[0,2983.16,3428.46,7947.13,5591.95],
[0,7950.1,3344.09,7964.13,3353.91],[0,3077.09,3348,7951.12,3412],
[0,10408.1,5542.99,10422.8,5552.62],[0,2989.09,3428.3,10410.1,5549],
[0,7968.32,3906.21,7982.77,3915.98],[0,3027.03,3425.04,7969.86,3948.95],
[0,5420.75,2837.38,5435.47,2847.01],[0,3027.73,2841,5422.8,3396.96],
[0,12803.5,2282.21,12818,2291.99],[0,3024.72,2286,12805,3395.96],
[0,8038.2,3122.09,8052.23,3131.91],[0,3058.04,3125.8,8039.2,3402],
[0,10414.5,6601.21,10429,6610.99],[0,2976.94,3428.71,10416,6993.71],
[0,10463.4,15083.6,10477.8,15095.5],[0,8174.57,15090.1,10467.6,16326.3],
[0,10486,19804.6,10495.4,19819.5],[0,8181.68,16329.6,10492,19807.3],
[0,10379.9,19833,10394,19842.8],[0,5600.95,18737.5,10381,19861.5],
[0,8024.94,17733.1,8039.8,17742.5],[0,5597.25,17736.5,8027.7,18717.9],
[0,5415.3,316.09,5429.33,325.91],[0,3035.98,320,5416.32,374],
[0,5415.1,315.09,5429.13,324.91],[0,3031.1,319,5416.1,321],
[0,10405.1,11239,10419.8,11248.6],[0,8144.5,10425,10407.2,11245],
[0,12732.5,10611,12747,10620.8],[0,8146.96,10422,12734,10617],
[0,10481.1,19850.3,10491.3,19865.1],[0,8156.83,19861.7,10486.9,22436.3],
[0,10482.1,19850.3,10492.1,19865.2],[0,8152.84,19861.9,10487.9,22544.9],
[0,10481.2,19850.9,10492.2,19865.6],[0,8130.39,19862,10486.9,22491.5],
[0,10466.1,19851.1,10480.1,19863.7],[0,5527.99,19858.5,10470.6,21142.3],
[0,12731.6,6252.2,12746,6261.98],[0,10641,6256,12733,6306],
[0,12732,6249.09,12746,6258.91],[0,10635,6253,12733,6255],
[0,12739.6,6241.02,12754,6250.8],[0,5548.29,6068.57,12741,6247],
[0,10364.5,6293.01,10379,6302.79],[0,8103.52,6125,10366.1,6299],
[0,10363,6242.09,10377,6251.91],[0,8103.54,6124,10364.1,6248],
[0,8037.43,6118.02,8051.86,6127.79],[0,5548.48,6082,8038.91,6124],
[0,15068.5,7667.01,15083,7676.79],[0,8137.43,7173.02,15070.1,7673],
[0,10398,5821.42,10412.7,5831.01],[0,8097.78,5825.02,10400.2,7146.79],
[0,10426.1,7686.99,10440.8,7696.62],[0,8131.38,7174.02,10428.2,7692.98],
[0,10451.1,6174.71,10465.9,6184.89],[0,8113.11,6179.06,10454.3,7147.92],
[0,15068.1,7664.99,15082.8,7674.62],[0,12870.8,7333.01,15070.1,7670.99],
[0,10458.7,19851.2,10473.3,19862.5],[0,3095.69,19856.8,10462.5,20829.3],
[0,5320.2,20825.1,5334.23,20834.9],[0,3096,20829,5321.2,20831],
[0,8002.68,23753.6,8017.07,23763.4],[0,2990.71,20847.2,8004.19,23829.9],
[0,5335.91,8098.21,5350.36,8107.99],[0,3033.48,8102,5337.42,8146],
[0,10389,8141.09,10403,8150.91],[0,3033.6,8145,10390,8147],
[0,10382.8,19835.6,10397,19845.4],[0,2973.71,8163.88,10384,20160],
[0,10450.1,19809,10464.9,19819.3],[0,8157.28,19000.5,10453.4,19814.8],
[0,10453.9,18060,10468.6,18070.7],[0,8154.16,18065,10457.5,18986.2],
[0,10474.5,19850.7,10486.8,19864.8],[0,5577.07,19860.5,10479.8,21669.5],
[0,10472.5,19850.6,10485,19864.7],[0,8165.79,19860.2,10477.7,21588.2],
[0,10468.1,19851.3,10482,19864.1],[0,5575.68,19859,10472.7,21216.8],
[0,10464.2,19850.9,10478.3,19863.4],[0,8158.17,19858.1,10468.6,21140],
[0,7898.3,612.09,7912.33,621.91],[0,3068.39,616,7899.3,640],
[0,7899.6,614.09,7913.63,623.91],[0,5573.78,618,7900.62,658],
[0,10322,525.09,10336,534.91],[0,5621.49,482,10323,531],
[0,10322,529.09,10336,538.91],[0,927.102,525,10323,559.188],
[0,5329.7,477.09,5343.73,486.91],[0,927.113,481,5330.71,523],
[0,10329,521.09,10343,530.91],[0,8167.66,450,10330,527],
[0,10321,527.09,10335,536.91],[0,3095.6,523,10322,533],
[0,5330.03,480.207,5344.47,489.984],[0,3094.68,484,5331.52,523],
[0,10451.7,13980.7,10466.4,13991.8],[0,8163.58,13986.1,10455.4,15088.8],
[0,10365.9,15063.6,10380,15073.4],[0,8168.79,15067.5,10367,15094],
[0,10485,19804.8,10494.4,19819.6],[0,8150.58,15103.7,10490.9,19807.5],
[0,7959.61,2138.01,7974.06,2147.79],[0,5585.49,1869.01,7961.21,2143.99],
[0,7914.3,1853.09,7928.33,1862.91],[0,5620,1857,7915.3,1859],
[0,12803.5,2271.03,12818.4,2280.34],[0,5616.37,1798.57,12806.3,2276.96],
[0,7945.52,2140.01,7959.96,2149.79],[0,5556.92,1947,7947.08,2146],
[0,10369,1874.09,10383,1883.91],[0,5561.98,1878,10370,1942],
[0,12803.5,2277.01,12818,2286.79],[0,5561.89,1936.55,12805.1,2283],
[0,10412.5,13968.2,10427,13978],[0,8156.92,13972,10414.1,14158],
[0,10487,19804.4,10496.4,19819.3],[0,8157.27,14157,10493,19807],
[0,10382,14226.1,10396,14235.9],[0,8162.27,14165,10383,14232],
[0,10388.1,14238.4,10402.8,14248],[0,8181.27,14242,10390.2,16075.3],
[0,10488,19804.9,10497.6,19819.6],[0,8182.77,16075.1,10494,19807],
[0,10431.8,19811.7,10446.6,19821.2],[0,5485.03,11887.8,10434.3,19817.7],
[0,10387,11635.1,10401,11644.9],[0,5569.85,11639,10388,11863],
[0,7951.91,11814.2,7966.36,11824],[0,5579.58,11818,7953.42,11869],
[0,10488,19805.1,10497.6,19819.9],[0,8183.4,11809,10494,19807.3],
[0,10394.5,11643.2,10409,11653],[0,8180.13,11647,10396.1,11809],
[0,10440.5,19810.3,10455.4,19819.7],[0,5521.2,11640,10443.3,19816.2],
[0,7960.93,11803,7975.36,11812.8],[0,5532.03,11632,7962.47,11809],
[0,10391.5,11629,10406,11638.8],[0,5532.23,11545.2,10393.1,11635],
[0,8011.11,2171.6,8025.96,2180.99],[0,5557.29,2175.05,8013.8,2881.99],
[0,10405.5,6531.01,10420,6540.79],[0,8103.5,6288,10407.1,6537],
[0,12738.5,6241.01,12753,6250.79],[0,8103.38,6130.36,12740,6283.99],
[0,10420.5,6585.01,10435,6594.79],[0,8103.47,6289.01,10422.1,6590.99],
[0,8037.9,6284.09,8051.93,6293.91],[0,5563.95,2885,8038.95,6290.54],
[0,10401.6,6533.02,10416,6542.8],[0,8103.52,6341,10403.1,6539],
[0,10346,6305.09,10360,6314.91],[0,8103.59,6309,10347,6341],
[0,10418.1,6585.99,10432.8,6595.62],[0,8103.5,6342,10420.1,6592],
[0,8037.73,6339.21,8052.16,6348.98],[0,5563.95,2884,8039.25,6345.47],
[0,12804,2282.09,12818,2291.91],[0,5553.17,2286,12805,2879.99],
[0,7980.87,3164.99,7995.58,3174.62],[0,5555.79,2896.01,7982.91,3170.99],
[0,7928.3,2156.09,7942.33,2165.91],[0,5586.77,2160,7929.34,2245],
[0,12803.5,2278.01,12818,2287.79],[0,5581.18,2108.96,12805,2284],
[0,7976.43,3167.02,7990.86,3176.79],[0,5576.48,2256.01,7978.03,3172.99],
[0,8037.9,6338.09,8051.93,6347.91],[0,5617.11,2946.02,8038.95,6344.54],
[0,8013.09,2171.61,8027.95,2180.99],[0,5588.16,2175.05,8015.81,2932.99],
[0,7977.32,3167.02,7991.77,3176.79],[0,5594.51,2952,7978.89,3173],
[0,12804,2282.09,12818,2291.91],[0,5578.54,2286,12805,2930.99],
[0,8038,6284.09,8052.03,6293.91],[0,5616.81,2946.02,8039.05,6290.54],
[0,8038,6335.09,8052.03,6344.91],[0,5592.09,6313,8039.01,6341],
[0,8038,6281.09,8052.03,6290.91],[0,5592.09,6285,8039.01,6313],
[0,10386.1,3187.38,10400.8,3197.01],[0,8176.7,3191.02,10388.2,5337],
[0,10425.1,5794.99,10439.8,5804.62],[0,8158.64,5347.01,10427.2,5800.98],
[0,10385.1,10058.4,10399.8,10068],[0,8207.97,10062,10387.2,13280],
[0,10377.8,18034.7,10392.6,18044.2],[0,8209.67,13282,10380.3,18040.7],
[0,5392.06,18182.4,5406.31,18192.3],[0,2979.79,10015.6,5393.36,18188.4],
[0,10409.5,10040,10424,10049.8],[0,3052.88,9727.82,10411.1,10046],
[0,10400.6,8151.2,10415,8160.98],[0,3032.93,8155,10402.1,9984.96],
[0,10381.8,18044.2,10396,18054],[0,2979.79,10015.6,10383,18169.3],
[0,10393,10154.1,10407,10163.9],[0,3069.5,9992.97,10394,10160],
[0,10385.5,10098,10400,10107.8],[0,3068.17,9948.02,10387.1,10104],
[0,10486,19850.2,10495.4,19865.1],[0,8114.14,19862.4,10492,23640.2],
[0,10466.1,16560.3,10480.1,16573],[0,8096.76,16567.8,10470.6,18555.3],
[0,10459.4,19807.6,10473.8,19819.5],[0,8125.41,18585.1,10463.5,19813.1],
[0,7967.93,15030.4,7982.36,15040.2],[0,5543.57,15034.2,7969.51,21000],
[0,10453.9,18059.9,10468.6,18070.6],[0,5548.64,18064.9,10457.5,20993.4],
[0,7993.94,3191.39,8008.67,3201.01],[0,5539.43,3195.04,7996.19,21002.9],
[0,10365.9,15064.8,10380,15074.6],[0,5543.57,15068.7,10367,20999.9],
[0,10377.8,18036.8,10392.6,18046.3],[0,8126.93,10519.1,10380.3,18042.8],
[0,10391.1,8147.38,10405.8,8157.01],[0,8130.7,8151.02,10393.2,10531],
[0,10485,19850.1,10494.4,19864.9],[0,8166.42,19862.2,10490.9,23031.3],
[0,10379,23023.1,10393,23032.9],[0,8167,23027,10380,23029],
[0,10437,23131.1,10451,23140.9],[0,8167,23135,10438,23137],
[0,10485.1,19850.6,10495,19865.4],[0,8166.12,19862.3,10490.9,23139.5],
[0,5348.8,23990.1,5362.83,23999.9],[0,3071.9,23994,5349.8,23996],
[0,10478.4,19851.1,10490.4,19865.4],[0,3069.16,19861.3,10483.9,23991.8],
[0,10447,5920.09,10461,5929.91],[0,8103.58,5924,10448,5978],
[0,10453,5973.09,10467,5982.91],[0,8103.6,5977,10454,5979],
[0,8038,5973.09,8052.03,5982.91],[0,5574.19,5977,8039.01,6003],
[0,7964.2,6026.09,7978.23,6035.91],[0,5573.79,6003,7965.21,6032],
[0,10452.1,19851.4,10466.9,19861.6],[0,8147.26,19855.8,10455.4,20749],
[0,5415.27,20507.9,5429.68,20517.7],[0,3001.41,20511.7,5416.79,20725.5],
[0,10455.8,19851.1,10470.5,19862],[0,3001.7,19856.3,10459.5,20728],
[0,7986.05,20750.6,8000.12,20760.4],[0,3001.39,20726.2,7987.11,20756.5],
[0,5437.68,20929.4,5452.07,20939.2],[0,3001.42,20728.4,5439.18,20935.4],
[0,10463.4,19851.5,10477.8,19863.4],[0,5534.49,19858,10467.6,21084.5],
[0,7989.08,19047.2,8003.55,19057],[0,5526.26,19051,7990.72,21075.4],
[0,10462.3,19850.8,10476.6,19863],[0,8108.21,19857.6,10466.6,21052.9],
[0,10424.9,18056.5,10439.7,18066.1],[0,5634.73,18060.1,10427.2,18468.5],
[0,12736,6255.09,12750,6264.91],[0,8103.42,6259,12737.1,6577],
[0,10412,6594.09,10426,6603.91],[0,8103.59,6577,10413,6600],
[0,10410.1,7105.99,10424.8,7115.62],[0,8103.59,6580,10412.2,7111.99],
[0,8038.1,6573.09,8052.13,6582.91],[0,5519.09,6550,8039.11,6579],
[0,10370.5,6314.21,10385,6323.99],[0,8103.51,6318,10372.1,6523],
[0,10384.5,6262.21,10399,6271.99],[0,8103.49,6266.01,10386.1,6521.99],
[0,10411.6,6592.02,10426,6601.8],[0,8103.57,6524,10413,6598],
[0,10409.1,7105.99,10423.8,7115.62],[0,8103.39,6526,10411.2,7111.99],
[0,8038.1,6519.09,8052.13,6528.91],[0,5519.09,6523,8039.11,6552],
[0,12767.4,23754.8,12781.9,23764.6],[0,10526.9,23509,12769.1,23760.8],
[0,12757,23493.4,12771,23503.2],[0,10527,23497.3,12758,23507.9],
[0,10459.8,23512.5,10474.6,23522],[0,8167.57,23516,10462.3,24175],
[0,10488,19804.9,10497.6,19819.7],[0,8132.26,10986,10494,19807.1],
[0,10477.4,13935.4,10489.2,13949.8],[0,8127.21,10990,10482.8,13939.5],
[0,10378.9,19831.2,10393,19841],[0,5560.39,18678.1,10380,19840.6],
[0,7953.44,16978.8,7968.06,16988.5],[0,5562.91,16982.5,7955.36,18672.8],
[0,10427.8,18057.2,10442.6,18066.7],[0,5563.38,18060.7,10430.2,18673.9],
[0,10478.2,13935.7,10489.3,13950.4],[0,8132,11070,10483.8,13939.5],
[0,10488,19804.9,10497.6,19819.7],[0,8127.93,11065.1,10494,19807.1],
[0,10367.9,15058,10382,15067.8],[0,5557.1,14999.8,10369,15063.9],
[0,10365.9,15060.6,10380,15070.4],[0,8178.59,15040.1,10367,15066.5],
[0,10414.1,9985.99,10428.8,9995.62],[0,8150.65,9563.01,10416.2,9991.98],
[0,10377.9,18037.3,10392.7,18046.8],[0,8154.1,9545,10380.3,18043.3],
[0,10434.5,9830.01,10449,9839.79],[0,8151.78,9562.01,10436.1,9835.99],
[0,10376.9,18035.9,10391.7,18045.4],[0,8085.21,11307.5,10379.3,18041.9],
[0,10371,11256.1,10385,11265.9],[0,8189.18,11260,10372,11290],
[0,10372.1,9797.38,10386.8,9807.01],[0,8183.26,9801.02,10374.2,11285],
[0,10377.8,18034.8,10392.6,18044.3],[0,8100.6,13038.2,10380.3,18040.8],
[0,10368,9901.42,10382.7,9911.01],[0,8097.77,9905.04,10370.3,13004.8],
[0,10486,19850.6,10495.4,19865.5],[0,8205.59,19862.8,10492,23188.2],
[0,10334,23185.1,10348,23194.9],[0,8207.6,23189,10335,23191],
[0,10471.7,19850.7,10485,19864.3],[0,8158.58,19859.5,10476.7,21532.1],
[0,10379.9,18033.5,10394.7,18043.1],[0,8129.18,14427.9,10382.2,18039.5],
[0,10388.1,8141.38,10402.8,8151.01],[0,8127.35,8145.03,10390.2,14442.5],
[0,10472.6,11275.2,10485.6,11289],[0,8130.2,11284.3,10477.8,14439],
[0,10375.9,16528.5,10390.7,16538.1],[0,8131.08,14432,10378.2,16534.5],
[0,10472.6,11275.2,10485.6,11289],[0,8162.21,11284.3,10477.8,14546],
[0,10379.9,18033.3,10394.7,18042.9],[0,8161.84,14537,10382.2,18039.3],
[0,7981.1,1976.09,7995.13,1985.91],[0,5570.32,1791,7982.18,1982],
[0,7964.1,1762.09,7978.13,1771.91],[0,5577.59,1766,7965.11,1785],
[0,10447.1,18059.5,10462,18069.6],[0,8177.66,18063.8,10450.4,18816.5],
[0,5346.57,20836.3,5360.98,20846.1],[0,3081.82,20840.1,5348.08,21029.9],
[0,10462.4,19851.5,10476.8,19863.3],[0,3099.1,19857.9,10466.6,21038.5],
[0,12781.1,7593.38,12795.8,7603.01],[0,10531.9,7597.03,12783.2,8087.99],
[0,15002.9,16149,15017,16158.8],[0,12916,16131.7,15004,16154.9],
[0,10486,19804.6,10495.4,19819.5],[0,8186.86,16384.4,10492,19807.3],
[0,12719.9,15193,12734,15202.8],[0,8176.37,15196.9,12721,16379.2],
[0,10408,13959.1,10422,13968.9],[0,8196.58,13921,10409,13965],
[0,10455.5,12972.1,10470,12983.7],[0,8179.46,12978.1,10459.5,13912],
[0,10487,19804.1,10496.4,19818.9],[0,8095.82,13937.3,10493,19806.6],
[0,10425.1,13948,10439.8,13957.6],[0,8134.02,13530,10427.2,13954],
[0,10457.7,12238.7,10472.4,12249.8],[0,8146.59,12244.1,10461.5,13518],
[0,10488,19804.9,10497.6,19819.7],[0,8141.51,13526,10494,19807.1],
[0,10432.6,12970.6,10447.5,12980],[0,8141.39,12974,10435.3,13513],
[0,10407.2,18025,10421.9,18034.7],[0,5491.33,9717.5,10409.2,18031],
[0,8000.69,3193.61,8015.55,3202.99],[0,5490.62,3197.04,8003.39,9682.48],
[0,10385.7,19822.9,10400,19832.7],[0,5578.98,18463.9,10387.1,19828.9],
[0,10400.6,12962.2,10415,12972],[0,5582.61,12966,10402.1,18464.1],
[0,10422.1,12936,10436.8,12945.6],[0,8174.64,12520,10424.2,12942],
[0,10488,19805,10497.6,19819.8],[0,8216.1,12507,10494,19807.2],
[0,10412.5,12228.2,10427,12238],[0,8179.68,12232,10414.1,12497],
[0,10427.6,12935,10442.5,12944.4],[0,8159.66,12463,10430.2,12941],
[0,10488,19805.2,10497.6,19820],[0,8169.44,12446,10494,19807.4],
[0,10455.7,11503.7,10470.4,11514.8],[0,8167.68,11509.1,10459.5,12447],
[0,10476.3,12972,10487.9,12986.5],[0,8134.58,12982.4,10481.8,15541.3],
[0,10490,19805.2,10499.8,19819.7],[0,8132.48,15531.7,10496,19806.9],
[0,10429.8,19848.6,10444.6,19858.1],[0,3077.34,17285,10432.3,20278.7],
[0,5424.28,16040.1,5439.13,16049.8],[0,3067.05,16044,5427.37,17276.9],
[0,5372.03,18444.8,5386.6,18454.5],[0,3066.55,17291.2,5373.84,18450.8],
[0,10393,12957.1,10407,12966.9],[0,3078.04,12961,10394.1,17285.5],
[0,7989.83,12044.2,8004.27,12054],[0,5519.34,12048,7991.45,12839.9],
[0,10427.9,19812.3,10442.7,19821.8],[0,5543.62,12859,10430.2,19818.3],
[0,10411.6,13954,10426,13963.8],[0,5524.27,12867.1,10413.1,13960],
[0,10427.5,12005,10442,12014.8],[0,5511.94,11939.9,10429.1,12838.9],
[0,10390.1,8140.38,10404.8,8150.01],[0,8163.97,8144.02,10392.2,17493.4],
[0,10479.2,19804.8,10490.4,19819.4],[0,8175.38,17484.2,10484.9,19808.6],
[0,10438.2,13979.2,10453.1,13988.9],[0,8174.5,13983.1,10441.4,17487.7],
[0,10405.2,18025.5,10419.9,18035.2],[0,8159.77,17492.8,10407.2,18031.5],
[0,10443.2,12932.1,10458.1,12941.8],[0,8158.98,12246,10446.3,12937.9],
[0,10402,12219.1,10416,12228.9],[0,8170.7,12223,10403,12238],
[0,10488,19805,10497.6,19819.7],[0,8195.25,12179,10494,19807.1],
[0,10401.5,12216,10416,12225.8],[0,8198.18,12185,10403,12222],
[0,10447.5,12932,10462.4,12941.3],[0,8176.64,12193,10450.4,12937.9],
[0,10444.5,11502.7,10459.4,11512],[0,8174.47,11506.1,10447.3,12174],
[0,10488,19804.9,10497.6,19819.6],[0,8170.84,12608,10494,19807],
[0,10409.5,12940,10424,12949.8],[0,8156.57,12626,10411.1,12946],
[0,10487,19804.6,10496.4,19819.5],[0,8155.7,12679,10493,19807.2],
[0,10386,12639.1,10400,12648.9],[0,8169.89,12643,10387,12670],
[0,10404.6,12941,10419,12950.8],[0,8156.28,12678,10406.1,12947],
[0,10390.5,8145.21,10405,8154.99],[0,8147.27,8149,10392,8229],
[0,10402.5,7989.21,10417,7998.99],[0,8142.7,7993,10404.1,8224],
[0,10488,19804.9,10497.6,19819.7],[0,8139.55,8219.66,10494,19807.1],
[0,10467.2,12973.2,10481.4,12985.5],[0,8097.22,12980.2,10471.6,14895.7],
[0,10489,19805,10498.6,19819.7],[0,8108.87,14919.2,10495,19807.1],
[0,10432.6,12934,10447.5,12943.4],[0,8107.87,12402,10435.3,12940],
[0,10488,19805,10497.6,19819.8],[0,8107.08,12391.3,10494,19807.2],
[0,10488,19805,10497.6,19819.8],[0,8131.44,10693,10494,19807.2],
[0,10477.4,13935.4,10489.2,13949.8],[0,8127.09,10697,10482.8,13939.5],
[0,15055.2,4932.16,15070.1,4941.93],[0,10590.9,4936.08,15058.4,5659.88],
[0,15057.1,4890.11,15071.9,4900.29],[0,10592.9,4124.44,15060.4,4895.91],
[0,14963.5,5477.21,14978,5486.99],[0,5524.04,5481,14965.1,5766.24],
[0,7972.61,6672.01,7987.06,6681.79],[0,5506.91,5630.12,7974.23,6677.99],
[0,14985,4911.09,14999,4920.91],[0,5516.72,4914.09,14986,5606.96],
[0,8014.89,3195.61,8029.73,3204.98],[0,5517.09,3199.06,8017.63,5606.95],
[0,10388,4156.09,10402,4165.91],[0,5513.75,4159.68,10389,5604.93],
[0,10414,6590.09,10428,6599.91],[0,5511.11,5628.08,10415.1,6596],
[0,10389,5611.09,10403,5620.91],[0,5524.4,5615,10390,5617],
[0,10408.5,5078.01,10423,5087.79],[0,8147.79,3961,10410.2,5083.99],
[0,10410.5,13955,10425,13964.8],[0,8123.94,13814,10412.1,13961],
[0,10488,19805,10497.6,19819.7],[0,8122.03,13804.1,10494,19807.1],
[0,10391.1,11059.4,10405.8,11069],[0,8120.59,11063,10393.2,13806],
[0,10421,18055.9,10435.7,18065.5],[0,2974.52,11355.8,10423.2,18395.3],
[0,10373,11258.1,10387,11267.9],[0,3056.5,11262,10374,11341.7],
[0,5369.9,11285.1,5383.93,11294.9],[0,3056.28,11289,5370.92,11337],
[0,10383.5,16550.1,10398,16559.9],[0,2972.2,11356,10385.1,16742.8],
[0,10398.5,8150.21,10413,8159.99],[0,3056.41,8154,10400.1,11338],
[0,12820.5,13397.6,12832.8,13411.8],[0,10539,13407.4,12825.8,15539.2],
[0,12766.7,15418,12781,15427.8],[0,10538.9,15421.8,12768.1,15537],
[0,12767.9,15559.3,12782,15569.1],[0,10539,15537.5,12769,15565.2],
[0,10407,13962.1,10421,13971.9],[0,5541.29,13966,10408,14012],
[0,8062.72,20211.6,8072.08,20226.4],[0,5494.61,14029.4,8068.65,20214.3],
[0,10395.5,13371,10410,13380.8],[0,5522,13353,10397,14000],
[0,8012.94,13229.2,8027.37,13239],[0,5517.84,13233,8014.5,13998.9],
[0,7970.37,14308,7985.08,14317.6],[0,5536.68,14018,7972.42,14314],
[0,10423.9,19812.9,10438.7,19822.5],[0,5494.41,14029.4,10426.2,19818.9],
[0,10488,19804.9,10497.6,19819.6],[0,8168.86,10247,10494,19807],
[0,15072.2,7692.18,15086.4,7704.53],[0,8181.16,7699.21,15076.6,10228],
[0,10452.7,7723.68,10467.4,7734.77],[0,8194.85,7729.12,10456.5,10234],
[0,10478.2,13935.7,10489.3,13950.4],[0,8155.57,10249,10483.8,13939.5],
[0,10393.2,16525.4,10407.8,16535.1],[0,8151.29,15705.5,10395.2,16531.4],
[0,10436.6,15082.1,10451.4,15091.5],[0,8148.57,15085.5,10439.3,15693.1],
[0,2870.4,1248.09,2884.43,1257.91],[0,937.223,1252,2871.41,1279],
[0,10409.7,23854,10424,23863.8],[0,8154.93,23702.4,10411.1,23859.9],
[0,10488,19850.3,10497.6,19865.1],[0,8156.25,19862.9,10494,23703.3],
[0,10406.1,8128.99,10420.8,8138.62],[0,8170.27,7372.01,10408.2,8134.99],
[0,10417.5,6442.21,10432,6451.99],[0,8173.07,6446.01,10419.1,7355.99],
[0,12802.6,2272.01,12817.5,2281.41],[0,10583.8,1781.02,12805.2,2277.98],
[0,5375.03,8081.02,5389.47,8090.79],[0,3034.35,7740.01,5376.64,8086.99],
[0,10413.1,8126.99,10427.8,8136.62],[0,3042.75,7657.52,10415.1,8132.99],
[0,5385.91,7465.22,5400.36,7474.98],[0,3038.49,7469,5387.51,7726],
[0,10401.6,11109.2,10416,11119],[0,8210.96,11113,10403.2,14486],
[0,10487,19805,10496.6,19819.8],[0,8213.06,14488,10493,19807.3],
[0,7968.82,3172.02,7983.26,3181.79],[0,5583.96,3092,7970.34,3178],
[0,5395.43,3301.21,5409.86,3310.98],[0,3070.86,3305,5396.93,7788.99],
[0,10379,18038.3,10393,18048.1],[0,3065.7,7779,10380,18044.2],
[0,10488,18059.5,10497.6,18074.2],[0,8213.16,18072.1,10494,21863.5],
[0,10370,21864.9,10384,21874.7],[0,8216.3,21865.2,10371,21870.8],
[0,10488,18059,10497.6,18073.8],[0,8203.5,18071.6,10494,21919.7],
[0,12725,21889.7,12739,21899.5],[0,8203.89,21893.6,12726,21920.3],
[0,10487,19850.4,10496.4,19865.3],[0,8103.52,19862.7,10493,23557.5],
[0,10387,23573.8,10401,23583.6],[0,8103.59,23551.3,10388,23579.7],
[0,8037.9,23547.1,8051.93,23556.9],[0,5542.7,23551,8038.9,23553],
[0,10402.4,18052,10416.9,18061.7],[0,5557.92,18055.7,10404.1,18279.1],
[0,10388.6,18047.8,10403,18057.6],[0,8161.92,18051.6,10390.1,18230.2],
[0,10488,19804.9,10497.6,19819.6],[0,8146.38,16018.5,10494,19807],
[0,10445.2,13980.2,10460.1,13989.9],[0,8148.64,13984.1,10448.4,16025.3],
[0,10486,19804.5,10495.4,19819.3],[0,8170.42,14610,10492,19807.2],
[0,10469.8,11831.8,10483.2,11845.2],[0,8223.46,11840.3,10474.7,14588],
[0,10416.1,11120.4,10430.8,11130],[0,8126.12,11124,10418.1,11710],
[0,10488,19804.7,10497.4,19819.6],[0,8153.2,11732,10494,19807.3],
[0,10382,11807.1,10396,11816.9],[0,8162.26,11726,10383,11813],
[0,10400.6,8151.2,10415,8160.98],[0,5548.07,8155,10402.1,8330.45],
[0,10393.5,8147.21,10408,8156.99],[0,8148.24,8151,10395.1,8281],
[0,10436.6,18058.8,10451.4,18068.2],[0,5543.25,18062.2,10439.3,18779.6],
[0,10489,19850.6,10498.6,19865.3],[0,8173.11,19863.2,10495,24080.8],
[0,10489,19850.3,10498.6,19865],[0,8182.98,19862.9,10495,23971.5],
[0,10489,19850.7,10498.6,19865.4],[0,8179.49,19863.3,10495,24026],
[0,7955.71,18811.5,7970.09,18821.3],[0,5554.52,18624.8,7957.18,18817.5],
[0,7953.95,16979,7968.57,16988.7],[0,5558.11,16982.7,7955.86,18619],
[0,10378.9,19829.4,10393,19839.2],[0,5556.2,18623.6,10380,19835.3],
[0,10423.9,18056.4,10438.7,18066],[0,5558.48,18060,10426.2,18619.9],
[0,5409.54,8114.59,5424.38,8123.99],[0,2990.29,8118.05,5412.2,9896.71],
[0,5427.72,18157.5,5442.55,18167.6],[0,3046.41,9920.02,5431.01,18163.3],
[0,10411.1,10039,10425.8,10048.6],[0,3040.26,9602.37,10413.2,10045],
[0,10369.8,16545.7,10384,16555.6],[0,3045.29,9920.02,10371.1,16652],
[0,10379,18039.5,10393,18049.3],[0,3046.41,9920.02,10380,18049.6],
[0,10393.5,10153,10408,10162.8],[0,3052.56,9914,10395,10159],
[0,10387.5,10097,10402,10106.8],[0,3052.59,9900.45,10389.1,10103],
[0,10389,8142.09,10403,8151.91],[0,2987.99,8146,10390,9896.71],
[0,5394,822.09,5408.03,831.91],[0,2999.71,826.004,5395.09,1035],
[0,5388.1,1083.09,5402.13,1092.91],[0,2999.78,1036,5389.12,1089],
[0,5386.7,1031.09,5400.73,1040.91],[0,2999.8,1035,5387.7,1037],
[0,2934,1031.09,2948.03,1040.91],[0,924.109,1035,2935,1037],
[0,10397.1,9875.99,10411.8,9885.62],[0,8162.05,9347.01,10399.1,9881.99],
[0,10397.1,9766.99,10411.8,9776.62],[0,8174.77,8969.01,10399.2,9772.98],
[0,5367.52,20839.9,5382.1,20849.6],[0,3024.6,20843.6,5369.33,21288],
[0,10469.9,19851.4,10483.6,19864.5],[0,3038.59,19859.5,10474.7,21318.4],
[0,5400.2,23935,5414.59,23944.8],[0,2984.59,21315.1,5401.69,23941],
[0,5379.46,23976.6,5394.02,23986.3],[0,3080.07,23673.4,5381.23,23982.6],
[0,5405.96,23927.7,5420.45,23937.5],[0,3092.09,23672.4,5407.61,23933.7],
[0,5329.43,20834.5,5344.23,20844],[0,2979.89,20838,5331.87,23642.2],
[0,8000.56,23744.5,8014.72,23754.3],[0,5508.77,23660,8001.73,23750.4],
[0,8025.65,23639.4,8039.73,23649.2],[0,5508.79,23643.3,8026.71,23660.8],
[0,5443,23655.1,5457.03,23664.9],[0,3151.6,23659,5444,23661],
[0,10478.4,19851,10490.4,19865.3],[0,3014.82,19861.2,10483.9,23643.3],
[0,10408,13961.1,10422,13970.9],[0,3046,13965,10409,13967],
[0,10407,11478.1,10421,11487.9],[0,2980.5,11341.4,10408.1,13948.4],
[0,10409.3,19844.4,10423.9,19854.1],[0,2975.32,13983.8,10411.2,20141.1],
[0,10390.5,12948,10405,12957.8],[0,2997.85,12872.1,10392,13949.8],
[0,5340.54,16009.9,5355.27,16019.5],[0,2984.9,13983.4,5342.71,16015.9],
[0,10486,19850.6,10495.4,19865.5],[0,8136,19862.8,10492,23249],
[0,10408,23243,10422,23252.8],[0,8137.5,23243.1,10409,23248.9],
[0,10486,19850.6,10495.4,19865.5],[0,8111.34,19862.8,10492,23303],
[0,12776,23268.4,12790,23278.2],[0,8112.1,23272.3,12777,23298.8],
[0,10461.4,19850.6,10475.7,19862.6],[0,5566.29,19857.2,10465.5,20898.8],
[0,10458.6,19851.1,10473.2,19862.4],[0,8139.88,19856.8,10462.5,20919],
[0,2878.08,15426.5,2892.68,15436.2],[0,886.078,15430.2,2879.95,15738.6],
[0,2853.04,17324.3,2867.72,17333.9],[0,845.852,15763.1,2855.09,17330.3],
[0,10471.8,12030.8,10485.2,12044.2],[0,8152.44,12039.3,10476.7,14673],
[0,10486,19804.8,10495.4,19819.6],[0,8220.28,14690.1,10492,19807.5],
[0,10480.2,19850.6,10491.4,19865.3],[0,8169.3,19861.5,10485.9,22381.1],
[0,10487,19804.6,10496.4,19819.5],[0,8131.55,14264.6,10493,19807.2],
[0,10417.5,13971.2,10432,13981],[0,8130.57,13975,10419.1,14266],
[0,5409.3,46.0898,5423.33,55.9102],[0,2999.79,50,5410.31,78],
[0,5427.73,98.0195,5442.16,107.793],[0,2999.79,76,5429.21,104],
[0,2934.1,72.0898,2948.13,81.9102],[0,895.211,76,2935.1,78],
[0,10409.1,5489.99,10423.8,5499.62],[0,8103.27,4903.01,10411.2,5495.99],
[0,10407.5,4637.21,10422,4646.99],[0,8103.49,4641.01,10409.1,4897.99],
[0,8038,4895.09,8052.03,4904.91],[0,5610.1,4899,8039,4901],
[0,10424.1,4225.38,10438.8,4235.01],[0,8174.77,4229.02,10426.2,4726.99],
[0,10400.5,5545.01,10415,5554.79],[0,8183.26,4748.01,10402.2,5550.98],
[0,10408,3343.09,10422,3352.91],[0,8103.58,3347,10409,3400],
[0,10415.5,2867.21,10430,2876.99],[0,8103.59,2871.02,10417.2,3398],
[0,10382,3292.09,10396,3301.91],[0,8103.56,3296,10383,3400],
[0,10432,3395.09,10446,3404.91],[0,8103.6,3399,10433,3401],
[0,8038,3396.09,8052.03,3405.91],[0,5619.58,3400,8039.02,3455],
[0,7972.82,3169.02,7987.26,3178.79],[0,3053.99,3038.8,7974.33,3175],
[0,7983.92,1974.02,7998.36,1983.79],[0,3000.89,1929.62,7985.49,3026.86],
[0,5366.3,3082.09,5380.33,3091.91],[0,3053.78,3043,5367.32,3088],
[0,10411.1,11041,10425.8,11050.7],[0,3049.37,3036,10413.1,11047],
[0,10412.5,8128.01,10427,8137.79],[0,5561.35,7858.5,10414.2,8133.99],
[0,10399.5,8132.01,10414,8141.79],[0,8175.1,7924,10401.1,8138],
[0,10432.7,16775.9,10447.5,16785.4],[0,8111.69,16779.4,10435.3,17335.2],
[0,15069,7673.09,15083,7682.91],[0,12889.9,7677,15070.1,7820],
[0,15068.5,7674.21,15083,7683.99],[0,12882.9,7678,15070.1,7873],
[0,10439.5,2692.01,10454,2701.79],[0,8190.39,2676,10441,2698],
[0,12761,2743.09,12775,2752.91],[0,8189.98,2661.46,12762.1,2749],
[0,10482.2,19804.3,10493.1,19819],[0,8220.65,17036.9,10487.9,19807.9],
[0,10362,17025.1,10376,17034.9],[0,8237.3,17029,10363,17031],
[0,10364.6,9265.59,10379.5,9274.99],[0,8231.45,9269.07,10367.4,17026.1],
[0,15068.5,7672.21,15083,7681.99],[0,10595,7676,15070,7709.7],
[0,10489,19850.4,10498.6,19865.1],[0,8184.67,19863,10495,23917.2],
[0,10400.5,9876.01,10415,9885.79],[0,8103.57,9448.01,10402.2,9881.98],
[0,10390.5,9768.01,10405,9777.79],[0,8103.47,9449.01,10392.1,9773.99],
[0,10407.1,10040,10421.8,10049.6],[0,8103.39,9448,10409.2,10046],
[0,10437.1,9826.99,10451.8,9836.62],[0,8103.47,9449.01,10439.2,9832.99],
[0,8037.62,9444.21,8052.06,9453.98],[0,5577.24,9448,8039.2,10266],
[0,10402.5,9876.01,10417,9885.79],[0,8103.47,9503.01,10404.2,9881.99],
[0,10408.5,10040,10423,10049.8],[0,8103.59,9502,10410.2,10046],
[0,10435.1,9827.99,10449.8,9837.65],[0,8103.47,9503.01,10437.1,9833.99],
[0,10390.1,11242,10404.8,11251.6],[0,8103.6,9498,10392.2,11248],
[0,8037.72,9498.21,8052.16,9507.98],[0,5576.18,9502,8039.3,10265],
[0,10415.5,9986.01,10430,9995.79],[0,8103.34,9611.01,10417.2,9991.98],
[0,10388.5,9878.01,10403,9887.79],[0,8103.48,9610.01,10390.1,9883.99],
[0,10410.1,10039,10424.8,10048.6],[0,8103.44,9611.01,10412.2,10045],
[0,10392.1,11241,10406.8,11250.6],[0,8103.14,9613.03,10394.2,11247],
[0,8036.92,9615.59,8051.77,9624.99],[0,5573.39,9619.05,8039.6,10265],
[0,10409.2,18024.8,10423.9,18034.5],[0,5586.41,10267,10411.2,18030.8],
[0,10403.3,18026.1,10417.9,18035.8],[0,5545.57,17631.2,10405.1,18032.1],
[0,8010.6,17625.1,8024.63,17634.9],[0,5546.2,17629,8011.6,17631],
[0,10394.5,10170.2,10409,10180],[0,5493.69,10174,10396.1,17612.8],
[0,10389.6,19821.2,10404,19831],[0,5504.93,17646,10391.1,19827.2],
[0,8038.2,7505.09,8052.23,7514.91],[0,5546.2,7509,8039.2,7515],
[0,10433.5,24024.9,10448,24034.7],[0,8182.8,23815.1,10435.1,24030.9],
[0,10489,19850.2,10498.6,19864.9],[0,8204.6,19862.8,10495,23805.7],
[0,10407.5,9932.01,10422,9941.79],[0,8157.36,9400.01,10409.2,9937.99],
[0,8036.2,10179.1,8050.23,10188.9],[0,5616.34,10183,8037.26,10321],
[0,8004.4,10128.1,8018.43,10137.9],[0,5606.92,10132,8005.48,10319],
[0,10435.5,19811.2,10450.4,19820.6],[0,5563.17,11807,10438.3,19817.2],
[0,10387,11634.1,10401,11643.9],[0,5565.07,11635.4,10388,11810],
[0,7951.1,11811.1,7965.13,11820.9],[0,5572.3,11815,7952.1,11817],
[0,10437.6,19810.6,10452.4,19820],[0,5563.17,11753,10440.3,19816.6],
[0,10387,11634.1,10401,11643.9],[0,5565.87,11622.5,10388,11756],
[0,7951.71,11808,7966.16,11817.8],[0,5571.48,11763,7953.22,11814],
[0,10489,19804.6,10498.6,19819.3],[0,8171.11,15641.1,10495,19806.7],
[0,10453.1,13555.7,10467.9,13565.9],[0,8172.99,13560.1,10456.5,15645.3],
[0,10431.6,12970.6,10446.5,12980],[0,8131.94,12974,10434.3,13598],
[0,10336,13539.1,10350,13548.9],[0,8176.27,13543,10337,13610],
[0,10489,19805,10498.6,19819.7],[0,8171.34,13605,10495,19807.1],
[0,7930.7,8056.09,7944.73,8065.91],[0,5580.39,8046,7931.71,8062],
[0,10394.6,8134.02,10409,8143.8],[0,5579.58,8022.75,10396,8140],
[0,8004.52,9677.01,8019.37,9686.41],[0,5577.88,8049.01,8007.18,9682.96],
[0,10414.5,13953,10429,13962.8],[0,8113.9,13723,10416.1,13959],
[0,10488,19804.9,10497.6,19819.7],[0,8113.96,13722,10494,19807.1],
[0,12804,7165.09,12818,7174.91],[0,8112.88,7169,12805.1,13728.3],
[0,14999.5,2399.21,15014,2408.99],[0,12869,2403,15001,2455],
[0,14960.5,2349.21,14975,2358.99],[0,12869,2353,14962,2455],
[0,14979,2501.09,14993,2510.91],[0,12869,2455,14980,2507],
[0,12804,2452.09,12818,2461.91],[0,10625.9,2456,12805.1,2599],
[0,12760,2749.09,12774,2758.91],[0,10572,2753,12761,2805],
[0,12760,2801.09,12774,2810.91],[0,10572,2805,12761,2807],
[0,12732,6247.09,12746,6256.91],[0,8103.35,6222.22,12733,6466.99],
[0,10413.5,6590.01,10428,6599.79],[0,8103.55,6470,10415.1,6596],
[0,8037.8,6465.09,8051.83,6474.91],[0,5580,6469,8038.8,6471],
[0,10390.5,12948,10405,12957.8],[0,3115.47,12815.6,10392,12954],
[0,10403.3,19843.2,10417.9,19852.9],[0,2975.93,12963.8,10405.1,20104.2],
[0,10389,12952.1,10403,12961.9],[0,5595.7,12945,10390,12958],
[0,10408.5,13957,10423,13966.8],[0,8188.76,13870,10410,13963],
[0,10488,19804.9,10497.6,19819.7],[0,8189.56,13861,10494,19807.1],
[0,10452.7,12972.7,10467.4,12983.8],[0,8175.87,12978.1,10456.4,13858],
[0,12803.5,2278.01,12818,2287.79],[0,8217.89,2147.12,12805,2284],
[0,12804,2280.09,12818,2289.91],[0,10633,2198,12805,2286],
[0,5360.37,20811.6,5374.85,20821.4],[0,2999.69,20550.1,5362.01,20817.6],
[0,10393,12957.1,10407,12966.9],[0,2999.2,12961,10394.1,20533.9],
[0,2934.2,20543.1,2948.23,20552.9],[0,933.969,20547,2935.2,20549],
[0,5399.25,20806.8,5414.02,20816.4],[0,2999.36,20324.6,5401.52,20812.8],
[0,10405,11480.1,10419,11489.9],[0,2999.58,11421.5,10406,20329.8],
[0,2933.62,20321.1,2948.07,20330.9],[0,919.246,20324.9,2935.21,20539.7],
[0,10472.5,19850.3,10485.1,19864.3],[0,862.344,19859.8,10477.7,21465.3],
[0,10382.8,19824.4,10397,19834.3],[0,5585.77,18518.8,10384,19830.4],
[0,7957.46,13459.4,7972.18,13469],[0,5595.56,13463,7959.55,18516.3],
[0,10482.1,19804.8,10492.1,19819.7],[0,8151.45,17080.9,10487.9,19808.1],
[0,10363.9,17028.1,10378,17037.9],[0,8151.58,17032,10365,17083.3],
[0,10479.2,12972.6,10490.3,12987.3],[0,8148.98,12983.5,10484.9,17090],
[0,10394.5,19819.5,10408.9,19829.3],[0,5503.07,17051.2,10396.1,19825.5],
[0,10368.8,17018.6,10383,17028.5],[0,5610.94,16944.9,10370,17026.6],
[0,10395.5,12959.2,10410,12969],[0,5497.05,12963,10397.1,17016.7],
[0,10367.8,17030.9,10382,17040.7],[0,8250.16,17034.8,10369,17131.3],
[0,10479.2,12972.6,10490.3,12987.3],[0,8236.54,12983.5,10484.9,17128.8],
[0,10480.1,19805.3,10490.4,19820.1],[0,8156.23,17153.5,10485.9,19808.7],
[0,10468,19851.6,10481.9,19864.5],[0,8179.64,19859.4,10472.7,21360.2],
[0,10384.7,18045.7,10399,18055.5],[0,8176.64,18049.5,10386.1,18177.3],
[0,10470.7,19805.5,10484,19819.1],[0,8178.37,18185.9,10475.7,19810.3],
[0,10409.2,18024.9,10423.9,18034.6],[0,8125.44,17637.1,10411.2,18030.9],
[0,10483.1,10181.9,10492.8,10196.8],[0,8129.25,10193.6,10488.9,17626.4],
[0,10475.5,19805.2,10487.8,19819.4],[0,8122.67,17638.6,10480.8,19809.5],
[0,10411.2,19844.9,10425.8,19854.6],[0,8167.54,19848.6,10413.2,20227.9],
[0,10378.9,18041.4,10393,18051.2],[0,8198.18,18045.3,10380,18088.7],
[0,10469,19805.6,10482.7,19818.6],[0,8138.62,18104.5,10473.7,19810.6],
[0,10474.6,19851.2,10487.5,19865],[0,8166.27,19860.5,10479.8,21808.4],
[0,5391.86,18182.1,5406.11,18192],[0,2975.73,10483.8,5393.17,18188.1],
[0,10392,10046.1,10406,10055.9],[0,3020.66,9959.04,10393.1,10455],
[0,10401.5,8151.21,10416,8160.99],[0,2983.98,8155,10403.1,10448.6],
[0,10391.6,19839.7,10406,19849.5],[0,2975.73,10483.8,10393.1,20029.8],
[0,10405.3,18052.6,10419.9,18062.3],[0,2975.52,10483.8,10407.1,18327.9],
[0,10389.5,10167.2,10404,10177],[0,3035.77,10171,10391.1,10466],
[0,10375.5,10102,10390,10111.8],[0,3022.39,10013.3,10377,10456],
[0,10488,19805.2,10497.6,19820],[0,8115.71,12337.4,10494,19807.4],
[0,10386,12341.1,10400,12350.9],[0,8118,12345,10387,12347],
[0,10436.6,12933,10451.5,12942.4],[0,8116.88,12349,10439.3,12939],
[0,10431.6,12019.2,10446,12029],[0,8116.36,12023,10433.1,12342],
[0,10427,12011.1,10441,12020.9],[0,8165.19,12015,10428,12038],
[0,10488,19805,10497.6,19819.7],[0,8207.29,12559,10494,19807.1],
[0,10388.5,12480.2,10403,12490],[0,8204.57,12484,10390,12559],
[0,10416.1,12938,10430.8,12947.6],[0,8170.07,12574,10418.2,12944],
[0,12759.6,12310,12774,12319.8],[0,8180.06,12130,12761,12316],
[0,10450.1,12931.1,10464.9,12941.3],[0,8167.38,12138,10453.4,12936.9],
[0,10434.7,18058.3,10449.5,18067.7],[0,8149.95,18061.7,10437.3,18654.4],
[0,10387.1,18029.8,10401.8,18039.4],[0,8185.66,16281.7,10389.2,18035.8],
[0,10462.3,15082.9,10476.5,15095.1],[0,8178.97,15089.7,10466.6,16271.4],
[0,10390.1,11051,10404.8,11060.6],[0,8159.14,7431.04,10392.2,11057],
[0,10407.5,7692.01,10422,7701.79],[0,8176.18,7429.01,10409.1,7697.99],
[0,10427.5,6766.21,10442,6775.99],[0,8178.96,6770.01,10429.2,7406.99],
[0,10406.5,6715.21,10421,6724.99],[0,8180.56,6719.01,10408.2,7407.99],
[0,15068.5,7670.01,15083,7679.79],[0,8170.87,7430.01,15070,7676],
[0,5363.32,8083.01,5377.76,8092.79],[0,3052.3,7847,5364.9,8089],
[0,10409.1,8127.99,10423.8,8137.62],[0,3060.76,7789.71,10411.1,8133.99],
[0,8038.1,7505.09,8052.13,7514.91],[0,3045.56,7508.02,8039.11,7829.99],
[0,10418.4,24134.5,10432.9,24144.2],[0,8191.58,23872.7,10420.1,24140.5],
[0,10489,19850.5,10498.6,19865.2],[0,8232.07,19863.1,10495,23852.2],
[0,12797.7,3752.23,12812.4,3763.32],[0,10552.9,2919.01,12801.4,3757.91],
[0,12762,2752.09,12776,2761.91],[0,10554.9,2756,12763.1,2911],
[0,8037.62,5108.02,8052.06,5117.79],[0,5560.45,4995,8039.15,5114],
[0,8037.43,4790.21,8051.86,4799.98],[0,5557.62,4794,8038.98,4987],
[0,8038.2,4987.09,8052.23,4996.91],[0,5561.9,4991,8039.2,4993],
[0,8002.48,23740.6,8016.95,23750.4],[0,5512.38,22852.6,8004.11,23746.6],
[0,10479.2,19850.7,10490.4,19865.4],[0,5519.09,19861.6,10484.9,22827.3],
[0,10487,19849.9,10496.6,19864.7],[0,8112.84,19862.4,10493,23357.1],
[0,10392,23347.1,10406,23356.9],[0,8113.5,23351,10393,23353],
[0,10446.1,13979.7,10460.9,13989.9],[0,8105.09,13984.1,10449.4,15972.2],
[0,10488,19804.9,10497.6,19819.7],[0,8104.62,15964.3,10494,19807.1],
[0,10470.8,11274.8,10484.2,11288.2],[0,8143,11283.3,10475.7,16216.4],
[0,10395.4,16525.5,10409.9,16535.2],[0,8142.37,16231.7,10397.1,16531.5],
[0,10387.1,18029.9,10401.8,18039.5],[0,8151.93,16223.7,10389.2,18035.9],
[0,10389.1,8140.38,10403.8,8150.01],[0,8146.32,8144.03,10391.2,16218],
[0,10480.2,19850.5,10491.4,19865.1],[0,8156.73,19861.3,10485.9,22328],
[0,10417.5,13951,10432,13960.8],[0,8140.48,13673,10419.1,13957],
[0,10489,19804.8,10498.6,19819.5],[0,8150.37,15748.2,10495,19806.9],
[0,12813.8,3792.79,12827.2,3806.18],[0,10565.9,3801.31,12818.7,8691],
[0,10413.4,16079.6,10427.9,16089.3],[0,8147.52,16083.3,10415.1,17536.8],
[0,10406.3,18025.2,10420.9,18034.9],[0,8137.64,17546.4,10408.2,18031.2],
[0,10439.7,16056,10454.5,16065.4],[0,8141.77,15490.3,10442.3,16062],
[0,10452.7,12361.7,10467.4,12372.8],[0,8136.08,12367.1,10456.5,15475.1],
[0,10484.1,19804.4,10494,19819.2],[0,8145.09,15477.7,10489.9,19807.5],
[0,10411.1,8154.38,10425.8,8164.01],[0,5540.14,8158.01,10413.1,8850.99],
[0,8019.97,9769.02,8034.82,9778.38],[0,5520.97,8874.05,8022.71,9774.95],
[0,10480.1,19850.1,10490.4,19864.9],[0,8161.32,19861.4,10485.9,22273.5],
[0,10485.1,19850.9,10495,19865.7],[0,8146.57,19862.6,10491,23487.5],
[0,10461,23502,10475,23511.8],[0,8167,23497.3,10462,23507.9],
[0,10391.5,9172.21,10406,9181.99],[0,8103.55,9176,10393,9284],
[0,10364,9260.09,10378,9269.91],[0,8103.59,9264,10365,9285],
[0,8037.8,9279.09,8051.83,9288.91],[0,5587.6,9283,8038.8,9285],
[0,10366.5,9254.01,10381,9263.79],[0,8145.36,9178,10368,9260],
[0,10389,9167.09,10403,9176.91],[0,8146,9171,10390,9177],
[0,10476.4,15607.9,10488.5,15622.1],[0,8147.14,15617.9,10481.8,17945.8],
[0,10468,19805.6,10481.9,19818.5],[0,8113.07,17976.4,10472.7,19810.7],
[0,10378.6,17035,10393,17044.8],[0,3019.62,16560.9,10380,17195.9],
[0,10390.5,14166,10405,14175.8],[0,2982.65,14053.7,10392.1,16530.5],
[0,10397.3,15572.7,10411.9,15582.4],[0,3005.98,15299.5,10399.1,16532.9],
[0,10419.1,19846.6,10433.8,19856.2],[0,2975.93,16565.9,10421.2,20211.2],
[0,5326.5,16543.1,5340.53,16552.9],[0,3046.5,16547,5327.5,16549],
[0,5360.37,16754.4,5374.77,16764.2],[0,3042.11,16553.2,5361.89,16760.4],
[0,10427,12007.1,10441,12016.9],[0,2977.35,11943.3,10428,16530.1],
[0,10387.5,15599.5,10401.9,15609.3],[0,8180.79,15603.3,10389.1,15851.4],
[0,10389.1,14184.4,10403.8,14194],[0,8200.93,14188,10391.2,15855.4],
[0,10489,19805.1,10498.6,19819.8],[0,8211.57,15863.9,10495,19807.2],
[0,10486,19804.6,10495.4,19819.5],[0,8206.6,16442,10492,19807.3],
[0,12702.9,15267.8,12717,15277.6],[0,8189.15,15271.7,12704,16431.6],
[0,10374.7,17016.4,10389,17026.2],[0,5546.77,16447.6,10376.1,17022.4],
[0,12738.4,15252,12752.9,15261.7],[0,5500.14,14926.5,12740.1,16423.4],
[0,7940.91,16537.5,7955.12,16547.3],[0,5554.56,16442,7942.14,16543.4],
[0,10420.1,19813.8,10434.8,19823.4],[0,5554.76,16436.1,10422.2,19819.8],
[0,10391.6,14058,10406,14067.8],[0,5499,13995.2,10393.1,16423],
[0,7923.16,16485.9,7937.32,16495.7],[0,5555.28,16440.5,7924.32,16491.8],
[0,10427,12008.1,10441,12017.9],[0,5502.97,11977.6,10428,16423.4],
[0,10488,19804.8,10497.6,19819.5],[0,8109.71,14758.1,10494,19806.9],
[0,10404.1,14080.4,10418.8,14090],[0,8180.76,14084,10406.2,14731],
[0,12742.3,15251.4,12756.9,15261.1],[0,8194.62,14750,12744.1,15257.4],
[0,12703.9,15341.3,12718,15351.1],[0,8203.91,15345.2,12705,17864.3],
[0,10472.7,19805.4,10485.9,19819],[0,8142.63,17882.6,10477.7,19810.2],
[0,10364.9,17021.3,10379,17031.1],[0,5546.36,16501.7,10366,17027.2],
[0,12706.8,15333.3,12721,15343.1],[0,5553.5,15259.6,12708,16491],
[0,7936.7,16540.2,7950.82,16550],[0,5555.28,16494.5,7937.82,16546.1],
[0,10414.1,19814.6,10428.8,19824.3],[0,5554.76,16490.1,10416.2,19820.6],
[0,10381,14119.1,10395,14128.9],[0,5555.25,14107.4,10382,16496.2],
[0,7921.7,16489.1,7935.73,16498.9],[0,5555.6,16493,7922.7,16495],
[0,10427,12011.1,10441,12020.9],[0,5552.19,12015,10428,16500.6],
[0,12708.8,15332.2,12723,15342],[0,8211.57,15188,12710,15338.1],
[0,10397.1,14133.4,10411.8,14143],[0,8130.73,14137,10399.1,15170.4],
[0,10485,19804.8,10494.4,19819.6],[0,8100.1,15203,10490.9,19807.5],
[0,10396.3,15572.8,10410.9,15582.5],[0,5601.64,15320.9,10398.1,16539.2],
[0,10410.2,19815.6,10424.9,19825.3],[0,5618.68,16552.3,10412.2,19821.6],
[0,12710.7,15273,12725,15282.8],[0,10526.9,15276.8,12712.1,15391.6],
[0,12703.9,15341,12718,15350.8],[0,10527,15344.9,12705,15392.4],
[0,10460.4,15391.3,10474.9,15401.1],[0,8194.55,15395.1,10462.1,16484.7],
[0,10486,19804.6,10495.4,19819.5],[0,8214.56,16497.9,10492,19807.3],
[0,10376.6,15577,10391,15586.8],[0,8103.52,15393.2,10378.1,15583],
[0,12703.9,15269.3,12718,15279.1],[0,8103.47,15273.2,12705,15392.3],
[0,8037.55,15392.8,8052.22,15402.5],[0,5605.22,15396.5,8039.58,18565.1],
[0,10380.8,19826.1,10395,19835.9],[0,5590.76,18573.7,10382,19832],
[0,10392.4,15573.7,10406.9,15583.5],[0,5594.55,15352.7,10394.1,16594.4],
[0,10404.3,19816.8,10418.9,19826.5],[0,5510.17,16618.8,10406.1,19822.8],
[0,10478.2,19805,10489.5,19819.6],[0,8097.66,16619,10483.8,19808.8],
[0,10460.4,15390.9,10474.9,15400.7],[0,8189.15,15394.7,10462.1,16594.3],
[0,10399.4,19817.9,10413.9,19827.7],[0,5495.73,16787.5,10401.1,19823.9],
[0,10378.6,15576.7,10393,15586.5],[0,5508.46,15440.8,10380.1,16753.2],
[0,10460.4,15391.1,10474.9,15400.9],[0,8188.75,15394.9,10462.1,16540],
[0,10485,19804.7,10494.4,19819.5],[0,8204.2,16549.7,10490.9,19807.4],
[0,10479.2,19850.6,10490.4,19865.3],[0,8146.82,19861.5,10484.9,22218.1],
[0,10487,19850.2,10496.4,19865.1],[0,8138.39,19862.4,10493,23411.2],
[0,10420,23401.1,10434,23410.9],[0,8140,23405,10421,23407],
[0,12770,3769.09,12784,3778.91],[0,10569,3672,12771,3775],
[0,15069,7671.09,15083,7680.91],[0,12882,7675,15070,7677],
[0,12760,2745.09,12774,2754.91],[0,10547,2698,12761,2751],
[0,10435,7426.09,10449,7435.91],[0,8134.38,5390,10436.1,7432],
[0,10429.6,3853.2,10444,3862.98],[0,8134.35,3857,10431.1,5392],
[0,10399.5,11241,10414,11250.8],[0,8148.76,10937,10401.1,11247],
[0,10365.4,16531.6,10380.3,16541],[0,8157.07,10920,10368.3,16537.5],
[0,10405.1,10628.4,10419.8,10638],[0,8150.48,10632,10407.1,10920],
[0,10377.9,18036.6,10392.7,18046.1],[0,8154.97,10919,10380.3,18042.6],
[0,10390.1,8146.38,10404.8,8156.01],[0,8141.48,8150.02,10392.2,10917],
[0,10373,11250.1,10387,11259.9],[0,8161.97,11184,10374,11256],
[0,10365.6,16531.4,10380.4,16540.8],[0,8157.34,11174,10368.3,16537.3],
[0,12742.6,10626.2,12757,10636],[0,8148.26,10630,12744.1,11173],
[0,10377.8,18036.4,10392.6,18045.9],[0,8154.87,11173,10380.3,18042.4],
[0,10389.1,8146.38,10403.8,8156.01],[0,8162.11,8150.02,10391.2,11186],
[0,7967.7,3176.09,7981.73,3185.91],[0,3054.7,3180,7968.7,3197],
[0,7967.23,3178.21,7981.66,3187.98],[0,5562.98,3182,7968.71,3219],
[0,10392.1,8148.38,10406.8,8158.01],[0,8144.35,8152.02,10394.2,10314],
[0,10364.5,16531.9,10379.4,16541.2],[0,8163.66,10339,10367.4,16537.8],
[0,5436.2,1509.09,5450.23,1518.91],[0,880.492,1490,5437.21,1515],
[0,5436,1508.09,5450.03,1517.91],[0,2999.78,1468,5437.02,1514],
[0,10479.2,19850.6,10490.4,19865.3],[0,5532.58,19861.5,10484.9,22102.5],
[0,10477.4,19851.1,10489.5,19865.3],[0,8136.63,19861.1,10482.8,22050.3],
[0,10469.8,19850.6,10483.1,19864.1],[0,5544.46,19859.2,10474.7,21300.9],
[0,10466.1,19851.1,10480.1,19863.7],[0,8130.2,19858.5,10470.6,21235.7],
[0,8003.3,17225.1,8017.33,17234.9],[0,5508.8,17229,8004.3,17231],
[0,7985.3,17277.2,7999.43,17287],[0,5508.78,17229.6,7986.42,17283.1],
[0,10386.7,16750.7,10401,16760.5],[0,5508.25,16725,10388.1,17224],
[0,5443,17225.1,5457.03,17234.9],[0,3008.9,17229,5444,17231],
[0,8003.2,17226.6,8017.32,17236.4],[0,5508.78,17230.5,8004.32,17284.4],
[0,7985.1,17279.1,7999.13,17288.9],[0,5508.8,17283,7986.1,17285],
[0,8029.2,17332.1,8043.32,17341.9],[0,5508.78,17283.6,8030.32,17338],
[0,5442.91,17278.3,5457.02,17288.1],[0,3008.88,17229.8,5444.02,17284.2],
[0,10451,18059.7,10465.8,18070.2],[0,5502.78,18064.4,10454.4,20263.3],
[0,7960.59,18833,7975.24,18842.7],[0,5502.78,18836.7,7962.57,20263.3],
[0,5380.6,20278.9,5394.82,20288.7],[0,3072.26,20282.8,5381.84,20373.2],
[0,8009.45,18841,8024.31,18850.4],[0,3074.5,18844.4,8012.21,20378.7],
[0,10452.9,18060,10467.7,18070.6],[0,3074.6,18064.9,10456.4,20379.5],
[0,10453.9,19851,10468.6,19861.7],[0,3050.46,19856,10457.5,20709.1],
[0,2872.5,1662.09,2886.53,1671.91],[0,936.855,1641,2873.52,1668],
[0,7923.2,2151.09,7937.23,2160.91],[0,5551.2,2155,7924.2,2157],
[0,12803.5,2277.01,12818,2286.79],[0,5550.16,2092.92,12805.1,2283],
[0,10439.5,19810.5,10454.4,19819.9],[0,5548.86,2160.01,10442.3,19816.4],
[0,10473.6,19851.2,10486.6,19865],[0,8173.46,19860.4,10478.8,21715],
[0,10467.1,16560.2,10481,16573],[0,8111.87,16567.8,10471.7,18350],
[0,10402.3,18052,10416.9,18061.7],[0,8156.27,18055.7,10404.1,18356.4],
[0,10458.6,19807.5,10473.2,19818.8],[0,8104.38,18382.4,10462.5,19813.1],
[0,10478.2,19850.5,10489.5,19865.1],[0,3044.75,19861.3,10483.8,21991.3],
[0,10396.9,17399.7,10411,17409.5],[0,3011.8,17383.2,10398,21706.5],
[0,7980.3,21532.8,7994.42,21542.6],[0,3046.75,21536.7,7981.44,21717.8],
[0,10395.9,17403.1,10410,17412.9],[0,8128.19,17407,10397,17430.5],
[0,7980.5,21529.4,7994.62,21539.2],[0,5632.58,21491.7,7981.62,21535.3],
[0,10472.7,19851.3,10485.8,19864.9],[0,5630.47,19860.2,10477.7,21517.5],
[0,12708.1,18000.1,12722.8,18009.7],[0,5540.21,18003.7,12710.2,21474.3],
[0,12658,17985.1,12672,17994.9],[0,10654,17989,12659,17991],
[0,7988.02,21540,8002.46,21549.8],[0,5557.6,21543.8,7989.6,21791.3],
[0,10476.4,19850.7,10488.6,19865],[0,5565.4,19860.7,10481.8,21799.1],
[0,15096,18005.1,15105.6,18019.9],[0,5564.8,18017.7,15102,23457.9],
[0,15036.8,17967.5,15051.6,17977],[0,12895.8,17419.9,15039.2,17973.5],
[0,10370,11253.1,10384,11262.9],[0,8162.99,11236,10371,11259]],
[0,[2,12842,17990,173.002,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,12842,17993.7,"nvidia-kernel-legacy-173xx-dkms","14px serif",
[0,"#000000"],0],
[2,15107,17990,104,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,17993.7,"nvidia-kernel-dkms","14px serif",[0,"#000000"],0],
[2,8076.4,17430,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,17433.7,"fglrx-glx","14px serif",[0,"#000000"],0],
[2,10499,17990,154.001,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,10499,17993.7,"nvidia-glx-legacy-173xx (x 2)","14px serif",
[0,"#000000"],0],
[2,2972.4,21721,75.9996,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,2972.4,21724.7,"fglrx-glx-ia32","14px serif",[0,"#000000"],0],
[2,5481.4,21798,83.9988,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,5481.4,21801.7,"nvidia-glx-ia32","14px serif",[0,"#000000"],0],
[2,10499,17407,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,17410.7,"fglrx-driver (x 2)","14px serif",[0,"#000000"],0],
[2,12842,17407,84.9996,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,12842,17410.7,"nvidia-glx (x 2)","14px serif",[0,"#000000"],0],
[2,831.43,1641,105.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,1644.7,"zephyr-server-krb5","14px serif",[0,"#000000"],0],
[2,2972.4,1614,79.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,1617.7,"zephyr-server","14px serif",[0,"#000000"],0],
[2,2972.4,1668,88.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,1671.7,"libzephyr4-krb5","14px serif",[0,"#000000"],0],
[2,5481.4,1668,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1671.7,"libzephyr4","14px serif",[0,"#000000"],0],
[2,5481.4,21249,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21252.7,"xmpuzzles","14px serif",[0,"#000000"],0],
[2,8076.4,21238,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21241.7,"xpuzzles","14px serif",[0,"#000000"],0],
[2,8076.4,9700,109.001,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,9703.7,"libxerces-c-dev (x 2)","14px serif",[0,"#000000"],0],
[2,10499,10112,115.999,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,10115.7,"libxerces-c2-dev (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,22069,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,22072.7,"xabacus","14px serif",[0,"#000000"],0],
[2,8076.4,22050,60.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22053.7,"xmabacus","14px serif",[0,"#000000"],0],
[2,10499,23406,68.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23409.7,"wx2.6-i18n","14px serif",[0,"#000000"],0],
[2,12842,23406,68.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,23409.7,"wx2.8-i18n","14px serif",[0,"#000000"],0],
[2,831.43,1491,48.9996,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,831.43,1494.7,"wl-beta","14px serif",[0,"#000000"],0],
[2,2972.4,1468,27,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,2972.4,1471.7,"wl","14px serif",[0,"#000000"],0],
[2,2972.4,3196,82.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,3199.7,"wims-extra-all","14px serif",[0,"#000000"],0],
[2,5481.4,3219,81,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,3222.7,"wims-extra-es","14px serif",[0,"#000000"],0],
[2,10499,23352,96.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23355.7,"w3m-el-snapshot","14px serif",[0,"#000000"],0],
[2,12842,23352,47.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,23355.7,"w3m-el","14px serif",[0,"#000000"],0],
[2,10499,10621,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,10624.7,"libvtk5.4-qt3 (x 3)","14px serif",[0,"#000000"],0],
[2,12842,10621,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,10624.7,"libvtk5.4-qt4 (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,22218,69.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22221.7,"tasks-hildon","14px serif",[0,"#000000"],0],
[2,10499,22218,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,22221.7,"tasks (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,2730,48.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,2733.7,"sysvinit","14px serif",[0,"#000000"],0],
[2,10499,2698,47.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,2701.7,"upstart","14px serif",[0,"#000000"],0],
[2,5481.4,16770,128.999,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,5481.4,16773.7,"sugar-read-activity-0.84","14px serif",[0,"#000000"],0],
[2,8076.4,16548,128.999,18.5,[0,"#ffd4d4"],[0,"#000000"]],
[3,8076.4,16551.7,"sugar-read-activity-0.86","14px serif",[0,"#000000"],0],
[2,5481.4,16602,128.002,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,5481.4,16605.7,"sugar-chat-activity-0.84","14px serif",[0,"#000000"],0],
[2,8076.4,16602,128.002,18.5,[0,"#ffd4d4"],[0,"#000000"]],
[3,8076.4,16605.7,"sugar-chat-activity-0.86","14px serif",[0,"#000000"],0],
[2,5481.4,16548,142.999,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,5481.4,16551.7,"sugar-browse-activity-0.84","14px serif",[0,"#000000"],
0],
[2,8076.4,16494,142.999,18.5,[0,"#ffd4d4"],[0,"#000000"]],
[3,8076.4,16497.7,"sugar-browse-activity-0.86","14px serif",[0,"#000000"],
0],
[1,[0,[0,15080,15325],[0,15134,15325],[0,15134,15361],[0,15080,15361]],0,
[0,"#ff0000"]],
[3,15107,15346.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,15592,128.002,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,10499,15595.7,"python-sugar-0.84 (x 2)","14px serif",[0,"#000000"],0],
[2,12842,15271,128.002,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,12842,15274.7,"python-sugar-0.86 (x 2)","14px serif",[0,"#000000"],0],
[2,12842,15343,128.002,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,12842,15346.7,"python-sugar-0.88 (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,14108],[0,12869,14108],[0,12869,14144],[0,12815,14144]],0,
[0,"#ff0000"]],
[3,12842,14129.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,14180,106.999,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,10499,14183.7,"sugar-artwork-0.84","14px serif",[0,"#000000"],0],
[2,10499,14072,106.999,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,10499,14075.7,"sugar-artwork-0.86","14px serif",[0,"#000000"],0],
[2,10499,14126,106.999,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,10499,14129.7,"sugar-artwork-0.88","14px serif",[0,"#000000"],0],
[2,8076.4,22272,84.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22275.7,"stardict-gnome","14px serif",[0,"#000000"],0],
[2,10499,22272,68.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,22275.7,"stardict-gtk","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,13648],[0,10526,13648],[0,10526,13684],[0,10472,13684]],0,
[0,"#ff0000"]],
[3,10499,13669.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,13666,70.9992,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,13669.7,"snd-gtk-jack","14px serif",[0,"#000000"],0],
[2,8076.4,12762,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,12765.7,"snd-gtk-pulse","14px serif",[0,"#000000"],0],
[2,8076.4,15754,75.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,15757.7,"snd-nox (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,22326,79.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22329.7,"libsnack2-alsa","14px serif",[0,"#000000"],0],
[2,10499,22326,82.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,22329.7,"libsnack2 (x 3)","14px serif",[0,"#000000"],0],
[2,5481.4,15970,41.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,15973.7,"sim-qt","14px serif",[0,"#000000"],0],
[2,8076.4,15970,28.0001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,15973.7,"sim","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,10837],[0,12869,10837],[0,12869,10873],[0,12815,10873]],0,
[0,"#ff0000"]],
[3,12842,10858.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,11167,84.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,11170.7,"shorewall (x 6)","14px serif",[0,"#000000"],0],
[2,10499,10713,83.9988,18.5,[0,"#ffd7d7"],[0,"#000000"]],
[3,10499,10716.7,"shorewall6-lite","14px serif",[0,"#000000"],0],
[2,10499,10913,27,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,10499,10916.7,"uif","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,10891],[0,12869,10891],[0,12869,10927],[0,12815,10927]],0,
[0,"#ff0000"]],
[3,12842,10912.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,10767,78.0012,18.5,[0,"#ffd7d7"],[0,"#000000"]],
[3,10499,10770.7,"shorewall-lite","14px serif",[0,"#000000"],0],
[2,5481.4,1514,33.9998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1517.7,"semi","14px serif",[0,"#000000"],0],
[2,8076.4,1514,51.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,1517.7,"vm (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,11234,117,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,11237.7,"libscotchparmetis-dev","14px serif",[0,"#000000"],0],
[2,8076.4,11236,86.0004,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,11239.7,"libparmetis-dev","14px serif",[0,"#000000"],0],
[2,5481.4,11288,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,11291.7,"libscotchmetis-dev","14px serif",[0,"#000000"],0],
[2,2972.4,21590,56.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,21593.7,"rxvt-beta","14px serif",[0,"#000000"],0],
[2,5481.4,20938,32,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,20941.7,"rxvt","14px serif",[0,"#000000"],0],
[2,5481.4,21690,47.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21693.7,"rxvt-ml","14px serif",[0,"#000000"],0],
[2,10499,23580,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23583.7,"ruby1.8-elisp (x 2)","14px serif",[0,"#000000"],0],
[2,12842,23822,84.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,23825.7,"ruby1.9.1-elisp","14px serif",[0,"#000000"],0],
[2,2972.4,15417,115.999,18.5,[0,"#ffb0b0"],[0,"#000000"]],
[3,2972.4,15420.7,"libreadline5-dev (x 2)","14px serif",[0,"#000000"],0],
[2,10499,15067,122,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,15070.7,"libreadline6-dev (x 20)","14px serif",[0,"#000000"],0],
[2,10499,12481,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,12484.7,"quassel-data-kde4","14px serif",[0,"#000000"],0],
[2,12842,12321,73.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,12324.7,"quassel-data","14px serif",[0,"#000000"],0],
[2,2972.4,20268,47.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,20271.7,"quagga","14px serif",[0,"#000000"],0],
[2,5481.4,20280,91.0008,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,5481.4,20283.7,"libzbar-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,12292,130,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,12295.7,"qt3-dev-tools-embedded","14px serif",[0,"#000000"],0],
[2,10499,12346,101.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,12349.7,"qt4-dev-tools (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,12038,87.9984,18.5,[0,"#ffbcbc"],[0,"#000000"]],
[3,8076.4,12041.7,"qt-x11-free-dbg","14px serif",[0,"#000000"],0],
[2,10499,12223,86.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,12226.7,"libqt4-dbg (x 4)","14px serif",[0,"#000000"],0],
[2,5481.4,21852,48.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21855.7,"qca-dev","14px serif",[0,"#000000"],0],
[2,8076.4,21812,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21815.7,"libqca2-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,14218,128.999,18.5,[0,"#ffc6c6"],[0,"#000000"]],
[3,8076.4,14221.7,"python-pysqlite1.1 (x 2)","14px serif",[0,"#000000"],0],
[2,10499,14234,108,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,14237.7,"python-sqlite (x 15)","14px serif",[0,"#000000"],0],
[2,10499,23028,109.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23031.7,"python-pyorbit-omg","14px serif",[0,"#000000"],0],
[2,12842,23028,114.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,23031.7,"python-omniorb-omg","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,16418],[0,10526,16418],[0,10526,16454],[0,10472,16454]],0,
[0,"#ff0000"]],
[3,10499,16439.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,18182,105.001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,18185.7,"libpt2.4.5-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,17630,54,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,17633.7,"libpt-dev","14px serif",[0,"#000000"],0],
[2,8076.4,18090,122,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,18093.7,"libpt-1.10.10-dev (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,21344,90,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21347.7,"libportaudio-dev","14px serif",[0,"#000000"],0],
[2,8076.4,21368,118.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21371.7,"portaudio19-dev (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,17034,146.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,17037.7,"network-manager-kde (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,17138,191.999,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,17141.7,"plasma-widget-networkmanagement","14px serif",
[0,"#000000"],0],
[2,8076.4,2156,141.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,2159.7,"libapache2-mod-php5 (x 3)","14px serif",[0,"#000000"],0],
[2,10499,2194,139,18.5,[0,"#ffa8a8"],[0,"#000000"]],
[3,10499,2197.7,"libapache2-mod-php5filter","14px serif",[0,"#000000"],0],
[2,5481.4,12946,114.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,12949.7,"phonon-backend-null","14px serif",[0,"#000000"],0],
[2,8076.4,13866,115.999,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,13869.7,"phonon-backend-xine","14px serif",[0,"#000000"],0],
[2,2972.4,12946,171,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,12949.7,"phonon-backend-gstreamer (x 2)","14px serif",
[0,"#000000"],0],
[2,10499,12957,97.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,12960.7,"libphonon4 (x 45)","14px serif",[0,"#000000"],0],
[2,12842,12957,79.9992,18.5,[0,"#ff5050"],[0,"#000000"]],
[3,12842,12960.7,"libqt4-phonon","14px serif",[0,"#000000"],0],
[2,12842,2623,43.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,2626.7,"pgpool","14px serif",[0,"#000000"],0],
[2,15107,2623,50.0004,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,15107,2626.7,"pgpool2","14px serif",[0,"#000000"],0],
[2,12842,2806,70.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,2809.7,"libpcp3 (x 6)","14px serif",[0,"#000000"],0],
[2,5481.4,17630,64.0008,18.5,[0,"#ff9a9a"],[0,"#000000"]],
[3,5481.4,17633.7,"libopal-dev","14px serif",[0,"#000000"],0],
[2,10499,11259,118.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,11262.7,"libopenmpi-dev (x 20)","14px serif",[0,"#000000"],0],
[2,5481.4,23995,121,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,23998.7,"obex-data-server (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,24130,74.9988,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,24133.7,"obexd-server","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,24474],[0,10526,24474],[0,10526,24510],[0,10472,24510]],0,
[0,"#ff0000"]],
[3,10499,24495.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,24492,132.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,24495.7,"notification-daemon-xfce","14px serif",[0,"#000000"],0],
[2,8076.4,24546,60.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,24549.7,"notify-osd","14px serif",[0,"#000000"],0],
[2,8076.4,24438,74.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,24441.7,"xfce4-notifyd","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,24420],[0,10526,24420],[0,10526,24456],[0,10472,24456]],0,
[0,"#ff0000"]],
[3,10499,24441.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,23914,109.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23917.7,"notification-daemon","14px serif",[0,"#000000"],0],
[2,10499,7708,95.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,7711.7,"nfs-kernel-server","14px serif",[0,"#000000"],0],
[2,12842,7676,38.9988,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,12842,7679.7,"unfs3","14px serif",[0,"#000000"],0],
[2,8076.4,2676,114.001,18.5,[0,"#ffc8c8"],[0,"#000000"]],
[3,8076.4,2679.7,"netscript-2.4-upstart","14px serif",[0,"#000000"],0],
[2,10499,17030,126,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,17033.7,"network-manager (x 4)","14px serif",[0,"#000000"],0],
[2,831.43,1360,52.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,1363.7,"netpipes","14px serif",[0,"#000000"],0],
[2,2972.4,1360,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,1363.7,"timelimit","14px serif",[0,"#000000"],0],
[2,8076.4,6778,56.0016,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,6781.7,"telnet-ssl","14px serif",[0,"#000000"],0],
[2,10499,6762,66.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,6765.7,"telnet (x 5)","14px serif",[0,"#000000"],0],
[2,5481.4,7897,81,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,7900.7,"libneon27-dev","14px serif",[0,"#000000"],0],
[2,8076.4,7916,114.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,7919.7,"libneon27-gnutls-dev","14px serif",[0,"#000000"],0],
[2,8076.4,14272,57.9996,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,14275.7,"mpd (x 3)","14px serif",[0,"#000000"],0],
[2,10499,14288,73.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,14291.7,"mpich2 (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,22380,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22383.7,"moon-buggy-esd","14px serif",[0,"#000000"],0],
[2,10499,22380,72,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,22383.7,"moon-buggy","14px serif",[0,"#000000"],0],
[2,5481.4,20884,84.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,20887.7,"minbif-webcam","14px serif",[0,"#000000"],0],
[2,8076.4,20924,66.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,20927.7,"minbif (x 2)","14px serif",[0,"#000000"],0],
[2,10499,23248,79.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23251.7,"mew-beta-bin","14px serif",[0,"#000000"],0],
[2,12842,23273,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,23276.7,"mew-bin","14px serif",[0,"#000000"],0],
[2,10499,16976,128.002,18.5,[0,"#ffc8c8"],[0,"#000000"]],
[3,10499,16979.7,"libgl1-mesa-swx11 (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,16976,117,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,16979.7,"libgl1-mesa-glx (x 10)","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,8182],[0,10526,8182],[0,10526,8218],[0,10472,8218]],0,
[0,"#ff0000"]],
[3,10499,8203.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,8960,115.999,18.5,[0,"#ffcaca"],[0,"#000000"]],
[3,8076.4,8963.7,"libmeep-openmpi-dev","14px serif",[0,"#000000"],0],
[2,8076.4,8528,69.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,8531.7,"libmeep-dev","14px serif",[0,"#000000"],0],
[2,8076.4,8582,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,8585.7,"libmeep-mpi-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,8236],[0,10526,8236],[0,10526,8272],[0,10472,8272]],0,
[0,"#ff0000"]],
[3,10499,8257.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,9338,103,18.5,[0,"#ffadad"],[0,"#000000"]],
[3,8076.4,9341.7,"libmeep-mpich-dev","14px serif",[0,"#000000"],0],
[2,10499,23190,154.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23193.7,"maemo-af-desktop-l10n-engb","14px serif",[0,"#000000"],0],
[2,12842,23190,164.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,23193.7,"maemo-af-desktop-l10n-english","14px serif",
[0,"#000000"],0],
[2,8076.4,13466,109.001,18.5,[0,"#ff8888"],[0,"#000000"]],
[3,8076.4,13469.7,"libtextcat-data (x 5)","14px serif",[0,"#000000"],0],
[2,10499,13539,157,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,13542.7,"openoffice.org-common (x 97)","14px serif",[0,"#000000"],
0],
[2,5481.4,13466,106.999,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,5481.4,13469.7,"libtextcat-data-utf8","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,24582],[0,10526,24582],[0,10526,24618],[0,10472,24618]],0,
[0,"#ff0000"]],
[3,10499,24603.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,24076,99,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,24079.7,"libsdl1.2debian-all","14px serif",[0,"#000000"],0],
[2,8076.4,23968,106.999,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,23971.7,"libsdl1.2debian-alsa","14px serif",[0,"#000000"],0],
[2,8076.4,24762,106.999,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,24765.7,"libsdl1.2debian-arts","14px serif",[0,"#000000"],0],
[2,8076.4,24022,104,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,24025.7,"libsdl1.2debian-esd","14px serif",[0,"#000000"],0],
[2,8076.4,24708,105.001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,24711.7,"libsdl1.2debian-nas","14px serif",[0,"#000000"],0],
[2,8076.4,24600,103,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,24603.7,"libsdl1.2debian-oss","14px serif",[0,"#000000"],0],
[2,8076.4,24654,140,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,24657.7,"libsdl1.2debian-pulseaudio","14px serif",[0,"#000000"],
0],
[2,5481.4,18782,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,18785.7,"libqwt-dev","14px serif",[0,"#000000"],0],
[2,8076.4,18664,90,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,18667.7,"libqwt5-qt3-dev","14px serif",[0,"#000000"],0],
[2,5481.4,8303,66.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,8306.7,"libpqxx-dev","14px serif",[0,"#000000"],0],
[2,8076.4,8284,73.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,8287.7,"libpqxx3-dev","14px serif",[0,"#000000"],0],
[2,8076.4,10836,52.9992,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,10839.7,"libnl-dev","14px serif",[0,"#000000"],0],
[2,10499,11113,84.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,11116.7,"libnl2-dev (x 4)","14px serif",[0,"#000000"],0],
[2,10499,18044,109.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,18047.7,"libjpeg62-dev (x 44)","14px serif",[0,"#000000"],0],
[2,12842,18044,69.9984,18.5,[0,"#ff7a7a"],[0,"#000000"]],
[3,12842,18047.7,"libjpeg8-dev","14px serif",[0,"#000000"],0],
[2,8076.4,9792,74.9988,18.5,[0,"#ffd1d1"],[0,"#000000"]],
[3,8076.4,9795.7,"libiodbc2-dev","14px serif",[0,"#000000"],0],
[2,10499,10166,101.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,10169.7,"unixodbc-dev (x 6)","14px serif",[0,"#000000"],0],
[2,5481.4,18182,82.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,18185.7,"libhdf4-alt-dev","14px serif",[0,"#000000"],0],
[2,8076.4,18236,92.0016,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,18239.7,"libhdf4-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,24384,110.002,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,8076.4,24387.7,"libgpod4-nogtk (x 2)","14px serif",[0,"#000000"],0],
[2,10499,24149,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,24152.7,"libgpod4 (x 8)","14px serif",[0,"#000000"],0],
[2,10499,21870,118.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,21873.7,"libgdchart-gd2-noxpm","14px serif",[0,"#000000"],0],
[2,12842,21894,105.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,21897.7,"libgdchart-gd2-xpm","14px serif",[0,"#000000"],0],
[2,5481.4,3311,78.0012,18.5,[0,"#ff7a7a"],[0,"#000000"]],
[3,5481.4,3314.7,"libgd2-noxpm","14px serif",[0,"#000000"],0],
[2,8076.4,3181,96.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,3184.7,"libgd2-xpm (x 97)","14px serif",[0,"#000000"],0],
[2,2972.4,3097,114.998,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,2972.4,3100.7,"libgd-gd2-noxpm-perl","14px serif",[0,"#000000"],0],
[2,5481.4,3089,104,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,3092.7,"libgd-gd2-perl (x 9)","14px serif",[0,"#000000"],0],
[2,8076.4,6232,110.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,6235.7,"libalog0.3-base (x 3)","14px serif",[0,"#000000"],0],
[2,10499,6438,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,6441.7,"libalog0.3-full","14px serif",[0,"#000000"],0],
[2,8076.4,24276,115.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,24279.7,"lxde-settings-daemon","14px serif",[0,"#000000"],0],
[2,10499,23865,81,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23868.7,"lxsession (x 2)","14px serif",[0,"#000000"],0],
[2,2972.4,1252,91.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,1255.7,"liblua50-socket2","14px serif",[0,"#000000"],0],
[2,5481.4,1252,56.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1255.7,"luasocket","14px serif",[0,"#000000"],0],
[2,831.43,1279,105.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,1282.7,"liblua50-socket-dev","14px serif",[0,"#000000"],0],
[2,2972.4,1306,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,1309.7,"luasocket-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,7420],[0,12869,7420],[0,12869,7456],[0,12815,7456]],0,
[0,"#ff0000"]],
[3,12842,7441.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,7378,27,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,7381.7,"lsb","14px serif",[0,"#000000"],0],
[2,10499,7178,60.0012,18.5,[0,"#ffa0a0"],[0,"#000000"]],
[3,10499,7181.7,"nullmailer","14px serif",[0,"#000000"],0],
[2,10499,4794,37.0008,18.5,[0,"#ff9393"],[0,"#000000"]],
[3,10499,4797.7,"xmail","14px serif",[0,"#000000"],0],
[2,10499,13278,27,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,13281.7,"lpr","14px serif",[0,"#000000"],0],
[2,12842,13382,63,18.5,[0,"#ffcaca"],[0,"#000000"]],
[3,12842,13385.7,"lprng (x 2)","14px serif",[0,"#000000"],0],
[2,15107,16155,92.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,16158.7,"lesstif2-dev (x 3)","14px serif",[0,"#000000"],0],
[2,16710,16209,68.0004,18.5,[0,"#ffd7d7"],[0,"#000000"]],
[3,16710,16212.7,"libmotif-dev","14px serif",[0,"#000000"],0],
[2,15107,16209,59.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,16212.7,"lesstif-doc","14px serif",[0,"#000000"],0],
[2,15107,16263,57.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,16266.7,"lesstif-bin","14px serif",[0,"#000000"],0],
[2,16710,16263,70.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,16710,16266.7,"motif-clients","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,9665],[0,12869,9665],[0,12869,9701],[0,12815,9701]],0,
[0,"#ff0000"]],
[3,12842,9686.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,9842,56.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,9845.7,"lam4-dev","14px serif",[0,"#000000"],0],
[2,10499,9696,48.9996,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,9699.7,"mpi-doc","14px serif",[0,"#000000"],0],
[2,10499,9588,66.9996,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,9591.7,"mpich2-doc","14px serif",[0,"#000000"],0],
[2,10499,9642,73.0008,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,9645.7,"openmpi-doc","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,9584],[0,12869,9584],[0,12869,9620],[0,12815,9620]],0,
[0,"#ff0000"]],
[3,12842,9605.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,9534,66.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,9537.7,"lam-mpidoc","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,10695],[0,12869,10695],[0,12869,10731],[0,12815,10731]],0,
[0,"#ff0000"]],
[3,12842,10716.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,10690,56.0016,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,8076.4,10693.7,"knetfilter","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,10749],[0,12869,10749],[0,12869,10785],[0,12815,10785]],0,
[0,"#ff0000"]],
[3,12842,10770.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,12400,32,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,12403.7,"klog","14px serif",[0,"#000000"],0],
[2,10499,9950,105.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,9953.7,"openafs-client (x 5)","14px serif",[0,"#000000"],0],
[2,5481.4,14910,51.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,14913.7,"kdiff3-qt","14px serif",[0,"#000000"],0],
[2,8076.4,14910,38.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,14913.7,"kdiff3","14px serif",[0,"#000000"],0],
[2,8076.4,12616,101.999,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,12619.7,"kdesdk-kio-plugins","14px serif",[0,"#000000"],0],
[2,10499,12643,101.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,12646.7,"kdesvn-kio-plugins","14px serif",[0,"#000000"],0],
[2,5481.4,16024,140,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,16027.7,"kdegraphics-libs-data (x 5)","14px serif",[0,"#000000"],
0],
[2,8076.4,16024,72,18.5,[0,"#ffbdbd"],[0,"#000000"]],
[3,8076.4,16027.7,"libkipi0 (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,18458,105.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,18461.7,"kdelibs5-dev (x 17)","14px serif",[0,"#000000"],0],
[2,8076.4,17484,99,18.5,[0,"#ffb9b9"],[0,"#000000"]],
[3,8076.4,17487.7,"kdelibs4-dev (x 2)","14px serif",[0,"#000000"],0],
[2,10499,13966,79.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,13969.7,"libjack0 (x 16)","14px serif",[0,"#000000"],0],
[2,12842,15194,113,18.5,[0,"#ff5f5f"],[0,"#000000"]],
[3,12842,15197.7,"libjack-jackd2-0 (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,9300],[0,12869,9300],[0,12869,9336],[0,12815,9336]],0,
[0,"#ff0000"]],
[3,12842,9321.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,9372,43.9992,18.5,[0,"#ffd7d7"],[0,"#000000"]],
[3,10499,9375.7,"racoon","14px serif",[0,"#000000"],0],
[2,10499,9318,87.0012,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,10499,9321.7,"openswan (x 3)","14px serif",[0,"#000000"],0],
[2,10499,9264,123.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,9267.7,"strongswan-ikev2 (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,9246],[0,12869,9246],[0,12869,9282],[0,12815,9282]],0,
[0,"#ff0000"]],
[3,12842,9267.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,9172,99,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,9175.7,"strongswan-ikev1","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,9354],[0,12869,9354],[0,12869,9390],[0,12815,9390]],0,
[0,"#ff0000"]],
[3,12842,9375.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,9426,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,9429.7,"isakmpd","14px serif",[0,"#000000"],0],
[2,10499,7432,52.9992,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,7435.7,"inn (x 2)","14px serif",[0,"#000000"],0],
[2,12842,7584,65.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,7587.7,"inn2-inews","14px serif",[0,"#000000"],0],
[2,12842,7222,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,7225.7,"inn2-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,4009],[0,12869,4009],[0,12869,4045],[0,12815,4045]],0,
[0,"#ff0000"]],
[3,12842,4030.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,4054,90,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,4057.7,"inetutils-telnetd","14px serif",[0,"#000000"],0],
[2,8076.4,3958,73.0008,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,3961.7,"krb5-telnetd","14px serif",[0,"#000000"],0],
[2,10499,4000,63,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,4003.7,"telnetd-ssl","14px serif",[0,"#000000"],0],
[2,10499,4108,46.0008,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,10499,4111.7,"telnetd","14px serif",[0,"#000000"],0],
[2,8076.4,10782,74.9988,18.5,[0,"#ffb7b7"],[0,"#000000"]],
[3,8076.4,10785.7,"inetutils-ping","14px serif",[0,"#000000"],0],
[2,10499,11059,96.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,11062.7,"iputils-ping (x 24)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,16418],[0,12869,16418],[0,12869,16454],[0,12815,16454]],0,
[0,"#ff0000"]],
[3,12842,16439.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,16382,79.9992,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,16385.7,"inetutils-inetd","14px serif",[0,"#000000"],0],
[2,10499,16762,106.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,16765.7,"openbsd-inetd (x 2)","14px serif",[0,"#000000"],0],
[2,10499,16490,43.9992,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,16493.7,"rlinetd","14px serif",[0,"#000000"],0],
[2,10499,16328,68.0004,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,16331.7,"xinetd (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,9408],[0,12869,9408],[0,12869,9444],[0,12815,9444]],0,
[0,"#ff0000"]],
[3,12842,9429.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,9480,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,9483.7,"ike (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,1126],[0,8103.4,1126],[0,8103.4,1162],[0,8049.4,1162]],0,
[0,"#ff0000"]],
[3,8076.4,1147.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,1090,82.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1093.7,"hunspell-de-ch","14px serif",[0,"#000000"],0],
[2,5481.4,1144,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1147.7,"myspell-de-ch","14px serif",[0,"#000000"],0],
[2,5481.4,1198,110.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1201.7,"hunspell-de-ch-frami","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,748],[0,8103.4,748],[0,8103.4,784],[0,8049.4,784]],0,
[0,"#ff0000"]],
[3,8076.4,769.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,820,82.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,823.7,"hunspell-de-at","14px serif",[0,"#000000"],0],
[2,5481.4,712,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,715.7,"myspell-de-at","14px serif",[0,"#000000"],0],
[2,5481.4,766,110.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,769.7,"hunspell-de-at-frami","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,2268],[0,10526,2268],[0,10526,2304],[0,10472,2304]],0,
[0,"#ff0000"]],
[3,10499,2289.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,2302,82.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,2305.7,"ifupdown (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,2248,74.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,2251.7,"netscript-2.4","14px serif",[0,"#000000"],0],
[2,10499,15484,103,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,15487.7,"hylafax-client (x 2)","14px serif",[0,"#000000"],0],
[2,12842,15419,65.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,15422.7,"mgetty-fax","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,937],[0,8103.4,937],[0,8103.4,973],[0,8049.4,973]],0,
[0,"#ff0000"]],
[3,8076.4,958.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,874,119.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,877.7,"myspell-de-de-oldspell","14px serif",[0,"#000000"],0],
[2,5481.4,1036,83.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1039.7,"hunspell-de-de","14px serif",[0,"#000000"],0],
[2,5481.4,928,78.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,931.7,"myspell-de-de","14px serif",[0,"#000000"],0],
[2,5481.4,982,110.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,985.7,"hunspell-de-de-frami","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,4077],[0,12869,4077],[0,12869,4113],[0,12815,4113]],0,
[0,"#ff0000"]],
[3,12842,4098.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,4308,114.998,18.5,[0,"#ff9696"],[0,"#000000"]],
[3,10499,4311.7,"heimdal-servers (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,3328],[0,12869,3328],[0,12869,3364],[0,12815,3364]],0,
[0,"#ff0000"]],
[3,12842,3349.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,2968,74.0016,18.5,[0,"#ffaaaa"],[0,"#000000"]],
[3,10499,2971.7,"inetutils-ftpd","14px serif",[0,"#000000"],0],
[2,10499,3022,56.0016,18.5,[0,"#ffaaaa"],[0,"#000000"]],
[3,10499,3025.7,"krb5-ftpd","14px serif",[0,"#000000"],0],
[2,10499,3238,46.0008,18.5,[0,"#ffaaaa"],[0,"#000000"]],
[3,10499,3241.7,"ftpd-ssl","14px serif",[0,"#000000"],0],
[2,10499,3454,31,18.5,[0,"#ffa8a8"],[0,"#000000"]],
[3,10499,3457.7,"ftpd","14px serif",[0,"#000000"],0],
[2,10499,3562,65.9988,18.5,[0,"#ffa8a8"],[0,"#000000"]],
[3,10499,3565.7,"muddleftpd","14px serif",[0,"#000000"],0],
[2,10499,3184,106.999,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,10499,3187.7,"proftpd-basic (x 10)","14px serif",[0,"#000000"],0],
[2,10499,3346,79.9992,18.5,[0,"#ffabab"],[0,"#000000"]],
[3,10499,3349.7,"pure-ftpd-ldap","14px serif",[0,"#000000"],0],
[2,10499,2860,87.9984,18.5,[0,"#ffb2b2"],[0,"#000000"]],
[3,10499,2863.7,"pure-ftpd-mysql","14px serif",[0,"#000000"],0],
[2,10499,3292,110.002,18.5,[0,"#ffabab"],[0,"#000000"]],
[3,10499,3295.7,"pure-ftpd-postgresql","14px serif",[0,"#000000"],0],
[2,10499,3400,56.0016,18.5,[0,"#ffabab"],[0,"#000000"]],
[3,10499,3403.7,"pure-ftpd","14px serif",[0,"#000000"],0],
[2,10499,3670,69.9984,18.5,[0,"#ffa9a9"],[0,"#000000"]],
[3,10499,3673.7,"twoftpd-run","14px serif",[0,"#000000"],0],
[2,10499,3508,41.0004,18.5,[0,"#ffa8a8"],[0,"#000000"]],
[3,10499,3511.7,"vsftpd","14px serif",[0,"#000000"],0],
[2,10499,3616,50.0004,18.5,[0,"#ffa8a8"],[0,"#000000"]],
[3,10499,3619.7,"wu-ftpd","14px serif",[0,"#000000"],0],
[2,10499,3130,78.0012,18.5,[0,"#ffb0b0"],[0,"#000000"]],
[3,10499,3133.7,"wzdftpd (x 7)","14px serif",[0,"#000000"],0],
[2,8076.4,7970,70.9992,18.5,[0,"#ff8d8d"],[0,"#000000"]],
[3,8076.4,7973.7,"heimdal-dev","14px serif",[0,"#000000"],0],
[2,10499,8146,99,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,8149.7,"libkrb5-dev (x 24)","14px serif",[0,"#000000"],0],
[2,8076.4,8636,110.999,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,8639.7,"heimdal-clients (x 3)","14px serif",[0,"#000000"],0],
[2,10499,8308,27,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,8311.7,"otp","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,8452],[0,10526,8452],[0,10526,8488],[0,10472,8488]],0,
[0,"#ff0000"]],
[3,10499,8473.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,8744,84.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,8747.7,"krb5-user (x 4)","14px serif",[0,"#000000"],0],
[2,8076.4,9392,95.0004,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,9395.7,"openafs-kpasswd","14px serif",[0,"#000000"],0],
[2,10499,8362,69.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,8365.7,"krb5-clients","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,9932],[0,12869,9932],[0,12869,9968],[0,12815,9968]],0,
[0,"#ff0000"]],
[3,12842,9953.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,10004,95.0004,18.5,[0,"#ffacac"],[0,"#000000"]],
[3,10499,10007.7,"libhdf5-lam-1.8.4","14px serif",[0,"#000000"],0],
[2,10499,9896,132.001,18.5,[0,"#ffafaf"],[0,"#000000"]],
[3,10499,9899.7,"libhdf5-mpich-1.8.4 (x 3)","14px serif",[0,"#000000"],0],
[2,10499,9788,150.998,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,10499,9791.7,"libhdf5-openmpi-1.8.4 (x 21)","14px serif",[0,"#000000"],
0],
[2,10499,10058,103,18.5,[0,"#ffb2b2"],[0,"#000000"]],
[3,10499,10061.7,"libhdf5-serial-1.8.4","14px serif",[0,"#000000"],0],
[2,8076.4,7310,110.999,18.5,[0,"#ffa0a0"],[0,"#000000"]],
[3,8076.4,7313.7,"harden-servers (x 2)","14px serif",[0,"#000000"],0],
[2,10499,5724,60.0012,18.5,[0,"#ffbdbd"],[0,"#000000"]],
[3,10499,5727.7,"uw-imapd","14px serif",[0,"#000000"],0],
[2,10499,7124,99,18.5,[0,"#ffa1a1"],[0,"#000000"]],
[3,10499,7127.7,"sendmail-bin (x 3)","14px serif",[0,"#000000"],0],
[2,10499,7524,42.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,7527.7,"pyftpd","14px serif",[0,"#000000"],0],
[1,[0,[0,17509,7658],[0,17563,7658],[0,17563,7694],[0,17509,7694]],0,
[0,"#ff0000"]],
[3,17536,7679.6,"#","14px serif",[0,"#ff0000"],0],
[2,16710,7676,51.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,16710,7679.7,"portmap","14px serif",[0,"#000000"],0],
[2,16710,7622,47.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,16710,7625.7,"rpcbind","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,4244],[0,12869,4244],[0,12869,4280],[0,12815,4280]],0,
[0,"#ff0000"]],
[3,12842,4265.6,"#","14px serif",[0,"#ff0000"],0],
[2,12842,7876,41.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,7879.7,"rwalld","14px serif",[0,"#000000"],0],
[2,12842,7822,47.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,7825.7,"rusersd","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,7512],[0,12869,7512],[0,12869,7548],[0,12815,7548]],0,
[0,"#ff0000"]],
[3,12842,7533.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,7616,60.9984,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,7619.7,"rsh-server","14px serif",[0,"#000000"],0],
[2,10499,6654,99,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,10499,6657.7,"rsh-redone-server","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,8398],[0,10526,8398],[0,10526,8434],[0,10472,8434]],0,
[0,"#ff0000"]],
[3,10499,8419.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,8690,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,8693.7,"midentd","14px serif",[0,"#000000"],0],
[2,8076.4,8798,74.0016,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,8801.7,"pidentd (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,3571],[0,12869,3571],[0,12869,3607],[0,12815,3607]],0,
[0,"#ff0000"]],
[3,12842,3592.6,"#","14px serif",[0,"#ff0000"],0],
[1,[0,[0,12815,5242],[0,12869,5242],[0,12869,5278],[0,12815,5278]],0,
[0,"#ff0000"]],
[3,12842,5263.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,5092,87.0012,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,5095.7,"krb5-rsh-server","14px serif",[0,"#000000"],0],
[2,8076.4,6924,81,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,8076.4,6927.7,"harden-clients","14px serif",[0,"#000000"],0],
[2,10499,7232,41.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,7235.7,"x2vnc","14px serif",[0,"#000000"],0],
[2,5481.4,15002,74.9988,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,5481.4,15005.7,"guile-1.6-dev","14px serif",[0,"#000000"],0],
[2,8076.4,15040,101.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,15043.7,"guile-1.8-dev (x 4)","14px serif",[0,"#000000"],0],
[2,8076.4,11074,56.0016,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,11077.7,"guidedog","14px serif",[0,"#000000"],0],
[2,8076.4,10982,56.9988,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,10985.7,"guarddog","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,17239],[0,10526,17239],[0,10526,17275],[0,10472,17275]],0,
[0,"#ff0000"]],
[3,10499,17260.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,17230,61.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,17233.7,"gtalk (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,17284,79.9992,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,17287.7,"inetutils-talkd","14px serif",[0,"#000000"],0],
[2,8076.4,17338,36,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,8076.4,17341.7,"talkd","14px serif",[0,"#000000"],0],
[2,831.43,23660,133.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,23663.7,"gstreamer0.10-gnomevfs","14px serif",[0,"#000000"],0],
[2,2972.4,23660,178.999,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,2972.4,23663.7,"gnome-desktop-environment (x 2)","14px serif",
[0,"#000000"],0],
[2,5481.4,7970,51.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,7973.7,"gss-man","14px serif",[0,"#000000"],0],
[1,[0,[0,15080,23615],[0,15134,23615],[0,15134,23651],[0,15080,23651]],0,
[0,"#ff0000"]],
[3,15107,23636.6,"#","14px serif",[0,"#ff0000"],0],
[2,12842,23768,68.0004,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,12842,23771.7,"grub-legacy","14px serif",[0,"#000000"],0],
[2,12842,23660,105.998,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,12842,23663.7,"grub-coreboot (x 2)","14px serif",[0,"#000000"],0],
[2,12842,23714,112,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,12842,23717.7,"grub-efi-amd64 (x 2)","14px serif",[0,"#000000"],0],
[2,12842,23552,74.0016,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,12842,23555.7,"grub-efi-ia32","14px serif",[0,"#000000"],0],
[2,12842,23606,83.0016,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,12842,23609.7,"grub-ieee1275","14px serif",[0,"#000000"],0],
[2,12842,23498,74.0016,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,12842,23501.7,"grub-pc (x 3)","14px serif",[0,"#000000"],0],
[2,5481.4,18404,195.001,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,5481.4,18407.7,"graphicsmagick-libmagick-dev-compat","14px serif",
[0,"#000000"],0],
[2,8076.4,1988,90,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,1991.7,"perlmagick (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,18826,123.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,18829.7,"libmagickcore-dev (x 5)","14px serif",[0,"#000000"],0],
[2,5481.4,1722,191.999,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,1725.7,"graphicsmagick-imagemagick-compat","14px serif",
[0,"#000000"],0],
[2,8076.4,1712,77.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,1715.7,"octave-image","14px serif",[0,"#000000"],0],
[2,8076.4,1766,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,1769.7,"imagemagick (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,19048,75.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,19051.7,"gpivtools-mpi","14px serif",[0,"#000000"],0],
[2,10499,19048,55.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,19051.7,"gpivtools","14px serif",[0,"#000000"],0],
[2,5481.4,21084,52.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21087.7,"gpiv-mpi","14px serif",[0,"#000000"],0],
[2,8076.4,21054,32,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21057.7,"gpiv","14px serif",[0,"#000000"],0],
[2,5481.4,20507,56.0016,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,5481.4,20510.7,"gpe-login","14px serif",[0,"#000000"],0],
[2,8076.4,20480,32,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,20483.7,"xdm","14px serif",[0,"#000000"],0],
[2,8076.4,20534,34.9999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,20537.7,"wdm","14px serif",[0,"#000000"],0],
[2,8076.4,20426,31,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,20429.7,"slim","14px serif",[0,"#000000"],0],
[2,8076.4,15538,57.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,15541.7,"kdm (x 2)","14px serif",[0,"#000000"],0],
[2,2972.4,1560,60.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,1563.7,"gnus (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,16224,74.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,16227.7,"libmrml1-dev","14px serif",[0,"#000000"],0],
[2,8076.4,16224,74.9988,18.5,[0,"#ffbdbd"],[0,"#000000"]],
[3,8076.4,16227.7,"libslicer3-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,23734],[0,10526,23734],[0,10526,23770],[0,10472,23770]],0,
[0,"#ff0000"]],
[3,10499,23755.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,23752,65.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23755.7,"gdm (x 13)","14px serif",[0,"#000000"],0],
[2,8076.4,23644,38.9988,18.5,[0,"#ffc6c6"],[0,"#000000"]],
[3,8076.4,23647.7,"gdm3","14px serif",[0,"#000000"],0],
[2,2972.4,21038,126,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,2972.4,21041.7,"indicator-applet-session","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,23626],[0,10526,23626],[0,10526,23662],[0,10472,23662]],0,
[0,"#ff0000"]],
[3,10499,23647.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,11870,70.9992,18.5,[0,"#ffc6c6"],[0,"#000000"]],
[3,8076.4,11873.7,"gdb-minimal","14px serif",[0,"#000000"],0],
[2,10499,12015,60.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,12018.7,"gdb (x 12)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,2414],[0,8103.4,2414],[0,8103.4,2450],[0,8049.4,2450]],0,
[0,"#ff0000"]],
[3,8076.4,2435.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,2889,83.9988,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,5481.4,2892.7,"fusionforge-full","14px serif",[0,"#000000"],0],
[2,5481.4,2248,106.999,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,5481.4,2251.7,"fusionforge-minimal","14px serif",[0,"#000000"],0],
[2,5481.4,2943,137.999,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,5481.4,2946.7,"fusionforge-standard (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,6924,60.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,6927.7,"ftp-upload","14px serif",[0,"#000000"],0],
[2,10499,11640,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,11643.7,"fso-gsm0710muxd","14px serif",[0,"#000000"],0],
[2,12842,11640,83.9988,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,12842,11643.7,"gsm0710muxd","14px serif",[0,"#000000"],0],
[2,5481.4,11629,51.0012,18.5,[0,"#ffa8a8"],[0,"#000000"]],
[3,5481.4,11632.7,"fso-gpsd","14px serif",[0,"#000000"],0],
[2,10499,11488,83.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,11491.7,"libgps19 (x 13)","14px serif",[0,"#000000"],0],
[2,8076.4,11816,114.001,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,8076.4,11819.7,"fso-frameworkd (x 3)","14px serif",[0,"#000000"],0],
[2,10499,11816,109.001,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,10499,11819.7,"libphone-utils0 (x 4)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,12798],[0,8103.4,12798],[0,8103.4,12834],[0,8049.4,12834]],
0,[0,"#ff0000"]],
[3,8076.4,12819.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,11870,97.9992,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,5481.4,11873.7,"fso-config-general","14px serif",[0,"#000000"],0],
[2,5481.4,11816,90,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,5481.4,11819.7,"fso-config-gta01","14px serif",[0,"#000000"],0],
[2,5481.4,11762,90,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,5481.4,11765.7,"fso-config-gta02","14px serif",[0,"#000000"],0],
[2,8076.4,1858,150.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,1861.7,"fossology-agents-single (x 2)","14px serif",
[0,"#000000"],0],
[2,10499,1877,119.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,1880.7,"fossology-agents (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,24330,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,24333.7,"fontforge-nox","14px serif",[0,"#000000"],0],
[2,10499,24036,56.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,24039.7,"fontforge","14px serif",[0,"#000000"],0],
[2,5481.4,10382,47.0016,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,10385.7,"flex-old","14px serif",[0,"#000000"],0],
[2,8076.4,10182,29.0002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,10185.7,"flex","14px serif",[0,"#000000"],0],
[2,831.43,524,96.0012,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,831.43,527.7,"firebird2.5-classic","14px serif",[0,"#000000"],0],
[2,2972.4,524,123.001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,2972.4,527.7,"firebird2.5-superclassic","14px serif",[0,"#000000"],0],
[2,5481.4,482,140,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,485.7,"firebird2.5-classic-common","14px serif",[0,"#000000"],0],
[2,8076.4,448,92.0016,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,451.7,"firebird2.5-super","14px serif",[0,"#000000"],0],
[2,8076.4,616,167,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,619.7,"firebird2.1-server-common (x 2)","14px serif",
[0,"#000000"],0],
[2,10499,532,167,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,535.7,"firebird2.5-server-common (x 2)","14px serif",
[0,"#000000"],0],
[2,2972.4,639,96.0012,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,2972.4,642.7,"firebird2.1-classic","14px serif",[0,"#000000"],0],
[2,5481.4,658,92.0016,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,5481.4,661.7,"firebird2.1-super","14px serif",[0,"#000000"],0],
[2,8076.4,10582,51.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,10585.7,"filtergen","14px serif",[0,"#000000"],0],
[2,10499,2752,38.9988,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,10499,2755.7,"file-rc","14px serif",[0,"#000000"],0],
[2,12842,2752,70.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,2755.7,"sysv-rc (x 4)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,10999],[0,12869,10999],[0,12869,11035],[0,12815,11035]],0,
[0,"#ff0000"]],
[3,12842,11020.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,11005,29.0002,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,10499,11008.7,"fiaif","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,10945],[0,12869,10945],[0,12869,10981],[0,12815,10981]],0,
[0,"#ff0000"]],
[3,12842,10966.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,21192,95.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21195.7,"festvox-kdlpc16k","14px serif",[0,"#000000"],0],
[2,8076.4,21146,87.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21149.7,"festvox-kdlpc8k","14px serif",[0,"#000000"],0],
[2,5481.4,21636,96.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21639.7,"festvox-kallpc16k","14px serif",[0,"#000000"],0],
[2,8076.4,21590,90,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21593.7,"festvox-kallpc8k","14px serif",[0,"#000000"],0],
[2,8076.4,10474,33.9998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,10477.7,"ferm","14px serif",[0,"#000000"],0],
[2,12842,7276,73.0008,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,12842,7279.7,"libfam0 (x 3)","14px serif",[0,"#000000"],0],
[2,15107,7320,66.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,7323.7,"gamin (x 9)","14px serif",[0,"#000000"],0],
[2,12842,7330,29.0002,18.5,[0,"#ffd4d4"],[0,"#000000"]],
[3,12842,7333.7,"fam","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,6290],[0,12869,6290],[0,12869,6326],[0,12815,6326]],0,
[0,"#ff0000"]],
[3,12842,6311.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,6308,142.999,18.5,[0,"#ffacac"],[0,"#000000"]],
[3,10499,6311.7,"exim4-daemon-heavy (x 3)","14px serif",[0,"#000000"],0],
[2,10499,6254,135,18.5,[0,"#ffa7a7"],[0,"#000000"]],
[3,10499,6257.7,"exim4-daemon-light (x 2)","14px serif",[0,"#000000"],0],
[2,10499,6492,36,18.5,[0,"#ffb0b0"],[0,"#000000"]],
[3,10499,6495.7,"rmail","14px serif",[0,"#000000"],0],
[2,2972.4,23941,63,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,2972.4,23944.7,"evince-gtk","14px serif",[0,"#000000"],0],
[2,5481.4,23941,69.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,23944.7,"evince (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,21138,46.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21141.7,"esound","14px serif",[0,"#000000"],0],
[2,8076.4,20242,167,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,20245.7,"pulseaudio-esound-compat (x 2)","14px serif",
[0,"#000000"],0],
[1,[0,[0,10472,22470],[0,10526,22470],[0,10526,22506],[0,10472,22506]],0,
[0,"#ff0000"]],
[3,10499,22491.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,22434,79.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22437.7,"emacs23-lucid","14px serif",[0,"#000000"],0],
[2,8076.4,22542,75.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22545.7,"emacs23-nox","14px serif",[0,"#000000"],0],
[2,8076.4,22488,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22491.7,"emacs23","14px serif",[0,"#000000"],0],
[2,5481.4,320,55.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,323.7,"libelf-dev","14px serif",[0,"#000000"],0],
[2,8076.4,320,93.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,323.7,"libelfg0-dev (x 2)","14px serif",[0,"#000000"],0],
[2,2972.4,374,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,377.7,"libasm-dev","14px serif",[0,"#000000"],0],
[2,5481.4,374,73.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,377.7,"libelfsh0-dev","14px serif",[0,"#000000"],0],
[2,5481.4,428,69.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,431.7,"libasm0-dev","14px serif",[0,"#000000"],0],
[2,831.43,320,70.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,323.7,"libdwarf-dev","14px serif",[0,"#000000"],0],
[2,2972.4,320,57.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,323.7,"libdw-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,3994],[0,8103.4,3994],[0,8103.4,4030],[0,8049.4,4030]],0,
[0,"#ff0000"]],
[3,8076.4,4015.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,2835,51.0012,18.5,[0,"#ffb7b7"],[0,"#000000"]],
[3,5481.4,2838.7,"dtc-core","14px serif",[0,"#000000"],0],
[2,5481.4,4162,56.0016,18.5,[0,"#ff9d9d"],[0,"#000000"]],
[3,5481.4,4165.7,"dtc-cyrus","14px serif",[0,"#000000"],0],
[2,5481.4,3858,126,18.5,[0,"#ff8f8f"],[0,"#000000"]],
[3,5481.4,3861.7,"dtc-postfix-courier (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,4452],[0,12869,4452],[0,12869,4488],[0,12815,4488]],0,
[0,"#ff0000"]],
[3,12842,4473.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,5146,104,18.5,[0,"#ffb0b0"],[0,"#000000"]],
[3,10499,5149.7,"citadel-server (x 2)","14px serif",[0,"#000000"],0],
[2,10499,4632,92.0016,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,10499,4635.7,"courier-pop (x 2)","14px serif",[0,"#000000"],0],
[2,10499,4216,83.0016,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,10499,4219.7,"dovecot-pop3d","14px serif",[0,"#000000"],0],
[2,10499,4162,100.001,18.5,[0,"#ffb6b6"],[0,"#000000"]],
[3,10499,4165.7,"kolab-cyrus-pop3d","14px serif",[0,"#000000"],0],
[2,10499,4524,86.0004,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,10499,4527.7,"mailutils-pop3d","14px serif",[0,"#000000"],0],
[2,10499,4470,47.0016,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,10499,4473.7,"popa3d","14px serif",[0,"#000000"],0],
[2,10499,4416,74.9988,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,10499,4419.7,"qpopper-drac","14px serif",[0,"#000000"],0],
[2,10499,4578,51.0012,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,10499,4581.7,"qpopper","14px serif",[0,"#000000"],0],
[2,10499,4686,66.9996,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,10499,4689.7,"solid-pop3d","14px serif",[0,"#000000"],0],
[2,10499,4362,37.0008,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,10499,4365.7,"ipopd","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,5517],[0,12869,5517],[0,12869,5553],[0,12815,5553]],0,
[0,"#ff0000"]],
[3,12842,5538.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,5400,74.9988,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,10499,5403.7,"bincimap-run","14px serif",[0,"#000000"],0],
[2,10499,5508,97.9992,18.5,[0,"#ffc6c6"],[0,"#000000"]],
[3,10499,5511.7,"courier-imap (x 2)","14px serif",[0,"#000000"],0],
[2,10499,5562,109.001,18.5,[0,"#ffcccc"],[0,"#000000"]],
[3,10499,5565.7,"dovecot-imapd (x 2)","14px serif",[0,"#000000"],0],
[2,10499,5616,99,18.5,[0,"#ffbdbd"],[0,"#000000"]],
[3,10499,5619.7,"kolab-cyrus-imapd","14px serif",[0,"#000000"],0],
[2,10499,5454,92.0016,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,10499,5457.7,"mailutils-imap4d","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,6852],[0,12869,6852],[0,12869,6888],[0,12815,6888]],0,
[0,"#ff0000"]],
[3,12842,6873.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,6546,93.9996,18.5,[0,"#ffa6a6"],[0,"#000000"]],
[3,10499,6549.7,"courier-mta (x 4)","14px serif",[0,"#000000"],0],
[2,10499,6870,32,18.5,[0,"#ffa5a5"],[0,"#000000"]],
[3,10499,6873.7,"dma","14px serif",[0,"#000000"],0],
[2,10499,6924,61.9992,18.5,[0,"#ffa0a0"],[0,"#000000"]],
[3,10499,6927.7,"esmtp-run","14px serif",[0,"#000000"],0],
[2,10499,7016,56.9988,18.5,[0,"#ffa0a0"],[0,"#000000"]],
[3,10499,7019.7,"masqmail","14px serif",[0,"#000000"],0],
[2,10499,6816,66.9996,18.5,[0,"#ffa5a5"],[0,"#000000"]],
[3,10499,6819.7,"msmtp-mta","14px serif",[0,"#000000"],0],
[2,10499,6600,75.9996,18.5,[0,"#ffb6b6"],[0,"#000000"]],
[3,10499,6603.7,"postfix (x 14)","14px serif",[0,"#000000"],0],
[2,10499,7070,39.9996,18.5,[0,"#ffa0a0"],[0,"#000000"]],
[3,10499,7073.7,"ssmtp","14px serif",[0,"#000000"],0],
[2,8076.4,5843,69.0012,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,8076.4,5846.7,"dhcp-helper","14px serif",[0,"#000000"],0],
[2,10499,5816,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,5819.7,"dhcp3-server (x 5)","14px serif",[0,"#000000"],0],
[2,10499,5870,69.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,5873.7,"dhcp3-relay","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,4560],[0,12869,4560],[0,12869,4596],[0,12815,4596]],0,
[0,"#ff0000"]],
[3,12842,4581.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,5200,69.0012,18.5,[0,"#ffb5b5"],[0,"#000000"]],
[3,10499,5203.7,"dbmail (x 3)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,5409],[0,12869,5409],[0,12869,5445],[0,12815,5445]],0,
[0,"#ff0000"]],
[3,12842,5430.6,"#","14px serif",[0,"#ff0000"],0],
[1,[0,[0,12815,22875],[0,12869,22875],[0,12869,22911],[0,12815,22911]],0,
[0,"#ff0000"]],
[3,12842,22896.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,22866,100.001,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,10499,22869.7,"libdb4.8-java (x 2)","14px serif",[0,"#000000"],0],
[2,10499,22920,100.001,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,10499,22923.7,"libdb4.5-java (x 2)","14px serif",[0,"#000000"],0],
[2,10499,22974,100.001,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,10499,22977.7,"libdb4.6-java (x 2)","14px serif",[0,"#000000"],0],
[2,10499,22812,100.001,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,10499,22815.7,"libdb4.7-java (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,7912],[0,12869,7912],[0,12869,7948],[0,12815,7948]],0,
[0,"#ff0000"]],
[3,12842,7933.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,7984,96.9984,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,10499,7987.7,"libdb4.8-dev (x 3)","14px serif",[0,"#000000"],0],
[2,10499,7930,96.9984,18.5,[0,"#ffcccc"],[0,"#000000"]],
[3,10499,7933.7,"libdb4.5-dev (x 2)","14px serif",[0,"#000000"],0],
[2,10499,7838,96.9984,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,10499,7841.7,"libdb4.6-dev (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,7460,96.9984,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,5481.4,7463.7,"libdb4.7-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,22596,70.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22599.7,"dates-hildon","14px serif",[0,"#000000"],0],
[2,10499,22596,38.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,22599.7,"dates","14px serif",[0,"#000000"],0],
[2,10499,3800,95.0004,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,10499,3803.7,"daemontools-run","14px serif",[0,"#000000"],0],
[2,12842,3777,60.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,3780.7,"runit (x 5)","14px serif",[0,"#000000"],0],
[2,2972.4,212,167,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,215.7,"libsasl2-modules-gssapi-heimdal","14px serif",
[0,"#000000"],0],
[2,5481.4,212,144,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,215.7,"libsasl2-modules-gssapi-mit","14px serif",[0,"#000000"],0],
[2,831.43,266,128.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,269.7,"cyrus-sasl2-heimdal-dbg","14px serif",[0,"#000000"],0],
[2,2972.4,266,87.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,269.7,"cyrus-sasl2-dbg","14px serif",[0,"#000000"],0],
[2,12842,5173,137.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,5176.7,"libcyrus-imap-perl22 (x 2)","14px serif",[0,"#000000"],0],
[2,15107,5472,153,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,5475.7,"kolab-libcyrus-imap-perl (x 3)","14px serif",
[0,"#000000"],0],
[1,[0,[0,12815,4506],[0,12869,4506],[0,12869,4542],[0,12815,4542]],0,
[0,"#ff0000"]],
[3,12842,4527.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,4740,90,18.5,[0,"#ffb9b9"],[0,"#000000"]],
[3,10499,4743.7,"cyrus-pop3d-2.2","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,4614],[0,12869,4614],[0,12869,4650],[0,12815,4650]],0,
[0,"#ff0000"]],
[3,12842,4635.6,"#","14px serif",[0,"#ff0000"],0],
[1,[0,[0,12815,8398],[0,12869,8398],[0,12869,8434],[0,12815,8434]],0,
[0,"#ff0000"]],
[3,12842,8419.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,8038,90,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,10499,8041.7,"cyrus-nntpd-2.2","14px serif",[0,"#000000"],0],
[2,10499,8092,33.0001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,8095.7,"inn2","14px serif",[0,"#000000"],0],
[2,10499,8524,52.9992,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,8527.7,"leafnode","14px serif",[0,"#000000"],0],
[2,10499,8578,27,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,8581.7,"sn","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,8128],[0,12869,8128],[0,12869,8164],[0,12815,8164]],0,
[0,"#ff0000"]],
[3,12842,8149.6,"#","14px serif",[0,"#ff0000"],0],
[1,[0,[0,12815,5463],[0,12869,5463],[0,12869,5499],[0,12815,5499]],0,
[0,"#ff0000"]],
[3,12842,5484.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,5254,90,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,10499,5257.7,"cyrus-imapd-2.2","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,5355],[0,12869,5355],[0,12869,5391],[0,12815,5391]],0,
[0,"#ff0000"]],
[3,12842,5376.6,"#","14px serif",[0,"#ff0000"],0],
[2,12842,5000,128.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,5003.7,"cyrus-common-2.2 (x 2)","14px serif",[0,"#000000"],0],
[2,15107,4916,110.999,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,15107,4919.7,"kolab-cyrus-common","14px serif",[0,"#000000"],0],
[2,5481.4,6686,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,6689.7,"cyrus-clients-2.2","14px serif",[0,"#000000"],0],
[2,8076.4,6686,101.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,6689.7,"kolab-cyrus-clients","14px serif",[0,"#000000"],0],
[2,5481.4,8100,135,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,5481.4,8103.7,"libcurl4-gnutls-dev (x 15)","14px serif",[0,"#000000"],0],
[2,8076.4,8062,133.999,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,8076.4,8065.7,"libcurl4-openssl-dev (x 2)","14px serif",[0,"#000000"],0],
[2,10499,13382,96.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,13385.7,"cups-client (x 13)","14px serif",[0,"#000000"],0],
[2,8076.4,13228,52.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,13231.7,"cups-bsd","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,6574],[0,12869,6574],[0,12869,6610],[0,12815,6610]],0,
[0,"#ff0000"]],
[3,12842,6595.6,"#","14px serif",[0,"#ff0000"],0],
[1,[0,[0,15080,6898],[0,15134,6898],[0,15134,6934],[0,15080,6934]],0,
[0,"#ff0000"]],
[3,15107,6919.6,"#","14px serif",[0,"#ff0000"],0],
[2,12842,6254,99,18.5,[0,"#ffb4b4"],[0,"#000000"]],
[3,12842,6257.7,"exim4-config (x 4)","14px serif",[0,"#000000"],0],
[2,8076.4,3346,115.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,3349.7,"courier-maildrop (x 5)","14px serif",[0,"#000000"],0],
[2,10499,3076,52.9992,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,10499,3079.7,"maildrop","14px serif",[0,"#000000"],0],
[2,5481.4,20410,65.9988,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,20413.7,"controlaula","14px serif",[0,"#000000"],0],
[2,8076.4,20334,87.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,20337.7,"ltsp-controlaula","14px serif",[0,"#000000"],0],
[2,5481.4,20830,150.001,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,20833.7,"gnome-control-center (x 17)","14px serif",[0,"#000000"],
0],
[2,8076.4,20756,78.9984,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,8076.4,20759.7,"gpe-conf (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,6032,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,6035.7,"console-tools (x 3)","14px serif",[0,"#000000"],0],
[2,10499,6032,29.0002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,6035.7,"kbd","14px serif",[0,"#000000"],0],
[2,5481.4,14326,103,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,14329.7,"console-setup-mini","14px serif",[0,"#000000"],0],
[2,8076.4,14326,121,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,14329.7,"console-terminus (x 4)","14px serif",[0,"#000000"],0],
[2,10499,16132,74.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,16135.7,"libcoin60-doc","14px serif",[0,"#000000"],0],
[2,12842,16132,73.0008,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,12842,16135.7,"inventor-dev","14px serif",[0,"#000000"],0],
[2,10499,16078,75.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,16081.7,"libcoin60-dev","14px serif",[0,"#000000"],0],
[2,5481.4,5508,70.9992,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,5481.4,5511.7,"clamav-data","14px serif",[0,"#000000"],0],
[2,8076.4,5554,122,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,5557.7,"clamav-freshclam (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,6344],[0,12869,6344],[0,12869,6380],[0,12815,6380]],0,
[0,"#ff0000"]],
[3,12842,6365.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,6178,92.0016,18.5,[0,"#ff9393"],[0,"#000000"]],
[3,8076.4,6181.7,"citadel-mta (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,6944],[0,12869,6944],[0,12869,6980],[0,12815,6980]],0,
[0,"#ff0000"]],
[3,12842,6965.6,"#","14px serif",[0,"#ff0000"],0],
[2,831.43,1414,45,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,1417.7,"chrony","14px serif",[0,"#000000"],0],
[2,2972.4,1414,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,1417.7,"ntp (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,4846,50.0004,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,4849.7,"cfingerd","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,5290],[0,10526,5290],[0,10526,5326],[0,10472,5326]],0,
[0,"#ff0000"]],
[3,10499,5311.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,5284,51.0012,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,5287.7,"efingerd","14px serif",[0,"#000000"],0],
[2,8076.4,5446,51.0012,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,5449.7,"xfingerd","14px serif",[0,"#000000"],0],
[2,5481.4,7310,78.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,7313.7,"pawserv (x 2)","14px serif",[0,"#000000"],0],
[2,2972.4,17338,115.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,17341.7,"libpacklib1-dev (x 11)","14px serif",[0,"#000000"],0],
[2,10499,17936,69.9984,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,10499,17939.7,"ccache (x 2)","14px serif",[0,"#000000"],0],
[2,12842,17936,178.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,17939.7,"nvidia-kernel-legacy-173xx-source","14px serif",
[0,"#000000"],0],
[2,5481.4,21544,99,18.5,[0,"#ffafaf"],[0,"#000000"]],
[3,5481.4,21547.7,"lib32bz2-1.0 (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,21536,84.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21539.7,"ia32-libs (x 31)","14px serif",[0,"#000000"],0],
[2,5481.4,5843,46.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,5846.7,"udhcpd","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,8776],[0,12869,8776],[0,12869,8812],[0,12815,8812]],0,
[0,"#ff0000"]],
[3,12842,8797.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,8740,91.0008,18.5,[0,"#ffcccc"],[0,"#000000"]],
[3,10499,8743.7,"busybox-syslogd","14px serif",[0,"#000000"],0],
[2,10499,8956,73.0008,18.5,[0,"#ffd7d7"],[0,"#000000"]],
[3,10499,8959.7,"dsyslog (x 5)","14px serif",[0,"#000000"],0],
[2,10499,8902,90,18.5,[0,"#ffcccc"],[0,"#000000"]],
[3,10499,8905.7,"inetutils-syslogd","14px serif",[0,"#000000"],0],
[2,10499,8794,70.9992,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,10499,8797.7,"rsyslog (x 6)","14px serif",[0,"#000000"],0],
[2,10499,8686,68.0004,18.5,[0,"#ffcaca"],[0,"#000000"]],
[3,10499,8689.7,"socklog-run","14px serif",[0,"#000000"],0],
[2,10499,8632,52.9992,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,10499,8635.7,"sysklogd","14px serif",[0,"#000000"],0],
[2,10499,8848,56.9988,18.5,[0,"#ffcccc"],[0,"#000000"]],
[3,10499,8851.7,"syslog-ng","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,8830],[0,12869,8830],[0,12869,8866],[0,12815,8866]],0,
[0,"#ff0000"]],
[3,12842,8851.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,9064,37.0008,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,10499,9067.7,"klogd","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,5652],[0,10526,5652],[0,10526,5688],[0,10472,5688]],0,
[0,"#ff0000"]],
[3,10499,5673.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,5500,46.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,5503.7,"fingerd","14px serif",[0,"#000000"],0],
[2,8076.4,15916,124.999,18.5,[0,"#ff8f8f"],[0,"#000000"]],
[3,8076.4,15919.7,"libboost1.40-dev (x 17)","14px serif",[0,"#000000"],0],
[2,10499,16544,124.999,18.5,[0,"#ffc4c4"],[0,"#000000"]],
[3,10499,16547.7,"libboost1.42-dev (x 53)","14px serif",[0,"#000000"],0],
[2,8076.4,10636,140,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,10639.7,"libboost-mpi-python1.40.0","14px serif",[0,"#000000"],0],
[2,10499,10821,140,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,10824.7,"libboost-mpi-python1.42.0","14px serif",[0,"#000000"],0],
[2,5481.4,10112,54,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,5481.4,10115.7,"bison++","14px serif",[0,"#000000"],0],
[2,8076.4,10074,56.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,10077.7,"bison-doc","14px serif",[0,"#000000"],0],
[2,8076.4,10128,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,10131.7,"bison (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,9100],[0,10526,9100],[0,10526,9136],[0,10472,9136]],0,
[0,"#ff0000"]],
[3,10499,9121.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,8906,47.9988,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,8909.7,"bidentd","14px serif",[0,"#000000"],0],
[2,8076.4,8852,42.9984,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,8855.7,"ident2","14px serif",[0,"#000000"],0],
[2,8076.4,9068,60.9984,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,9071.7,"nullidentd","14px serif",[0,"#000000"],0],
[2,8076.4,9014,47.9988,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,9017.7,"oidentd","14px serif",[0,"#000000"],0],
[2,8076.4,9122,50.0004,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,9125.7,"slidentd","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,8992],[0,10526,8992],[0,10526,9028],[0,10472,9028]],0,
[0,"#ff0000"]],
[3,10499,9013.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,3781,59.0004,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,3784.7,"bcron-run","14px serif",[0,"#000000"],0],
[2,10499,3854,57.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,3857.7,"cron (x 5)","14px serif",[0,"#000000"],0],
[2,5481.4,3365,97.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,3368.7,"bandwidthd-pgsql","14px serif",[0,"#000000"],0],
[2,8076.4,3292,69.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,3295.7,"bandwidthd","14px serif",[0,"#000000"],0],
[2,8076.4,22650,66.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22653.7,"babel-1.4.0","14px serif",[0,"#000000"],0],
[2,10499,22650,87.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,22653.7,"openbabel (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,86],[0,8103.4,86],[0,8103.4,122],[0,8049.4,122]],0,
[0,"#ff0000"]],
[3,8076.4,107.6,"#","14px serif",[0,"#ff0000"],0],
[2,5481.4,50,60.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,53.7,"aumix-gtk","14px serif",[0,"#000000"],0],
[2,5481.4,104,41.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,107.7,"aumix","14px serif",[0,"#000000"],0],
[2,5481.4,158,73.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,161.7,"oss-preserve","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,5960],[0,12869,5960],[0,12869,5996],[0,12815,5996]],0,
[0,"#ff0000"]],
[3,12842,5981.6,"#","14px serif",[0,"#ff0000"],0],
[2,10499,5924,41.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,5927.7,"atftpd","14px serif",[0,"#000000"],0],
[2,10499,5978,34.9999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,5981.7,"tftpd","14px serif",[0,"#000000"],0],
[2,10499,6162,56.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,6165.7,"tftpd-hpa","14px serif",[0,"#000000"],0],
[2,5481.4,21744,117,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,21747.7,"asterisk-prompt-es-co","14px serif",[0,"#000000"],0],
[2,8076.4,21720,103,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21723.7,"asterisk-prompt-es","14px serif",[0,"#000000"],0],
[2,8076.4,6632,42.0012,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,6635.7,"arping","14px serif",[0,"#000000"],0],
[2,10499,6708,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,6711.7,"iputils-arping (x 3)","14px serif",[0,"#000000"],0],
[1,[0,[0,15080,15547],[0,15134,15547],[0,15134,15583],[0,15080,15583]],0,
[0,"#ff0000"]],
[3,15107,15568.6,"#","14px serif",[0,"#ff0000"],0],
[2,12842,15511,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,15514.7,"apsfilter","14px serif",[0,"#000000"],0],
[2,12842,15565,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,15568.7,"magicfilter","14px serif",[0,"#000000"],0],
[2,12842,15619,83.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,15622.7,"printfilters-ppd","14px serif",[0,"#000000"],0],
[2,5481.4,7606,112,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,5481.4,7609.7,"apache2-prefork-dev","14px serif",[0,"#000000"],0],
[2,8076.4,7602,121,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,8076.4,7605.7,"apache2-threaded-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,16683,2491],[0,16737,2491],[0,16737,2527],[0,16683,2527]],0,
[0,"#ff0000"]],
[3,16710,2512.6,"#","14px serif",[0,"#ff0000"],0],
[2,15107,2455,110.999,18.5,[0,"#ff9f9f"],[0,"#000000"]],
[3,15107,2458.7,"apache2-mpm-event","14px serif",[0,"#000000"],0],
[2,15107,2509,118.001,18.5,[0,"#ffa0a0"],[0,"#000000"]],
[3,15107,2512.7,"apache2-mpm-worker","14px serif",[0,"#000000"],0],
[2,15107,2677,110.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,2680.7,"torrus-apache2 (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,16683,2410],[0,16737,2410],[0,16737,2446],[0,16683,2446]],0,
[0,"#ff0000"]],
[3,16710,2431.6,"#","14px serif",[0,"#ff0000"],0],
[2,15107,2401,96.9984,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,15107,2404.7,"apache2-mpm-itk","14px serif",[0,"#000000"],0],
[2,15107,2347,145.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,15107,2350.7,"apache2-mpm-prefork (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,17722,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,17725.7,"ant (x 6)","14px serif",[0,"#000000"],0],
[2,10499,17882,69.9984,18.5,[0,"#ffc8c8"],[0,"#000000"]],
[3,10499,17885.7,"ant1.7 (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,19664,87.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,19667.7,"ant-optional-gcj","14px serif",[0,"#000000"],0],
[2,8076.4,18772,104,18.5,[0,"#ffc4c4"],[0,"#000000"]],
[3,8076.4,18775.7,"ant1.7-optional-gcj","14px serif",[0,"#000000"],0],
[2,5481.4,19094,45,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,19097.7,"ant-gcj","14px serif",[0,"#000000"],0],
[2,8076.4,18718,60.9984,18.5,[0,"#ffc4c4"],[0,"#000000"]],
[3,8076.4,18721.7,"ant1.7-gcj","14px serif",[0,"#000000"],0],
[2,10499,23136,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,23139.7,"anacron","14px serif",[0,"#000000"],0],
[2,12842,23136,36,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,23139.7,"fcron","14px serif",[0,"#000000"],0],
[2,8076.4,3904,101.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,3907.7,"amavisd-new (x 2)","14px serif",[0,"#000000"],0],
[2,10499,3908,109.001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,10499,3911.7,"phamm-ldap-amavis","14px serif",[0,"#000000"],0],
[2,10499,19835,109.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,19838.7,"libasound2 (x 1350)","14px serif",[0,"#000000"],0],
[2,12842,19835,110.999,18.5,[0,"#ff1414"],[0,"#000000"]],
[3,12842,19838.7,"liboss-salsa-asound2","14px serif",[0,"#000000"],0],
[2,5481.4,20606,99,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,20609.7,"festvox-rablpc16k","14px serif",[0,"#000000"],0],
[2,8076.4,20626,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,20629.7,"festvox-rablpc8k","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,22740],[0,10526,22740],[0,10526,22776],[0,10472,22776]],0,
[0,"#ff0000"]],
[3,10499,22761.6,"#","14px serif",[0,"#ff0000"],0],
[2,8076.4,22704,79.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22707.7,"conky-all (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,23082,52.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23085.7,"conky-cli","14px serif",[0,"#000000"],0],
[2,8076.4,22758,57.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,22761.7,"conky-std","14px serif",[0,"#000000"],0],
[2,8076.4,16808,50.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,16811.7,"amoeba","14px serif",[0,"#000000"],0],
[2,5481.4,21398,47.9988,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,5481.4,21401.7,"dssi-vst","14px serif",[0,"#000000"],0],
[2,831.43,23,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,26.7,"ora2pg (x 10)","14px serif",[0,"#000000"],0],
[1,[0,[0,2917.4,5],[0,3027.4,5],[0,3027.4,41],[0,2917.4,41]],0,
[0,"#0000ff"]],
[3,2972.4,26.6,"MISSING DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,15808,124.999,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,15811.7,"sapgui-package (x 256)","14px serif",[0,"#000000"],0],
[2,5481.4,17799,139,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,17802.7,"libace-foxreactor-dev (x 3)","14px serif",[0,"#000000"],
0],
[2,8076.4,15592,78.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,15595.7,"adept (x 311)","14px serif",[0,"#000000"],0],
[2,12842,7768,77.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,12842,7771.7,"am-utils (x 6)","14px serif",[0,"#000000"],0],
[1,[0,[0,15080,7658],[0,15134,7658],[0,15134,7694],[0,15080,7694]],0,
[0,"#0000ff"]],
[3,15107,7679.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,7656,108,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,7659.7,"libaprutil1-dev (x 5)","14px serif",[0,"#000000"],0],
[2,8076.4,17814,69.0012,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,17817.7,"libarts1-dev","14px serif",[0,"#000000"],0],
[2,5481.4,2102,131,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,2105.7,"auth2db-frontend (x 21)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,2268],[0,12869,2268],[0,12869,2304],[0,12815,2304]],0,
[0,"#ee82ee"]],
[3,12842,2289.6,"DEP","14px serif",[0,"#ee82ee"],0],
[2,10499,7286,97.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,7289.7,"bcfg2-server (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,7150],[0,12869,7150],[0,12869,7186],[0,12815,7186]],0,
[0,"#0000ff"]],
[3,12842,7171.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,14380,110.999,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,8076.4,14383.7,"libboost-all-dev (x 9)","14px serif",[0,"#000000"],0],
[2,5481.4,10882,177.998,18.5,[0,"#ff8e8e"],[0,"#000000"]],
[3,5481.4,10885.7,"libboost-mpi-python1.40-dev (x 2)","14px serif",
[0,"#000000"],0],
[2,5481.4,11535,114.001,18.5,[0,"#ff8e8e"],[0,"#000000"]],
[3,5481.4,11538.7,"libboost-mpi1.40-dev","14px serif",[0,"#000000"],0],
[2,8076.4,11128,177.998,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,8076.4,11131.7,"libboost-mpi-python1.42-dev (x 2)","14px serif",
[0,"#000000"],0],
[2,8076.4,13336,95.0004,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,13339.7,"libcegui-mk2-dev","14px serif",[0,"#000000"],0],
[2,831.43,17010,115.999,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,831.43,17013.7,"cernlib-core-dev (x 6)","14px serif",[0,"#000000"],0],
[2,8076.4,9230,87.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,9233.7,"cl-sql-odbc (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,10166,52.9992,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,5481.4,10169.7,"clisp-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,7492],[0,8103.4,7492],[0,8103.4,7528],[0,8049.4,7528]],0,
[0,"#0000ff"]],
[3,8076.4,7513.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,7786,83.9988,18.5,[0,"#ffa4a4"],[0,"#000000"]],
[3,8076.4,7789.7,"courier-faxmail","14px serif",[0,"#000000"],0],
[2,10499,5038,78.0012,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,10499,5041.7,"cyrus-dev-2.2","14px serif",[0,"#000000"],0],
[2,8076.4,22866,91.0008,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,8076.4,22869.7,"libdb4.8-java-gcj","14px serif",[0,"#000000"],0],
[2,8076.4,22920,91.0008,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,8076.4,22923.7,"libdb4.5-java-gcj","14px serif",[0,"#000000"],0],
[2,8076.4,22974,91.0008,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,8076.4,22977.7,"libdb4.6-java-gcj","14px serif",[0,"#000000"],0],
[2,8076.4,22812,91.0008,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,8076.4,22815.7,"libdb4.7-java-gcj","14px serif",[0,"#000000"],0],
[2,2972.4,11284,73.0008,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,2972.4,11287.7,"libdeal.ii-dev","14px serif",[0,"#000000"],0],
[2,2972.4,12804,69.9984,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,2972.4,12807.7,"digikam-dbg","14px serif",[0,"#000000"],0],
[2,2972.4,16024,74.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,16027.7,"digikam (x 8)","14px serif",[0,"#000000"],0],
[2,5481.4,2997,119.999,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,5481.4,3000.7,"docvert-openoffice.org","14px serif",[0,"#000000"],0],
[2,12842,7384,90,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,12842,7387.7,"doodle-dbg (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,10220,131,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,5481.4,10223.7,"libdose2-ocaml-dev (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,16132,51.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,16135.7,"dssi-dev","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,16114],[0,8103.4,16114],[0,8103.4,16150],[0,8049.4,16150]],
0,[0,"#0000ff"]],
[3,8076.4,16135.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,5481.4,2302,96.9984,18.5,[0,"#ffbcbc"],[0,"#000000"]],
[3,5481.4,2305.7,"dtc-common (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,3109],[0,8103.4,3109],[0,8103.4,3145],[0,8049.4,3145]],0,
[0,"#0000ff"]],
[3,8076.4,3130.6,"DEP","14px serif",[0,"#0000ff"],0],
[1,[0,[0,8049.4,5097],[0,8103.4,5097],[0,8103.4,5133],[0,8049.4,5133]],0,
[0,"#0000ff"]],
[3,8076.4,5118.6,"DEP","14px serif",[0,"#0000ff"],0],
[1,[0,[0,8049.4,4236],[0,8103.4,4236],[0,8103.4,4272],[0,8049.4,4272]],0,
[0,"#ee82ee"]],
[3,8076.4,4257.6,"DEP","14px serif",[0,"#ee82ee"],0],
[1,[0,[0,8049.4,4666],[0,8103.4,4666],[0,8103.4,4702],[0,8049.4,4702]],0,
[0,"#ee82ee"]],
[3,8076.4,4687.6,"DEP","14px serif",[0,"#ee82ee"],0],
[1,[0,[0,8049.4,4144],[0,8103.4,4144],[0,8103.4,4180],[0,8049.4,4180]],0,
[0,"#0000ff"]],
[3,8076.4,4165.6,"DEP","14px serif",[0,"#0000ff"],0],
[1,[0,[0,8049.4,4974],[0,8103.4,4974],[0,8103.4,5010],[0,8049.4,5010]],0,
[0,"#ee82ee"]],
[3,8076.4,4995.6,"DEP","14px serif",[0,"#ee82ee"],0],
[1,[0,[0,8049.4,4774],[0,8103.4,4774],[0,8103.4,4810],[0,8049.4,4810]],0,
[0,"#ee82ee"]],
[3,8076.4,4795.6,"DEP","14px serif",[0,"#ee82ee"],0],
[2,2972.4,3411,104,18.5,[0,"#ff9090"],[0,"#000000"]],
[3,2972.4,3414.7,"dtc-postfix-dovecot","14px serif",[0,"#000000"],0],
[2,8076.4,16332,105.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,16335.7,"libecasound2.2-dev","14px serif",[0,"#000000"],0],
[2,5481.4,18728,146.999,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,18731.7,"eclipse-emf-examples (x 12)","14px serif",[0,"#000000"],
0],
[2,8076.4,10420,70.9992,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,10423.7,"libelmer-dev","14px serif",[0,"#000000"],0],
[2,5481.4,6082,66.9996,18.5,[0,"#ffaeae"],[0,"#000000"]],
[3,5481.4,6085.7,"exim4 (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,6106],[0,8103.4,6106],[0,8103.4,6142],[0,8049.4,6142]],0,
[0,"#0000ff"]],
[3,8076.4,6127.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,7163,74.9988,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,7166.7,"fai-quickstart","14px serif",[0,"#000000"],0],
[2,2972.4,20830,123.001,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,2972.4,20833.7,"fast-user-switch-applet","14px serif",[0,"#000000"],0],
[2,2972.4,8146,60.9984,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,2972.4,8149.7,"fatrat-dev","14px serif",[0,"#000000"],0],
[2,8076.4,18994,88.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,18997.7,"fenix-dev (x 32)","14px serif",[0,"#000000"],0],
[2,8076.4,15094,92.0016,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,15097.7,"libfluidsynth-dev","14px serif",[0,"#000000"],0],
[2,5481.4,1858,137.999,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,5481.4,1861.7,"fossology-web-single (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,1942,79.9992,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,5481.4,1945.7,"fossology-web","14px serif",[0,"#000000"],0],
[2,8076.4,14164,86.0004,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,14167.7,"freevo-lirc (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,16078,106.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,16081.7,"python-freevo (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,6268],[0,8103.4,6268],[0,8103.4,6304],[0,8049.4,6304]],0,
[0,"#ee82ee"]],
[3,8076.4,6289.6,"DEP","14px serif",[0,"#ee82ee"],0],
[1,[0,[0,8049.4,6322],[0,8103.4,6322],[0,8103.4,6358],[0,8049.4,6358]],0,
[0,"#0000ff"]],
[3,8076.4,6343.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,5481.4,6313,110.002,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,5481.4,6316.7,"gforge-lists-mailman","14px serif",[0,"#000000"],0],
[2,8076.4,5338,100.001,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,8076.4,5341.7,"gadmin-tools (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,13282,132.998,18.5,[0,"#ffb1b1"],[0,"#000000"]],
[3,8076.4,13285.7,"python-gamera-dev (x 3)","14px serif",[0,"#000000"],0],
[2,2972.4,9998,96.9984,18.5,[0,"#ffa7a7"],[0,"#000000"]],
[3,2972.4,10001.7,"libgdal1-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,18572,78.0012,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,8076.4,18575.7,"libgecode-dev","14px serif",[0,"#000000"],0],
[2,5481.4,20992,66.9996,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,5481.4,20995.7,"libgeda-dev","14px serif",[0,"#000000"],0],
[2,8076.4,10528,54,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,10531.7,"libgs-dev","14px serif",[0,"#000000"],0],
[2,8076.4,23028,90,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23031.7,"gnome-osd (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,23136,90,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23139.7,"gnome-schedule","14px serif",[0,"#000000"],0],
[2,2972.4,23995,99,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,23998.7,"gnome-user-share","14px serif",[0,"#000000"],0],
[2,5481.4,6003,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,6006.7,"goto-fai-backend","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,5960],[0,8103.4,5960],[0,8103.4,5996],[0,8049.4,5996]],0,
[0,"#0000ff"]],
[3,8076.4,5981.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,2972.4,20727,29.0002,18.5,[0,"#ffa7a7"],[0,"#000000"]],
[3,2972.4,20730.7,"gpe","14px serif",[0,"#000000"],0],
[2,5481.4,6551,37.0008,18.5,[0,"#ffd1d1"],[0,"#000000"]],
[3,5481.4,6554.7,"gross","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,6560],[0,8103.4,6560],[0,8103.4,6596],[0,8049.4,6596]],0,
[0,"#ee82ee"]],
[3,8076.4,6581.6,"DEP","14px serif",[0,"#ee82ee"],0],
[1,[0,[0,8049.4,6506],[0,8103.4,6506],[0,8103.4,6542],[0,8049.4,6542]],0,
[0,"#0000ff"]],
[3,8076.4,6527.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,24184,109.001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,24187.7,"grub-choose-default","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,23489],[0,10526,23489],[0,10526,23525],[0,10472,23525]],0,
[0,"#0000ff"]],
[3,10499,23510.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,5481.4,18674,82.0008,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,18677.7,"libguichan-dev","14px serif",[0,"#000000"],0],
[2,8076.4,9554,87.0012,18.5,[0,"#ffa8a8"],[0,"#000000"]],
[3,8076.4,9557.7,"libhdf5-lam-dev","14px serif",[0,"#000000"],0],
[2,8076.4,11290,113,18.5,[0,"#ffcaca"],[0,"#000000"]],
[3,8076.4,11293.7,"libhdf5-mpi-dev (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,13022,97.9992,18.5,[0,"#ffaeae"],[0,"#000000"]],
[3,8076.4,13025.7,"libhdf5-mpich-dev","14px serif",[0,"#000000"],0],
[2,8076.4,23190,131,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23193.7,"hildon-desktop-dbg (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,14434,54,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,8076.4,14437.7,"ifrit (x 8)","14px serif",[0,"#000000"],0],
[2,8076.4,14542,87.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,14545.7,"libluminate-dev","14px serif",[0,"#000000"],0],
[2,5481.4,1785,96.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,1788.7,"imagemagick-dbg","14px serif",[0,"#000000"],0],
[2,8076.4,16386,110.002,18.5,[0,"#ff5e5e"],[0,"#000000"]],
[3,8076.4,16389.7,"jackd2-firewire (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,13920,121,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,13923.7,"kaffeine-mozilla (x 10)","14px serif",[0,"#000000"],0],
[2,8076.4,13520,70.9992,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,13523.7,"kaffeine-dbg","14px serif",[0,"#000000"],0],
[2,5481.4,9700,109.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,9703.7,"libkaya-gd-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,12508,140,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,12511.7,"kdeaccessibility-dbg (x 14)","14px serif",[0,"#000000"],
0],
[2,8076.4,12454,101.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,12457.7,"kdeartwork (x 17)","14px serif",[0,"#000000"],0],
[2,2972.4,17284,105.001,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,2972.4,17287.7,"libkdcraw-dev (x 3)","14px serif",[0,"#000000"],0],
[2,5481.4,12854,65.9988,18.5,[0,"#ffb5b5"],[0,"#000000"]],
[3,5481.4,12857.7,"kdelibs-dbg","14px serif",[0,"#000000"],0],
[2,8076.4,12238,93.9996,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,12241.7,"kdepim-dbg (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,12184,122,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,12187.7,"kdeplasma-addons-dbg","14px serif",[0,"#000000"],0],
[2,8076.4,12670,92.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,12673.7,"kdesvn-dbg (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,8230,70.9992,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,8076.4,8233.7,"libsvnqt-dev","14px serif",[0,"#000000"],0],
[2,5481.4,5616,42.9984,18.5,[0,"#ff9696"],[0,"#000000"]],
[3,5481.4,5619.7,"kolabd","14px serif",[0,"#000000"],0],
[2,8076.4,13812,47.9988,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,13815.7,"ksniffer","14px serif",[0,"#000000"],0],
[2,2972.4,11338,83.9988,18.5,[0,"#ffbdbd"],[0,"#000000"]],
[3,2972.4,11341.7,"liblife-dbg (x 2)","14px serif",[0,"#000000"],0],
[2,10499,15538,38.9988,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,10499,15541.7,"lprfax","14px serif",[0,"#000000"],0],
[2,5481.4,14012,59.0004,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,5481.4,14015.7,"ltsp-client","14px serif",[0,"#000000"],0],
[2,8076.4,10236,119.999,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,10239.7,"ltsp-server-standalone","14px serif",[0,"#000000"],0],
[2,8076.4,15700,79.9992,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,8076.4,15703.7,"libluabind-dev","14px serif",[0,"#000000"],0],
[2,8076.4,23698,82.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23701.7,"lxde-core (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,7364,109.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,7367.7,"libalog-full-dbg (x 2)","14px serif",[0,"#000000"],0],
[2,10499,1766,167,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,1769.7,"libapache2-mod-log-sql-dbi (x 5)","14px serif",
[0,"#000000"],0],
[2,2972.4,7732,72,18.5,[0,"#ffb9b9"],[0,"#000000"]],
[3,2972.4,7735.7,"libetpan-dev","14px serif",[0,"#000000"],0],
[2,8076.4,14488,137.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,14491.7,"libfsoframework-dev (x 2)","14px serif",[0,"#000000"],0],
[2,2972.4,7786,99,18.5,[0,"#ff7a7a"],[0,"#000000"]],
[3,2972.4,7789.7,"libgd2-noxpm-dev","14px serif",[0,"#000000"],0],
[2,8076.4,21866,139,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21869.7,"libgdchart-gd2-noxpm-dev","14px serif",[0,"#000000"],0],
[2,8076.4,21920,127.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,21923.7,"libgdchart-gd2-xpm-dev","14px serif",[0,"#000000"],0],
[2,5481.4,23552,60.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,23555.7,"haml-elisp","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,23534],[0,8103.4,23534],[0,8103.4,23570],[0,8049.4,23570]],
0,[0,"#0000ff"]],
[3,8076.4,23555.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,14596,167,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,14599.7,"libphone-ui-20100517-dbg (x 2)","14px serif",
[0,"#000000"],0],
[2,8076.4,11724,87.0012,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,8076.4,11727.7,"libphone-ui-dev","14px serif",[0,"#000000"],0],
[2,5481.4,18620,77.0004,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,5481.4,18623.7,"libtuxcap-dev","14px serif",[0,"#000000"],0],
[2,2972.4,9914,79.9992,18.5,[0,"#ff9898"],[0,"#000000"]],
[3,2972.4,9917.7,"libmapnik-dev","14px serif",[0,"#000000"],0],
[2,831.43,1036,92.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,1039.7,"hunspell-de-med","14px serif",[0,"#000000"],0],
[1,[0,[0,2945.4,1018],[0,2999.4,1018],[0,2999.4,1054],[0,2945.4,1054]],0,
[0,"#0000ff"]],
[3,2972.4,1039.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,2972.4,21298,65.9988,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,2972.4,21301.7,"gnome-dbg","14px serif",[0,"#000000"],0],
[1,[0,[0,5454.4,23642],[0,5508.4,23642],[0,5508.4,23678],[0,5454.4,23678]],
0,[0,"#0000ff"]],
[3,5481.4,23663.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,2972.4,13966,73.0008,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,2972.4,13969.7,"kde-full (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,23244,60.9984,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23247.7,"mew-beta","14px serif",[0,"#000000"],0],
[2,8076.4,23298,34.9999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23301.7,"mew","14px serif",[0,"#000000"],0],
[2,831.43,15746,61.9992,18.5,[0,"#ffacac"],[0,"#000000"]],
[3,831.43,15749.7,"mn-fit-dev","14px serif",[0,"#000000"],0],
[2,8076.4,14688,146.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,14691.7,"monodevelop-debugger-gdb","14px serif",[0,"#000000"],0],
[2,831.43,77,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,80.7,"mpg123-el","14px serif",[0,"#000000"],0],
[1,[0,[0,2945.4,59],[0,2999.4,59],[0,2999.4,95],[0,2945.4,95]],0,
[0,"#0000ff"]],
[3,2972.4,80.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,5481.4,4900,128.002,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,5481.4,4903.7,"mysqmail-courier-logger","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,4882],[0,8103.4,4882],[0,8103.4,4918],[0,8049.4,4918]],0,
[0,"#0000ff"]],
[3,8076.4,4903.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,4738,132.998,18.5,[0,"#ffb5b5"],[0,"#000000"]],
[3,8076.4,4741.7,"mysqmail-dovecot-logger","14px serif",[0,"#000000"],0],
[2,5481.4,3457,140,18.5,[0,"#ffb6b6"],[0,"#000000"]],
[3,5481.4,3460.7,"mysqmail-pure-ftpd-logger","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,3382],[0,8103.4,3382],[0,8103.4,3418],[0,8049.4,3418]],0,
[0,"#0000ff"]],
[3,8076.4,3403.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,2972.4,3043,81,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,2972.4,3046.7,"nagiosgrapher","14px serif",[0,"#000000"],0],
[2,8076.4,17030,159.998,18.5,[0,"#fff0f0"],[0,"#000000"]],
[3,8076.4,17033.7,"network-manager-strongswan","14px serif",[0,"#000000"],
0],
[2,5481.4,10274,112,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,10277.7,"octave-pkg-dev (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,9428],[0,8103.4,9428],[0,8103.4,9464],[0,8049.4,9464]],0,
[0,"#0000ff"]],
[3,8076.4,9449.6,"DEP","14px serif",[0,"#0000ff"],0],
[1,[0,[0,8049.4,9482],[0,8103.4,9482],[0,8103.4,9518],[0,8049.4,9518]],0,
[0,"#0000ff"]],
[3,8076.4,9503.6,"DEP","14px serif",[0,"#0000ff"],0],
[1,[0,[0,8049.4,9590],[0,8103.4,9590],[0,8103.4,9626],[0,8049.4,9626]],0,
[0,"#0000ff"]],
[3,8076.4,9611.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,5481.4,7514,64.0008,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,7517.7,"open-cobol","14px serif",[0,"#000000"],0],
[2,8076.4,23806,128.002,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23809.7,"open-font-design-toolkit","14px serif",[0,"#000000"],0],
[2,5481.4,10328,148,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,10331.7,"openafs-modules-dkms (x 4)","14px serif",[0,"#000000"],
0],
[2,8076.4,15646,96.9984,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,15649.7,"openoffice.org-gcj","14px serif",[0,"#000000"],0],
[2,8076.4,13612,101.002,18.5,[0,"#ffe6e6"],[0,"#000000"]],
[3,8076.4,13615.7,"openoffice.org-kde","14px serif",[0,"#000000"],0],
[2,5481.4,8046,99,18.5,[0,"#ffb9b9"],[0,"#000000"]],
[3,5481.4,8049.7,"libsaml2-dev (x 3)","14px serif",[0,"#000000"],0],
[2,8076.4,13720,38.0016,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,13723.7,"oxine","14px serif",[0,"#000000"],0],
[2,10499,2606,141.001,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,2609.7,"libapache2-mod-passenger","14px serif",[0,"#000000"],0],
[1,[0,[0,12815,2437],[0,12869,2437],[0,12869,2473],[0,12815,2473]],0,
[0,"#0000ff"]],
[3,12842,2458.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,10499,2806,73.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,2809.7,"pcp-gui (x 8)","14px serif",[0,"#000000"],0],
[2,5481.4,6470,97.9992,18.5,[0,"#ffd4d4"],[0,"#000000"]],
[3,5481.4,6473.7,"pfqueue-dbg (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,6452],[0,8103.4,6452],[0,8103.4,6488],[0,8049.4,6488]],0,
[0,"#0000ff"]],
[3,8076.4,6473.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,831.43,20548,101.999,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,831.43,20551.7,"pidgin-awayonlock","14px serif",[0,"#000000"],0],
[1,[0,[0,2945.4,20530],[0,2999.4,20530],[0,2999.4,20566],[0,2945.4,20566]],
0,[0,"#0000ff"]],
[3,2972.4,20551.6,"DEP","14px serif",[0,"#0000ff"],0],
[1,[0,[0,2945.4,20304],[0,2999.4,20304],[0,2999.4,20340],[0,2945.4,20340]],
0,[0,"#0000ff"]],
[3,2972.4,20325.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,5481.4,18512,115.999,18.5,[0,"#ff8787"],[0,"#000000"]],
[3,5481.4,18515.7,"deskbar-plugins-pinot","14px serif",[0,"#000000"],0],
[2,8076.4,17084,74.9988,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,17087.7,"knm-runtime","14px serif",[0,"#000000"],0],
[2,2972.4,10466,63,18.5,[0,"#ffa7a7"],[0,"#000000"]],
[3,2972.4,10469.7,"libqgis-dev","14px serif",[0,"#000000"],0],
[2,8076.4,12346,41.0004,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,12349.7,"qt-sdk","14px serif",[0,"#000000"],0],
[2,8076.4,12562,131,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,8076.4,12565.7,"quassel-client-kde4 (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,12130,104,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,12133.7,"quassel-client (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,16278,113,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,16281.7,"r-base-core-dbg (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,7418,132.998,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,7421.7,"redhat-cluster-suite (x 2)","14px serif",[0,"#000000"],0],
[2,2972.4,7840,90,18.5,[0,"#ffdada"],[0,"#000000"]],
[3,2972.4,7843.7,"librdf0-dev (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,23860,177.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23863.7,"rhythmbox-plugin-coherence (x 2)","14px serif",
[0,"#000000"],0],
[2,10499,2914,56.0016,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,10499,2917.7,"runit-run","14px serif",[0,"#000000"],0],
[2,5481.4,4992,79.9992,18.5,[0,"#ffc8c8"],[0,"#000000"]],
[3,5481.4,4995.7,"sa-learn-cyrus","14px serif",[0,"#000000"],0],
[2,5481.4,22839,51.9984,18.5,[0,"#fff7f7"],[0,"#000000"]],
[3,5481.4,22842.7,"sabayon","14px serif",[0,"#000000"],0],
[2,8076.4,23352,37.0008,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23355.7,"sepia","14px serif",[0,"#000000"],0],
[2,8076.4,17538,70.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,17541.7,"libsoqt3-dev","14px serif",[0,"#000000"],0],
[2,8076.4,15484,70.9992,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,15487.7,"libsoqt4-dev","14px serif",[0,"#000000"],0],
[2,5481.4,8860,69.0012,18.5,[0,"#ffcfcf"],[0,"#000000"]],
[3,5481.4,8863.7,"libsqlxx-dev","14px serif",[0,"#000000"],0],
[2,8076.4,23498,90,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,23501.7,"startupmanager","14px serif",[0,"#000000"],0],
[2,5481.4,9284,105.998,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,9287.7,"strongswan-starter","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,9266],[0,8103.4,9266],[0,8103.4,9302],[0,8049.4,9302]],0,
[0,"#0000ff"]],
[3,8076.4,9287.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,9176,69.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,9179.7,"strongswan","14px serif",[0,"#000000"],0],
[2,8076.4,17960,132.001,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,8076.4,17963.7,"python-jarabe-0.84 (x 4)","14px serif",[0,"#000000"],0],
[2,2972.4,16548,74.0016,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,2972.4,16551.7,"sucrose-0.84","14px serif",[0,"#000000"],0],
[2,8076.4,15862,137.002,18.5,[0,"#ffbdbd"],[0,"#000000"]],
[3,8076.4,15865.7,"sugar-emulator-0.84 (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,16440,132.001,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,8076.4,16443.7,"python-jarabe-0.86 (x 4)","14px serif",[0,"#000000"],0],
[2,5481.4,16440,74.0016,18.5,[0,"#ffbaba"],[0,"#000000"]],
[3,5481.4,16443.7,"sucrose-0.86","14px serif",[0,"#000000"],0],
[2,8076.4,14742,137.002,18.5,[0,"#ffbdbd"],[0,"#000000"]],
[3,8076.4,14745.7,"sugar-emulator-0.86 (x 2)","14px serif",[0,"#000000"],0],
[2,8076.4,17868,132.001,18.5,[0,"#ffbfbf"],[0,"#000000"]],
[3,8076.4,17871.7,"python-jarabe-0.88 (x 4)","14px serif",[0,"#000000"],0],
[2,5481.4,16494,74.0016,18.5,[0,"#ffb9b9"],[0,"#000000"]],
[3,5481.4,16497.7,"sucrose-0.88","14px serif",[0,"#000000"],0],
[2,8076.4,15186,137.002,18.5,[0,"#ffbcbc"],[0,"#000000"]],
[3,8076.4,15189.7,"sugar-emulator-0.88 (x 2)","14px serif",[0,"#000000"],0],
[1,[0,[0,10472,15374],[0,10526,15374],[0,10526,15410],[0,10472,15410]],0,
[0,"#0000ff"]],
[3,10499,15395.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,5481.4,18566,123.998,18.5,[0,"#ffdede"],[0,"#000000"]],
[3,5481.4,18569.7,"sugar-calculate-activity","14px serif",[0,"#000000"],0],
[1,[0,[0,8049.4,15374],[0,8103.4,15374],[0,8103.4,15410],[0,8049.4,15410]],
0,[0,"#0000ff"]],
[3,8076.4,15395.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,8076.4,23406,63,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,8076.4,23409.7,"tipptrainer","14px serif",[0,"#000000"],0],
[2,8076.4,5392,57.9996,18.5,[0,"#ffebeb"],[0,"#000000"]],
[3,8076.4,5395.7,"uucpsend","14px serif",[0,"#000000"],0],
[2,8076.4,10928,86.0004,18.5,[0,"#ffb9b9"],[0,"#000000"]],
[3,8076.4,10931.7,"libvtk5-qt3-dev","14px serif",[0,"#000000"],0],
[2,8076.4,11182,86.0004,18.5,[0,"#ffb9b9"],[0,"#000000"]],
[3,8076.4,11185.7,"libvtk5-qt4-dev","14px serif",[0,"#000000"],0],
[2,8076.4,10328,115.999,18.5,[0,"#ffc2c2"],[0,"#000000"]],
[3,8076.4,10331.7,"libwtdbopostgres-dev","14px serif",[0,"#000000"],0],
[2,2972.4,17230,36,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,2972.4,17233.7,"ytalk","14px serif",[0,"#000000"],0],
[1,[0,[0,5454.4,17212],[0,5508.4,17212],[0,5508.4,17248],[0,5454.4,17248]],
0,[0,"#ee82ee"]],
[3,5481.4,17233.6,"DEP","14px serif",[0,"#ee82ee"],0],
[1,[0,[0,5454.4,17266],[0,5508.4,17266],[0,5508.4,17302],[0,5454.4,17302]],
0,[0,"#0000ff"]],
[3,5481.4,17287.6,"DEP","14px serif",[0,"#0000ff"],0],
[2,2972.4,20376,101.999,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,2972.4,20379.7,"libzbarqt-dev (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,2156,69.0012,18.5,[0,"#ffffff"],[0,"#000000"]],
[3,5481.4,2159.7,"zoneminder","14px serif",[0,"#000000"],0],
[2,8076.4,18366,97.9992,18.5,[0,"#ffc0c0"],[0,"#000000"]],
[3,8076.4,18369.7,"libcgal-demo (x 2)","14px serif",[0,"#000000"],0],
[2,5481.4,21490,151.999,18.5,[0,"#ffe1e1"],[0,"#000000"]],
[3,5481.4,21493.7,"nvidia-glx-legacy-173xx-ia32","14px serif",
[0,"#000000"],0],
[0,[0,[0,13015,17990],[1,13462,17990,14645,17990,15003,17990]],0,
[0,"#ff0000"]],
[0,
[0,[0,8125.8,17435.5],[1,8165,17440.2,8220.9,17447.7,8269.4,17457],
[1,9196.5,17635.1,9407.3,17775.1,10332,17963],
[1,10355,17967.6,10380,17972,10403,17975.8]],
0,[0,"#ff0000"]],
[0,[0,[0,3048.5,21723.3],[1,3417,21734.6,5013.7,21783.6,5398,21795.4]],0,
[0,"#ff0000"]],
[0,[0,[0,10592,17407],[1,10969,17407,12393,17407,12757,17407]],0,
[0,"#ff0000"]],
[0,[0,[0,936.87,1640],[1,1309.9,1635,2562.7,1619,2892.4,1615]],0,
[0,"#ff0000"]],
[0,[0,[0,3061.7,1668],[1,3461,1668,5077.9,1668,5418.3,1668]],0,
[0,"#ff0000"]],
[0,[0,[0,5544.9,21248.7],[1,5905,21247.2,7685.9,21239.7,8021.7,21238.2]],0,
[0,"#ff0000"]],
[0,
[0,[0,8151.9,9713],[1,8436.9,9763,9475.5,9943,10332,10085],
[1,10360,10090,10391,10095,10418,10099]],
0,[0,"#ff0000"]],
[0,[0,[0,5532.7,22068.6],[1,5860.7,22066.2,7663.1,22053,8016.4,22050.4]],0,
[0,"#ff0000"]],
[0,[0,[0,10568,23406],[1,10909,23406,12433,23406,12774,23406]],0,
[0,"#ff0000"]],
[0,[0,[0,880.43,1490],[1,1176.4,1487,2720.6,1471,2945.2,1468]],0,
[0,"#ff0000"]],
[0,[0,[0,3054.5,3197],[1,3434.4,3200,5020.4,3215,5399.7,3218]],0,
[0,"#ff0000"]],
[0,[0,[0,10596,23352],[1,10994,23352,12504,23352,12794,23352]],0,
[0,"#ff0000"]],
[0,[0,[0,10600,10621],[1,10985,10621,12356,10621,12741,10621]],0,
[0,"#ff0000"]],
[0,[0,[0,8147,22218],[1,8503,22218,10099,22218,10436,22218]],0,
[0,"#ff0000"]],
[0,[0,[0,8125.7,2729],[1,8438.2,2725,10143,2703,10451,2699]],0,
[0,"#ff0000"]],
[0,[0,[0,5592.1,16760.5],[1,6017,16724.2,7541.3,16593.8,7965.9,16557.5]],0,
[0,"#ff0000"]],
[0,[0,[0,5610.1,16602],[1,6052.2,16602,7505.7,16602,7947.7,16602]],0,
[0,"#ff0000"]],
[0,[0,[0,5623.3,16545],[1,6075.8,16535.6,7482.1,16506.4,7934.6,16497]],0,
[0,"#ff0000"]],
[0,[0,[0,10619,15585.5],[1,11308,15548.3,14740,15362.8,15080,15344.5]],0,
[0,"#ff0000"]],
[0,[0,[0,12968,15275],[1,13407,15289,14864,15335.3,15080,15342.1]],0,
[0,"#ff0000"]],
[0,[0,[0,12971,15343],[1,13414,15343,14863,15343,15080,15343]],0,
[0,"#ff0000"]],
[0,[0,[0,10606,14178],[1,11031,14168,12591,14132,12815,14127]],0,
[0,"#ff0000"]],
[0,[0,[0,10606,14074],[1,11031,14084,12591,14120,12815,14125]],0,
[0,"#ff0000"]],
[0,[0,[0,10607,14126],[1,11033,14126,12591,14126,12815,14126]],0,
[0,"#ff0000"]],
[0,[0,[0,8161.6,22272],[1,8542.6,22272,10087,22272,10431,22272]],0,
[0,"#ff0000"]],
[0,[0,[0,8148,13666],[1,8520.9,13666,10235,13666,10472,13666]],0,
[0,"#ff0000"]],
[0,
[0,[0,8150.1,12768],[1,8186.4,12772,8230.7,12779,8269.4,12789],
[1,9208.5,13036,10289,13561,10472,13652]],
0,[0,"#ff0000"]],
[0,
[0,[0,8153.2,15753.8],[1,8189.9,15751.1,8233.5,15744,8269.4,15727],
[1,9409.8,15186.6,10367,13855,10487,13684]],
0,[0,"#ff0000"]],
[0,[0,[0,8156.7,22326],[1,8524.3,22326,10045,22326,10417,22326]],0,
[0,"#ff0000"]],
[0,[0,[0,5523,15970],[1,5833.6,15970,7787.8,15970,8047.8,15970]],0,
[0,"#ff0000"]],
[0,[0,[0,10571,11157],[1,10938,11109,12584,10889,12815,10859]],0,
[0,"#ff0000"]],
[0,[0,[0,10580,10718],[1,10964,10741,12586,10839,12815,10853]],0,
[0,"#ff0000"]],
[0,[0,[0,10527,10912],[1,10770,10906,12572,10862,12815,10856]],0,
[0,"#ff0000"]],
[0,[0,[0,10575,10772],[1,10948,10794,12584,10893,12815,10907]],0,
[0,"#ff0000"]],
[0,[0,[0,10575,11159],[1,10948,11118,12584,10937,12815,10912]],0,
[0,"#ff0000"]],
[0,[0,[0,10527,10913],[1,10770,10913,12572,10909,12815,10909]],0,
[0,"#ff0000"]],
[0,[0,[0,5515.7,1514],[1,5793.9,1514,7683,1514,8023.8,1514]],0,
[0,"#ff0000"]],
[0,[0,[0,5599.2,11234],[1,6042.5,11234,7604.1,11236,7989.8,11236]],0,
[0,"#ff0000"]],
[0,[0,[0,5582,11286],[1,6000.3,11278,7599.8,11246,7990.1,11238]],0,
[0,"#ff0000"]],
[0,
[0,[0,3012.7,21577.1],[1,3236.6,21505.6,4352.1,21155.1,5286.4,20965],
[1,5343.5,20953.4,5411.1,20945.3,5449.8,20941.1]],
0,[0,"#ff0000"]],
[0,[0,[0,3029.5,21592.3],[1,3369.5,21605.8,5121.7,21675.7,5433.8,21688.1]],
0,[0,"#ff0000"]],
[0,[0,[0,10587,23589],[1,10960,23627.6,12415,23777.8,12766,23814.1]],0,
[0,"#ff0000"]],
[0,
[0,[0,3023.4,15400.7],[1,3269.6,15322.8,4362.2,14988.3,5286.4,14883],
[1,6603.7,14733,6944.8,14828.4,8269.4,14883],
[1,9096.2,14917,10091,15021.8,10402,15056.1]],
0,[0,"#ff0000"]],
[0,[0,[0,10594,12475],[1,10980,12448,12433,12349,12772,12326]],0,
[0,"#ff0000"]],
[0,[0,[0,3020,20268.2],[1,3322.9,20269.7,4981.2,20277.6,5390.2,20279.6]],0,
[0,"#ff0000"]],
[0,[0,[0,8205,12295],[1,8634,12304,10011,12335,10398,12344]],0,
[0,"#ff0000"]],
[0,[0,[0,8159.5,12044],[1,8532.3,12073,10049,12189,10418,12217]],0,
[0,"#ff0000"]],
[0,[0,[0,5530.9,21851.2],[1,5845.4,21846.4,7564.1,21819.9,7983.9,21813.4]],
0,[0,"#ff0000"]],
[0,[0,[0,8205.8,14219],[1,8633.5,14222,9996.8,14231,10391,14233]],0,
[0,"#ff0000"]],
[0,[0,[0,10609,23028],[1,11000,23028,12329,23028,12728,23028]],0,
[0,"#ff0000"]],
[0,
[0,[0,8137.8,18167.3],[1,8176.9,18156.5,8227.9,18139.7,8269.4,18117],
[1,9300.6,17553.2,9258.4,16940.1,10332,16463],
[1,10379,16442.5,10438,16437.4,10472,16436.2]],
0,[0,"#ff0000"]],
[0,
[0,[0,8117.8,17618.2],[1,8157.4,17606.5,8218.5,17587,8269.4,17565],
[1,9223.7,17152.8,9347.5,16795.4,10332,16463],
[1,10380,16446.9,10439,16440.3,10472,16437.6]],
0,[0,"#ff0000"]],
[0,
[0,[0,8112.5,18072.7],[1,8152,18053.4,8216.6,18020.4,8269.4,17987],
[1,9233.3,17378.4,9281.7,16905.1,10332,16463],
[1,10379,16443.4,10438,16438,10472,16436.5]],
0,[0,"#ff0000"]],
[0,[0,[0,5571.9,21344.8],[1,5963.9,21348.5,7516.4,21362.8,7958.4,21366.9]],
0,[0,"#ff0000"]],
[0,[0,[0,5620.9,17039.6],[1,6059.8,17057.2,7411.8,17111.4,7899.1,17130.9]],
0,[0,"#ff0000"]],
[0,[0,[0,8217.6,2158],[1,8647.1,2165,9934.4,2185,10361,2192]],0,
[0,"#ff0000"]],
[0,
[0,[0,5518.2,12963],[1,5736.8,13064,6888.6,13588,7883.4,13839],
[1,7913.8,13847,7947.4,13852,7977.9,13856]],
0,[0,"#ff0000"]],
[0,[0,[0,3143.9,12946],[1,3622.9,12946,4966.5,12946,5367.2,12946]],0,
[0,"#ff0000"]],
[0,[0,[0,10598,12957],[1,10987,12957,12408,12957,12762,12957]],0,
[0,"#ff0000"]],
[0,[0,[0,12887,2623],[1,13172,2623,14754,2623,15057,2623]],0,[0,"#ff0000"]],
[0,[0,[0,12911,2800],[1,13251,2773,14766,2651,15058,2627]],0,[0,"#ff0000"]],
[0,
[0,[0,5493.8,17612.3],[1,5526.5,17565,5616.7,17431,5676.4,17311],
[1,6870.5,14910.6,5800.6,13385,7883.4,11697],
[1,8678.3,11053,10064,11197,10416,11246]],
0,[0,"#ff0000"]],
[0,[0,[0,5595.9,24001],[1,6039.5,24024,7639.1,24107.2,8002.6,24126.2]],0,
[0,"#ff0000"]],
[0,[0,[0,8208.9,24492],[1,8678.2,24492,10247,24492,10472,24492]],0,
[0,"#ff0000"]],
[0,[0,[0,8136.3,24544.7],[1,8483.8,24536.9,10233,24497.9,10472,24492.6]],0,
[0,"#ff0000"]],
[0,[0,[0,8151.6,24439.7],[1,8532,24448.2,10236,24486.1,10472,24491.4]],0,
[0,"#ff0000"]],
[0,[0,[0,8207.1,24489.1],[1,8674.3,24478.7,10246,24443.7,10472,24438.6]],0,
[0,"#ff0000"]],
[0,
[0,[0,8164.1,23924.8],[1,8197.2,23929.2,8235.1,23934.8,8269.4,23941],
[1,9181.3,24106.1,10286,24383.8,10472,24431.1]],
0,[0,"#ff0000"]],
[0,[0,[0,8151.9,24438],[1,8533,24438,10236,24438,10472,24438]],0,
[0,"#ff0000"]],
[0,[0,[0,10595,7707],[1,10995,7701,12537,7680,12803,7677]],0,[0,"#ff0000"]],
[0,
[0,[0,8175.9,2667],[1,8209.7,2670,8245.1,2679,8269.4,2703],
[1,12820,7234,5830.6,12424,10332,17003],
[1,10344,17014.7,10358,17022.6,10374,17027.8]],
0,[0,"#ff0000"]],
[0,[0,[0,884.62,1360],[1,1180.2,1360,2617.6,1360,2917.5,1360]],0,
[0,"#ff0000"]],
[0,[0,[0,8133,6778],[1,8457.8,6775,10081,6765,10432,6762]],0,[0,"#ff0000"]],
[0,[0,[0,5563,7898],[1,5940.6,7900,7518.5,7912,7960.7,7915]],0,
[0,"#ff0000"]],
[0,[0,[0,8135.1,14272],[1,8462.8,14275,10064,14285,10426,14288]],0,
[0,"#ff0000"]],
[0,[0,[0,8169.2,22380],[1,8561.2,22380,10078,22380,10427,22380]],0,
[0,"#ff0000"]],
[0,[0,[0,5566.3,20885.3],[1,5965.4,20891.5,7650.9,20917.4,8009.3,20923]],0,
[0,"#ff0000"]],
[0,[0,[0,10579,23248.9],[1,10948,23252.8,12479,23269.1,12788,23272.4]],0,
[0,"#ff0000"]],
[0,
[0,[0,10585,16989.5],[1,10611,16993.7,10640,16998.4,10666,17003],
[1,11504,17148.5,12520,17344.5,12780,17394.8]],
0,[0,"#ff0000"]],
[0,[0,[0,8194.1,16976],[1,8601.2,16976,9947.5,16976,10371,16976]],0,
[0,"#ff0000"]],
[0,
[0,[0,8173.8,8950],[1,8204.6,8946,8238.7,8940,8269.4,8933],
[1,9212,8708,9392.3,8462,10332,8227],
[1,10381,8215,10439,8207,10472,8203]],
0,[0,"#ff0000"]],
[0,[0,[0,8138.8,8520],[1,8491.9,8472,10234,8236,10472,8204]],0,
[0,"#ff0000"]],
[0,
[0,[0,8152.1,8572],[1,8187.7,8567,8230.8,8561,8269.4,8555],
[1,8729.1,8486,10250,8240,10472,8204]],
0,[0,"#ff0000"]],
[0,
[0,[0,8171.5,9331],[1,8203.2,9327,8238.2,9321,8269.4,9311],
[1,9248.2,9007,9357,8595,10332,8281],
[1,10380,8266,10439,8259,10472,8256]],
0,[0,"#ff0000"]],
[0,[0,[0,8140.9,8521],[1,8498.8,8480,10233,8284,10472,8257]],0,
[0,"#ff0000"]],
[0,[0,[0,8152.3,8572],[1,8534,8520,10236,8290,10472,8258]],0,[0,"#ff0000"]],
[0,[0,[0,10654,23190],[1,11075,23190,12243,23190,12677,23190]],0,
[0,"#ff0000"]],
[0,[0,[0,8184.5,13469],[1,8572.5,13481,9896.5,13521,10348,13534]],0,
[0,"#ff0000"]],
[0,[0,[0,5589.2,13466],[1,6010.3,13466,7542,13466,7966.6,13466]],0,
[0,"#ff0000"]],
[0,
[0,[0,8158.8,24086],[1,8193.1,24090.6,8233.3,24096.5,8269.4,24103],
[1,9181.3,24268.1,10286,24545.8,10472,24593.1]],
0,[0,"#ff0000"]],
[0,
[0,[0,8165.7,23978.1],[1,8198.5,23982.4,8235.8,23988.1,8269.4,23995],
[1,9187.6,24183,10287,24531.7,10472,24591.2]],
0,[0,"#ff0000"]],
[0,[0,[0,8176.3,24755.3],[1,8600.4,24727,10240,24617.3,10472,24601.8]],0,
[0,"#ff0000"]],
[0,
[0,[0,8163.2,24032.2],[1,8196.5,24036.6,8234.9,24042.3,8269.4,24049],
[1,9184.2,24225.5,10287,24538.8,10472,24592.2]],
0,[0,"#ff0000"]],
[0,[0,[0,8178.6,24703.4],[1,8606.3,24684.4,10241,24611.5,10472,24601.2]],0,
[0,"#ff0000"]],
[0,[0,[0,8179.8,24600],[1,8609.3,24600,10242,24600,10472,24600]],0,
[0,"#ff0000"]],
[0,[0,[0,8214.5,24650.9],[1,8690.6,24640.3,10247,24605.6,10472,24600.6]],0,
[0,"#ff0000"]],
[0,[0,[0,5543.7,18779.2],[1,5890.3,18763.4,7582.3,18686.5,7988.6,18668]],0,
[0,"#ff0000"]],
[0,[0,[0,5548.5,8303],[1,5910.2,8300,7625.4,8287,8002.9,8285]],0,
[0,"#ff0000"]],
[0,[0,[0,8126.8,10842],[1,8433.8,10877,10054,11062,10424,11104]],0,
[0,"#ff0000"]],
[0,[0,[0,10609,18044],[1,11017,18044,12438,18044,12772,18044]],0,
[0,"#ff0000"]],
[0,[0,[0,8140,9802],[1,8477,9854,10054,10097,10422,10154]],0,[0,"#ff0000"]],
[0,[0,[0,5563.4,18183.7],[1,5948.8,18191.7,7579.4,18225.7,7984.8,18234.1]],
0,[0,"#ff0000"]],
[0,[0,[0,8171.4,24374.8],[1,8566.8,24336.4,10078,24189.9,10427,24156]],0,
[0,"#ff0000"]],
[0,[0,[0,10617,21871.2],[1,11022,21875.3,12350,21889,12736,21892.9]],0,
[0,"#ff0000"]],
[0,[0,[0,5557.7,3307],[1,5931.6,3288,7569.8,3206,7982,3186]],0,
[0,"#ff0000"]],
[0,[0,[0,3088,3097],[1,3511.1,3095,4972.2,3091,5376.8,3089]],0,
[0,"#ff0000"]],
[0,[0,[0,8174.8,6240],[1,8575,6274,10076,6402,10426,6432]],0,[0,"#ff0000"]],
[0,
[0,[0,8156.3,24262.8],[1,8191,24257.1,8232.2,24250.2,8269.4,24244],
[1,9126.3,24100.2,10168,23921.9,10435,23876.1]],
0,[0,"#ff0000"]],
[0,[0,[0,3063.6,1252],[1,3468.1,1252,5095.7,1252,5423.7,1252]],0,
[0,"#ff0000"]],
[0,[0,[0,937.24,1280],[1,1311.3,1285,2566.4,1301,2893.8,1305]],0,
[0,"#ff0000"]],
[0,[0,[0,10527,7379],[1,10770,7385,12572,7431,12815,7437]],0,[0,"#ff0000"]],
[0,[0,[0,10556,7184],[1,10888,7221,12581,7409,12815,7435]],0,[0,"#ff0000"]],
[0,
[0,[0,10513,4811],[1,10688,5032,12506,7323,12662,7411],
[1,12711,7438,12778,7441,12815,7440]],
0,[0,"#ff0000"]],
[0,[0,[0,10527,13279],[1,10760,13290,12434,13364,12780,13379]],0,
[0,"#ff0000"]],
[0,[0,[0,15200,16158.1],[1,15491,16167.9,16388,16198.1,16642,16206.7]],0,
[0,"#ff0000"]],
[0,[0,[0,15167,16209],[1,15417,16209,16376,16209,16642,16209]],0,
[0,"#ff0000"]],
[0,[0,[0,15166,16263],[1,15413,16263,16369,16263,16639,16263]],0,
[0,"#ff0000"]],
[0,[0,[0,15165,16261],[1,15413,16252.7,16377,16220.2,16642,16211.3]],0,
[0,"#ff0000"]],
[0,[0,[0,10555,9838],[1,10884,9816,12580,9701,12815,9685]],0,[0,"#ff0000"]],
[0,[0,[0,10549,9696],[1,10864,9694,12577,9684,12815,9683]],0,[0,"#ff0000"]],
[0,[0,[0,10566,9591],[1,10920,9605,12582,9672,12815,9682]],0,[0,"#ff0000"]],
[0,[0,[0,10573,9643],[1,10941,9650,12583,9678,12815,9683]],0,[0,"#ff0000"]],
[0,[0,[0,10566,9536],[1,10921,9546,12582,9594,12815,9601]],0,[0,"#ff0000"]],
[0,[0,[0,10549,9694],[1,10862,9681,12579,9613,12815,9603]],0,[0,"#ff0000"]],
[0,[0,[0,10567,9588],[1,10923,9591,12582,9600,12815,9602]],0,[0,"#ff0000"]],
[0,[0,[0,10573,9641],[1,10941,9634,12583,9606,12815,9602]],0,[0,"#ff0000"]],
[0,
[0,[0,8131.1,10685],[1,8404.2,10663,9647.6,10566,10666,10594],
[1,11550,10618,12632,10697,12815,10711]],
0,[0,"#ff0000"]],
[0,[0,[0,10584,10713],[1,10972,10713,12586,10713,12815,10713]],0,
[0,"#ff0000"]],
[0,[0,[0,10527,10911],[1,10770,10890,12572,10736,12815,10715]],0,
[0,"#ff0000"]],
[0,
[0,[0,8132.9,10689],[1,8409.8,10685,9650.4,10667,10666,10686],
[1,11549,10702,12632,10756,12815,10766]],
0,[0,"#ff0000"]],
[0,[0,[0,10578,10767],[1,10956,10767,12585,10767,12815,10767]],0,
[0,"#ff0000"]],
[0,[0,[0,10527,10911],[1,10770,10896,12572,10784,12815,10769]],0,
[0,"#ff0000"]],
[0,
[0,[0,8108.3,12402],[1,8148.4,12403,8218.2,12401,8269.4,12373],
[1,9503,11700,9106.1,10663,10332,9977],
[1,10352,9966,10375,9959,10398,9955]],
0,[0,"#ff0000"]],
[0,[0,[0,5534.1,14910],[1,5873.2,14910,7741.8,14910,8037.1,14910]],0,
[0,"#ff0000"]],
[0,[0,[0,8178.6,12617],[1,8574,12622,10001.5,12637,10397,12642]],0,
[0,"#ff0000"]],
[0,[0,[0,5622.3,16024],[1,6100.5,16024,7651.1,16024,8004.4,16024]],0,
[0,"#ff0000"]],
[0,
[0,[0,5576.1,18449.8],[1,5608.3,18445.8,5644.3,18439.8,5676.4,18431],
[1,6701.7,18151.4,6858.4,17791.4,7883.4,17511],
[1,7916.6,17501.9,7953.8,17495.8,7986.6,17491.7]],
0,[0,"#ff0000"]],
[0,
[0,[0,10535,13982],[1,10569,13998,10621,14022,10666,14045],
[1,11551,14487,12615,15069.3,12811,15176.6]],
0,[0,"#ff0000"]],
[0,[0,[0,10544,9371],[1,10845,9364,12576,9324,12815,9319]],0,[0,"#ff0000"]],
[0,[0,[0,10587,9318],[1,10982,9318,12587,9318,12815,9318]],0,[0,"#ff0000"]],
[0,[0,[0,10623,9267],[1,11070,9277,12593,9312,12815,9317]],0,[0,"#ff0000"]],
[0,[0,[0,10544,9370],[1,10845,9356,12576,9276,12815,9265]],0,[0,"#ff0000"]],
[0,[0,[0,10587,9316],[1,10981,9307,12587,9270,12815,9265]],0,[0,"#ff0000"]],
[0,[0,[0,10596,9176],[1,11007,9192,12589,9254,12815,9263]],0,[0,"#ff0000"]],
[0,[0,[0,10544,9372],[1,10846,9372,12577,9372,12815,9372]],0,[0,"#ff0000"]],
[0,[0,[0,10551,9425],[1,10870,9417,12578,9378,12815,9373]],0,[0,"#ff0000"]],
[0,[0,[0,10587,9320],[1,10981,9329,12587,9366,12815,9371]],0,[0,"#ff0000"]],
[0,[0,[0,10552,7435],[1,10860,7455,12439,7558,12778,7580]],0,[0,"#ff0000"]],
[0,[0,[0,10551,7427],[1,10861,7400,12476,7255,12790,7227]],0,[0,"#ff0000"]],
[0,[0,[0,10590,4053],[1,10989,4048,12586,4030,12815,4027]],0,[0,"#ff0000"]],
[0,
[0,[0,8149.6,3958],[1,8456.3,3958,9669.4,3958,10666,3973],
[1,11549,3987,12632,4020,12815,4026]],
0,[0,"#ff0000"]],
[0,[0,[0,10562,4001],[1,10909,4005,12582,4024,12815,4027]],0,[0,"#ff0000"]],
[0,[0,[0,10546,4106],[1,10853,4096,12578,4036,12815,4028]],0,[0,"#ff0000"]],
[0,[0,[0,8144.7,10790],[1,8489.7,10829,10039,11006,10416,11049]],0,
[0,"#ff0000"]],
[0,[0,[0,10579,16383.8],[1,10960,16392.6,12586,16430.1,12815,16435.4]],0,
[0,"#ff0000"]],
[0,[0,[0,10582,16750.5],[1,10968,16696.8,12585,16471.8,12815,16439.8]],0,
[0,"#ff0000"]],
[0,[0,[0,10543,16489],[1,10843,16482.1,12576,16442.1,12815,16436.6]],0,
[0,"#ff0000"]],
[0,[0,[0,10567,16331.1],[1,10924,16347.6,12582,16424,12815,16434.7]],0,
[0,"#ff0000"]],
[0,[0,[0,10551,9479],[1,10870,9471,12578,9432,12815,9427]],0,[0,"#ff0000"]],
[0,[0,[0,10544,9373],[1,10845,9380,12576,9420,12815,9425]],0,[0,"#ff0000"]],
[0,[0,[0,10585,9322],[1,10976,9340,12586,9414,12815,9425]],0,[0,"#ff0000"]],
[0,[0,[0,5563.7,1092],[1,5975.8,1100,7804.7,1138,8049.4,1143]],0,
[0,"#ff0000"]],
[0,[0,[0,5560.2,1144],[1,5965,1144,7803.3,1144,8049.2,1144]],0,
[0,"#ff0000"]],
[0,[0,[0,5592.1,1196],[1,6053.3,1186,7809.6,1150,8049.3,1145]],0,
[0,"#ff0000"]],
[0,[0,[0,5563.4,818],[1,5974.8,810,7804.6,772,8049.3,767]],0,[0,"#ff0000"]],
[0,[0,[0,5559.4,714],[1,5962.9,722,7803,760,8049.2,765]],0,[0,"#ff0000"]],
[0,[0,[0,5592.1,766],[1,6053.3,766,7809.6,766,8049.3,766]],0,[0,"#ff0000"]],
[0,[0,[0,8159.1,2301],[1,8553.9,2299,10237,2288,10472,2286]],0,
[0,"#ff0000"]],
[0,[0,[0,8156.4,2663],[1,8545.9,2600,10236,2328,10472,2290]],0,
[0,"#ff0000"]],
[0,[0,[0,8150.6,2249],[1,8529,2255,10236,2282,10472,2286]],0,[0,"#ff0000"]],
[0,[0,[0,10601,15481.2],[1,11000,15470.1,12452,15429.8,12777,15420.8]],0,
[0,"#ff0000"]],
[0,[0,[0,5598.4,878],[1,6069,892,7810,947,8049.1,954]],0,[0,"#ff0000"]],
[0,[0,[0,5564.1,1033],[1,5976.9,1021,7804.9,963,8049.4,956]],0,
[0,"#ff0000"]],
[0,[0,[0,5560.5,929],[1,5966.1,933,7803.5,952,8049.2,955]],0,[0,"#ff0000"]],
[0,[0,[0,5592.9,981],[1,6055.4,976,7809.9,958,8049.3,955]],0,[0,"#ff0000"]],
[0,[0,[0,10599,4299],[1,11014,4261,12588,4118,12815,4097]],0,[0,"#ff0000"]],
[0,[0,[0,10590,4056],[1,10989,4063,12586,4091,12815,4095]],0,[0,"#ff0000"]],
[0,[0,[0,10562,4003],[1,10909,4017,12582,4084,12815,4094]],0,[0,"#ff0000"]],
[0,[0,[0,10546,4108],[1,10853,4106,12578,4096,12815,4095]],0,[0,"#ff0000"]],
[0,
[0,[0,10543,4291],[1,10577,4278,10625,4260,10666,4243],
[1,11552,3888,12631,3435,12815,3357]],
0,[0,"#ff0000"]],
[0,[0,[0,10561,2978],[1,10906,3034,12581,3304,12815,3342]],0,[0,"#ff0000"]],
[0,[0,[0,10551,3029],[1,10872,3074,12578,3309,12815,3342]],0,[0,"#ff0000"]],
[0,[0,[0,10546,3240],[1,10852,3254,12577,3334,12815,3345]],0,[0,"#ff0000"]],
[0,[0,[0,10530,3453],[1,10788,3441,12572,3358,12815,3347]],0,[0,"#ff0000"]],
[0,[0,[0,10562,3556],[1,10909,3524,12582,3370,12815,3348]],0,[0,"#ff0000"]],
[0,[0,[0,10599,3191],[1,11012,3219,12588,3328,12815,3344]],0,[0,"#ff0000"]],
[0,[0,[0,10580,3346],[1,10963,3346,12586,3346,12815,3346]],0,[0,"#ff0000"]],
[0,
[0,[0,10571,2871],[1,10600,2875,10635,2881,10666,2887],
[1,11552,3052,12631,3298,12815,3340]],
0,[0,"#ff0000"]],
[0,[0,[0,10609,3295],[1,11038,3304,12590,3340,12815,3345]],0,[0,"#ff0000"]],
[0,[0,[0,10556,3399],[1,10888,3391,12581,3352,12815,3347]],0,[0,"#ff0000"]],
[0,[0,[0,10561,3661],[1,10907,3614,12581,3382,12815,3350]],0,[0,"#ff0000"]],
[0,[0,[0,10541,3505],[1,10832,3485,12576,3364,12815,3348]],0,[0,"#ff0000"]],
[0,[0,[0,10547,3610],[1,10858,3575,12578,3376,12815,3349]],0,[0,"#ff0000"]],
[0,[0,[0,10572,3137],[1,10940,3171,12584,3322,12815,3344]],0,[0,"#ff0000"]],
[0,[0,[0,8145.4,7975],[1,8488.9,8000,10015,8111,10407,8139]],0,
[0,"#ff0000"]],
[0,[0,[0,8162,8624],[1,8561.9,8570,10239,8343,10472,8312]],0,[0,"#ff0000"]],
[0,[0,[0,8179,8629],[1,8607.3,8600,10241,8488,10472,8472]],0,[0,"#ff0000"]],
[0,[0,[0,8151.6,8735],[1,8532,8692,10236,8500,10472,8473]],0,[0,"#ff0000"]],
[0,
[0,[0,8163.4,9385],[1,8196.9,9381,8235.3,9374,8269.4,9365],
[1,9228.5,9101,9376.2,8771,10332,8497],
[1,10381,8483,10439,8476,10472,8472]],
0,[0,"#ff0000"]],
[0,[0,[0,8167.7,8626],[1,8560.6,8581,10102,8407,10436,8369]],0,
[0,"#ff0000"]],
[0,[0,[0,10594,10002],[1,11000,9992,12588,9956,12815,9951]],0,
[0,"#ff0000"]],
[0,[0,[0,10630,9899],[1,11086,9910,12594,9944,12815,9949]],0,[0,"#ff0000"]],
[0,[0,[0,10630,9797],[1,11087,9829,12594,9933,12815,9948]],0,[0,"#ff0000"]],
[0,[0,[0,10599,10053],[1,11014,10034,12588,9962,12815,9951]],0,
[0,"#ff0000"]],
[0,
[0,[0,8105.4,7292],[1,8143.4,7269,8211.9,7227,8269.4,7190],
[1,9198.7,6586,9351.3,6305,10332,5789],
[1,10374,5767,10424,5749,10458,5737]],
0,[0,"#ff0000"]],
[0,[0,[0,8177.5,7302],[1,8575,7272,10028,7160,10408,7131]],0,[0,"#ff0000"]],
[0,[0,[0,8174.4,7319],[1,8587.4,7355,10178,7496,10457,7520]],0,
[0,"#ff0000"]],
[0,
[0,[0,8187.4,7312],[1,8215.5,7316,8244.6,7323,8269.4,7337],
[1,9500.7,8007,9059.8,9135,10332,9723],
[1,10459,9781,12703,9742,12842,9742],
[1,12842,9742,12842,9742,15107,9742],
[1,16446,9742,17424,7898,17527,7694]],
0,[0,"#ff0000"]],
[0,[0,[0,16763,7676],[1,16922,7676,17391,7676,17509,7676]],0,[0,"#ff0000"]],
[0,[0,[0,16758,7625],[1,16910,7635,17390,7666,17509,7674]],0,[0,"#ff0000"]],
[0,
[0,[0,8162.5,7322],[1,8195.9,7326,8234.5,7332,8269.4,7337],
[1,9122.4,7468,10155,7648,10430,7696]],
0,[0,"#ff0000"]],
[0,
[0,[0,8112.8,7293],[1,8153.9,7272,8221.4,7235,8269.4,7190],
[1,9423.6,6104,8927.1,5014,10332,4281],
[1,10448,4221,12551,4257,12815,4261]],
0,[0,"#ff0000"]],
[0,[0,[0,10614,4306],[1,11051,4297,12592,4267,12815,4263]],0,[0,"#ff0000"]],
[0,[0,[0,10545,4111],[1,10851,4131,12577,4245,12815,4260]],0,[0,"#ff0000"]],
[0,
[0,[0,8164.5,7321],[1,8197.5,7326,8235.3,7331,8269.4,7337],
[1,9192.1,7497,9403.2,7650,10332,7766],
[1,11328,7890,12561,7880,12801,7877]],
0,[0,"#ff0000"]],
[0,
[0,[0,8164,7321],[1,8197.1,7326,8235.1,7331,8269.4,7337],
[1,9190.6,7490,9404.5,7630,10332,7735],
[1,11320,7847,12539,7828,12794,7823]],
0,[0,"#ff0000"]],
[0,
[0,[0,8165.8,7321],[1,8529.2,7365,9897.3,7528,10332,7551],
[1,10481,7559,10518,7552,10666,7551],
[1,11549,7547,12632,7533,12815,7530]],
0,[0,"#ff0000"]],
[0,
[0,[0,10611,4313],[1,10631,4317,10650,4324,10666,4335],
[1,12045,5242,11374,6434,12662,7465],
[1,12709,7502,12778,7519,12815,7526]],
0,[0,"#ff0000"]],
[0,[0,[0,10561,7614],[1,10904,7601,12581,7540,12815,7531]],0,[0,"#ff0000"]],
[0,
[0,[0,10583,6664],[1,10610,6668,10640,6674,10666,6681],
[1,11586,6933,11771,7129,12662,7465],
[1,12716,7485,12780,7508,12815,7520]],
0,[0,"#ff0000"]],
[0,
[0,[0,8177.5,7318],[1,8207.5,7322,8240.2,7328,8269.4,7337],
[1,9251.1,7646,9354.1,8069,10332,8389],
[1,10380,8405,10439,8411,10472,8414]],
0,[0,"#ff0000"]],
[0,[0,[0,8125.7,8684],[1,8446.1,8648,10230,8446,10472,8419]],0,
[0,"#ff0000"]],
[0,
[0,[0,8141.2,8789],[1,8178.7,8784,8226.8,8777,8269.4,8771],
[1,8729.1,8702,10250,8456,10472,8420]],
0,[0,"#ff0000"]],
[0,
[0,[0,8114.5,7293],[1,8156.3,7273,8223.6,7236,8269.4,7190],
[1,9515.6,5927,8820.4,4701,10332,3773],
[1,10555,3636,12558,3594,12815,3589]],
0,[0,"#ff0000"]],
[0,[0,[0,10552,4292],[1,10874,4193,12579,3670,12815,3597]],0,[0,"#ff0000"]],
[0,[0,[0,10530,3456],[1,10788,3471,12572,3573,12815,3587]],0,[0,"#ff0000"]],
[0,[0,[0,10566,3563],[1,10921,3567,12582,3586,12815,3589]],0,[0,"#ff0000"]],
[0,[0,[0,10541,3509],[1,10834,3520,12577,3580,12815,3588]],0,[0,"#ff0000"]],
[0,[0,[0,10549,3615],[1,10865,3612,12578,3592,12815,3589]],0,[0,"#ff0000"]],
[0,
[0,[0,8107.9,7293],[1,8147,7271,8215.1,7230,8269.4,7190],
[1,9250,6461,9199.4,5830,10332,5373],
[1,10454,5324,12551,5268,12815,5261]],
0,[0,"#ff0000"]],
[0,
[0,[0,10592,4319],[1,10617,4323,10643,4328,10666,4335],
[1,11594,4606,11759,4855,12662,5200],
[1,12716,5220,12780,5241,12815,5252]],
0,[0,"#ff0000"]],
[0,[0,[0,10582,5098],[1,10968,5126,12585,5242,12815,5258]],0,[0,"#ff0000"]],
[0,
[0,[0,10589,6646],[1,10615,6642,10642,6636,10666,6627],
[1,11651,6250,11742,5859,12662,5346],
[1,12715,5317,12780,5287,12815,5272]],
0,[0,"#ff0000"]],
[0,[0,[0,8147.3,6933],[1,8513,6980,10181,7191,10460,7227]],0,[0,"#ff0000"]],
[0,[0,[0,8154.6,6919],[1,8524.4,6894,10094,6789,10434,6766]],0,
[0,"#ff0000"]],
[0,[0,[0,5557,15003.1],[1,5927.3,15008.5,7550,15032.3,7974.5,15038.5]],0,
[0,"#ff0000"]],
[0,[0,[0,8127.3,11066],[1,8437.5,11020,10072,10777,10430,10723]],0,
[0,"#ff0000"]],
[0,[0,[0,8128.7,11067],[1,8442.6,11028,10075,10821,10431,10776]],0,
[0,"#ff0000"]],
[0,[0,[0,8130.7,10976],[1,8447.6,10941,10057,10762,10425,10721]],0,
[0,"#ff0000"]],
[0,[0,[0,8131.9,10977],[1,8452.1,10949,10063,10806,10427,10773]],0,
[0,"#ff0000"]],
[0,[0,[0,8138.5,17230.7],[1,8490.9,17234.6,10234,17254,10472,17256.7]],0,
[0,"#ff0000"]],
[0,
[0,[0,8177,7302],[1,8210.2,7305,8244.8,7314,8269.4,7337],
[1,11500,10348,8401.9,13085,10332,17057],
[1,10370,17133.9,10443,17206.3,10479,17238.9]],
0,[0,"#ff0000"]],
[0,[0,[0,8156.4,17283.1],[1,8545.9,17278.8,10236,17259.9,10472,17257.3]],0,
[0,"#ff0000"]],
[0,[0,[0,8112.6,17336.8],[1,8393.7,17327.4,10226,17266.1,10472,17257.9]],0,
[0,"#ff0000"]],
[0,[0,[0,966.17,23660],[1,1337.2,23660,2374.2,23660,2793.3,23660]],0,
[0,"#ff0000"]],
[0,[0,[0,5534.1,7970],[1,5862.6,7970,7626.3,7970,8004.9,7970]],0,
[0,"#ff0000"]],
[0,[0,[0,12909,23764],[1,13257,23743.3,14851,23648.3,15080,23634.6]],0,
[0,"#ff0000"]],
[0,[0,[0,12948,23658.7],[1,13362,23653.8,14860,23635.9,15080,23633.3]],0,
[0,"#ff0000"]],
[0,[0,[0,12952,23710.1],[1,13372,23695.1,14860,23641.8,15080,23634]],0,
[0,"#ff0000"]],
[0,[0,[0,12916,23554.6],[1,13277,23567.5,14854,23623.9,15080,23632]],0,
[0,"#ff0000"]],
[0,[0,[0,12926,23607],[1,13305,23611.5,14855,23630,15080,23632.7]],0,
[0,"#ff0000"]],
[0,[0,[0,12915,23502.3],[1,13273,23523.7,14854,23617.9,15080,23631.4]],0,
[0,"#ff0000"]],
[0,
[0,[0,5508.3,18386.1],[1,5551.8,18355.6,5636.8,18288.8,5676.4,18209],
[1,8884.7,11748,4186.2,8323,7883.4,2129],
[1,7919.7,2068,7993.3,2026,8038.4,2004]],
0,[0,"#ff0000"]],
[0,
[0,[0,5592.4,18418.8],[1,5619.9,18422.6,5649.2,18426.9,5676.4,18431],
[1,6659.5,18581,6900.5,18648.3,7883.4,18799],
[1,7916.5,18804.1,7952.9,18809.3,7985.1,18813.7]],
0,[0,"#ff0000"]],
[0,[0,[0,5673.8,1721],[1,6200.3,1719,7648.8,1714,7999.3,1712]],0,
[0,"#ff0000"]],
[0,[0,[0,5670.9,1725],[1,6183.9,1734,7587.2,1758,7975.6,1764]],0,
[0,"#ff0000"]],
[0,[0,[0,8152.9,19048],[1,8523.4,19048,10126,19048,10444,19048]],0,
[0,"#ff0000"]],
[0,[0,[0,5534.4,21083.4],[1,5877.1,21079.4,7773.8,21057.5,8044.3,21054.4]],
0,[0,"#ff0000"]],
[0,[0,[0,5538,20506.4],[1,5889.9,20502.7,7771.7,20483.2,8043.7,20480.3]],0,
[0,"#ff0000"]],
[0,[0,[0,5538,20507.6],[1,5888.6,20511.2,7757.9,20530.7,8040.6,20533.6]],0,
[0,"#ff0000"]],
[0,[0,[0,5537.7,20505.2],[1,5889.6,20494.3,7779.5,20435.3,8045.3,20427]],0,
[0,"#ff0000"]],
[0,
[0,[0,5533.6,20499.7],[1,5576.6,20491.3,5636.8,20473.6,5676.4,20437],
[1,7423.8,18825.3,5979.9,16988.9,7883.4,15565],
[1,7922.6,15535.7,7979,15530.9,8020.8,15532.2]],
0,[0,"#ff0000"]],
[0,[0,[0,3033.5,1559],[1,3388.2,1552,5176.7,1520,5447.2,1515]],0,
[0,"#ff0000"]],
[0,[0,[0,5557,16224],[1,5935.5,16224,7621.9,16224,8000.7,16224]],0,
[0,"#ff0000"]],
[0,[0,[0,8141.6,23752],[1,8500.9,23752,10234,23752,10472,23752]],0,
[0,"#ff0000"]],
[0,[0,[0,8115.5,23645.7],[1,8406.1,23658.7,10228,23739.9,10472,23750.8]],0,
[0,"#ff0000"]],
[0,
[0,[0,2986.3,21056],[1,3162.5,21284.1,4956.3,23600.6,5286.4,23788],
[1,5540.7,23932.3,7592,24187.4,7883.4,24211],
[1,8054.4,24224.8,8098.8,24228.4,8269.4,24211],
[1,9188.1,24117.4,10287,23812.4,10472,23759.8]],
0,[0,"#ff0000"]],
[0,[0,[0,8140.6,23749.1],[1,8497.8,23733.2,10233,23655.9,10472,23645.2]],0,
[0,"#ff0000"]],
[0,[0,[0,8115.5,23644],[1,8406.1,23644,10228,23644,10472,23644]],0,
[0,"#ff0000"]],
[0,
[0,[0,5529.7,20516.6],[1,5571.7,20526.7,5632.5,20545.9,5676.4,20579],
[1,6999,21574.3,6415.7,22813.6,7883.4,23579],
[1,8004.4,23642.1,10202,23644,10472,23644]],
0,[0,"#ff0000"]],
[0,[0,[0,8146,11874],[1,8501,11895,10107,11991,10439,12011]],0,
[0,"#ff0000"]],
[0,
[0,[0,5553.8,2880],[1,5590.5,2875,5635.9,2868,5676.4,2862],
[1,6660.7,2705,6901.3,2634,7883.4,2464],
[1,7942.5,2454,8011.9,2442,8049.2,2436]],
0,[0,"#ff0000"]],
[0,[0,[0,5580.8,2255],[1,6023.7,2286,7807.4,2413,8049.2,2430]],0,
[0,"#ff0000"]],
[0,
[0,[0,5580.8,2930],[1,5611.5,2926,5645.4,2921,5676.4,2916],
[1,6659.1,2749,7855.3,2482,8049.3,2438]],
0,[0,"#ff0000"]],
[0,[0,[0,5542.7,6924],[1,5889,6924,7599.5,6924,7994.8,6924]],0,
[0,"#ff0000"]],
[0,[0,[0,10600,11640],[1,10991,11640,12399,11640,12758,11640]],0,
[0,"#ff0000"]],
[0,
[0,[0,5532.5,11627],[1,5786.6,11615,6939.1,11561,7883.4,11534],
[1,8879.5,11506,10089,11492,10415,11489]],
0,[0,"#ff0000"]],
[0,[0,[0,8190.4,11816],[1,8599.1,11816,9987.7,11816,10390,11816]],0,
[0,"#ff0000"]],
[0,
[0,[0,5516.4,11887],[1,5730.1,11989,6883.6,12531,7883.4,12789],
[1,7941.4,12804,8011.5,12811,8049.2,12814]],
0,[0,"#ff0000"]],
[0,
[0,[0,5565.9,11823],[1,5600.6,11827,5640.9,11833,5676.4,11843],
[1,6704.6,12129,6855.5,12502,7883.4,12789],
[1,7941.1,12805,8011.3,12812,8049.1,12814]],
0,[0,"#ff0000"]],
[0,
[0,[0,5566.5,11768],[1,5601.1,11772,5641.1,11779,5676.4,11789],
[1,6710.9,12088,6849.1,12489,7883.4,12789],
[1,7941.1,12806,8011.6,12812,8049.4,12815]],
0,[0,"#ff0000"]],
[0,[0,[0,8226.6,1859],[1,8671.9,1863,9978.8,1873,10381,1876]],0,
[0,"#ff0000"]],
[0,[0,[0,8145.7,24321.6],[1,8502.7,24278.3,10131,24080.7,10446,24042.4]],0,
[0,"#ff0000"]],
[0,[0,[0,5528.1,10378],[1,5854.3,10353,7786.5,10204,8047.3,10184]],0,
[0,"#ff0000"]],
[0,[0,[0,927.58,524],[1,1274.5,524,2461.7,524,2849.1,524]],0,[0,"#ff0000"]],
[0,[0,[0,5621.4,480],[1,6089.9,474,7595.3,454,7984.1,449]],0,[0,"#ff0000"]],
[0,[0,[0,8235.4,610],[1,8674.6,595,9900.9,553,10340,538]],0,[0,"#ff0000"]],
[0,[0,[0,3068.5,640],[1,3468,643,4995.8,654,5388.8,657]],0,[0,"#ff0000"]],
[0,[0,[0,8128.4,10585],[1,8437.9,10602,10037,10688,10418,10709]],0,
[0,"#ff0000"]],
[0,[0,[0,8127.9,10586],[1,8438,10610,10058,10733,10425,10761]],0,
[0,"#ff0000"]],
[0,[0,[0,10539,2752],[1,10810,2752,12412,2752,12771,2752]],0,[0,"#ff0000"]],
[0,[0,[0,10529,11005],[1,10780,11006,12573,11016,12815,11017]],0,
[0,"#ff0000"]],
[0,[0,[0,10581,11162],[1,10965,11137,12585,11034,12815,11019]],0,
[0,"#ff0000"]],
[0,[0,[0,10527,10914],[1,10770,10925,12572,11005,12815,11016]],0,
[0,"#ff0000"]],
[0,[0,[0,10529,11004],[1,10780,11000,12573,10968,12815,10963]],0,
[0,"#ff0000"]],
[0,
[0,[0,8127.9,10698],[1,8373,10734,9446.4,10887,10332,10940],
[1,11355,11001,12615,10969,12815,10964]],
0,[0,"#ff0000"]],
[0,[0,[0,10527,10914],[1,10770,10919,12572,10957,12815,10962]],0,
[0,"#ff0000"]],
[0,[0,[0,5576.1,21190.3],[1,5984.5,21183.1,7592.5,21154.6,7988.1,21147.6]],
0,[0,"#ff0000"]],
[0,[0,[0,5578,21634.3],[1,5988.8,21627,7587.5,21598.7,7986,21591.6]],0,
[0,"#ff0000"]],
[0,[0,[0,8110.2,10477],[1,8369.5,10503,10043,10668,10423,10705]],0,
[0,"#ff0000"]],
[0,[0,[0,8109.8,10478],[1,8369.2,10509,10065,10714,10430,10759]],0,
[0,"#ff0000"]],
[0,[0,[0,12916,7277],[1,13260,7284,14711,7312,15041,7319]],0,[0,"#ff0000"]],
[0,[0,[0,12872,7330],[1,13110,7329,14693,7322,15040,7320]],0,[0,"#ff0000"]],
[0,[0,[0,10643,6308],[1,11115,6308,12597,6308,12815,6308]],0,[0,"#ff0000"]],
[0,[0,[0,10633,6257],[1,11092,6268,12595,6302,12815,6307]],0,[0,"#ff0000"]],
[0,[0,[0,10535,6489],[1,10810,6468,12575,6329,12815,6310]],0,[0,"#ff0000"]],
[0,[0,[0,3035.7,23941],[1,3382.5,23941,5049.7,23941,5411.9,23941]],0,
[0,"#ff0000"]],
[0,
[0,[0,5527.3,21134.4],[1,5567.1,21130.6,5626.2,21123.5,5676.4,21111],
[1,6689.6,20859.3,6898.2,20652.3,7883.4,20307],
[1,7931,20290.3,7985.4,20272.1,8024.3,20259.2]],
0,[0,"#ff0000"]],
[0,[0,[0,8156.7,22435.8],[1,8546.9,22444.5,10236,22482.1,10472,22487.4]],0,
[0,"#ff0000"]],
[0,[0,[0,8152.6,22540.3],[1,8535,22531.8,10237,22493.9,10472,22488.6]],0,
[0,"#ff0000"]],
[0,[0,[0,8131,22488],[1,8465.4,22488,10231,22488,10472,22488]],0,
[0,"#ff0000"]],
[0,[0,[0,5536.5,320],[1,5864.8,320,7562.3,320,7982.3,320]],0,[0,"#ff0000"]],
[0,[0,[0,3036,374],[1,3382.1,374,5037.2,374,5407.7,374]],0,[0,"#ff0000"]],
[0,[0,[0,3036,375],[1,3383.4,383,5049.1,419,5411.6,426]],0,[0,"#ff0000"]],
[0,[0,[0,902.97,320],[1,1233.7,320,2610.9,320,2913.5,320]],0,[0,"#ff0000"]],
[0,
[0,[0,5532.1,2837],[1,5572.1,2840,5628.8,2847,5676.4,2862],
[1,6726.5,3192,6833.6,3655,7883.4,3985],
[1,7940.7,4003,8011.3,4009,8049.3,4011]],
0,[0,"#ff0000"]],
[0,[0,[0,5537.1,4159],[1,5889.2,4138,7799.1,4028,8049.4,4014]],0,
[0,"#ff0000"]],
[0,[0,[0,5598.4,3865],[1,6069,3893,7810,3996,8049.1,4010]],0,[0,"#ff0000"]],
[0,
[0,[0,10582,5135],[1,10609,5131,10639,5125,10666,5119],
[1,11571,4906,11757,4705,12662,4497],
[1,12716,4485,12780,4477,12815,4473]],
0,[0,"#ff0000"]],
[0,[0,[0,10587,4626],[1,10981,4599,12587,4488,12815,4472]],0,[0,"#ff0000"]],
[0,[0,[0,10574,4224],[1,10945,4264,12583,4442,12815,4467]],0,[0,"#ff0000"]],
[0,[0,[0,10605,4315],[1,11028,4345,12590,4453,12815,4468]],0,[0,"#ff0000"]],
[0,[0,[0,10581,4173],[1,10964,4223,12584,4436,12815,4466]],0,[0,"#ff0000"]],
[0,[0,[0,10586,4522],[1,10978,4513,12586,4476,12815,4471]],0,[0,"#ff0000"]],
[0,[0,[0,10547,4470],[1,10857,4470,12578,4470,12815,4470]],0,[0,"#ff0000"]],
[0,[0,[0,10574,4418],[1,10946,4426,12584,4464,12815,4469]],0,[0,"#ff0000"]],
[0,[0,[0,10550,4576],[1,10868,4561,12578,4482,12815,4471]],0,[0,"#ff0000"]],
[0,[0,[0,10563,4680],[1,10911,4648,12582,4494,12815,4472]],0,[0,"#ff0000"]],
[0,[0,[0,10537,4364],[1,10818,4377,12575,4458,12815,4469]],0,[0,"#ff0000"]],
[0,[0,[0,10536,4789],[1,10812,4751,12574,4507,12815,4474]],0,[0,"#ff0000"]],
[0,[0,[0,10573,5404],[1,10942,5426,12583,5520,12815,5533]],0,[0,"#ff0000"]],
[0,
[0,[0,10576,5158],[1,10604,5163,10637,5168,10666,5173],
[1,11554,5319,11774,5367,12662,5508],
[1,12717,5517,12780,5526,12815,5531]],
0,[0,"#ff0000"]],
[0,[0,[0,10598,5509],[1,11010,5514,12589,5532,12815,5535]],0,[0,"#ff0000"]],
[0,[0,[0,10609,5561],[1,11037,5556,12590,5538,12815,5535]],0,[0,"#ff0000"]],
[0,[0,[0,10597,5613],[1,11009,5598,12589,5544,12815,5536]],0,[0,"#ff0000"]],
[0,[0,[0,10590,5457],[1,10990,5471,12586,5526,12815,5534]],0,[0,"#ff0000"]],
[0,[0,[0,10558,5719],[1,10894,5692,12580,5556,12815,5537]],0,[0,"#ff0000"]],
[0,[0,[0,10576,6557],[1,10950,6608,12584,6834,12815,6866]],0,[0,"#ff0000"]],
[0,[0,[0,10532,6870],[1,10796,6870,12573,6870,12815,6870]],0,[0,"#ff0000"]],
[0,[0,[0,10561,6923],[1,10907,6915,12581,6876,12815,6871]],0,[0,"#ff0000"]],
[0,[0,[0,10556,7012],[1,10888,6992,12581,6886,12815,6872]],0,[0,"#ff0000"]],
[0,[0,[0,10566,6818],[1,10922,6826,12582,6864,12815,6869]],0,[0,"#ff0000"]],
[0,[0,[0,10554,7171],[1,10883,7128,12580,6905,12815,6874]],0,[0,"#ff0000"]],
[0,[0,[0,10568,6608],[1,10928,6649,12583,6840,12815,6867]],0,[0,"#ff0000"]],
[0,[0,[0,10585,7115],[1,10975,7072,12586,6898,12815,6873]],0,[0,"#ff0000"]],
[0,[0,[0,10540,7067],[1,10828,7042,12576,6893,12815,6872]],0,[0,"#ff0000"]],
[0,[0,[0,10518,4810],[1,10723,4992,12604,6659,12822,6852]],0,[0,"#ff0000"]],
[0,[0,[0,8146,5842],[1,8488.2,5838,9992.7,5822,10398,5817]],0,
[0,"#ff0000"]],
[0,[0,[0,8146,5844],[1,8497.8,5848,10078,5865,10430,5869]],0,[0,"#ff0000"]],
[0,
[0,[0,10580,5135],[1,10607,5130,10638,5125,10666,5119],
[1,11563,4931,11765,4787,12662,4605],
[1,12716,4594,12780,4586,12815,4581]],
0,[0,"#ff0000"]],
[0,[0,[0,10592,4630],[1,10994,4621,12587,4584,12815,4579]],0,[0,"#ff0000"]],
[0,
[0,[0,10562,5192],[1,10593,5187,10632,5181,10666,5173],
[1,11567,4973,11761,4800,12662,4605],
[1,12716,4593,12780,4585,12815,4581]],
0,[0,"#ff0000"]],
[0,[0,[0,10592,4319],[1,10996,4365,12587,4549,12815,4575]],0,[0,"#ff0000"]],
[0,
[0,[0,10575,4174],[1,10604,4179,10637,4184,10666,4189],
[1,11555,4341,11773,4404,12662,4551],
[1,12717,4560,12780,4569,12815,4574]],
0,[0,"#ff0000"]],
[0,[0,[0,10586,4526],[1,10978,4535,12586,4572,12815,4577]],0,[0,"#ff0000"]],
[0,[0,[0,10547,4472],[1,10856,4486,12578,4566,12815,4577]],0,[0,"#ff0000"]],
[0,[0,[0,10572,4421],[1,10939,4446,12584,4560,12815,4576]],0,[0,"#ff0000"]],
[0,[0,[0,10551,4578],[1,10869,4578,12578,4578,12815,4578]],0,[0,"#ff0000"]],
[0,[0,[0,10565,4683],[1,10919,4667,12581,4590,12815,4579]],0,[0,"#ff0000"]],
[0,[0,[0,10537,4365],[1,10816,4391,12574,4553,12815,4575]],0,[0,"#ff0000"]],
[0,[0,[0,10537,4791],[1,10816,4765,12574,4603,12815,4581]],0,[0,"#ff0000"]],
[0,[0,[0,10575,5401],[1,10948,5405,12584,5424,12815,5427]],0,[0,"#ff0000"]],
[0,[0,[0,10585,5156],[1,10977,5203,12586,5396,12815,5424]],0,[0,"#ff0000"]],
[0,[0,[0,10596,5505],[1,11007,5490,12589,5436,12815,5428]],0,[0,"#ff0000"]],
[0,[0,[0,10565,5206],[1,10916,5240,12581,5402,12815,5424]],0,[0,"#ff0000"]],
[0,[0,[0,10591,5609],[1,10991,5576,12587,5448,12815,5429]],0,[0,"#ff0000"]],
[0,[0,[0,10591,5453],[1,10993,5448,12587,5430,12815,5427]],0,[0,"#ff0000"]],
[0,[0,[0,10555,5717],[1,10884,5675,12580,5460,12815,5430]],0,[0,"#ff0000"]],
[0,[0,[0,10600,22867.2],[1,11015,22871.9,12588,22890.1,12815,22892.7]],0,
[0,"#ff0000"]],
[0,[0,[0,10600,22918.8],[1,11015,22914.1,12588,22895.9,12815,22893.3]],0,
[0,"#ff0000"]],
[0,[0,[0,10598,22970.6],[1,11011,22956.3,12588,22901.8,12815,22893.9]],0,
[0,"#ff0000"]],
[0,[0,[0,10598,22815.4],[1,11011,22829.7,12588,22884.2,12815,22892.1]],0,
[0,"#ff0000"]],
[0,[0,[0,10596,7982],[1,11007,7972,12589,7936,12815,7931]],0,[0,"#ff0000"]],
[0,[0,[0,10597,7930],[1,11009,7930,12589,7930,12815,7930]],0,[0,"#ff0000"]],
[0,[0,[0,10595,7842],[1,11003,7858,12588,7920,12815,7929]],0,[0,"#ff0000"]],
[0,
[0,[0,5575,7455],[1,5928.5,7437,7216,7382,8269.4,7483],
[1,9197.6,7572,9405,7768,10332,7865],
[1,11352,7972,12616,7937,12815,7931]],
0,[0,"#ff0000"]],
[0,[0,[0,8148,22596],[1,8515.6,22596,10186,22596,10461,22596]],0,
[0,"#ff0000"]],
[0,[0,[0,10595,3799],[1,10985,3795,12461,3781,12781,3778]],0,[0,"#ff0000"]],
[0,[0,[0,3139.5,212],[1,3603.4,212,4902.2,212,5337.3,212]],0,[0,"#ff0000"]],
[0,[0,[0,957.76,269],[1,1352.1,274,2554,274,2886.4,269]],0,[0,"#ff0000"]],
[0,[0,[0,12939,5186],[1,13309,5235,14627,5409,15005,5459]],0,[0,"#ff0000"]],
[0,
[0,[0,10581,5135],[1,10608,5131,10639,5125,10666,5119],
[1,11567,4919,11761,4746,12662,4551],
[1,12716,4539,12780,4531,12815,4527]],
0,[0,"#ff0000"]],
[0,[0,[0,10589,4628],[1,10988,4609,12586,4536,12815,4525]],0,[0,"#ff0000"]],
[0,[0,[0,10582,4732],[1,10967,4697,12585,4548,12815,4527]],0,[0,"#ff0000"]],
[0,[0,[0,10571,4225],[1,10936,4273,12584,4490,12815,4520]],0,[0,"#ff0000"]],
[0,[0,[0,10599,4317],[1,11013,4355,12588,4501,12815,4521]],0,[0,"#ff0000"]],
[0,[0,[0,10586,4524],[1,10979,4524,12587,4524,12815,4524]],0,[0,"#ff0000"]],
[0,[0,[0,10547,4471],[1,10857,4478,12578,4518,12815,4523]],0,[0,"#ff0000"]],
[0,[0,[0,10573,4419],[1,10942,4436,12583,4512,12815,4523]],0,[0,"#ff0000"]],
[0,[0,[0,10551,4577],[1,10869,4569,12578,4530,12815,4525]],0,[0,"#ff0000"]],
[0,[0,[0,10565,4681],[1,10916,4657,12581,4542,12815,4526]],0,[0,"#ff0000"]],
[0,[0,[0,10537,4365],[1,10816,4384,12574,4505,12815,4522]],0,[0,"#ff0000"]],
[0,[0,[0,10536,4790],[1,10814,4758,12574,4555,12815,4527]],0,[0,"#ff0000"]],
[0,
[0,[0,10579,5134],[1,10606,5130,10638,5124,10666,5119],
[1,11554,4948,12632,4684,12815,4639]],
0,[0,"#ff0000"]],
[0,[0,[0,10592,4632],[1,10995,4632,12587,4632,12815,4632]],0,[0,"#ff0000"]],
[0,[0,[0,10588,4736],[1,10984,4718,12587,4644,12815,4633]],0,[0,"#ff0000"]],
[0,
[0,[0,10561,5191],[1,10592,5187,10632,5180,10666,5173],
[1,11556,4991,12632,4691,12815,4640]],
0,[0,"#ff0000"]],
[0,[0,[0,10586,4320],[1,10979,4374,12587,4597,12815,4628]],0,[0,"#ff0000"]],
[0,[0,[0,10584,4528],[1,10974,4546,12586,4620,12815,4631]],0,[0,"#ff0000"]],
[0,[0,[0,10546,4473],[1,10854,4494,12578,4614,12815,4630]],0,[0,"#ff0000"]],
[0,[0,[0,10570,4422],[1,10932,4456,12583,4608,12815,4629]],0,[0,"#ff0000"]],
[0,[0,[0,10551,4579],[1,10869,4587,12578,4626,12815,4631]],0,[0,"#ff0000"]],
[0,[0,[0,10566,4684],[1,10922,4676,12582,4638,12815,4633]],0,[0,"#ff0000"]],
[0,[0,[0,10536,4366],[1,10814,4398,12574,4601,12815,4629]],0,[0,"#ff0000"]],
[0,[0,[0,10537,4791],[1,10816,4772,12574,4651,12815,4634]],0,[0,"#ff0000"]],
[0,[0,[0,10570,8049],[1,10932,8108,12583,8374,12815,8412]],0,[0,"#ff0000"]],
[0,[0,[0,10532,8096],[1,10794,8133,12573,8379,12815,8412]],0,[0,"#ff0000"]],
[0,[0,[0,10552,8522],[1,10875,8507,12579,8428,12815,8417]],0,[0,"#ff0000"]],
[0,[0,[0,10527,8576],[1,10770,8559,12572,8435,12815,8418]],0,[0,"#ff0000"]],
[0,[0,[0,10587,8042],[1,10983,8060,12587,8134,12815,8145]],0,[0,"#ff0000"]],
[0,[0,[0,10539,7444],[1,10826,7531,12576,8065,12815,8138]],0,[0,"#ff0000"]],
[0,[0,[0,10548,8516],[1,10859,8466,12578,8189,12815,8150]],0,[0,"#ff0000"]],
[0,
[0,[0,10526,8574],[1,10559,8569,10617,8560,10666,8551],
[1,11550,8397,12631,8187,12815,8151]],
0,[0,"#ff0000"]],
[0,[0,[0,10574,5403],[1,10946,5415,12584,5472,12815,5480]],0,[0,"#ff0000"]],
[0,[0,[0,10580,5157],[1,10962,5212,12586,5444,12815,5477]],0,[0,"#ff0000"]],
[0,[0,[0,10598,5507],[1,11010,5502,12589,5484,12815,5481]],0,[0,"#ff0000"]],
[0,[0,[0,10581,5262],[1,10965,5299,12585,5456,12815,5478]],0,[0,"#ff0000"]],
[0,[0,[0,10606,5558],[1,11031,5544,12591,5490,12815,5482]],0,[0,"#ff0000"]],
[0,[0,[0,10591,5455],[1,10993,5460,12587,5478,12815,5481]],0,[0,"#ff0000"]],
[0,[0,[0,10556,5718],[1,10889,5684,12581,5508,12815,5484]],0,[0,"#ff0000"]],
[0,[0,[0,10575,5399],[1,10948,5395,12584,5376,12815,5373]],0,[0,"#ff0000"]],
[0,[0,[0,10590,5155],[1,10990,5194,12586,5348,12815,5370]],0,[0,"#ff0000"]],
[0,[0,[0,10593,5503],[1,10999,5479,12588,5388,12815,5375]],0,[0,"#ff0000"]],
[0,[0,[0,10587,5258],[1,10983,5279,12587,5360,12815,5372]],0,[0,"#ff0000"]],
[0,[0,[0,10566,5205],[1,10922,5231,12582,5354,12815,5371]],0,[0,"#ff0000"]],
[0,[0,[0,10590,5451],[1,10990,5437,12586,5382,12815,5374]],0,[0,"#ff0000"]],
[0,[0,[0,10553,5716],[1,10879,5667,12579,5412,12815,5377]],0,[0,"#ff0000"]],
[0,[0,[0,12966,4995],[1,13366,4981,14620,4934,14998,4920]],0,[0,"#ff0000"]],
[0,[0,[0,5574.2,6686],[1,5974.8,6686,7555.4,6686,7974.2,6686]],0,
[0,"#ff0000"]],
[0,[0,[0,5615.9,8098],[1,6063,8091,7496.2,8070,7942.5,8064]],0,
[0,"#ff0000"]],
[0,[0,[0,10596,13382],[1,10987,13382,12456,13382,12779,13382]],0,
[0,"#ff0000"]],
[0,[0,[0,8129.9,13229],[1,8461.5,13236,10232,13272,10472,13277]],0,
[0,"#ff0000"]],
[0,[0,[0,10593,6548],[1,10998,6556,12588,6587,12815,6591]],0,[0,"#ff0000"]],
[0,[0,[0,10576,6600],[1,10951,6598,12584,6593,12815,6592]],0,[0,"#ff0000"]],
[0,[0,[0,10536,6494],[1,10812,6505,12574,6581,12815,6591]],0,[0,"#ff0000"]],
[0,
[0,[0,10590,6541],[1,10919,6526,12075,6482,13022,6565],
[1,13874,6639,14902,6869,15080,6910]],
0,[0,"#ff0000"]],
[0,[0,[0,10562,6924],[1,11083,6923,14729,6917,15080,6916]],0,[0,"#ff0000"]],
[0,
[0,[0,12926,6264],[1,12956,6268,12991,6274,13022,6281],
[1,13881,6475,14902,6841,15080,6906]],
0,[0,"#ff0000"]],
[0,
[0,[0,10557,7016],[1,10832,7015,12036,7012,13022,6989],
[1,13866,6970,14901,6925,15080,6917]],
0,[0,"#ff0000"]],
[0,[0,[0,10559,7175],[1,11069,7146,14730,6937,15080,6918]],0,[0,"#ff0000"]],
[0,[0,[0,10573,6605],[1,11136,6644,14732,6890,15080,6914]],0,[0,"#ff0000"]],
[0,
[0,[0,10596,7120],[1,10931,7106,12077,7057,13022,7014],
[1,13866,6976,14901,6926,15080,6917]],
0,[0,"#ff0000"]],
[0,
[0,[0,10540,7069],[1,10777,7063,12014,7033,13022,6999],
[1,13866,6970,14901,6925,15080,6917]],
0,[0,"#ff0000"]],
[0,
[0,[0,10535,4788],[1,10767,4751,12085,4565,13022,4973],
[1,14107,5445,14985,6731,15096,6898]],
0,[0,"#ff0000"]],
[0,[0,[0,8171,3335],[1,8574.4,3291,10144,3116,10448,3082]],0,[0,"#ff0000"]],
[0,[0,[0,5547.9,20408.1],[1,5904,20397.6,7586.5,20348.3,7989.5,20336.5]],0,
[0,"#ff0000"]],
[0,[0,[0,5627.4,20825.8],[1,6108.6,20812.1,7634.1,20768.6,7998,20758.2]],0,
[0,"#ff0000"]],
[0,[0,[0,8177.5,6032],[1,8602.2,6032,10232,6032,10470,6032]],0,
[0,"#ff0000"]],
[0,[0,[0,5584.8,14326],[1,5995.8,14326,7513.6,14326,7955.2,14326]],0,
[0,"#ff0000"]],
[0,[0,[0,10575,16132],[1,10929,16132,12419,16132,12769,16132]],0,
[0,"#ff0000"]],
[0,[0,[0,10576,16079.8],[1,10931,16087.9,12420,16122.3,12769,16130.3]],0,
[0,"#ff0000"]],
[0,[0,[0,5552.9,5509],[1,5909.7,5516,7500.2,5544,7954.7,5552]],0,
[0,"#ff0000"]],
[0,
[0,[0,8160.3,6186],[1,8456.8,6212,9483.1,6301,10332,6335],
[1,11356,6376,12615,6364,12815,6362]],
0,[0,"#ff0000"]],
[0,
[0,[0,10531,6865],[1,10565,6860,10619,6852,10666,6843],
[1,11553,6673,12632,6413,12815,6369]],
0,[0,"#ff0000"]],
[0,[0,[0,10641,6311],[1,11109,6322,12596,6356,12815,6361]],0,[0,"#ff0000"]],
[0,[0,[0,10627,6260],[1,11080,6281,12593,6351,12815,6361]],0,[0,"#ff0000"]],
[0,
[0,[0,10558,6807],[1,10590,6802,10630,6795,10666,6789],
[1,11551,6631,12631,6406,12815,6368]],
0,[0,"#ff0000"]],
[0,
[0,[0,8159.8,6186],[1,8194.1,6190,8234,6196,8269.4,6205],
[1,9215.8,6440,9372.4,6781,10332,6951],
[1,10844,7042,12577,6973,12815,6963]],
0,[0,"#ff0000"]],
[0,
[0,[0,10572,6557],[1,10602,6562,10636,6568,10666,6573],
[1,11550,6723,12632,6923,12815,6957]],
0,[0,"#ff0000"]],
[0,[0,[0,10532,6871],[1,10796,6882,12573,6951,12815,6961]],0,[0,"#ff0000"]],
[0,[0,[0,10561,6925],[1,10907,6931,12581,6958,12815,6962]],0,[0,"#ff0000"]],
[0,[0,[0,10557,7015],[1,10892,7007,12579,6968,12815,6963]],0,[0,"#ff0000"]],
[0,[0,[0,10565,6820],[1,10917,6842,12581,6946,12815,6960]],0,[0,"#ff0000"]],
[0,[0,[0,10557,7173],[1,10892,7142,12579,6986,12815,6965]],0,[0,"#ff0000"]],
[0,[0,[0,10564,6610],[1,10913,6664,12582,6922,12815,6958]],0,[0,"#ff0000"]],
[0,[0,[0,10592,7118],[1,10995,7090,12587,6980,12815,6964]],0,[0,"#ff0000"]],
[0,[0,[0,10540,7068],[1,10830,7055,12576,6974,12815,6963]],0,[0,"#ff0000"]],
[0,[0,[0,877.14,1414],[1,1155,1414,2615.5,1414,2917.7,1414]],0,
[0,"#ff0000"]],
[0,[0,[0,8126.5,4845],[1,8444.9,4838,10184,4801,10462,4795]],0,
[0,"#ff0000"]],
[0,
[0,[0,8123.7,4852],[1,8162.9,4857,8219.9,4865,8269.4,4873],
[1,9191.1,5028,9412.5,5116,10332,5281],
[1,10382,5290,10439,5299,10472,5304]],
0,[0,"#ff0000"]],
[0,[0,[0,8128.2,5285],[1,8455.3,5288,10231,5305,10472,5308]],0,
[0,"#ff0000"]],
[0,
[0,[0,8107.9,7293],[1,8147.1,7271,8215.3,7231,8269.4,7190],
[1,9254.6,6451,9229,5887,10332,5340],
[1,10378,5317,10438,5311,10472,5309]],
0,[0,"#ff0000"]],
[0,[0,[0,8127.3,5443],[1,8452.2,5425,10231,5323,10472,5310]],0,
[0,"#ff0000"]],
[0,[0,[0,5560.5,7310],[1,5934.7,7310,7527.3,7310,7964.8,7310]],0,
[0,"#ff0000"]],
[0,
[0,[0,2980.3,17356.1],[1,3071.3,17561.1,3939.3,19457.2,5286.4,20248],
[1,5317.5,20266.2,5355.9,20274.9,5390.4,20278.8]],
0,[0,"#ff0000"]],
[0,[0,[0,10570,17936],[1,10886,17936,12183,17936,12663,17936]],0,
[0,"#ff0000"]],
[0,[0,[0,10569,17937.6],[1,10887,17944.9,12202,17975.2,12673,17986.1]],0,
[0,"#ff0000"]],
[0,[0,[0,5580.8,21543.7],[1,5997.7,21542.4,7602.7,21537.5,7991.3,21536.3]],
0,[0,"#ff0000"]],
[0,[0,[0,5528.1,5843],[1,5840.9,5843,7630.3,5843,8006.9,5843]],0,
[0,"#ff0000"]],
[0,[0,[0,10590,8742],[1,10989,8751,12586,8788,12815,8793]],0,[0,"#ff0000"]],
[0,[0,[0,10570,8951],[1,10934,8926,12584,8812,12815,8796]],0,[0,"#ff0000"]],
[0,[0,[0,10588,8898],[1,10984,8880,12587,8806,12815,8795]],0,[0,"#ff0000"]],
[0,[0,[0,10571,8794],[1,10937,8794,12584,8794,12815,8794]],0,[0,"#ff0000"]],
[0,[0,[0,10567,8689],[1,10923,8706,12582,8782,12815,8793]],0,[0,"#ff0000"]],
[0,[0,[0,10551,8636],[1,10872,8658,12578,8776,12815,8792]],0,[0,"#ff0000"]],
[0,[0,[0,10557,8847],[1,10892,8839,12579,8800,12815,8795]],0,[0,"#ff0000"]],
[0,[0,[0,10588,8744],[1,10985,8762,12587,8836,12815,8847]],0,[0,"#ff0000"]],
[0,[0,[0,10572,8953],[1,10939,8936,12584,8860,12815,8849]],0,[0,"#ff0000"]],
[0,[0,[0,10589,8900],[1,10988,8891,12586,8854,12815,8849]],0,[0,"#ff0000"]],
[0,[0,[0,10571,8796],[1,10936,8804,12584,8842,12815,8847]],0,[0,"#ff0000"]],
[0,[0,[0,10565,8691],[1,10919,8715,12581,8830,12815,8846]],0,[0,"#ff0000"]],
[0,[0,[0,10537,9061],[1,10816,9035,12574,8873,12815,8851]],0,[0,"#ff0000"]],
[0,[0,[0,10557,8848],[1,10892,8848,12579,8848,12815,8848]],0,[0,"#ff0000"]],
[0,[0,[0,8121.9,5503],[1,8431.8,5525,10230,5651,10472,5668]],0,
[0,"#ff0000"]],
[0,
[0,[0,8124.9,5290],[1,8163.9,5296,8220.2,5304,8269.4,5311],
[1,8385.2,5328,10227,5626,10472,5666]],
0,[0,"#ff0000"]],
[0,
[0,[0,8105.9,7293],[1,8144.2,7270,8212.6,7228,8269.4,7190],
[1,9209,6559,9287.1,6131,10332,5697],
[1,10379,5678,10438,5672,10472,5671]],
0,[0,"#ff0000"]],
[0,[0,[0,8126.5,5451],[1,8449.1,5480,10230,5645,10472,5667]],0,
[0,"#ff0000"]],
[0,
[0,[0,8174.6,15927.2],[1,8205.1,15931.3,8238.8,15936.6,8269.4,15943],
[1,9201.2,16136.9,9402.8,16313.2,10332,16517],
[1,10357,16522.5,10385,16527.3,10410,16531.4]],
0,[0,"#ff0000"]],
[0,[0,[0,8197.4,10645],[1,8611,10677,9965.5,10780,10379,10812]],0,
[0,"#ff0000"]],
[0,[0,[0,5535.9,10111],[1,5873.2,10106,7673.2,10080,8019,10075]],0,
[0,"#ff0000"]],
[0,[0,[0,5535.9,10112],[1,5871.4,10114,7653.8,10125,8013.2,10128]],0,
[0,"#ff0000"]],
[0,[0,[0,8123.2,8910],[1,8437,8938,10230,9094,10472,9116]],0,[0,"#ff0000"]],
[0,[0,[0,8118.2,8857],[1,8417.4,8889,10228,9088,10472,9115]],0,
[0,"#ff0000"]],
[0,[0,[0,8137.5,9069],[1,8487.8,9076,10234,9113,10472,9117]],0,
[0,"#ff0000"]],
[0,[0,[0,8124.3,9016],[1,8440.9,9030,10229,9106,10472,9117]],0,
[0,"#ff0000"]],
[0,[0,[0,8141.6,8807],[1,8500.9,8854,10234,9083,10472,9114]],0,
[0,"#ff0000"]],
[0,[0,[0,8126.5,9122],[1,8449.1,9121,10230,9118,10472,9118]],0,
[0,"#ff0000"]],
[0,[0,[0,8124.3,8908],[1,8440.9,8922,10229,8998,10472,9009]],0,
[0,"#ff0000"]],
[0,
[0,[0,8184.1,7315],[1,8212.7,7319,8242.9,7326,8269.4,7337],
[1,9346.9,7800,9259.9,8508,10332,8983],
[1,10379,9003,10438,9009,10472,9010]],
0,[0,"#ff0000"]],
[0,[0,[0,8119,8855],[1,8420.5,8874,10228,8992,10472,9008]],0,[0,"#ff0000"]],
[0,[0,[0,8124.6,9014],[1,8442,9013,10229,9010,10472,9010]],0,[0,"#ff0000"]],
[0,[0,[0,8146.3,8804],[1,8516.1,8836,10236,8987,10472,9008]],0,
[0,"#ff0000"]],
[0,[0,[0,8135.7,3783],[1,8469.4,3793,10110,3842,10441,3852]],0,
[0,"#ff0000"]],
[0,[0,[0,5578.8,3362],[1,5998.6,3350,7648.3,3304,8007.2,3294]],0,
[0,"#ff0000"]],
[0,[0,[0,8143.4,22650],[1,8484.4,22650,10026,22650,10412,22650]],0,
[0,"#ff0000"]],
[0,[0,[0,5542.4,51],[1,5907.7,59,7799.6,98,8049.2,103]],0,[0,"#ff0000"]],
[0,[0,[0,5523,104],[1,5834.1,104,7793.9,104,8049.1,104]],0,[0,"#ff0000"]],
[0,[0,[0,5554.9,156],[1,5949,148,7803.1,110,8049.4,105]],0,[0,"#ff0000"]],
[0,[0,[0,10541,5925],[1,10832,5932,12576,5972,12815,5977]],0,[0,"#ff0000"]],
[0,[0,[0,10535,5978],[1,10810,5978,12575,5978,12815,5978]],0,[0,"#ff0000"]],
[0,[0,[0,10554,6158],[1,10883,6132,12580,5999,12815,5980]],0,[0,"#ff0000"]],
[0,[0,[0,5598.8,21742.9],[1,6035.4,21738.9,7561.3,21724.8,7973.3,21721]],0,
[0,"#ff0000"]],
[0,[0,[0,8119,6633],[1,8399.5,6642,9984.5,6692,10400,6705]],0,
[0,"#ff0000"]],
[0,[0,[0,12893,15512.2],[1,13205,15519.7,14849,15558.8,15080,15564.4]],0,
[0,"#ff0000"]],
[0,[0,[0,12906,15565],[1,13246,15565,14852,15565,15080,15565]],0,
[0,"#ff0000"]],
[0,[0,[0,12926,15617],[1,13305,15608,14855,15571,15080,15565.7]],0,
[0,"#ff0000"]],
[0,[0,[0,5594.2,7606],[1,6018.3,7605,7516,7603,7954.8,7602]],0,
[0,"#ff0000"]],
[0,[0,[0,15217,2459],[1,15545,2470,16509,2502,16683,2508]],0,[0,"#ff0000"]],
[0,[0,[0,15226,2509],[1,15562,2509,16511,2509,16683,2509]],0,[0,"#ff0000"]],
[0,[0,[0,15201,2667],[1,15513,2634,16506,2530,16683,2512]],0,[0,"#ff0000"]],
[0,[0,[0,15219,2453],[1,15548,2448,16510,2431,16683,2428]],0,[0,"#ff0000"]],
[0,[0,[0,15204,2403],[1,15519,2408,16506,2425,16683,2428]],0,[0,"#ff0000"]],
[0,[0,[0,15242,2354],[1,15592,2371,16514,2418,16683,2427]],0,[0,"#ff0000"]],
[0,[0,[0,15220,2503],[1,15550,2487,16510,2438,16683,2429]],0,[0,"#ff0000"]],
[0,[0,[0,8130.1,17725.5],[1,8447.7,17746.5,10077,17854.1,10431,17877.5]],0,
[0,"#ff0000"]],
[0,
[0,[0,5517.9,19647.6],[1,5736,19550.2,6890.6,19044.4,7883.4,18799],
[1,7916.3,18790.9,7952.9,18785,7985.4,18780.8]],
0,[0,"#ff0000"]],
[0,
[0,[0,5524.1,19087.7],[1,5759.9,19053,6928.1,18881.2,7883.4,18745],
[1,7929.8,18738.4,7982.5,18731,8021.1,18725.7]],
0,[0,"#ff0000"]],
[0,[0,[0,10551,23136],[1,10866,23136,12539,23136,12806,23136]],0,
[0,"#ff0000"]],
[0,[0,[0,8179,3904],[1,8572.5,3905,9983.9,3907,10390,3908]],0,
[0,"#ff0000"]],
[0,[0,[0,10609,19835],[1,11002,19835,12336,19835,12731,19835]],0,
[0,"#ff0000"]],
[0,[0,[0,5580.4,20606.8],[1,5994.1,20610,7582.8,20622.2,7984,20625.3]],0,
[0,"#ff0000"]],
[0,[0,[0,8156.7,22705.8],[1,8546.9,22714.5,10236,22752.1,10472,22757.4]],0,
[0,"#ff0000"]],
[0,[0,[0,8126.2,23075.3],[1,8448.1,23032.3,10230,22794,10472,22761.6]],0,
[0,"#ff0000"]],
[0,[0,[0,8135.1,22758],[1,8479.7,22758,10233,22758,10472,22758]],0,
[0,"#ff0000"]],
[0,[0,[0,8125.7,16811.4],[1,8420,16831.8,9949.6,16937.9,10384,16968]],0,
[0,"#ff0000"]],
[1,
[0,[0,10488,19862.4],[0,10484.8,19861],[0,10492,19853.2],
[0,10491.2,19863.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8156.4,22706.1],[1,8193,22703.9,8235.6,22696.5,8269.4,22677],
[1,9566.2,21930.7,10383,20107.2,10488,19862.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10488,19862.5],[0,10484.8,19861.1],[0,10491.9,19853.3],
[0,10491.2,19863.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8134.2,22761.1],[1,8174.6,22760.7,8228.5,22754.8,8269.4,22731],
[1,9578.7,21969.5,10385,20110.4,10488,19862.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,7983.8,21531.1],[0,7983.97,21527.6],[0,7993.79,21531.6],
[0,7983.63,21534.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5529,21400.5],[1,5838.1,21417,7563.1,21508.7,7983.8,21531.1]],0,
[0,"#0000ff"]],
[1,
[0,[0,10476,19860.4],[0,10473.5,19858],[0,10482.9,19853.1],
[0,10478.5,19862.8]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5529.4,21399.7],[1,5876.7,21411.6,7998.3,21480.6,8269.4,21395],
[1,9323.3,21062.3,10313,20035.2,10476,19860.4]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10448,13985],[0,10447,13981.6],[0,10457.6,13982.1],
[0,10449,13988.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5526.6,21404.3],[1,5570,21407.8,5634.8,21405.7,5676.4,21371],
[1,8087,19359.8,5433.6,16624.2,7883.4,14661],
[1,7950.7,14607,8184.8,14639,8269.4,14623],
[1,9160.3,14450,10207,14074,10448,13985]],
0,[0,"#0000ff"]],
[1,
[0,[0,10453,19856.2],[0,10451.5,19853],[0,10462,19851.9],
[0,10454.5,19859.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5579.7,20608.3],[1,6010.8,20618,7736.1,20650,8269.4,20561],
[1,9177.5,20409.4,10221,19959.2,10453,19856.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10449,19855.7],[0,10447.6,19852.5],[0,10458.2,19851.7],
[0,10450.4,19858.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8154,20616.1],[1,8189.5,20610.8,8231.9,20603.4,8269.4,20594],
[1,9162.4,20369.6,10209,19952.9,10449,19855.7]],
0,[0,"#0000ff"]],
[1,[0,[0,2906.3,23],[0,2906.3,19.5],[0,2916.3,23.0001],[0,2906.3,26.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,909.53,23],[1,1248.8,23,2591.7,23,2906.3,23]],0,[0,"#0000ff"]],
[1,
[0,[0,10494,19806.6],[0,10497.4,19805.9],[0,10495.9,19816.4],
[0,10490.6,19807.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8201.6,15808.6],[1,8225.6,15813.2,8249.5,15821.3,8269.4,15835],
[1,9850.4,16918,10431,19507.3,10494,19806.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10450,13985],[0,10448.9,13981.7],[0,10459.5,13981.8],
[0,10451.1,13988.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8194.7,15802.1],[1,8220.1,15797.9,8246.3,15791.3,8269.4,15781],
[1,9364,15293.2,9324,14692,10332,14045],
[1,10370,14021,10416,14000,10450,13985]],
0,[0,"#0000ff"]],
[1,
[0,[0,10385,18038.2],[0,10385.2,18034.7],[0,10395,18038.7],
[0,10384.8,18041.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5612.4,17805.2],[1,6011.3,17824.2,7246.1,17882.9,8269.4,17933],
[1,9079.7,17972.6,10055,18021.6,10385,18038.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,7968.9,16987.5],[0,7968.42,16984],[0,7978.81,16986.1],
[0,7969.38,16991]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5523.6,17781.8],[1,5756,17687.7,6904.3,17231.7,7883.4,17003],
[1,7910.9,16996.6,7940.9,16991.5,7968.9,16987.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10481,12983],[0,10478.2,12980.9],[0,10487,12975],
[0,10483.8,12985.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8154.2,15593.6],[1,8191,15591.4,8234.6,15584.1,8269.4,15565],
[1,8895.5,15222,10304,13236,10481,12983]],
0,[0,"#0000ff"]],
[1,
[0,[0,10495,19807],[0,10498.5,19806.6],[0,10496,19816.9],
[0,10491.5,19807.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8151.5,15587],[1,8189.8,15588,8235.5,15595.2,8269.4,15619],
[1,9906.7,16767.3,10439,19501.3,10495,19807]],
0,[0,"#0000ff"]],
[1,[0,[0,16648,7676],[0,16648,7672.5],[0,16658,7676],[0,16648,7679.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,15135,7676],[1,15318,7676,16378,7676,16648,7676]],0,[0,"#0000ff"]],
[1,[0,[0,16653,7624],[0,16653,7620.5],[0,16663,7624],[0,16653,7627.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,15135,7675],[1,15319,7669,16391,7633,16653,7624]],0,[0,"#0000ff"]],
[1,
[0,[0,15070,7678],[0,15069.7,7674.52],[0,15080,7677],[0,15070.3,7681.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12918,7765],[1,13279,7750,14811,7688,15070,7678]],0,[0,"#0000ff"]],
[1,
[0,[0,10386,19841.5],[0,10385.8,19838],[0,10396,19841],[0,10386.2,19845]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5511.4,19107.6],[1,5711.2,19197.8,6874.4,19709.4,7883.4,19868],
[1,8376.1,19945.4,9948.3,19865.7,10386,19841.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10383,19840],[0,10382.9,19836.5],[0,10393,19839.6],
[0,10383.1,19843.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5554.9,19674.1],[1,5848,19713.9,6961.5,19859.7,7883.4,19906],
[1,8054.8,19914.6,8097.9,19908.7,8269.4,19906],
[1,9078.7,19893.1,10053,19854,10383,19840]],
0,[0,"#0000ff"]],
[1,
[0,[0,10464,19812],[0,10466,19809.1],[0,10472.2,19817.7],
[0,10462,19814.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8136.6,18721.5],[1,8175.2,18725,8226.1,18731.7,8269.4,18745],
[1,9216,19034.5,10259,19682.1,10464,19812]],
0,[0,"#0000ff"]],
[1,
[0,[0,10425,17890.7],[0,10424.5,17887.2],[0,10434.9,17889.3],
[0,10425.5,17894.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8135.4,18713.2],[1,8173.9,18709.2,8225.2,18702.3,8269.4,18691],
[1,9219.3,18447.8,9385.2,18162.3,10332,17909],
[1,10362,17901,10396,17895,10425,17890.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10462,19812.2],[0,10463.8,19809.2],[0,10470.6,19817.3],
[0,10460.2,19815.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8170.9,18779.6],[1,8202.6,18783.6,8238,18789.7,8269.4,18799],
[1,9207.4,19075.8,10252,19686.9,10462,19812.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10425,17890.4],[0,10424.5,17886.9],[0,10434.9,17889],
[0,10425.5,17893.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8169.1,18763.7],[1,8201.2,18759.6,8237.2,18753.6,8269.4,18745],
[1,9225,18488.8,9379.7,18175.4,10332,17909],
[1,10362,17900.7,10396,17894.6,10425,17890.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10415,7971],[0,10415.3,7967.52],[0,10425,7972],[0,10414.7,7974.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5580.8,7598],[1,5942.3,7568,7221.3,7479,8269.4,7575],
[1,9198,7660,9413.7,7798,10332,7957],
[1,10359,7962,10389,7966,10415,7971]],
0,[0,"#0000ff"]],
[1,
[0,[0,10414,8133],[0,10414.3,8129.52],[0,10424,8134],[0,10413.7,8136.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5593.8,7605],[1,5972.3,7603,7235.1,7606,8269.4,7726],
[1,9196.6,7834,9413.2,7957,10332,8119],
[1,10359,8124,10388,8128,10414,8133]],
0,[0,"#0000ff"]],
[1,
[0,[0,10416,7970],[0,10416.7,7966.57],[0,10425.8,7971.96],
[0,10415.3,7973.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8166.3,7614],[1,8198.8,7619,8235.8,7624,8269.4,7629],
[1,8700.3,7693,10064,7914,10416,7970]],
0,[0,"#0000ff"]],
[1,
[0,[0,10412,8133],[0,10412.7,8129.57],[0,10421.8,8134.96],
[0,10411.3,8136.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8171,7613],[1,8202.4,7618,8237.5,7623,8269.4,7629],
[1,9195.6,7803,9408.2,7935,10332,8119],
[1,10358,8124,10386,8129,10412,8133]],
0,[0,"#0000ff"]],
[1,
[0,[0,10411,7972],[0,10411.3,7968.52],[0,10421,7973],[0,10410.7,7975.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8160.5,7667],[1,8532.6,7718,10029,7920,10411,7972]],0,
[0,"#0000ff"]],
[1,
[0,[0,10413,8133],[0,10413.3,8129.52],[0,10423,8134],[0,10412.7,8136.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8155.4,7668],[1,8190.4,7674,8232,7681,8269.4,7688],
[1,9190.1,7860,9411.4,7948,10332,8119],
[1,10359,8124,10387,8129,10413,8133]],
0,[0,"#0000ff"]],
[1,
[0,[0,10441,13984],[0,10439.6,13980.8],[0,10450.1,13979.9],
[0,10442.4,13987.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8137.3,17805.3],[1,8178.4,17796.8,8231.8,17780.3,8269.4,17749],
[1,9718.2,16544.1,8956.6,15332.5,10332,14045],
[1,10363,14016,10406,13996,10441,13984]],
0,[0,"#0000ff"]],
[1,
[0,[0,10480,19808.9],[0,10482.8,19806.8],[0,10486,19816.9],
[0,10477.2,19811]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8146.2,17814],[1,8184.1,17816.4,8231.1,17823.2,8269.4,17841],
[1,9379.5,18355.9,10335,19612.2,10480,19808.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10394,18034],[0,10394.3,18030.5],[0,10404,18035],
[0,10393.7,18037.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8141.9,17820.2],[1,8474.8,17851.8,9981.2,17994.8,10394,18034]],0,
[0,"#0000ff"]],
[1,
[0,[0,10479,19861.2],[0,10476.3,19858.9],[0,10485.5,19853.6],
[0,10481.7,19863.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5598.7,21742.6],[1,6112.2,21736.1,8142.7,21707.4,8269.4,21660],
[1,9371.2,21247.8,10330,20053.2,10479,19861.2]],
0,[0,"#0000ff"]],
[1,[0,[0,7926,2153],[0,7926,2149.5],[0,7936,2153],[0,7926,2156.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5611,2105],[1,6047.1,2114,7460.2,2143,7926,2153]],0,[0,"#0000ff"]],
[1,
[0,[0,7976.2,3173],[0,7976.54,3169.52],[0,7986.15,3173.98],
[0,7975.86,3176.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5592.5,2112],[1,5620.2,2116,5649.7,2121,5676.4,2129],
[1,6714,2434,6846.1,2848,7883.4,3154],
[1,7913,3163,7946,3169,7976.2,3173]],
0,[0,"#0000ff"]],
[1,[0,[0,15003,2396],[0,15003,2392.5],[0,15013,2396],[0,15003,2399.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,12869,2287],[1,13090,2299,14592,2375,15003,2396]],0,[0,"#ee82ee"]],
[1,[0,[0,14955,2343],[0,14955,2339.5],[0,14965,2343],[0,14955,2346.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,12869,2287],[1,13082,2292,14486,2330,14955,2343]],0,[0,"#ee82ee"]],
[1,
[0,[0,12805,2282],[0,12805.3,2278.52],[0,12815,2283],[0,12804.7,2285.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5609.3,2098],[1,6191.7,2080,8651.6,2016,10666,2109],
[1,11535,2149,12594,2259,12805,2282]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10488,19862.2],[0,10484.8,19860.8],[0,10492,19853],
[0,10491.2,19863.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8142.9,22652.6],[1,8182,22651.4,8231.2,22644.8,8269.4,22623],
[1,9553.8,21891.8,10380,20104,10488,19862.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,7974.9,3188],[0,7974.56,3184.52],[0,7984.85,3187.02],
[0,7975.24,3191.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5573.4,3358],[1,5973,3330,7556.9,3218,7974.9,3188]],0,
[0,"#0000ff"]],
[1,
[0,[0,15032,7315],[0,15032.3,7311.52],[0,15042,7316],[0,15031.7,7318.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12869,7170],[1,13095,7185,14668,7290,15032,7315]],0,[0,"#0000ff"]],
[1,
[0,[0,16664,7660],[0,16665.1,7656.68],[0,16673.5,7663.16],
[0,16662.9,7663.32]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,12870,7167],[1,13065,7163,14286,7141,15261,7293],
[1,15824,7381,16484,7599,16664,7660]],
0,[0,"#0000ff"]],
[1,
[0,[0,16665,7607],[0,16666,7603.65],[0,16674.6,7609.87],[0,16664,7610.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,12869,7167],[1,13065,7158,14285,7110,15261,7250],
[1,15826,7331,16489,7547,16665,7607]],
0,[0,"#0000ff"]],
[1,
[0,[0,12805,7170],[0,12804.7,7166.52],[0,12815,7169],[0,12805.3,7173.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10595,7281],[1,10996,7261,12545,7183,12805,7170]],0,[0,"#0000ff"]],
[1,[0,[0,12770,3777],[0,12770,3773.5],[0,12780,3777],[0,12770,3780.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8136.2,3781],[1,8419.3,3779,9654.1,3772,10666,3773],
[1,11493,3774,12496,3776,12770,3777]],
0,[0,"#0000ff"]],
[1,
[0,[0,12815,3801],[0,12812.5,3798.53],[0,12822.1,3793.93],
[0,12817.5,3803.47]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10545,5386],[1,10580,5374,10627,5356,10666,5335],
[1,11616,4821,12635,3956,12815,3801]],
0,[0,"#0000ff"]],
[1,
[0,[0,10377,16533.6],[0,10377.8,16530.2],[0,10386.7,16535.8],
[0,10376.2,16537]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8186.6,14383],[1,8214.7,14387,8244.1,14394,8269.4,14407],
[1,9440,14998.4,9168.2,15913.1,10332,16517],
[1,10346,16524.2,10362,16529.6,10377,16533.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10477,11285],[0,10474.4,11282.7],[0,10483.6,11277.5],
[0,10479.6,11287.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8188.1,14380],[1,8216.2,14376,8245.2,14368,8269.4,14353],
[1,9619.5,13534,9370.4,12713,10332,11461],
[1,10382,11396,10444,11323,10477,11285]],
0,[0,"#0000ff"]],
[1,
[0,[0,7941.4,15914.5],[0,7942.13,15911.1],[0,7951.18,15916.6],
[0,7940.67,15917.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5493.3,10900],[1,5524.8,10949,5612.4,11087,5676.4,11207],
[1,6760,13236,6030.9,14525,7883.4,15889],
[1,7900.4,15901.5,7920.6,15909.5,7941.4,15914.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10413,11243],[0,10413.7,11239.6],[0,10422.8,11245],
[0,10412.3,11246.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5643.7,10874],[1,6073.1,10856,7274.5,10818,8269.4,10901],
[1,8702.6,10937,10058,11179,10413,11243]],
0,[0,"#0000ff"]],
[1,
[0,[0,7953.1,10648],[0,7952.76,10644.5],[0,7963.05,10647],
[0,7953.44,10651.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5611.4,10870],[1,6056.9,10827,7518,10689,7953.1,10648]],0,
[0,"#0000ff"]],
[1,
[0,[0,7941.5,15913.9],[0,7942.26,15910.5],[0,7951.26,15916.1],
[0,7940.74,15917.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5561,11548],[1,5599.4,11558,5644.1,11574,5676.4,11602],
[1,7297.2,13004,6135.8,14649,7883.4,15889],
[1,7900.6,15901.2,7920.8,15909,7941.5,15913.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10378,11266],[0,10377.7,11262.5],[0,10388,11265],
[0,10378.3,11269.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5589.1,11529],[1,6244,11493,9685.7,11304,10378,11266]],0,
[0,"#0000ff"]],
[1,
[0,[0,10368,16536.4],[0,10369.1,16533.1],[0,10377.5,16539.5],
[0,10366.9,16539.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8236,11136],[1,8248,11141,8259.4,11147,8269.4,11155],
[1,10269,12743,8350,14907.7,10332,16517],
[1,10343,16525.5,10355,16531.8,10368,16536.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10378,11252],[0,10378.3,11248.5],[0,10388,11253],
[0,10377.7,11255.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8233.5,11136],[1,8684.3,11161,9975,11231,10378,11252]],0,
[0,"#0000ff"]],
[1,
[0,[0,10389,10835],[0,10388.7,10831.5],[0,10399,10834],
[0,10389.3,10838.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8187.6,11114],[1,8592.6,11063,9985.7,10886,10389,10835]],0,
[0,"#0000ff"]],
[1,
[0,[0,10380,18039.5],[0,10380.8,18036.1],[0,10389.7,18041.9],
[0,10379.2,18042.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8124.9,13352],[1,8167.7,13368,8229.5,13396,8269.4,13439],
[1,9793.9,15068.9,8561,16659.6,10332,18017],
[1,10346,18027.7,10363,18034.8,10380,18039.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10378,10119],[0,10377.3,10115.6],[0,10387.8,10117],
[0,10378.7,10122.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8170.8,13339],[1,8204.1,13335,8240.5,13327,8269.4,13309],
[1,9687.9,12407,8923.7,11056,10332,10139],
[1,10346,10130,10362,10124,10378,10119]],
0,[0,"#0000ff"]],
[1,
[0,[0,2879.1,17324],[0,2879.62,17320.5],[0,2888.99,17325.5],
[0,2878.58,17327.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,914.13,17022.8],[1,1184.2,17064.4,2064.8,17200.2,2793.4,17311],
[1,2821.2,17315.2,2851.5,17319.8,2879.1,17324]],
0,[0,"#0000ff"]],
[1,
[0,[0,15004,16155.9],[0,15004,16152.4],[0,15014,16155.8],
[0,15004,16159.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,882.43,16993.8],[1,1251.7,16877.6,3556.2,16178,5481.4,16178],
[1,5481.4,16178,5481.4,16178,10499,16178],
[1,12304,16178,14505,16160.2,15004,16155.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,2907.5,1362],[0,2907.16,1358.52],[0,2917.45,1361.02],
[0,2907.84,1365.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,877.14,1413],[1,1152,1406,2584.3,1370,2907.5,1362]],0,
[0,"#0000ff"]],
[1,
[0,[0,10401,5157],[0,10400.7,5153.52],[0,10411,5156],[0,10401.3,5160.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8163.1,6172],[1,8196.8,6168,8235.4,6161,8269.4,6151],
[1,9241.5,5860,9363.5,5474,10332,5173],
[1,10354,5166,10378,5161,10401,5157]],
0,[0,"#0000ff"]],
[1,
[0,[0,10403,10155],[0,10403.3,10151.5],[0,10413,10156],
[0,10402.7,10158.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8159.1,9237],[1,8193.6,9241,8233.9,9247,8269.4,9257],
[1,9230.1,9524,9374.7,9861,10332,10139],
[1,10355,10146,10380,10151,10403,10155]],
0,[0,"#0000ff"]],
[1,
[0,[0,10403,8157],[0,10402.3,8153.57],[0,10412.8,8155.04],
[0,10403.7,8160.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8160.4,9224],[1,8194.7,9220,8234.5,9214,8269.4,9203],
[1,9248.2,8899,9357,8487,10332,8173],
[1,10355,8166,10380,8160,10403,8157]],
0,[0,"#0000ff"]],
[1,
[0,[0,10395,15054.3],[0,10395.4,15050.8],[0,10404.9,15055.5],
[0,10394.6,15057.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5532.7,10161],[1,5575.2,10159,5635,10163,5676.4,10193],
[1,7501.6,11522,6034.1,13474,7883.4,14769],
[1,7954,14818.5,8183.7,14798.7,8269.4,14808],
[1,9088.8,14897,10076,15015.7,10395,15054.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10414,7971],[0,10414.3,7967.52],[0,10424,7972],[0,10413.7,7974.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,7514],[1,8141.1,7520,8210.5,7531,8269.4,7542],
[1,9189.3,7711,9412.2,7790,10332,7957],
[1,10359,7962,10388,7967,10414,7971]],
0,[0,"#0000ff"]],
[1,
[0,[0,10419,7916],[0,10419.3,7912.52],[0,10429,7917],[0,10418.7,7919.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,7514],[1,8141,7521,8210.3,7532,8269.4,7542],
[1,9110.3,7685,10128,7864,10419,7916]],
0,[0,"#0000ff"]],
[1,[0,[0,8039.3,7516],[0,8038.6,7512.57],[0,8049.1,7514],[0,8040,7519.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5534.7,10169],[1,5575.7,10168,5632.8,10163,5676.4,10139],
[1,6996.8,9420,6636.1,8415,7883.4,7575],
[1,7932,7542,7998.4,7525,8039.3,7516]],
0,[0,"#0000ff"]],
[1,
[0,[0,8003.3,10129],[0,8003.3,10125.5],[0,8013.3,10129],
[0,8003.3,10132.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5535,10165],[1,5865.3,10160,7622,10135,8003.3,10129]],0,
[0,"#0000ff"]],
[1,
[0,[0,10463,19857.9],[0,10461.2,19854.9],[0,10471.6,19852.8],
[0,10464.8,19860.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5620.5,20836.8],[1,6110.6,20859.4,7755.9,20925.3,8269.4,20816],
[1,9218.7,20613.9,10258,19985.9,10463,19857.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10439,19854.3],[0,10437.9,19851],[0,10448.5,19851.3],
[0,10440.1,19857.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5548.1,20410.8],[1,5917.6,20414.7,7718.7,20430,8269.4,20361],
[1,9146.8,20251.1,10182,19935.5,10439,19854.3]],
0,[0,"#0000ff"]],
[1,[0,[0,10400,13389],[0,10400,13385.5],[0,10410,13389],[0,10400,13392.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5527.3,20396.9],[1,5571.4,20382,5637.2,20353.5,5676.4,20307],
[1,7704.6,17904.1,5410,15526.6,7883.4,13585],
[1,7896.1,13575,9922.2,13425,10400,13389]],
0,[0,"#0000ff"]],
[1,
[0,[0,10425,19851.8],[0,10424.2,19848.4],[0,10434.8,19849.7],
[0,10425.8,19855.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8146.7,20323.1],[1,8183.3,20317.2,8228.9,20309.6,8269.4,20302],
[1,9119.1,20142.7,10143,19915,10425,19851.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,12769,15413.1],[0,12769.6,15409.6],[0,12778.9,15414.8],
[0,12768.4,15416.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8119.9,7802],[1,8161.9,7818,8225.4,7848,8269.4,7889],
[1,9534.6,9071,8868.1,10270,10332,11194],
[1,10459,11274,10545,11146,10666,11232],
[1,12331,12414,11092,14065,12662,15370],
[1,12692,15394.7,12733,15407,12769,15413.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10405,6556],[0,10404.3,6552.57],[0,10414.8,6554.04],
[0,10405.7,6559.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8107.9,7769],[1,8146.1,7749,8212.5,7713,8269.4,7683],
[1,9187.2,7191,9346.4,6907,10332,6573],
[1,10356,6565,10381,6560,10405,6556]],
0,[0,"#0000ff"]],
[1,[0,[0,10398,13376],[0,10398,13372.5],[0,10408,13376],[0,10398,13379.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8129,13231],[1,8434.8,13251,9985.4,13349,10398,13376]],0,
[0,"#0000ff"]],
[1,[0,[0,10390,8145],[0,10390,8141.5],[0,10400,8145],[0,10390,8148.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5616.3,8101],[1,6338,8108,9735.1,8139,10390,8145]],0,
[0,"#0000ff"]],
[1,
[0,[0,10392,8142],[0,10392.3,8138.52],[0,10402,8143],[0,10391.7,8145.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8206.7,8067],[1,8635.5,8081,9998.1,8129,10392,8142]],0,
[0,"#0000ff"]],
[1,
[0,[0,12707,5165],[0,12707.3,5161.52],[0,12717,5166],[0,12706.7,5168.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10576,5042],[1,10913,5062,12270,5140,12707,5165]],0,[0,"#0000ff"]],
[1,[0,[0,12705,5002],[0,12705,4998.5],[0,12715,5002],[0,12705,5005.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10578,5037],[1,10918,5031,12268,5009,12705,5002]],0,[0,"#0000ff"]],
[1,
[0,[0,12731,5012],[0,12730.7,5008.52],[0,12741,5011],[0,12731.3,5015.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10579,5245],[1,10928,5208,12325,5056,12731,5012]],0,[0,"#0000ff"]],
[1,[0,[0,12808,5024],[0,12805.9,5021.2],[0,12816,5018],[0,12810.1,5026.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10589,8037],[1,10616,8033,10644,8025,10666,8011],
[1,11980,7185,11606,6283,12662,5146],
[1,12708,5097,12770,5051,12808,5024]],
0,[0,"#0000ff"]],
[1,
[0,[0,12732,4988],[0,12732.3,4984.52],[0,12742,4989],[0,12731.7,4991.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10579,4749],[1,10928,4788,12327,4943,12732,4988]],0,[0,"#0000ff"]],
[1,[0,[0,2876.2,263],[0,2876.2,259.5],[0,2886.2,263],[0,2876.2,266.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,957.76,263],[1,1348.2,258,2530,258,2876.2,263]],0,[0,"#0000ff"]],
[1,[0,[0,2799.8,216],[0,2799.8,212.5],[0,2809.8,216],[0,2799.8,219.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,958.15,263],[1,1323.9,254,2381.9,227,2799.8,216]],0,[0,"#0000ff"]],
[1,
[0,[0,10487,19862.4],[0,10483.8,19861],[0,10490.9,19853.2],
[0,10490.2,19863.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8147.4,22598.3],[1,8185.7,22596.7,8232.6,22589.7,8269.4,22569],
[1,9540.8,21853.2,10377,20102.4,10487,19862.4]],
0,[0,"#0000ff"]],
[1,[0,[0,10388,22866],[0,10388,22862.5],[0,10398,22866],[0,10388,22869.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167.7,22866],[1,8544.4,22866,9977.3,22866,10388,22866]],0,
[0,"#0000ff"]],
[1,
[0,[0,10489,19862.7],[0,10485.8,19861.4],[0,10492.8,19853.5],
[0,10492.2,19864]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8167.3,22867.8],[1,8201.3,22864.9,8239,22857,8269.4,22839],
[1,9604,22046.9,10390,20116.5,10489,19862.7]],
0,[0,"#0000ff"]],
[1,[0,[0,10388,22920],[0,10388,22916.5],[0,10398,22920],[0,10388,22923.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167.7,22920],[1,8544.4,22920,9977.3,22920,10388,22920]],0,
[0,"#0000ff"]],
[1,
[0,[0,10489,19862.8],[0,10485.8,19861.5],[0,10492.8,19853.6],
[0,10492.2,19864.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8167.3,22921.9],[1,8201.4,22919,8239.1,22911.2,8269.4,22893],
[1,9616.8,22085.6,10392,20119.4,10489,19862.8]],
0,[0,"#0000ff"]],
[1,[0,[0,10388,22974],[0,10388,22970.5],[0,10398,22974],[0,10388,22977.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167.7,22974],[1,8544.4,22974,9977.3,22974,10388,22974]],0,
[0,"#0000ff"]],
[1,
[0,[0,10489,19862.9],[0,10485.8,19861.6],[0,10492.8,19853.6],
[0,10492.2,19864.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8166.9,22976.1],[1,8201.1,22973.2,8239,22965.4,8269.4,22947],
[1,9629.7,22124.2,10395,20122.3,10489,19862.9]],
0,[0,"#0000ff"]],
[1,[0,[0,10388,22812],[0,10388,22808.5],[0,10398,22812],[0,10388,22815.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167.7,22812],[1,8544.4,22812,9977.3,22812,10388,22812]],0,
[0,"#0000ff"]],
[1,
[0,[0,10489,19862.6],[0,10485.7,19861.5],[0,10492,19853.1],
[0,10492.3,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8167.2,22813.6],[1,8201.2,22810.7,8238.9,22802.9,8269.4,22785],
[1,9591.3,22008.2,10388,20113.5,10489,19862.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10399,11246],[0,10399.3,11242.5],[0,10409,11247],
[0,10398.7,11249.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3039,11276],[1,3488,11226,6123.5,10945,8269.4,11047],
[1,9094.7,11086,10086,11206,10399,11246]],
0,[0,"#0000ff"]],
[1,
[0,[0,10377,16552.8],[0,10376.7,16549.3],[0,10387,16552],
[0,10377.3,16556.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3042.6,11279],[1,3078.6,11280,3121.1,11287,3151.4,11311],
[1,5157.7,12902,3166.8,15225.6,5286.4,16662],
[1,5423.6,16755,8103.8,16666.4,8269.4,16662],
[1,9074.2,16640.7,10041,16576.3,10377,16552.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,5369.8,11288],[0,5369.8,11284.5],[0,5379.8,11288],
[0,5369.8,11291.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3045.5,11284],[1,3399.9,11285,4940.3,11287,5369.8,11288]],0,
[0,"#0000ff"]],
[1,
[0,[0,10410,12945],[0,10410.3,12941.5],[0,10420,12946],
[0,10409.7,12948.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3041.2,12800],[1,3496.9,12773,6129.2,12629,8269.4,12735],
[1,9104.6,12776,10109,12905,10410,12945]],
0,[0,"#0000ff"]],
[1,
[0,[0,10431,12207],[0,10432,12203.6],[0,10440.6,12209.9],
[0,10430,12210.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2993.1,12787],[1,3154.4,12653,4234.4,11783,5286.4,11508],
[1,5454.1,11464,5503.4,11499,5676.4,11508],
[1,6661.8,11562,6901.9,11649,7883.4,11751],
[1,8054.9,11769,8098.9,11764,8269.4,11789],
[1,9128.7,11915,10159,12145,10431,12207]],
0,[0,"#0000ff"]],
[1,
[0,[0,10399,19846.3],[0,10398.6,19842.8],[0,10408.9,19845.2],
[0,10399.4,19849.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3011,12819],[1,3051.8,12837,3115,12871,3151.4,12919],
[1,5135.1,15550.7,2641.8,18053.6,5286.4,20020],
[1,5419.4,20118.9,8103.8,20026.9,8269.4,20020],
[1,9093.8,19985.9,10085,19881,10399,19846.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,5334.7,16017.2],[0,5335.57,16013.8],[0,5344.38,16019.7],
[0,5333.83,16020.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3005.2,12820],[1,3043.3,12840,3106.6,12876,3151.4,12919],
[1,4349.3,14075,3867.9,15125.4,5286.4,15997],
[1,5301.2,16006,5317.7,16012.6,5334.7,16017.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,5330.8,16024],[0,5330.8,16020.5],[0,5340.8,16024],
[0,5330.8,16027.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3048.2,16024],[1,3397.5,16024,4855.5,16024,5330.8,16024]],0,
[0,"#0000ff"]],
[1,
[0,[0,10416,19850.3],[0,10415.3,19846.9],[0,10425.8,19848.4],
[0,10416.7,19853.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2979.6,16042],[1,3088.5,16316,4419.1,19627,5286.4,20134],
[1,5429.5,20217.6,8104.1,20145,8269.4,20134],
[1,9112.5,20077.7,10123,19903.1,10416,19850.3]],
0,[0,"#0000ff"]],
[1,[0,[0,10391,12956],[0,10391,12952.5],[0,10401,12956],[0,10391,12959.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2979.2,16006],[1,3060.7,15794.1,3870.2,13766,5286.4,13054],
[1,5522.4,12935,9662.9,12952,10391,12956]],
0,[0,"#0000ff"]],
[1,
[0,[0,8016.1,2176],[0,8015.08,2172.65],[0,8025.67,2173.1],
[0,8017.12,2179.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5581.1,2987],[1,5611.9,2983,5645.7,2977,5676.4,2970],
[1,6684.4,2731,6902.2,2553,7883.4,2221],
[1,7927.9,2206,7978.1,2189,8016.1,2176]],
0,[0,"#0000ff"]],
[1,
[0,[0,10339,13533],[0,10339.3,13529.5],[0,10349,13534],
[0,10338.7,13536.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5575.6,3008],[1,5611.8,3017,5650.7,3033,5676.4,3062],
[1,8799,6551,4343.3,10299,7883.4,13363],
[1,7976.6,13444,9783.9,13514,10339,13533]],
0,[0,"#0000ff"]],
[1,
[0,[0,7975,3174],[0,7975.34,3170.52],[0,7984.95,3174.98],
[0,7974.66,3177.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5590,3005],[1,6015.1,3035,7562.9,3145,7975,3174]],0,[0,"#0000ff"]],
[1,
[0,[0,12805,2288],[0,12804.7,2284.52],[0,12815,2287],[0,12805.3,2291.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5572.3,2985],[1,5605.2,2981,5642.5,2975,5676.4,2970],
[1,6660.5,2815,6894,2695,7883.4,2578],
[1,8916.5,2456,12406,2305,12805,2288]],
0,[0,"#ee82ee"]],
[1,[0,[0,15031,7322],[0,15031,7318.5],[0,15041,7322],[0,15031,7325.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12932,7381],[1,13300,7371,14688,7332,15031,7322]],0,[0,"#0000ff"]],
[1,
[0,[0,15070,7671],[0,15070.3,7667.52],[0,15080,7672],[0,15069.7,7674.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12918,7394],[1,13279,7440,14811,7638,15070,7671]],0,[0,"#0000ff"]],
[1,
[0,[0,10386,15056.3],[0,10386.3,15052.8],[0,10396,15057.2],
[0,10385.7,15059.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5612.6,10220],[1,5635.4,10225,5657.8,10233,5676.4,10247],
[1,7496,11570,6039.9,13513,7883.4,14802],
[1,7909.6,14820.3,9887.7,15009,10386,15056.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,8039.6,7516],[0,8038.9,7512.57],[0,8049.4,7514],[0,8040.3,7519.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5609.3,10216],[1,5632.6,10211,5656,10204,5676.4,10193],
[1,7009.1,9458,6625.4,8431,7883.4,7575],
[1,7931.9,7542,7998.6,7524,8039.6,7516]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19807.3],[0,10494.3,19806.2],[0,10494,19816.8],
[0,10487.7,19808.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.5,16135.2],[1,8143.6,16141.1,8219.4,16157.1,8269.4,16197],
[1,9660.1,17305.3,10403,19533.7,10491,19807.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,12731,15185.3],[0,12731.3,15181.8],[0,12741,15186.1],
[0,12730.7,15188.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.7,16130.2],[1,8141.4,16127.3,8211.5,16120.2,8269.4,16105],
[1,9222.3,15854.8,9368.3,15496.7,10332,15294],
[1,11242,15102.9,12376,15160.6,12731,15185.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,8038.8,16132],[0,8038.8,16128.5],[0,8048.8,16132],
[0,8038.8,16135.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5532.7,16132],[1,5868.4,16132,7748.3,16132,8038.8,16132]],0,
[0,"#0000ff"]],
[1,
[0,[0,7936.3,2164],[0,7935.96,2160.52],[0,7946.25,2163.02],
[0,7936.64,2167.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5574.6,2297],[1,5964.6,2275,7468,2190,7936.3,2164]],0,
[0,"#0000ff"]],
[1,
[0,[0,7979.8,3171],[0,7980.49,3167.57],[0,7989.6,3172.98],
[0,7979.11,3174.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5519,2319],[1,5740,2416,6893.3,2912,7883.4,3154],
[1,7914.4,3162,7948.8,3167,7979.8,3171]],
0,[0,"#0000ff"]],
[1,[0,[0,12805,2285],[0,12805,2281.5],[0,12815,2285],[0,12805,2288.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5575.8,2298],[1,5898.1,2283,6984.9,2236,7883.4,2221],
[1,9936.9,2186,12469,2273,12805,2285]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10383,3181],[0,10383.3,3177.52],[0,10393,3182],[0,10382.7,3184.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,3128],[1,8332.2,3133,9934.8,3171,10383,3181]],0,
[0,"#0000ff"]],
[1,
[0,[0,10411,2870],[0,10410.7,2866.52],[0,10421,2869],[0,10411.3,2873.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,3124],[1,8337.3,3098,10006,2914,10411,2870]],0,
[0,"#0000ff"]],
[1,
[0,[0,8039.5,3115],[0,8040.55,3111.66],[0,8049.04,3118.01],
[0,8038.45,3118.34]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5530.4,2318],[1,5859.9,2422,7750.7,3023,8039.5,3115]],0,
[0,"#0000ff"]],
[1,
[0,[0,8004.4,2175],[0,8003.38,2171.65],[0,8013.97,2172.1],
[0,8005.42,2178.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5522.5,2824],[1,5817.9,2747,7620.3,2275,8004.4,2175]],0,
[0,"#0000ff"]],
[1,
[0,[0,7987,3169],[0,7987.34,3165.52],[0,7996.95,3169.98],
[0,7986.66,3172.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5529.2,2841],[1,5839.9,2883,7572,3114,7987,3169]],0,[0,"#0000ff"]],
[1,[0,[0,12805,2287],[0,12805,2283.5],[0,12815,2287],[0,12805,2290.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5523.7,2825],[1,5757.7,2769,6918.1,2501,7883.4,2405],
[1,9114.5,2283,9429.6,2376,10666,2346],
[1,11534,2325,12595,2293,12805,2287]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8039.5,3123],[0,8039.85,3119.52],[0,8049.45,3124.01],
[0,8039.15,3126.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5530.1,2840],[1,5858.9,2877,7750.7,3090,8039.5,3123]],0,
[0,"#0000ff"]],
[1,
[0,[0,10402,5248],[0,10402.3,5244.52],[0,10412,5249],[0,10401.7,5251.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,5117],[1,8335.6,5130,9982.3,5224,10402,5248]],0,
[0,"#0000ff"]],
[1,
[0,[0,10413,5603],[0,10413.3,5599.52],[0,10423,5604],[0,10412.7,5606.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.4,5121],[1,8290.5,5164,9412.2,5418,10332,5589],
[1,10358,5594,10387,5599,10413,5603]],
0,[0,"#0000ff"]],
[1,
[0,[0,8039.5,5101],[0,8040.83,5097.76],[0,8048.74,5104.81],
[0,8038.17,5104.24]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5518.6,4176],[1,5811.8,4283,7747.4,4994,8039.5,5101]],0,
[0,"#0000ff"]],
[1,
[0,[0,7956.7,5544],[0,7957.38,5540.57],[0,7966.51,5545.94],
[0,7956.02,5547.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5503.2,4179],[1,5673.4,4309,6811.2,5162,7883.4,5527],
[1,7906.6,5535,7932.1,5540,7956.7,5544]],
0,[0,"#0000ff"]],
[1,
[0,[0,8023.9,3201],[0,8022.55,3197.77],[0,8033.13,3197.15],
[0,8025.25,3204.23]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5518.1,4148],[1,5804.8,4040,7684.2,3329,8023.9,3201]],0,
[0,"#0000ff"]],
[1,
[0,[0,8000.5,2175],[0,7999.46,2171.66],[0,8010.04,2172.02],
[0,8001.54,2178.34]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5497.9,4145],[1,5645.4,3990,6762.6,2837,7883.4,2221],
[1,7920,2201,7963.8,2186,8000.5,2175]],
0,[0,"#0000ff"]],
[1,[0,[0,12704,4999],[0,12704,4995.5],[0,12714,4999],[0,12704,5002.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.5,4263],[1,8289.5,4322,9400.3,4672,10332,4821],
[1,11229,4964,12324,4993,12704,4999]],
0,[0,"#ee82ee"]],
[1,[0,[0,10391,4166],[0,10391,4162.5],[0,10401,4166],[0,10391,4169.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,8103.6,4253],[1,8333.6,4244,9953.9,4183,10391,4166]],0,
[0,"#ee82ee"]],
[1,[0,[0,8039.1,4253],[0,8039.1,4249.5],[0,8049.1,4253],[0,8039.1,4256.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5537.7,4164],[1,5886.9,4176,7751.2,4242,8039.1,4253]],0,
[0,"#ee82ee"]],
[1,[0,[0,10399,4738],[0,10399,4734.5],[0,10409,4738],[0,10399,4741.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,8103.6,4685],[1,8335.1,4690,9975,4728,10399,4738]],0,
[0,"#ee82ee"]],
[1,[0,[0,14986,4914],[0,14986,4910.5],[0,14996,4914],[0,14986,4917.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.5,4686],[1,8291,4700,9415.5,4784,10332,4821],
[1,10809,4840,14290,4902,14986,4914]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8039.4,4677],[0,8040.09,4673.57],[0,8049.21,4678.96],
[0,8038.71,4680.43]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5529.2,4172],[1,5855.6,4237,7750.2,4618,8039.4,4677]],0,
[0,"#ee82ee"]],
[1,
[0,[0,10416,4728],[0,10416.3,4724.52],[0,10426,4729],[0,10415.7,4731.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.7,4170],[1,8291,4221,9408.8,4526,10332,4713],
[1,10359,4718,10389,4724,10416,4728]],
0,[0,"#0000ff"]],
[1,[0,[0,10388,4162],[0,10388,4158.5],[0,10398,4162],[0,10388,4165.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,4162],[1,8333.1,4162,9947.6,4162,10388,4162]],0,
[0,"#0000ff"]],
[1,[0,[0,8039.1,4162],[0,8039.1,4158.5],[0,8049.1,4162],[0,8039.1,4165.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5538,4162],[1,5888,4162,7751.4,4162,8039.1,4162]],0,[0,"#0000ff"]],
[1,[0,[0,8038.9,3129],[0,8038.9,3125.5],[0,8048.9,3129],[0,8038.9,3132.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5510.2,4146],[1,5706.1,4042,6865.2,3434,7883.4,3154],
[1,7936.3,3139,7999.6,3133,8038.9,3129]],
0,[0,"#0000ff"]],
[1,
[0,[0,12805,2289],[0,12804.7,2285.52],[0,12815,2288],[0,12805.3,2292.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5500.3,4145],[1,5657.7,4002,6772.6,3014,7883.4,2649],
[1,7914.6,2639,12351,2321,12805,2289]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7976.8,3914],[0,7976.46,3910.52],[0,7986.75,3913.03],
[0,7977.14,3917.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5535.6,4157],[1,5860.2,4124,7547.3,3957,7976.8,3914]],0,
[0,"#0000ff"]],
[1,[0,[0,12704,5000],[0,12704,4996.5],[0,12714,5000],[0,12704,5003.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,8103.5,4992],[1,8447.3,4993,11959,4999,12704,5000]],0,
[0,"#ee82ee"]],
[1,
[0,[0,10411,5603],[0,10411.7,5599.57],[0,10420.8,5604.96],
[0,10410.3,5606.43]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.6,5000],[1,8290.5,5057,9406.1,5392,10332,5589],
[1,10358,5594,10385,5599,10411,5603]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8039.2,4988],[0,8039.54,4984.52],[0,8049.15,4988.99],
[0,8038.86,4991.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5516.8,4176],[1,5732.7,4262,6897,4716,7883.4,4960],
[1,7936.9,4973,8000,4983,8039.2,4988]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10418,5241],[0,10418.7,5237.57],[0,10427.8,5242.96],
[0,10417.3,5244.43]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.7,4795],[1,8141.1,4800,8210.5,4809,8269.4,4819],
[1,9191.1,4974,9412.5,5062,10332,5227],
[1,10360,5232,10390,5237,10418,5241]],
0,[0,"#ee82ee"]],
[1,[0,[0,14986,4915],[0,14986,4911.5],[0,14996,4915],[0,14986,4918.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.5,4793],[1,8291.2,4799,9416.3,4835,10332,4854],
[1,12185,4891,14443,4911,14986,4915]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8039.1,4788],[0,8039.44,4784.52],[0,8049.05,4788.97],
[0,8038.76,4791.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5523.3,4174],[1,5756.3,4242,6916.5,4577,7883.4,4765],
[1,7937.2,4775,8000.1,4783,8039.1,4788]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10411,4621],[0,10411.3,4617.52],[0,10421,4622],[0,10410.7,4624.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5581.3,3847],[1,5945,3809,7232.4,3696,8269.4,3877],
[1,9227.2,4044,9390.3,4365,10332,4605],
[1,10358,4611,10385,4617,10411,4621]],
0,[0,"#0000ff"]],
[1,
[0,[0,7976.4,3359],[0,7975.71,3355.57],[0,7986.21,3357.04],
[0,7977.09,3362.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5549.5,3843],[1,5833.6,3779,6954,3532,7883.4,3373],
[1,7913.5,3368,7946.4,3363,7976.4,3359]],
0,[0,"#0000ff"]],
[1,[0,[0,7964.2,3902],[0,7964.2,3898.5],[0,7974.2,3902],[0,7964.2,3905.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5607,3860],[1,6051,3868,7542.2,3895,7964.2,3902]],0,[0,"#0000ff"]],
[1,[0,[0,12805,2288],[0,12805,2284.5],[0,12815,2288],[0,12805,2291.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5505.8,3840],[1,5685,3711,6820.7,2912,7883.4,2616],
[1,8009.5,2581,12356,2316,12805,2288]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8039,3131],[0,8038.66,3127.52],[0,8048.95,3130.04],
[0,8039.34,3134.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5529,3841],[1,5773.8,3755,6918,3362,7883.4,3154],
[1,7936.9,3142,7999.9,3135,8039,3131]],
0,[0,"#0000ff"]],
[1,
[0,[0,8004.6,2175],[0,8003.57,2171.66],[0,8014.15,2172.05],
[0,8005.63,2178.34]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5502.5,3840],[1,5670.6,3699,6814.8,2752,7883.4,2221],
[1,7921.9,2202,7967.4,2186,8004.6,2175]],
0,[0,"#0000ff"]],
[1,[0,[0,8010,3198],[0,8009.3,3194.57],[0,8019.8,3196],[0,8010.7,3201.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5542.1,3842],[1,5891.5,3751,7645.3,3293,8010,3198]],0,
[0,"#0000ff"]],
[1,
[0,[0,7953.1,5546],[0,7953.44,5542.52],[0,7963.05,5546.99],
[0,7952.76,5549.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5499.7,3876],[1,5653.7,4027,6760.4,5087,7883.4,5527],
[1,7905.3,5536,7929.4,5541,7953.1,5546]],
0,[0,"#0000ff"]],
[1,
[0,[0,10412,5495],[0,10412.7,5491.57],[0,10421.8,5496.96],
[0,10411.3,5498.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5510.9,3876],[1,5707.7,3992,6854.7,4655,7883.4,4927],
[1,8050.1,4971,8099.6,4936,8269.4,4965],
[1,9200.7,5126,9406.6,5291,10332,5481],
[1,10358,5486,10386,5491,10412,5495]],
0,[0,"#0000ff"]],
[1,
[0,[0,10417,6593],[0,10417.3,6589.52],[0,10427,6594],[0,10416.7,6596.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5495.8,3876],[1,5661.8,4086,7225.1,6051,7883.4,6367],
[1,7912.8,6381,9976.4,6556,10417,6593]],
0,[0,"#0000ff"]],
[1,[0,[0,10407,4213],[0,10407,4209.5],[0,10417,4213],[0,10407,4216.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3026.9,3426],[1,3280.5,3497,4371.1,3794,5286.4,3920],
[1,6332.9,4064,9794.5,4191,10407,4213]],
0,[0,"#0000ff"]],
[1,[0,[0,7923.8,2156],[0,7923.8,2152.5],[0,7933.8,2156],[0,7923.8,2159.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,2996.1,3393],[1,3168.9,3266,4258.2,2483,5286.4,2221],
[1,5541.8,2156,7378,2155,7923.8,2156]],
0,[0,"#ee82ee"]],
[1,[0,[0,7969.9,3184],[0,7969.9,3180.5],[0,7979.9,3184],[0,7969.9,3187.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3071.1,3405],[1,3390.8,3385,4427.8,3323,5286.4,3284],
[1,6332.2,3236,7599.2,3196,7969.9,3184]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7947.1,5559],[0,7946.76,5555.52],[0,7957.05,5558.01],
[0,7947.44,5562.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2984,3429],[1,3099.4,3607,4067.8,5056,5286.4,5535],
[1,5535.3,5633,7431.2,5576,7947.1,5559]],
0,[0,"#0000ff"]],
[1,[0,[0,7951.1,3349],[0,7951.1,3345.5],[0,7961.1,3349],[0,7951.1,3352.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3077.1,3411],[1,3438.1,3410,4664,3405,5676.4,3392],
[1,6547.1,3381,7595.2,3357,7951.1,3349]],
0,[0,"#0000ff"]],
[1,
[0,[0,10410,5548],[0,10410.7,5544.57],[0,10419.8,5549.96],
[0,10409.3,5551.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2989.8,3429],[1,3136.7,3578,4192.4,4628,5286.4,5019],
[1,6538.7,5467,6947.2,5114,8269.4,5257],
[1,9104.4,5347,10109,5501,10410,5548]],
0,[0,"#0000ff"]],
[1,
[0,[0,7969.8,3911],[0,7969.46,3907.52],[0,7979.75,3910.02],
[0,7970.14,3914.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3027.3,3426],[1,3281.5,3497,4370.8,3789,5286.4,3885],
[1,6327.2,3994,7598.3,3933,7969.8,3911]],
0,[0,"#0000ff"]],
[1,
[0,[0,5422.7,2842],[0,5422.01,2838.57],[0,5432.51,2840.04],
[0,5423.39,2845.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3028,3396],[1,3283.9,3326,4375.9,3033,5286.4,2862],
[1,5331.9,2853,5383.8,2846,5422.7,2842]],
0,[0,"#0000ff"]],
[1,
[0,[0,12805,2287],[0,12804.7,2283.52],[0,12815,2286],[0,12805.3,2290.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3025,3395],[1,3275.2,3322,4371.9,3003,5286.4,2808],
[1,6430.9,2564,6718.2,2482,7883.4,2375],
[1,8143.4,2351,12364,2293,12805,2287]],
0,[0,"#ee82ee"]],
[1,[0,[0,8039.2,3127],[0,8039.2,3123.5],[0,8049.2,3127],[0,8039.2,3130.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3058.1,3401],[1,3361.7,3365,4414,3243,5286.4,3192],
[1,6411.8,3126,7796.1,3126,8039.2,3127]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10416,6606],[0,10415.7,6602.52],[0,10426,6605],[0,10416.3,6609.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2977.9,3429],[1,3047.5,3656,3776.7,5927,5286.4,6713],
[1,6462.5,7325,6944.1,6747,8269.4,6713],
[1,9107.7,6692,10121,6626,10416,6606]],
0,[0,"#0000ff"]],
[1,
[0,[0,10467,15090.9],[0,10465,15088],[0,10475.3,15085.3],
[0,10469,15093.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8174.7,16325.3],[1,8205.6,16321.3,8239.4,16315,8269.4,16305],
[1,9239.3,15980.5,10274,15233.9,10467,15090.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19807],[0,10494.4,19806],[0,10493.9,19816.6],
[0,10487.6,19808]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8181.8,16330.6],[1,8212,16334.3,8243.6,16342.5,8269.4,16359],
[1,9718.7,17287.3,10411,19530.9,10491,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,10381,19837.9],[0,10380.9,19834.4],[0,10391,19837.7],
[0,10381.1,19841.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5601.1,18738.5],[1,5626.3,18742.4,5652.5,18747.7,5676.4,18755],
[1,6720.2,19072.7,6820.5,19583.8,7883.4,19830],
[1,8128.1,19886.7,9902.6,19849.1,10381,19837.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,8027.4,17737.5],[0,8026.32,17734.2],[0,8036.92,17734.4],
[0,8028.48,17740.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5597.4,18716.9],[1,5623.6,18713,5651.2,18707.9,5676.4,18701],
[1,6701,18422.8,6889.3,18159.8,7883.4,17787],
[1,7932,17768.8,7988.2,17750.1,8027.4,17737.5]],
0,[0,"#0000ff"]],
[1,[0,[0,5416.3,321],[0,5416.3,317.5],[0,5426.3,321],[0,5416.3,324.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3036,373],[1,3384.9,365,5063.6,329,5416.3,321]],0,[0,"#0000ff"]],
[1,[0,[0,5416.1,320],[0,5416.1,316.5],[0,5426.1,320],[0,5416.1,323.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3031.1,320],[1,3368.6,320,5061.1,320,5416.1,320]],0,[0,"#0000ff"]],
[1,
[0,[0,10407,11244],[0,10407.7,11240.6],[0,10416.8,11246],
[0,10406.3,11247.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8144.6,10426],[1,8181.9,10430,8228.6,10437,8269.4,10447],
[1,9219.1,10690,9389.1,10960,10332,11227],
[1,10356,11234,10382,11239,10407,11244]],
0,[0,"#0000ff"]],
[1,
[0,[0,12734,10616],[0,12734.3,10612.5],[0,12744,10617],
[0,12733.7,10619.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8147,10423],[1,8680.9,10445,12080,10589,12734,10616]],0,
[0,"#0000ff"]],
[1,
[0,[0,10486,19862.2],[0,10482.8,19860.8],[0,10490.1,19853.1],
[0,10489.2,19863.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8156.9,22435.3],[1,8193.2,22432.8,8235.4,22425.5,8269.4,22407],
[1,9503.8,21736.3,10369,20093.5,10486,19862.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10487,19862.3],[0,10483.8,19860.9],[0,10491,19853.1],
[0,10490.2,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8152.9,22543.9],[1,8190.1,22541.8,8234.2,22534.6,8269.4,22515],
[1,9528.6,21814.2,10374,20098.9,10487,19862.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10486,19862.4],[0,10482.9,19860.7],[0,10490.8,19853.6],
[0,10489.1,19864.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8130.4,22490.5],[1,8171,22490.1,8226.7,22484.5,8269.4,22461],
[1,9515.8,21775.4,10371,20097.2,10486,19862.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10470,19859.3],[0,10467.8,19856.6],[0,10477.8,19853],
[0,10472.2,19862]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5528,21138.4],[1,5870.5,21141.2,7994.6,21155.6,8269.4,21081],
[1,9261.1,20811.9,10284,20009.3,10470,19859.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,12733,6257],[0,12732.7,6253.51],[0,12743,6256.09],
[0,12733.3,6260.49]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10641,6305],[1,11070,6295,12351,6265,12733,6257]],0,[0,"#0000ff"]],
[1,[0,[0,12733,6254],[0,12733,6250.5],[0,12743,6254],[0,12733,6257.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10635,6254],[1,11057,6254,12348,6254,12733,6254]],0,[0,"#0000ff"]],
[1,
[0,[0,12741,6246],[0,12741.3,6242.51],[0,12751,6246.91],
[0,12740.7,6249.49]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5548.3,6081],[1,5993.2,6075,8569.7,6044,10666,6119],
[1,11467,6147,12431,6221,12741,6246]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10366,6298],[0,10366.3,6294.52],[0,10376,6299],[0,10365.7,6301.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6126],[1,8329.4,6143,9895.9,6262,10366,6298]],0,
[0,"#0000ff"]],
[1,[0,[0,10364,6247],[0,10364,6243.5],[0,10374,6247],[0,10364,6250.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6125],[1,8329.1,6138,9890.6,6221,10364,6247]],0,
[0,"#0000ff"]],
[1,
[0,[0,8038.9,6123],[0,8039.24,6119.52],[0,8048.85,6123.98],
[0,8038.56,6126.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5548.5,6083],[1,5923.5,6089,7753,6119,8038.9,6123]],0,
[0,"#0000ff"]],
[1,
[0,[0,15070,7672],[0,15070.3,7668.52],[0,15080,7673],[0,15069.7,7675.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8137.6,7174],[1,8400,7219,9456.4,7395,10332,7459],
[1,11525,7547,11828,7444,13022,7503],
[1,13853,7544,14865,7650,15070,7672]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10400,5826],[0,10399.2,5822.58],[0,10409.8,5823.83],
[0,10400.8,5829.42]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8098.4,7146],[1,8263.3,7017,9327.2,6204,10332,5843],
[1,10354,5835,10377,5830,10400,5826]],
0,[0,"#0000ff"]],
[1,
[0,[0,10428,7692],[0,10428.7,7688.57],[0,10437.8,7693.96],
[0,10427.3,7695.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8131.6,7175],[1,8451.7,7247,10068,7611,10428,7692]],0,
[0,"#0000ff"]],
[1,
[0,[0,10454,6180],[0,10452.6,6176.8],[0,10463.1,6175.94],
[0,10455.4,6183.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8113.5,7147],[1,8327.6,7056,9427.5,6591,10332,6227],
[1,10373,6211,10420,6192,10454,6180]],
0,[0,"#0000ff"]],
[1,
[0,[0,15070,7670],[0,15070.7,7666.57],[0,15079.8,7671.96],
[0,15069.3,7673.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,12871,7334],[1,12907,7340,12969,7349,13022,7357],
[1,13852,7483,14866,7639,15070,7670]],
0,[0,"#0000ff"]],
[1,
[0,[0,10462,19857.7],[0,10460.2,19854.7],[0,10470.7,19852.7],
[0,10463.8,19860.7]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3095.7,20828.3],[1,3441.2,20823.8,4449,20810.7,5286.4,20803],
[1,5369.3,20802.2,8188.3,20799.8,8269.4,20783],
[1,9213.1,20587.4,10254,19982.7,10462,19857.7]],
0,[0,"#ee82ee"]],
[1,
[0,[0,5321.2,20830],[0,5321.2,20826.5],[0,5331.2,20830],
[0,5321.2,20833.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3096,20830],[1,3511.1,20830,4855.8,20830,5321.2,20830]],0,
[0,"#0000ff"]],
[1,
[0,[0,8004.1,23758.4],[0,8003.8,23754.9],[0,8014.06,23757.5],
[0,8004.4,23761.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2991.4,20847.9],[1,3024.8,20879.7,3095.9,20948.6,3151.4,21011],
[1,4162.2,22148.2,3923.3,23011.1,5286.4,23687],
[1,5782.4,23933,7616.4,23791.6,8004.1,23758.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,5337.4,8103],[0,5337.05,8099.52],[0,5347.35,8102],
[0,5337.75,8106.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3033.5,8145],[1,3355.8,8139,4862.1,8111,5337.4,8103]],0,
[0,"#0000ff"]],
[1,[0,[0,10390,8146],[0,10390,8142.5],[0,10400,8146],[0,10390,8149.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,3033.6,8146],[1,3695,8146,9517.2,8146,10390,8146]],0,
[0,"#ee82ee"]],
[1,
[0,[0,10384,19840.5],[0,10383.9,19837],[0,10394,19840.1],
[0,10384.1,19844]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2974.7,8164],[1,3036.3,8651,4334.3,18840.1,5286.4,19691],
[1,6277.7,20576.9,6940.2,19937.5,8269.4,19914],
[1,9079.5,19899.7,10054,19856,10384,19840.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10453,19813.9],[0,10454.5,19810.7],[0,10462.1,19818],
[0,10451.5,19817.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8157.4,19001.5],[1,8192.2,19005.7,8233.2,19012,8269.4,19021],
[1,9174.6,19246.8,10223,19709.7,10453,19813.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10457,18065.9],[0,10455.4,18062.8],[0,10465.9,18061.3],
[0,10458.6,18069]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8154.3,18985.2],[1,8189.8,18980.1,8232.2,18972.6,8269.4,18962],
[1,9185.4,18701.2,10234,18179,10457,18065.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10479,19861.1],[0,10476.2,19859],[0,10485,19853.1],
[0,10481.8,19863.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5577.1,21639.1],[1,6037.3,21653.2,8011.7,21708.3,8269.4,21617],
[1,9367.2,21228,10329,20051.4,10479,19861.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10477,19860.9],[0,10474.2,19858.7],[0,10483.1,19853],
[0,10479.8,19863.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8165.9,21587.2],[1,8199.4,21583.6,8237.2,21576.6,8269.4,21563],
[1,9326.1,21117.3,10315,20041.3,10477,19860.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10472,19859.7],[0,10469.8,19857],[0,10479.7,19853.3],
[0,10474.2,19862.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5575.7,21194.3],[1,6032.7,21205.1,8006,21246.9,8269.4,21173],
[1,9279.8,20889.4,10294,20017.8,10472,19859.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10468,19858.9],[0,10465.9,19856.1],[0,10475.9,19852.8],
[0,10470.1,19861.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8158.3,21139],[1,8193.3,21134.3,8234.1,21126.6,8269.4,21114],
[1,9241.3,20767.4,10277,20003.7,10468,19858.9]],
0,[0,"#0000ff"]],
[1,[0,[0,7899.3,617],[0,7899.3,613.5],[0,7909.3,617],[0,7899.3,620.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3068.4,639],[1,3684.4,636,7081.6,620,7899.3,617]],0,[0,"#0000ff"]],
[1,[0,[0,7900.6,619],[0,7900.6,615.5],[0,7910.6,619],[0,7900.6,622.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5573.8,657],[1,5953.2,650,7395.7,627,7900.6,619]],0,[0,"#0000ff"]],
[1,[0,[0,10323,530],[0,10323,526.5],[0,10333,530],[0,10323,533.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5621.5,483],[1,6332,490,9533.1,522,10323,530]],0,[0,"#0000ff"]],
[1,[0,[0,10323,534],[0,10323,530.5],[0,10333,534],[0,10323,537.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,927.12,526],[1,1211.5,531,2076.1,546,2793.4,551],
[1,5806.8,572,9483.1,541,10323,534]],
0,[0,"#ee82ee"]],
[1,[0,[0,5330.7,482],[0,5330.7,478.5],[0,5340.7,482],[0,5330.7,485.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,927.13,522],[1,1211.5,518,2076.2,504,2793.4,497],
[1,3760.1,488,4922.3,484,5330.7,482]],
0,[0,"#0000ff"]],
[1,[0,[0,10330,526],[0,10330,522.5],[0,10340,526],[0,10330,529.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167.7,451],[1,8528.3,464,9856.6,510,10330,526]],0,[0,"#0000ff"]],
[1,[0,[0,10322,532],[0,10322,528.5],[0,10332,532],[0,10322,535.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,3095.6,524],[1,3973.9,525,9280.8,531,10322,532]],0,[0,"#ee82ee"]],
[1,
[0,[0,5331.5,485],[0,5331.16,481.516],[0,5341.45,484.034],
[0,5331.84,488.484]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3094.7,522],[1,3511.5,515,4875.6,492,5331.5,485]],0,[0,"#0000ff"]],
[1,
[0,[0,10455,13987],[0,10453.3,13983.9],[0,10463.7,13982.1],
[0,10456.7,13990.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8163.7,15087.8],[1,8197.3,15083.8,8235.6,15077.4,8269.4,15067],
[1,9247.1,14765,9411.5,14491,10332,14045],
[1,10374,14025,10422,14002,10455,13987]],
0,[0,"#0000ff"]],
[1,[0,[0,10367,15068.5],[0,10367,15065],[0,10377,15068.4],[0,10367,15072]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8168.8,15093],[1,8540.9,15088.8,9930.3,15073.3,10367,15068.5]],0,
[0,"#0000ff"]],
[1,
[0,[0,10490,19807.2],[0,10493.3,19806.1],[0,10493,19816.7],
[0,10486.7,19808.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8150.8,15104.7],[1,8189.9,15113.6,8236.5,15129.8,8269.4,15159],
[1,9088.3,15885,10365,19456,10490,19807.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,7961.1,2143],[0,7961.45,2139.52],[0,7971.05,2144],
[0,7960.75,2146.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5585.6,1870],[1,5999.6,1918,7527.6,2093,7961.1,2143]],0,
[0,"#0000ff"]],
[1,[0,[0,7915.3,1858],[0,7915.3,1854.5],[0,7925.3,1858],[0,7915.3,1861.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5620,1858],[1,6062.9,1858,7442.2,1858,7915.3,1858]],0,
[0,"#0000ff"]],
[1,
[0,[0,12806,2276],[0,12807.1,2272.68],[0,12815.5,2279.16],
[0,12804.9,2279.32]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5616.4,1854],[1,6327.6,1833,9645.2,1745,10666,1850],
[1,11546,1941,12597,2219,12806,2276]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7947,2145],[0,7947.35,2141.52],[0,7956.95,2146],[0,7946.65,2148.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5557,1948],[1,5919.8,1978,7484.1,2107,7947,2145]],0,[0,"#0000ff"]],
[1,[0,[0,10370,1879],[0,10370,1875.5],[0,10380,1879],[0,10370,1882.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5562,1941],[1,6139.9,1933,9650.6,1888,10370,1879]],0,
[0,"#0000ff"]],
[1,
[0,[0,12805,2282],[0,12805.3,2278.52],[0,12815,2283],[0,12804.7,2285.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5561.9,1941],[1,5894.9,1938,7198.4,1929,8269.4,1961],
[1,9335.8,1993,9602.4,2011,10666,2088],
[1,11534,2150,12594,2260,12805,2282]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10414,13973],[0,10413.7,13969.5],[0,10424,13972],
[0,10414.3,13976.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8157,14157],[1,8524.1,14127,10036,14004,10414,13973]],0,
[0,"#0000ff"]],
[1,
[0,[0,10492,19806.8],[0,10495.3,19805.8],[0,10494.9,19816.4],
[0,10488.7,19807.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8157.3,14158],[1,8195,14159,8238.2,14166,8269.4,14191],
[1,9281.7,14987.6,10395,19411.6,10492,19806.8]],
0,[0,"#0000ff"]],
[1,[0,[0,10383,14231],[0,10383,14227.5],[0,10393,14231],[0,10383,14234.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8162.3,14166],[1,8528.8,14177,9962.5,14218,10383,14231]],0,
[0,"#0000ff"]],
[1,
[0,[0,10390,14243],[0,10389.3,14239.6],[0,10399.8,14241],
[0,10390.7,14246.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8181.4,16074.3],[1,8210.9,16070.4,8242.2,16063.4,8269.4,16051],
[1,9374.4,15548.5,9232.8,14775,10332,14261],
[1,10350,14253,10370,14247,10390,14243]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19806.8],[0,10496.4,19806.1],[0,10495,19816.6],
[0,10489.6,19807.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8182.9,16076.1],[1,8212.8,16079.9,8244.1,16088.2,8269.4,16105],
[1,9781.9,17107.8,10421,19519.1,10493,19806.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10434,19816.7],[0,10434.9,19813.3],[0,10443.7,19819.3],
[0,10433.1,19820.1]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5486,11888],[1,5584.7,12275,7236.9,18727.7,7883.4,19260],
[1,7950.1,19314.9,8184.4,19291.8,8269.4,19307],
[1,9134.6,19461.6,10167,19742.6,10434,19816.7]],
0,[0,"#ee82ee"]],
[1,[0,[0,10388,11640],[0,10388,11636.5],[0,10398,11640],[0,10388,11643.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5569.9,11862],[1,5884.6,11834,6978.5,11739,7883.4,11697],
[1,8853.1,11652,10027,11642,10388,11640]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7953.4,11819],[0,7953.05,11815.5],[0,7963.35,11818],
[0,7953.75,11822.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5579.6,11868],[1,5982.3,11860,7507.6,11828,7953.4,11819]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19807.1],[0,10496.4,19806.4],[0,10495,19816.9],
[0,10489.6,19807.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8183.5,11810],[1,8214.3,11813,8245.9,11822,8269.4,11843],
[1,8604.1,12136,10369,19302.9,10493,19807.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10396,11648],[0,10395.7,11644.5],[0,10406,11647],
[0,10396.3,11651.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8180.2,11808],[1,8577.2,11780,9998.2,11676,10396,11648]],0,
[0,"#0000ff"]],
[1,
[0,[0,10443,19815.3],[0,10444.1,19812],[0,10452.5,19818.4],
[0,10441.9,19818.6]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5521.5,11641],[1,5565.7,11655,5636,11685,5676.4,11735],
[1,7840.5,14405,5257.7,16928.7,7883.4,19146],
[1,7949.4,19201.8,8184.8,19175.8,8269.4,19193],
[1,9151.8,19372.6,10193,19728,10443,19815.3]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7962.4,11808],[0,7962.74,11804.5],[0,7972.35,11809],
[0,7962.06,11811.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5532.1,11633],[1,5844.4,11655,7509.1,11775,7962.4,11808]],0,
[0,"#0000ff"]],
[1,
[0,[0,10393,11634],[0,10393.3,11630.5],[0,10403,11635],
[0,10392.7,11637.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5532.3,11626],[1,5809.1,11608,7162.6,11528,8269.4,11550],
[1,9086.7,11566,10071,11617,10393,11634]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8013.5,2176],[0,8012.48,2172.65],[0,8023.06,2173.07],
[0,8014.52,2179.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5557.4,2881],[1,5593.6,2877,5637.5,2870,5676.4,2862],
[1,6160.3,2758,7684.5,2280,8013.5,2176]],
0,[0,"#0000ff"]],
[1,
[0,[0,10407,6536],[0,10407.3,6532.52],[0,10417,6537],[0,10406.7,6539.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,8103.6,6289],[1,8336.5,6314,9995.2,6492,10407,6536]],0,
[0,"#ee82ee"]],
[1,
[0,[0,12740,6246],[0,12740.3,6242.52],[0,12750,6247],[0,12739.7,6249.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.5,6283],[1,8306.2,6258,9606.7,6106,10666,6135],
[1,11466,6157,12428,6224,12740,6246]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10422,6590],[0,10422.3,6586.52],[0,10432,6591],[0,10421.7,6593.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,8103.6,6290],[1,8339.4,6320,10037,6540,10422,6590]],0,
[0,"#ee82ee"]],
[1,[0,[0,8038.9,6289],[0,8038.9,6285.5],[0,8048.9,6289],[0,8038.9,6292.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5564,2886],[1,5600.8,2888,5643.3,2895,5676.4,2916],
[1,7182.5,3865,6378,5309,7883.4,6259],
[1,7930.8,6289,7997.6,6291,8038.9,6289]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10403,6538],[0,10403.3,6534.51],[0,10413,6538.91],
[0,10402.7,6541.49]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6342],[1,8335.8,6362,9985.1,6502,10403,6538]],0,
[0,"#0000ff"]],
[1,[0,[0,10347,6310],[0,10347,6306.5],[0,10357,6310],[0,10347,6313.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6340],[1,8326.4,6337,9853.9,6317,10347,6310]],0,
[0,"#0000ff"]],
[1,
[0,[0,10420,6591],[0,10420.7,6587.57],[0,10429.8,6592.96],
[0,10419.3,6594.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6343],[1,8339,6368,10030,6550,10420,6591]],0,[0,"#0000ff"]],
[1,
[0,[0,8039.2,6344],[0,8038.86,6340.52],[0,8049.15,6343.02],
[0,8039.54,6347.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5564,2885],[1,5600.9,2887,5643.4,2895,5676.4,2916],
[1,7196,3882,6364.6,5346,7883.4,6313],
[1,7930.8,6343,7997.9,6346,8039.2,6344]],
0,[0,"#0000ff"]],
[1,[0,[0,12805,2287],[0,12805,2283.5],[0,12815,2287],[0,12805,2290.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5553.3,2879],[1,5590.1,2874,5635.7,2868,5676.4,2862],
[1,6659.2,2714,6894.8,2604,7883.4,2502],
[1,8917.4,2396,12406,2298,12805,2287]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7982.8,3170],[0,7983.48,3166.57],[0,7992.61,3171.94],
[0,7982.12,3173.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5555.9,2897],[1,5926.7,2939,7571.3,3124,7982.8,3170]],0,
[0,"#0000ff"]],
[1,[0,[0,7929.3,2161],[0,7929.3,2157.5],[0,7939.3,2161],[0,7929.3,2164.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5586.8,2244],[1,5992.9,2230,7458,2178,7929.3,2161]],0,
[0,"#0000ff"]],
[1,
[0,[0,12805,2283],[0,12805.3,2279.52],[0,12815,2284],[0,12804.7,2286.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5581.2,2241],[1,5910,2220,6989.4,2151,7883.4,2129],
[1,9120,2098,9430.3,2105,10666,2149],
[1,11535,2180,12595,2266,12805,2283]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7977.9,3172],[0,7978.24,3168.52],[0,7987.85,3172.98],
[0,7977.56,3175.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5576.6,2257],[1,5608.6,2261,5644.4,2267,5676.4,2275],
[1,6697.2,2545,6862.8,2884,7883.4,3154],
[1,7913.7,3162,7947.3,3168,7977.9,3172]],
0,[0,"#0000ff"]],
[1,[0,[0,8038.9,6343],[0,8038.9,6339.5],[0,8048.9,6343],[0,8038.9,6346.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5617.3,2947],[1,5638.2,2951,5658.6,2959,5676.4,2970],
[1,7182.5,3919,6378,5363,7883.4,6313],
[1,7930.8,6343,7997.6,6345,8038.9,6343]],
0,[0,"#0000ff"]],
[1,
[0,[0,8015.5,2176],[0,8014.47,2172.66],[0,8025.05,2173.05],
[0,8016.53,2179.34]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5588.3,2932],[1,5617.1,2928,5648.1,2922,5676.4,2916],
[1,5921.7,2861,7665.9,2290,8015.5,2176]],
0,[0,"#0000ff"]],
[1,
[0,[0,7978.8,3172],[0,7979.14,3168.52],[0,7988.75,3172.98],
[0,7978.46,3175.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5594.6,2953],[1,6027.4,2993,7573.8,3135,7978.8,3172]],0,
[0,"#0000ff"]],
[1,[0,[0,12805,2287],[0,12805,2283.5],[0,12815,2287],[0,12805,2290.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5578.7,2930],[1,5610,2926,5644.7,2921,5676.4,2916],
[1,6659.8,2764,6894.4,2649,7883.4,2540],
[1,8917,2426,12406,2301,12805,2287]],
0,[0,"#ee82ee"]],
[1,[0,[0,8039,6289],[0,8039,6285.5],[0,8049,6289],[0,8039,6292.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5617,2947],[1,5637.9,2951,5658.5,2959,5676.4,2970],
[1,7169.1,3903,6391.4,5325,7883.4,6259],
[1,7930.9,6289,7997.7,6291,8039,6289]],
0,[0,"#ee82ee"]],
[1,[0,[0,8039,6340],[0,8039,6336.5],[0,8049,6340],[0,8039,6343.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5592.1,6314],[1,6047.2,6319,7763.5,6337,8039,6340]],0,
[0,"#0000ff"]],
[1,[0,[0,8039,6286],[0,8039,6282.5],[0,8049,6286],[0,8039,6289.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5592.1,6312],[1,6047.2,6307,7763.5,6289,8039,6286]],0,
[0,"#ee82ee"]],
[1,
[0,[0,10388,3192],[0,10387.3,3188.57],[0,10397.8,3190.04],
[0,10388.7,3195.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8176.8,5336],[1,8207.8,5333,8241.2,5325,8269.4,5311],
[1,9437.9,4722,9170.3,3812,10332,3211],
[1,10350,3202,10369,3196,10388,3192]],
0,[0,"#0000ff"]],
[1,
[0,[0,10427,5800],[0,10427.7,5796.57],[0,10436.8,5801.96],
[0,10426.3,5803.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8158.8,5348],[1,8193.1,5353,8233.2,5359,8269.4,5365],
[1,9122.3,5511,10148,5737,10427,5800]],
0,[0,"#0000ff"]],
[1,
[0,[0,10387,10063],[0,10386.3,10059.6],[0,10396.8,10061],
[0,10387.7,10066.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8208.2,13279],[1,8229.8,13274,8251.1,13267,8269.4,13255],
[1,9687.9,12353,8923.7,11002,10332,10085],
[1,10349,10074,10368,10067,10387,10063]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,18039.7],[0,10380.8,18036.3],[0,10389.7,18042.1],
[0,10379.2,18043.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8209.9,13283],[1,8231.3,13288,8252.1,13296,8269.4,13309],
[1,10090,14689,8526.3,16618,10332,18017],
[1,10346,18027.7,10363,18035,10380,18039.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,5393.3,18187.4],[0,5393.47,18183.9],[0,5403.29,18187.9],
[0,5393.13,18190.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2980.7,10016],[1,3007.7,10076,3094.5,10272,3151.4,10439],
[1,4296.5,13806,2640.5,15774.2,5286.4,18150],
[1,5315.1,18175.8,5356.2,18185.1,5393.3,18187.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10411,10045],[0,10411.3,10041.5],[0,10421,10046],
[0,10410.7,10048.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3053,9988],[1,3540.7,9928,6147,9626,8269.4,9765],
[1,8700.4,9793,10051,9991,10411,10045]],
0,[0,"#0000ff"]],
[1,
[0,[0,10402,8156],[0,10401.7,8152.51],[0,10412,8155.09],
[0,10402.3,8159.49]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3033.2,9984],[1,3068.7,9974,3113.9,9960,3151.4,9941],
[1,4197.7,9412,4175.5,8766,5286.4,8392],
[1,5600.6,8286,7938.3,8342,8269.4,8325],
[1,9096.2,8283,10092,8187,10402,8156]],
0,[0,"#0000ff"]],
[1,
[0,[0,10383,18049.1],[0,10382.9,18045.6],[0,10393,18048.7],
[0,10383.1,18052.6]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,2980.7,10016],[1,3007.6,10076,3094.2,10272,3151.4,10439],
[1,4289,13767,2508.6,15901.5,5286.4,18058],
[1,5548.3,18261.3,7938,18122.4,8269.4,18117],
[1,9079,18103.8,10053,18063.5,10383,18049.1]],
0,[0,"#ee82ee"]],
[1,[0,[0,10394,10159],[0,10394,10155.5],[0,10404,10159],[0,10394,10162.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3069.5,9997],[1,3596.7,9994,6168.5,9981,8269.4,10047],
[1,9087.9,10073,10074,10137,10394,10159]],
0,[0,"#0000ff"]],
[1,
[0,[0,10387,10103],[0,10387.3,10099.5],[0,10397,10104],
[0,10386.7,10106.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3068.2,9995],[1,3592.5,9980,6166.8,9912,8269.4,9976],
[1,9082.3,10001,10059,10076,10387,10103]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19862.7],[0,10487.7,19861.7],[0,10494,19853.1],
[0,10494.3,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8114.3,23639.2],[1,8156.2,23632.3,8223.8,23615.9,8269.4,23579],
[1,9683.9,22437,10408,20140.3,10491,19862.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10470,16568.6],[0,10467.8,16565.9],[0,10477.7,16562.2],
[0,10472.2,16571.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8097.4,18554.5],[1,8317.9,18369.9,10211,16785.4,10470,16568.6]],0,
[0,"#0000ff"]],
[1,
[0,[0,10463,19812.2],[0,10465,19809.3],[0,10471.3,19817.8],
[0,10461,19815.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8125.7,18586.1],[1,8165.2,18598,8221.7,18616.3,8269.4,18637],
[1,9195.2,19038.2,10254,19683.3,10463,19812.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,7969.4,15035.2],[0,7969.06,15031.7],[0,7979.35,15034.2],
[0,7969.74,15038.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5543.6,20998.9],[1,5585.4,21000.1,5639.5,20994.6,5676.4,20965],
[1,7861.2,19215.7,5699.9,16817.9,7883.4,15067],
[1,7907.5,15047.7,7938.9,15038.7,7969.4,15035.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10457,18065.8],[0,10455.4,18062.7],[0,10465.9,18061.2],
[0,10458.6,18068.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5548.7,20992.4],[1,5587.7,20990.3,5636.6,20983.6,5676.4,20965],
[1,6875.4,20405.4,6677.1,19510.6,7883.4,18967],
[1,8040.8,18896.1,8101.9,18965.6,8269.4,18924],
[1,9188.3,18695.8,10235,18178.3,10457,18065.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,7995.9,3196],[0,7995.2,3192.57],[0,8005.7,3194],[0,7996.6,3199.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5539.5,21001],[1,5583.3,21004.3,5641.5,21000.4,5676.4,20965],
[1,11244,15321.5,3135.3,9613,7883.4,3265],
[1,7910.3,3229,7955.9,3208,7995.9,3196]],
0,[0,"#0000ff"]],
[1,
[0,[0,10367,15069.7],[0,10366.9,15066.2],[0,10377,15069.5],
[0,10367.1,15073.2]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5543.6,20998.8],[1,5585.4,21000,5639.4,20994.5,5676.4,20965],
[1,7835.8,19245.2,5638.8,16766,7883.4,15159],
[1,7934.4,15122.5,9843.3,15080.5,10367,15069.7]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10380,18041.8],[0,10380.8,18038.4],[0,10389.7,18044.2],
[0,10379.2,18045.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8127,10521],[1,8170,10518,8230.8,10521,8269.4,10555],
[1,10856,12824,7769.9,15720.7,10332,18017],
[1,10346,18029.1,10363,18036.9,10380,18041.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10393,8152],[0,10392.3,8148.57],[0,10402.8,8150.04],
[0,10393.7,8155.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8130.7,10530],[1,8171.2,10530,8226.6,10524,8269.4,10501],
[1,9487.7,9848,9121.2,8839,10332,8173],
[1,10351,8163,10372,8156,10393,8152]],
0,[0,"#0000ff"]],
[1,
[0,[0,10490,19862.5],[0,10486.7,19861.4],[0,10493,19853],
[0,10493.3,19863.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8166.5,23030.3],[1,8200.8,23027.5,8239,23019.6,8269.4,23001],
[1,9643.4,22162.3,10398,20123.1,10490,19862.5]],
0,[0,"#0000ff"]],
[1,[0,[0,10380,23028],[0,10380,23024.5],[0,10390,23028],[0,10380,23031.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167,23028],[1,8540,23028,9958,23028,10380,23028]],0,
[0,"#0000ff"]],
[1,[0,[0,10438,23136],[0,10438,23132.5],[0,10448,23136],[0,10438,23139.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167,23136],[1,8559.6,23136,10110,23136,10438,23136]],0,
[0,"#0000ff"]],
[1,
[0,[0,10490,19862.6],[0,10486.8,19861.3],[0,10493.8,19853.4],
[0,10493.2,19863.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8166.2,23138.5],[1,8200.6,23135.8,8239,23127.9,8269.4,23109],
[1,9669.5,22239.1,10403,20128.3,10490,19862.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,5349.8,23995],[0,5349.8,23991.5],[0,5359.8,23995],
[0,5349.8,23998.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3071.9,23995],[1,3464.4,23995,4905,23995,5349.8,23995]],0,
[0,"#0000ff"]],
[1,
[0,[0,10483,19861.8],[0,10480.1,19859.8],[0,10488.7,19853.6],
[0,10485.9,19863.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3069.3,23990.8],[1,3096.8,23986.9,3126.1,23980,3151.4,23968],
[1,4306.6,23421.5,4097.6,22510.9,5286.4,22042],
[1,5440.6,21981.2,8116.3,22053.5,8269.4,21990],
[1,9446.2,21502.3,10353,20075.2,10483,19861.8]],
0,[0,"#0000ff"]],
[1,[0,[0,10448,5925],[0,10448,5921.5],[0,10458,5925],[0,10448,5928.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,5977],[1,8345.2,5972,10122,5932,10448,5925]],0,
[0,"#0000ff"]],
[1,[0,[0,10454,5978],[0,10454,5974.5],[0,10464,5978],[0,10454,5981.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,5978],[1,8346.7,5978,10143,5978,10454,5978]],0,
[0,"#0000ff"]],
[1,[0,[0,8039,5978],[0,8039,5974.5],[0,8049,5978],[0,8039,5981.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5574.2,6002],[1,6000.1,5998,7759.6,5981,8039,5978]],0,
[0,"#0000ff"]],
[1,[0,[0,7965.2,6031],[0,7965.2,6027.5],[0,7975.2,6031],[0,7965.2,6034.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5573.8,6004],[1,5971,6008,7533.3,6026,7965.2,6031]],0,
[0,"#0000ff"]],
[1,
[0,[0,10455,19856.7],[0,10453.6,19853.5],[0,10464.1,19852.6],
[0,10456.4,19859.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8147.4,20748],[1,8184.2,20742.9,8229.7,20735.1,8269.4,20724],
[1,9181.2,20469.9,10230,19967,10455,19856.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,5416.7,20512.7],[0,5416.39,20509.2],[0,5426.66,20511.8],
[0,5417.01,20516.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3001.5,20724.5],[1,3252.2,20702.5,5051,20544.7,5416.7,20512.7]],0,
[0,"#0000ff"]],
[1,
[0,[0,10459,19857.2],[0,10457.4,19854.1],[0,10467.8,19852.5],
[0,10460.6,19860.3]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3001.7,20727],[1,3418,20726.6,8131.2,20722.2,8269.4,20696],
[1,9199.5,20519.9,10243,19974.1,10459,19857.2]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7987.1,20755.5],[0,7987.13,20752],[0,7997.1,20755.6],
[0,7987.07,20759]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3001.4,20727.2],[1,3379.7,20729.3,7339.4,20751.8,7987.1,20755.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,5439.1,20934.4],[0,5439.4,20930.9],[0,5449.06,20935.3],
[0,5438.8,20937.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3001.5,20729.4],[1,3257.9,20751,5132.7,20908.7,5439.1,20934.4]],0,
[0,"#0000ff"]],
[1,
[0,[0,10467,19858.8],[0,10465,19855.9],[0,10475.3,19853.2],
[0,10469,19861.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5534.5,21083.5],[1,5896.3,21079.8,7995.5,21055.6,8269.4,20984],
[1,9242,20729.6,10274,19999.8,10467,19858.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,7990.6,19052],[0,7990.22,19048.5],[0,8000.54,19050.9],
[0,7990.98,19055.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5526.5,21074.4],[1,5567.5,21064.4,5628.6,21046.5,5676.4,21019],
[1,6808.7,20368.8,6703.5,19639.2,7883.4,19080],
[1,7916.5,19064.3,7956,19056.2,7990.6,19052]],
0,[0,"#0000ff"]],
[1,
[0,[0,10466,19858.4],[0,10464,19855.5],[0,10474.1,19852.6],
[0,10468,19861.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8108.3,21051.9],[1,8147.2,21048.6,8214.6,21040.6,8269.4,21022],
[1,9226.7,20697.6,10268,19995.4,10466,19858.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10427,18061.1],[0,10426.2,18057.7],[0,10436.7,18058.9],
[0,10427.8,18064.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5634.8,18415.2],[1,6056.4,18443.7,7267.7,18511.2,8269.4,18426],
[1,9126.2,18353.1,10148,18125.5,10427,18061.1]],
0,[0,"#0000ff"]],
[1,[0,[0,12737,6260],[0,12737,6256.5],[0,12747,6260],[0,12737,6263.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.5,6576],[1,8291.1,6561,9416,6474,10332,6411],
[1,11265,6347,12393,6280,12737,6260]],
0,[0,"#ee82ee"]],
[1,[0,[0,10413,6599],[0,10413,6595.5],[0,10423,6599],[0,10413,6602.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,8103.6,6578],[1,8337.6,6580,10011,6596,10413,6599]],0,
[0,"#ee82ee"]],
[1,
[0,[0,10412,7111],[0,10412.7,7107.57],[0,10421.8,7112.96],
[0,10411.3,7114.43]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8103.7,6581],[1,8141.2,6585,8210.7,6594,8269.4,6605],
[1,9195.7,6780,9408.1,6912,10332,7097],
[1,10358,7102,10386,7107,10412,7111]],
0,[0,"#ee82ee"]],
[1,[0,[0,8039.1,6578],[0,8039.1,6574.5],[0,8049.1,6578],[0,8039.1,6581.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5519.1,6551],[1,5813.9,6554,7745.8,6575,8039.1,6578]],0,
[0,"#ee82ee"]],
[1,
[0,[0,10372,6319],[0,10371.7,6315.52],[0,10382,6318],[0,10372.3,6322.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6522],[1,8330.4,6501,9909.4,6361,10372,6319]],0,
[0,"#0000ff"]],
[1,
[0,[0,10386,6267],[0,10385.7,6263.52],[0,10396,6266],[0,10386.3,6270.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6521],[1,8332.7,6495,9941.1,6316,10386,6267]],0,
[0,"#0000ff"]],
[1,
[0,[0,10413,6597],[0,10413.3,6593.51],[0,10423,6597.91],
[0,10412.7,6600.49]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6525],[1,8337.7,6532,10013,6585,10413,6597]],0,
[0,"#0000ff"]],
[1,
[0,[0,10411,7111],[0,10411.7,7107.57],[0,10420.8,7112.96],
[0,10410.3,7114.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.5,6527],[1,8140.9,6531,8210.7,6539,8269.4,6551],
[1,9199.2,6738,9404.7,6900,10332,7097],
[1,10358,7102,10386,7107,10411,7111]],
0,[0,"#0000ff"]],
[1,[0,[0,8039.1,6524],[0,8039.1,6520.5],[0,8049.1,6524],[0,8039.1,6527.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5519.1,6551],[1,5813.9,6548,7745.8,6527,8039.1,6524]],0,
[0,"#0000ff"]],
[1,
[0,[0,12769,23759.8],[0,12769.4,23756.3],[0,12778.9,23761],
[0,12768.6,23763.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10527,23510],[1,10758,23535.8,12401,23718.8,12769,23759.8]],0,
[0,"#0000ff"]],
[1,
[0,[0,12758,23498.3],[0,12758,23494.8],[0,12768,23498.3],
[0,12758,23501.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10527,23506.9],[1,10756,23506,12369,23499.8,12758,23498.3]],0,
[0,"#0000ff"]],
[1,
[0,[0,10462,23517],[0,10461.1,23513.6],[0,10471.7,23514.5],
[0,10462.9,23520.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8167.7,24174],[1,8200,24169.7,8236.5,24164.1,8269.4,24157],
[1,9203.4,23956.1,9413.4,23814.1,10332,23553],
[1,10377,23540.3,10428,23526.3,10462,23517]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8132.4,10987],[1,8175.7,10993,8234.1,11009,8269.4,11047],
[1,8600.2,11404,10374,19275.9,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10482,13939],[0,10484.9,13937.1],[0,10487.5,13947.3],
[0,10479.1,13940.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8127.4,10991],[1,8168.6,10999,8226.7,11016,8269.4,11047],
[1,8892.3,11493,10310,13673,10482,13939]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,19836.1],[0,10380,19832.6],[0,10390,19836],[0,10380,19839.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5560.5,18679.1],[1,5596.4,18682.9,5639.2,18689.5,5676.4,18701],
[1,6722.3,19022.6,6820,19534.3,7883.4,19792],
[1,8127.3,19851.1,9899.5,19840.2,10380,19836.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,7955.2,16983.5],[0,7954.65,16980],[0,7965.07,16981.9],
[0,7955.75,16987]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5563,18671.8],[1,5598.9,18668.6,5640.9,18661.6,5676.4,18647],
[1,6808.2,18183.2,6752,17467.6,7883.4,17003],
[1,7905.8,16993.8,7930.8,16987.6,7955.2,16983.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10430,18061.7],[0,10429.2,18058.3],[0,10439.7,18059.3],
[0,10430.8,18065.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5563.4,18672.9],[1,5899.7,18667.8,7206.3,18639.1,8269.4,18498],
[1,9130.7,18383.7,10158,18130.8,10430,18061.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10483,13939],[0,10486.1,13937.3],[0,10487.9,13947.7],
[0,10479.9,13940.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8132,11071],[1,8172.6,11071,8227.7,11077,8269.4,11101],
[1,8925,11480,10314,13671,10483,13939]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8128,11067],[1,8171,11064,8231.4,11067,8269.4,11101],
[1,8630,11424,10376,19277.2,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10369,15062.9],[0,10369.1,15059.4],[0,10379,15063.2],
[0,10368.9,15066.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5557.1,15001.7],[1,5882.3,15000.7,7192.9,14997.8,8269.4,15013],
[1,9067.5,15024.2,10026,15052.4,10369,15062.9]],
0,[0,"#0000ff"]],
[1,[0,[0,10367,15065.5],[0,10367,15062],[0,10377,15065.6],[0,10367,15069]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8178.6,15041.1],[1,8564.6,15045.4,9933.8,15060.7,10367,15065.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10416,9991],[0,10416.7,9987.57],[0,10425.8,9992.96],
[0,10415.3,9994.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8150.8,9564],[1,8186.7,9568,8230.4,9575,8269.4,9581],
[1,9190.5,9734,9413.1,9814,10332,9977],
[1,10359,9982,10389,9987,10416,9991]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,18042.3],[0,10380.8,18038.9],[0,10389.7,18044.6],
[0,10379.2,18045.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8154.1,9546],[1,8193.2,9546,8238.7,9553,8269.4,9581],
[1,11133,12169,7496.8,15398.4,10332,18017],
[1,10346,18029.4,10363,18037.3,10380,18042.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10436,9835],[0,10436.3,9831.52],[0,10446,9836],[0,10435.7,9838.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8151.9,9563],[1,8517.5,9606,10100,9795,10436,9835]],0,
[0,"#0000ff"]],
[1,
[0,[0,10379,18040.9],[0,10379.8,18037.5],[0,10388.7,18043.2],
[0,10378.2,18044.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8086.1,11308],[1,8116,11365,8208.1,11543,8269.4,11697],
[1,9363.1,14442,8087.4,16096,10332,18017],
[1,10346,18028.5,10362,18036.1,10379,18040.9]],
0,[0,"#0000ff"]],
[1,[0,[0,10372,11261],[0,10372,11257.5],[0,10382,11261],[0,10372,11264.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8189.2,11289],[1,8590.5,11283,9947.3,11266,10372,11261]],0,
[0,"#0000ff"]],
[1,
[0,[0,10374,9802],[0,10373.3,9798.57],[0,10383.8,9800.04],
[0,10374.7,9805.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8183.4,11284],[1,8212.1,11280,8242.5,11274,8269.4,11263],
[1,9311.6,10852,9294.7,10237,10332,9815],
[1,10346,9810,10360,9805,10374,9802]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,18039.8],[0,10380.8,18036.4],[0,10389.7,18042.2],
[0,10379.2,18043.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8101.2,13039],[1,8141.2,13069,8220.6,13132,8269.4,13201],
[1,9610.8,15104.4,8497.4,16583.5,10332,18017],
[1,10346,18027.8,10363,18035,10380,18039.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10370,9906],[0,10369.2,9902.58],[0,10379.8,9903.83],
[0,10370.8,9909.42]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8098.4,13004],[1,8135.7,12974,8213,12907,8269.4,12843],
[1,9316.1,11647,8984.5,10764,10332,9923],
[1,10344,9916,10357,9910,10370,9906]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19863.1],[0,10487.7,19862.1],[0,10493.9,19853.5],
[0,10494.3,19864.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8205.8,23187.2],[1,8228.2,23182.5,8250.4,23174.9,8269.4,23163],
[1,9682,22278,10404,20133.1,10491,19863.1]],
0,[0,"#0000ff"]],
[1,[0,[0,10335,23190],[0,10335,23186.5],[0,10345,23190],[0,10335,23193.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8207.6,23190],[1,8618.6,23190,9881.5,23190,10335,23190]],0,
[0,"#0000ff"]],
[1,
[0,[0,10476,19860.2],[0,10473.5,19857.8],[0,10482.9,19852.9],
[0,10478.5,19862.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8158.7,21531.1],[1,8193.9,21526.8,8234.8,21518.8,8269.4,21504],
[1,9309.7,21060,10311,20034,10476,19860.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10382,18038.5],[0,10382.8,18035.1],[0,10391.7,18040.7],
[0,10381.2,18041.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8129.2,14429],[1,8170.6,14428,8228.2,14433,8269.4,14461],
[1,9785.6,15480.7,8827.2,16981.2,10332,18017],
[1,10347,18027.1,10364,18033.9,10382,18038.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10390,8146],[0,10389.3,8142.57],[0,10399.8,8144.04],
[0,10390.7,8149.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8127.4,14441],[1,8170.1,14443,8230.2,14440,8269.4,14407],
[1,10511,12538,8111.1,10066,10332,8173],
[1,10349,8159,10369,8151,10390,8146]],
0,[0,"#0000ff"]],
[1,
[0,[0,10477,11285],[0,10474.4,11282.7],[0,10483.6,11277.5],
[0,10479.6,11287.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8130.2,14438],[1,8171.2,14438,8227.6,14433,8269.4,14407],
[1,9632.6,13572,9364,12733,10332,11461],
[1,10382,11396,10444,11323,10477,11285]],
0,[0,"#0000ff"]],
[1,
[0,[0,10378,16533.5],[0,10378.8,16530.1],[0,10387.7,16535.7],
[0,10377.2,16536.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8131.1,14433],[1,8171.3,14434,8226.3,14440,8269.4,14461],
[1,9428.6,15037.2,9179.5,15928.4,10332,16517],
[1,10347,16524.2,10362,16529.5,10378,16533.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10477,11285],[0,10474.4,11282.7],[0,10483.6,11277.5],
[0,10479.6,11287.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8162.3,14545],[1,8197.8,14542,8237.9,14535,8269.4,14515],
[1,9659.1,13648,9351,12772,10332,11461],
[1,10381,11396,10444,11323,10477,11285]],
0,[0,"#0000ff"]],
[1,
[0,[0,10382,18038.3],[0,10382.8,18034.9],[0,10391.7,18040.5],
[0,10381.2,18041.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8161.9,14538],[1,8197.7,14540,8238.1,14548,8269.4,14569],
[1,9758,15555.6,8854.5,17014.6,10332,18017],
[1,10347,18027,10364,18033.8,10382,18038.3]],
0,[0,"#0000ff"]],
[1,[0,[0,7982.1,1981],[0,7982.1,1977.5],[0,7992.1,1981],[0,7982.1,1984.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5570.4,1792],[1,5967.2,1823,7574.4,1949,7982.1,1981]],0,
[0,"#0000ff"]],
[1,[0,[0,7965.1,1767],[0,7965.1,1763.5],[0,7975.1,1767],[0,7965.1,1770.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5577.6,1784],[1,5980.9,1781,7534.3,1770,7965.1,1767]],0,
[0,"#0000ff"]],
[1,
[0,[0,10450,18064.7],[0,10448.6,18061.5],[0,10459.2,18060.7],
[0,10451.4,18067.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8177.8,18815.5],[1,8207.5,18811.4,8240,18806,8269.4,18799],
[1,9165.8,18586.5,10212,18163,10450,18064.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,5348,20841.1],[0,5347.69,20837.6],[0,5357.96,20840.2],
[0,5348.31,20844.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3081.9,21028.9],[1,3487.5,20995.3,4904.9,20877.8,5348,20841.1]],0,
[0,"#0000ff"]],
[1,
[0,[0,10466,19858.7],[0,10464.1,19855.8],[0,10474.3,19853.2],
[0,10467.9,19861.6]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3099.1,21037.5],[1,3879.5,21034.5,8011,21015.7,8269.4,20951],
[1,9237.8,20708.8,10271,19997.5,10466,19858.7]],
0,[0,"#ee82ee"]],
[1,
[0,[0,12783,7598],[0,12782.3,7594.57],[0,12792.8,7596.04],
[0,12783.7,7601.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10532,8087],[1,10565,8082,10620,8074,10666,8065],
[1,11511,7903,12529,7660,12783,7598]],
0,[0,"#0000ff"]],
[1,
[0,[0,15004,16153.9],[0,15004.1,16150.4],[0,15014,16154.1],
[0,15003.9,16157.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12916,16132.7],[1,13249,16136.1,14615,16150,15004,16153.9]],0,
[0,"#0000ff"]],
[1,
[0,[0,10491,19807],[0,10494.3,19806],[0,10493.9,19816.6],
[0,10487.7,19808]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8187,16385.4],[1,8215.6,16389.4,8245.1,16397.5,8269.4,16413],
[1,9705.3,17325.5,10408,19533.2,10491,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,12721,15197.9],[0,12720.9,15194.4],[0,12731,15197.6],
[0,12721.1,15201.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8176.5,16378.2],[1,8206.8,16374.2,8239.9,16368.2,8269.4,16359],
[1,9247.5,16056.4,9342.6,15595.6,10332,15334],
[1,10565,15272.7,12251,15213.4,12721,15197.9]],
0,[0,"#0000ff"]],
[1,[0,[0,10409,13964],[0,10409,13960.5],[0,10419,13964],[0,10409,13967.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8196.6,13922],[1,8619.8,13930,10036,13957,10409,13964]],0,
[0,"#0000ff"]],
[1,
[0,[0,10459,12979],[0,10457.1,12976],[0,10467.5,12973.7],
[0,10460.9,12982]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8179.6,13911],[1,8208.9,13907,8240.7,13901,8269.4,13893],
[1,9192.9,13639,10241,13095,10459,12979]],
0,[0,"#0000ff"]],
[1,
[0,[0,10492,19806.4],[0,10495.4,19805.4],[0,10494.8,19816],
[0,10488.6,19807.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8096.5,13938],[1,8134.7,13973,8218.6,14054,8269.4,14137],
[1,9614.5,16330.9,10411,19475,10492,19806.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10427,13953],[0,10427.7,13949.6],[0,10436.8,13955],
[0,10426.3,13956.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8134.2,13531],[1,8460,13591,10065,13886,10427,13953]],0,
[0,"#0000ff"]],
[1,
[0,[0,10461,12245],[0,10459.3,12241.9],[0,10469.7,12240.1],
[0,10462.7,12248.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8146.7,13517],[1,8183.9,13513,8230,13506,8269.4,13493],
[1,8300.5,13482,10167,12414,10461,12245]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8141.7,13527],[1,8183.2,13535,8235.3,13551,8269.4,13585],
[1,9276.3,14574,10399,19395,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10435,12975],[0,10434,12971.6],[0,10444.6,12972.1],
[0,10436,12978.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8141.5,13512],[1,8179,13508,8227,13501,8269.4,13493],
[1,9135.1,13329,10170,13048,10435,12975]],
0,[0,"#0000ff"]],
[1,
[0,[0,10409,18030],[0,10409.6,18026.5],[0,10418.9,18031.6],
[0,10408.4,18033.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5492.2,9718],[1,5523.9,9773,5618.2,9938,5676.4,10085],
[1,6955.2,13307,5212.4,15356,7883.4,17565],
[1,7949.8,17619.9,8184.2,17590.3,8269.4,17603],
[1,9194.4,17741,9412.2,17850.3,10332,18017],
[1,10357,18021.5,10384,18026,10409,18030]],
0,[0,"#0000ff"]],
[1,
[0,[0,8003.1,3198],[0,8002.07,3194.66],[0,8012.65,3195.05],
[0,8004.13,3201.34]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5491.5,9682],[1,5521.8,9627,5613.3,9457,5676.4,9311],
[1,6809.7,6685,5922.8,5348,7883.4,3265],
[1,7915.2,3231,7963,3210,8003.1,3198]],
0,[0,"#0000ff"]],
[1,
[0,[0,10387,19827.9],[0,10387.2,19824.4],[0,10397,19828.5],
[0,10386.8,19831.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5579.1,18464.9],[1,5610.7,18468.8,5645.5,18475.1,5676.4,18485],
[1,6730.8,18822.6,6818.9,19335.9,7883.4,19640],
[1,8005.5,19674.9,9901.6,19797.1,10387,19827.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10402,12967],[0,10401.7,12963.5],[0,10412,12966.1],
[0,10402.3,12970.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5582.7,18463.1],[1,5615.4,18460,5650,18451.3,5676.4,18431],
[1,7678,16895.1,5842.4,14684,7883.4,13201],
[1,7953.1,13150,8183.7,13176,8269.4,13168],
[1,9095,13094,10092,12997,10402,12967]],
0,[0,"#0000ff"]],
[1,
[0,[0,10424,12941],[0,10424.7,12937.6],[0,10433.8,12943],
[0,10423.3,12944.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8174.8,12521],[1,8205.2,12525,8238.7,12530,8269.4,12535],
[1,9118.2,12675,10141,12883,10424,12941]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19807],[0,10496.4,19806.3],[0,10495,19816.8],
[0,10489.6,19807.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8216.4,12508],[1,8235.8,12514,8254.2,12522,8269.4,12535],
[1,8890.2,13065,10382,19336,10493,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,10414,12233],[0,10413.7,12229.5],[0,10424,12232],
[0,10414.3,12236.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8179.8,12496],[1,8582.7,12448,10044,12277,10414,12233]],0,
[0,"#0000ff"]],
[1,
[0,[0,10430,12940],[0,10431,12936.6],[0,10439.6,12942.9],
[0,10429,12943.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8159.8,12464],[1,8193.8,12469,8233.6,12475,8269.4,12481],
[1,9126.7,12632,10157,12875,10430,12940]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19807.2],[0,10496.4,19806.5],[0,10495,19817],
[0,10489.6,19807.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8169.5,12447],[1,8204.4,12449,8242.2,12458,8269.4,12481],
[1,8894,13015,10383,19335.6,10493,19807.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10459,11510],[0,10457.3,11506.9],[0,10467.7,11505.1],
[0,10460.7,11513.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8167.8,12446],[1,8200.2,12442,8236.8,12436,8269.4,12427],
[1,9193.8,12172,10242,11625,10459,11510]],
0,[0,"#0000ff"]],
[1,
[0,[0,10481,12983],[0,10478,12981.1],[0,10486.3,12974.5],
[0,10484,12984.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8134.6,15540.3],[1,8174.7,15539.4,8228.1,15533.4,8269.4,15511],
[1,8889.5,15175.5,10302,13232,10481,12983]],
0,[0,"#0000ff"]],
[1,
[0,[0,10495,19806.7],[0,10498.5,19806.4],[0,10496,19816.7],
[0,10491.5,19807]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8132.5,15532.8],[1,8173.9,15531.9,8229.8,15537,8269.4,15565],
[1,9920,16729.1,10441,19497.1,10495,19806.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10432,19853.1],[0,10431.1,19849.7],[0,10441.7,19850.6],
[0,10432.9,19856.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3077.5,17286],[1,3103.1,17290.1,3129.4,17297.7,3151.4,17311],
[1,4521.5,18137.6,3866.6,19472,5286.4,20210],
[1,5433.5,20286.4,8104.4,20284.9,8269.4,20269],
[1,9134.3,20185.6,10162,19924.4,10432,19853.1]],
0,[0,"#ee82ee"]],
[1,
[0,[0,5427,16044.9],[0,5425.72,16041.6],[0,5436.31,16041.3],
[0,5428.28,16048.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3067.2,17275.9],[1,3094.8,17271.9,3124.7,17265.9,3151.4,17257],
[1,4174.1,16915.5,4312.9,16568.4,5286.4,16105],
[1,5333.1,16082.8,5387.6,16060.5,5427,16044.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,5373.7,18449.8],[0,5374.19,18446.3],[0,5383.6,18451.2],
[0,5373.21,18453.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3066.7,17292.2],[1,3094.4,17296.2,3124.5,17302.2,3151.4,17311],
[1,4169.8,17644.4,4266.1,18103.8,5286.4,18431],
[1,5314.1,18439.9,5344.9,18445.8,5373.7,18449.8]],
0,[0,"#0000ff"]],
[1,[0,[0,10394,12962],[0,10394,12958.5],[0,10404,12962],[0,10394,12965.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3078.2,17284.5],[1,3104,17280.4,3130.3,17272.2,3151.4,17257],
[1,4840.3,16042.6,3519.4,14189,5286.4,13092],
[1,5356.8,13048,8186.6,13051,8269.4,13049],
[1,9088,13026,10075,12978,10394,12962]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7991.3,12049],[0,7990.96,12045.5],[0,8001.25,12048],
[0,7991.64,12052.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5519.7,12839],[1,5743,12752,6902.3,12310,7883.4,12070],
[1,7918.4,12061,7957.5,12054,7991.3,12049]],
0,[0,"#0000ff"]],
[1,
[0,[0,10430,19817.3],[0,10430.8,19813.9],[0,10439.7,19819.6],
[0,10429.2,19820.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5543.8,12860],[1,5586.3,12868,5641,12884,5676.4,12919],
[1,7809.7,15028.3,5549.6,17412.9,7883.4,19298],
[1,7950.7,19352.3,8184.2,19330.5,8269.4,19345],
[1,9128.7,19491.4,10157,19747.8,10430,19817.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10413,13959],[0,10413.3,13955.5],[0,10423,13959.9],
[0,10412.7,13962.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5524.6,12868],[1,5564.2,12881,5624.5,12901,5676.4,12919],
[1,6664,13269,6861.3,13517,7883.4,13747],
[1,7946.7,13761,9968.2,13924,10413,13959]],
0,[0,"#0000ff"]],
[1,
[0,[0,10429,12010],[0,10429.3,12006.5],[0,10439,12011],
[0,10428.7,12013.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5512.4,12838],[1,5714.4,12734,6866.6,12158,7883.4,11978],
[1,8392.6,11888,10065,11987,10429,12010]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10392,8145],[0,10391.3,8141.57],[0,10401.8,8143.04],
[0,10392.7,8148.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8164,17492.4],[1,8200.8,17491.2,8241.5,17482.8,8269.4,17457],
[1,11375,14590,7257.6,11073,10332,8173],
[1,10349,8158,10370,8149,10392,8145]],
0,[0,"#0000ff"]],
[1,
[0,[0,10484,19808.1],[0,10487,19806.4],[0,10488.9,19816.8],
[0,10481,19809.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8175.5,17485.2],[1,8206.9,17488.9,8240.8,17496.4,8269.4,17511],
[1,9448.7,18113.8,10355,19590.5,10484,19808.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10441,13984],[0,10439.7,13980.8],[0,10450.3,13980.3],
[0,10442.3,13987.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8174.6,17486.7],[1,8207,17483.5,8241.7,17475.3,8269.4,17457],
[1,9748.8,16481.4,9017.2,15232.6,10332,14045],
[1,10364,14017,10407,13997,10441,13984]],
0,[0,"#0000ff"]],
[1,
[0,[0,10407,18030.5],[0,10407.6,18027],[0,10416.9,18032.1],
[0,10406.4,18034]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8159.9,17493.8],[1,8194,17498.3,8233.7,17504.1,8269.4,17511],
[1,9196.5,17689.1,9407.3,17829.1,10332,18017],
[1,10357,18021.9,10383,18026.5,10407,18030.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10446,12937],[0,10447.3,12933.8],[0,10455.3,12940.7],
[0,10444.7,12940.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8159.1,12247],[1,8193.5,12251,8233.6,12257,8269.4,12265],
[1,9157.1,12463,10202,12846,10446,12937]],
0,[0,"#0000ff"]],
[1,[0,[0,10403,12224],[0,10403,12220.5],[0,10413,12224],[0,10403,12227.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8170.7,12237],[1,8556.3,12235,10012,12226,10403,12224]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8195.4,12180],[1,8222.3,12184,8248.9,12193,8269.4,12211],
[1,8912.6,12767,10385,19323.9,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10403,12221],[0,10403.3,12217.5],[0,10413,12222],
[0,10402.7,12224.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8198.2,12186],[1,8621.3,12193,10022,12215,10403,12221]],0,
[0,"#0000ff"]],
[1,
[0,[0,10450,12937],[0,10451.1,12933.7],[0,10459.5,12940.2],
[0,10448.9,12940.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8176.8,12194],[1,8206.8,12199,8239.6,12204,8269.4,12211],
[1,9165.1,12422,10212,12840,10450,12937]],
0,[0,"#0000ff"]],
[1,
[0,[0,10447,11507],[0,10445.9,11503.7],[0,10456.5,11503.8],
[0,10448.1,11510.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8174.6,12173],[1,8205.2,12169,8238.9,12164,8269.4,12157],
[1,9156,11963,10203,11595,10447,11507]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19806.8],[0,10496.4,19806.1],[0,10495,19816.6],
[0,10489.6,19807.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8170.9,12609],[1,8205.4,12611,8242.5,12620,8269.4,12643],
[1,8882.6,13164,10379,19337.2,10493,19806.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10411,12945],[0,10411.3,12941.5],[0,10421,12946],
[0,10410.7,12948.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8156.7,12627],[1,8191.4,12632,8232.4,12638,8269.4,12643],
[1,9103,12760,10112,12902,10411,12945]],
0,[0,"#0000ff"]],
[1,
[0,[0,10492,19807],[0,10495.3,19806],[0,10494.9,19816.6],
[0,10488.7,19808]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8155.9,12680],[1,8194.7,12688,8239.5,12704,8269.4,12735],
[1,8825.9,13303,10374,19344.6,10492,19807]],
0,[0,"#0000ff"]],
[1,[0,[0,10387,12644],[0,10387,12640.5],[0,10397,12644],[0,10387,12647.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8169.9,12669],[1,8549.4,12665,9974,12649,10387,12644]],0,
[0,"#0000ff"]],
[1,
[0,[0,10406,12946],[0,10406.3,12942.5],[0,10416,12946.9],
[0,10405.7,12949.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8156.4,12679],[1,8520,12723,10017,12900,10406,12946]],0,
[0,"#0000ff"]],
[1,
[0,[0,10392,8150],[0,10391.7,8146.52],[0,10402,8149],[0,10392.3,8153.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8147.3,8228],[1,8490.2,8216,9977.2,8164,10392,8150]],0,
[0,"#0000ff"]],
[1,
[0,[0,10404,7994],[0,10403.7,7990.52],[0,10414,7993],[0,10404.3,7997.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8142.8,8223],[1,8480.3,8189,10005,8034,10404,7994]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8139.6,8221],[1,8181.8,8219,8235.5,8225,8269.4,8257],
[1,11815,11631,9348.7,14280,10332,19075],
[1,10391,19361.6,10470,19707.3,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10471,12981],[0,10468.9,12978.2],[0,10479,12975],
[0,10473.1,12983.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8097.8,14894.9],[1,8133.7,14869.5,8208.1,14816.2,8269.4,14769],
[1,9189.7,14060,10281,13141,10471,12981]],
0,[0,"#0000ff"]],
[1,
[0,[0,10494,19806.9],[0,10497.4,19806.2],[0,10495.9,19816.7],
[0,10490.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8109.2,14920.1],[1,8151.2,14934.6,8224.1,14965,8269.4,15013],
[1,9800.5,16634.1,10429,19493.8,10494,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10435,12939],[0,10436,12935.6],[0,10444.6,12941.9],
[0,10434,12942.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8108,12403],[1,8146.3,12408,8212.9,12416,8269.4,12427],
[1,9134.3,12590,10169,12867,10435,12939]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19807],[0,10496.4,19806.3],[0,10495,19816.8],
[0,10489.6,19807.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8107.2,12395],[1,8149.1,12390,8224,12388,8269.4,12427],
[1,8897.7,12966,10383,19331.9,10493,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19807],[0,10496.4,19806.3],[0,10495,19816.8],
[0,10489.6,19807.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8131.6,10694],[1,8175,10701,8234,10716,8269.4,10755],
[1,8439.4,10940,10367,19261.5,10493,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,10482,13939],[0,10484.9,13937.1],[0,10487.5,13947.3],
[0,10479.1,13940.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8127.3,10698],[1,8168.8,10707,8227.3,10723,8269.4,10755],
[1,8597.2,11001,10293,13643,10482,13939]],
0,[0,"#0000ff"]],
[1,
[0,[0,15058,4937],[0,15056.7,4933.75],[0,15067.3,4933.29],
[0,15059.3,4940.25]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10591,5623],[1,10921,5647,12083,5715,13022,5562],
[1,13862,5426,14832,5032,15058,4937]],
0,[0,"#0000ff"]],
[1,
[0,[0,15060,4895],[0,15061.4,4891.8],[0,15069.1,4899.06],
[0,15058.6,4898.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10593,4155],[1,10926,4133,12086,4072,13022,4235],
[1,13866,4382,14837,4796,15060,4895]],
0,[0,"#0000ff"]],
[1,
[0,[0,14965,5482],[0,14964.7,5478.52],[0,14975,5481],[0,14965.3,5485.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5524.1,5619],[1,5889.2,5644,8526.5,5815,10666,5751],
[1,11715,5720,11976,5677,13022,5611],
[1,13753,5565,14627,5505,14965,5482]],
0,[0,"#0000ff"]],
[1,
[0,[0,7974.1,6677],[0,7974.45,6673.52],[0,7984.05,6678],
[0,7973.75,6680.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5507.4,5631],[1,5694.3,5735,6856.6,6370,7883.4,6659],
[1,7912.4,6667,7944.5,6673,7974.1,6677]],
0,[0,"#0000ff"]],
[1,[0,[0,14986,4916],[0,14986,4912.5],[0,14996,4916],[0,14986,4919.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5517,5606],[1,5734,5542,6903.6,5210,7883.4,5088],
[1,9338.2,4907,14158,4913,14986,4916]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8017.3,3200],[0,8016.26,3196.66],[0,8026.84,3197.02],
[0,8018.34,3203.34]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5517.4,5606],[1,5558.2,5593,5625.8,5569,5676.4,5535],
[1,6840.5,4744,6726.1,4065,7883.4,3265],
[1,7924.8,3236,7977.5,3214,8017.3,3200]],
0,[0,"#0000ff"]],
[1,[0,[0,10389,4161],[0,10389,4157.5],[0,10399,4161],[0,10389,4164.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5514.1,5604],[1,5553.4,5589,5620.9,5563,5676.4,5535],
[1,6695.9,5024,6787.6,4542,7883.4,4227],
[1,8126.2,4157,9921.9,4160,10389,4161]],
0,[0,"#0000ff"]],
[1,[0,[0,10415,6595],[0,10415,6591.5],[0,10425,6595],[0,10415,6598.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5511.5,5629],[1,5712.3,5714,6880.4,6201,7883.4,6400],
[1,8136.7,6450,9994.3,6568,10415,6595]],
0,[0,"#0000ff"]],
[1,[0,[0,10390,5616],[0,10390,5612.5],[0,10400,5616],[0,10390,5619.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5524.4,5616],[1,5967.5,5616,9699,5616,10390,5616]],0,
[0,"#0000ff"]],
[1,
[0,[0,10410,5083],[0,10410.3,5079.52],[0,10420,5084],[0,10409.7,5086.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8147.9,3962],[1,8184.8,3966,8230.3,3972,8269.4,3985],
[1,9254.8,4301,9350.5,4738,10332,5065],
[1,10357,5073,10384,5079,10410,5083]],
0,[0,"#0000ff"]],
[1,
[0,[0,10412,13960],[0,10412.3,13956.5],[0,10422,13961],
[0,10411.7,13963.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8124,13815],[1,8420.8,13834,10018,13935,10412,13960]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10494.9,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8122.1,13806],[1,8164.8,13803,8228,13806,8269.4,13839],
[1,9329.6,14691,10402,19399.9,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10393,11064],[0,10392.3,11060.6],[0,10402.8,11062],
[0,10393.7,11067.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8120.8,13805],[1,8162.2,13796,8224.3,13779,8269.4,13747],
[1,9489,12880,9045.7,11850,10332,11086],
[1,10351,11075,10372,11068,10393,11064]],
0,[0,"#0000ff"]],
[1,
[0,[0,10423,18060.5],[0,10422.2,18057.1],[0,10432.8,18058.4],
[0,10423.8,18063.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2975.5,11356],[1,3036.6,11718,4012.2,17391.1,5286.4,18334],
[1,5353.1,18383.3,8186.8,18399.4,8269.4,18393],
[1,9120.9,18326.8,10139,18120.4,10423,18060.5]],
0,[0,"#0000ff"]],
[1,[0,[0,10374,11263],[0,10374,11259.5],[0,10384,11263],[0,10374,11266.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3056.5,11338],[1,3552.9,11340,6149.9,11349,8269.4,11317],
[1,9071.1,11305,10035,11274,10374,11263]],
0,[0,"#0000ff"]],
[1,
[0,[0,5370.9,11290],[0,5370.9,11286.5],[0,5380.9,11290],
[0,5370.9,11293.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3056.3,11336],[1,3430.3,11329,4947.1,11299,5370.9,11290]],0,
[0,"#0000ff"]],
[1,
[0,[0,10385,16554.9],[0,10384.7,16551.4],[0,10395,16553.9],
[0,10385.3,16558.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2973.2,11356],[1,2987.1,11645,3203.5,15330.3,5286.4,16700],
[1,5424.9,16791.1,8103.8,16705.8,8269.4,16700],
[1,9081.1,16671.6,10056,16585.4,10385,16554.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10400,8155],[0,10399.7,8151.52],[0,10410,8154],[0,10400.3,8158.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3056.5,11337],[1,3087.9,11334,3122.8,11327,3151.4,11311],
[1,4423.9,10608,4010.8,9530,5286.4,8833],
[1,5754.9,8577,9719.7,8215,10400,8155]],
0,[0,"#0000ff"]],
[1,
[0,[0,12825,13408],[0,12822.2,13405.9],[0,12831,13400],
[0,12827.8,13410.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10539,15538.2],[1,10574,15537,10626,15531.3,10666,15511],
[1,11781,14948.7,12691,13612,12825,13408]],
0,[0,"#0000ff"]],
[1,
[0,[0,12768,15422.8],[0,12767.8,15419.3],[0,12778,15422.2],
[0,12768.2,15426.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10539,15536],[1,10811,15522.2,12404,15441.3,12768,15422.8]],0,
[0,"#0000ff"]],
[1,
[0,[0,12769,15564.2],[0,12769,15560.7],[0,12779,15564.3],
[0,12769,15567.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10539,15538.5],[1,10812,15541.6,12407,15560,12769,15564.2]],0,
[0,"#0000ff"]],
[1,[0,[0,10408,13967],[0,10408,13963.5],[0,10418,13967],[0,10408,13970.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5541.3,14011],[1,6059,14007,9776.5,13973,10408,13967]],0,
[0,"#0000ff"]],
[1,
[0,[0,8067.7,20214],[0,8071.04,20212.9],[0,8070.72,20223.5],
[0,8064.36,20215.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5495.4,14030],[1,5529.5,14073,5618.7,14191,5676.4,14299],
[1,6947,16679.4,7963.9,19882.6,8067.7,20214]],
0,[0,"#0000ff"]],
[1,
[0,[0,10397,13376],[0,10397.3,13372.5],[0,10407,13377],
[0,10396.7,13379.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5522.3,13999],[1,5752.2,13925,6908.1,13565,7883.4,13439],
[1,8854.7,13314,10045,13359,10397,13376]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8014.4,13234],[0,8014.06,13230.5],[0,8024.35,13233],
[0,8014.74,13237.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5518.2,13998],[1,5737.8,13914,6899.3,13477,7883.4,13255],
[1,7926.7,13245,7976.3,13238,8014.4,13234]],
0,[0,"#0000ff"]],
[1,
[0,[0,7972.3,14313],[0,7972.98,14309.6],[0,7982.11,14314.9],
[0,7971.62,14316.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5536.8,14019],[1,5863.2,14058,7536.1,14261,7972.3,14313]],0,
[0,"#0000ff"]],
[1,
[0,[0,10426,19817.9],[0,10426.8,19814.5],[0,10435.7,19820.1],
[0,10425.2,19821.3]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5495.2,14030],[1,5528.9,14074,5617.1,14192,5676.4,14299],
[1,6858.7,16438.2,5922.3,17877.4,7883.4,19336],
[1,7952.8,19387.6,8184.1,19369.2,8269.4,19383],
[1,9122.6,19521.2,10146,19753.3,10426,19817.9]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10493,19806.8],[0,10496.4,19806.1],[0,10494.9,19816.6],
[0,10489.6,19807.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8169.1,10248],[1,8205,10257,8243.6,10273,8269.4,10301],
[1,8446.5,10496,10370,19246,10493,19806.8]],
0,[0,"#0000ff"]],
[1,[0,[0,15076,7700],[0,15073.9,7697.2],[0,15084,7694],[0,15078.1,7702.8]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8181.3,10227],[1,8210.3,10223,8241.4,10217,8269.4,10209],
[1,9240.8,9920,9357.4,9514,10332,9237],
[1,10476,9196,10518,9218,10666,9199],
[1,11715,9067,12022,9217,13022,8875],
[1,13933,8564,14893,7842,15076,7700]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10456,7730],[0,10454.3,7726.94],[0,10464.7,7725.14],
[0,10457.7,7733.06]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8195,10233],[1,8220.7,10229,8246.9,10221,8269.4,10209],
[1,9503.4,9535,9263,8724,10332,7811],
[1,10371,7778,10421,7749,10456,7730]],
0,[0,"#0000ff"]],
[1,
[0,[0,10483,13939],[0,10486.1,13937.3],[0,10487.9,13947.7],
[0,10479.9,13940.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8155.8,10250],[1,8193.3,10259,8236.8,10275,8269.4,10301],
[1,9647.4,11403,9413.6,12187,10332,13693],
[1,10388,13783,10453,13891,10483,13939]],
0,[0,"#0000ff"]],
[1,
[0,[0,10395,16530.4],[0,10395.6,16526.9],[0,10404.9,16532.1],
[0,10394.4,16533.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8151.4,15706.5],[1,8187.5,15710.6,8231.1,15717.1,8269.4,15727],
[1,9220.1,15972.1,9384.4,16261.7,10332,16517],
[1,10352,16522.3,10374,16526.8,10395,16530.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10439,15086.5],[0,10438,15083.2],[0,10448.6,15083.5],
[0,10440,15089.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8148.7,15692.1],[1,8185.1,15687.5,8229.8,15681.1,8269.4,15673],
[1,9143,15493.9,10181,15169,10439,15086.5]],
0,[0,"#0000ff"]],
[1,[0,[0,2871.4,1253],[0,2871.4,1249.5],[0,2881.4,1253],[0,2871.4,1256.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,937.24,1278],[1,1303.2,1273,2512.8,1258,2871.4,1253]],0,
[0,"#0000ff"]],
[1,
[0,[0,10411,23858.9],[0,10411.2,23855.4],[0,10421,23859.6],
[0,10410.8,23862.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8155,23703.4],[1,8517.7,23728.4,10029,23832.6,10411,23858.9]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19863.1],[0,10489.6,19862.4],[0,10495,19853.3],
[0,10496.4,19863.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8156.3,23702.3],[1,8193.4,23700.6,8236.6,23693.1,8269.4,23671],
[1,9809,22636.6,10425,20154.7,10493,19863.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10408,8134],[0,10408.7,8130.57],[0,10417.8,8135.96],
[0,10407.3,8137.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8170.4,7373],[1,8202.1,7377,8237.5,7383,8269.4,7391],
[1,9214.1,7621,9390.3,7879,10332,8119],
[1,10357,8125,10383,8130,10408,8134]],
0,[0,"#0000ff"]],
[1,
[0,[0,10419,6447],[0,10418.7,6443.52],[0,10429,6446],[0,10419.3,6450.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8173.2,7355],[1,8204.2,7351,8238.6,7346,8269.4,7337],
[1,9228.9,7072,9375.8,6740,10332,6465],
[1,10360,6457,10391,6451,10419,6447]],
0,[0,"#0000ff"]],
[1,
[0,[0,12805,2277],[0,12806,2273.65],[0,12814.6,2279.87],[0,12804,2280.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10584,1782],[1,10610,1787,10640,1792,10666,1798],
[1,11536,1979,12595,2228,12805,2277]],
0,[0,"#0000ff"]],
[1,
[0,[0,5376.5,8086],[0,5376.84,8082.52],[0,5386.45,8086.98],
[0,5376.16,8089.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3034.5,7741],[1,3303.1,7782,4391.5,7945,5286.4,8073],
[1,5315.6,8077,5347.3,8082,5376.5,8086]],
0,[0,"#0000ff"]],
[1,
[0,[0,10415,8132],[0,10415.7,8128.57],[0,10424.8,8133.96],
[0,10414.3,8135.43]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3042.8,7728],[1,3503.6,7702,6137.4,7569,8269.4,7759],
[1,9196.5,7842,9414.6,7965,10332,8119],
[1,10359,8123,10388,8128,10415,8132]],
0,[0,"#ee82ee"]],
[1,
[0,[0,5387.4,7470],[0,5387.05,7466.52],[0,5397.35,7468.99],
[0,5387.75,7473.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3038.6,7725],[1,3384.1,7687,4981.4,7514,5387.4,7470]],0,
[0,"#0000ff"]],
[1,
[0,[0,10403,11114],[0,10402.7,11110.5],[0,10413,11113.1],
[0,10403.3,11117.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8211.2,14485],[1,8231.8,14480,8252,14472,8269.4,14461],
[1,9725.8,13513,8886.3,12103,10332,11140],
[1,10353,11126,10379,11118,10403,11114]],
0,[0,"#0000ff"]],
[1,
[0,[0,10492,19807],[0,10495.4,19806.3],[0,10494,19816.8],
[0,10488.6,19807.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8213.3,14489],[1,8233.6,14494,8253.1,14502,8269.4,14515],
[1,9238.1,15261.3,10388,19425.1,10492,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,7970.3,3177],[0,7970.64,3173.52],[0,7980.25,3177.99],
[0,7969.96,3180.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5584,3093],[1,5998.6,3107,7549.2,3162,7970.3,3177]],0,
[0,"#0000ff"]],
[1,
[0,[0,5396.9,3306],[0,5396.56,3302.52],[0,5406.85,3305.03],
[0,5397.24,3309.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3071,7788],[1,3099.1,7784,3128.4,7776,3151.4,7759],
[1,4907.7,6464,3522.3,4622,5286.4,3338],
[1,5317.9,3315,5359.9,3307,5396.9,3306]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,18043.2],[0,10380,18039.7],[0,10390,18043.2],
[0,10380,18046.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3065.8,7780],[1,3096.5,7783,3128.7,7792,3151.4,7813],
[1,6464.6,10932,1839.6,14855.4,5286.4,17826],
[1,5485.7,17997.8,9618.7,18037.3,10380,18043.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,18072.3],[0,10489.6,18071.6],[0,10494.9,18062.5],
[0,10496.4,18073]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8213.4,21862.5],[1,8233.3,21857.6,8252.7,21850.2,8269.4,21839],
[1,9798.3,20817,10423,18362.8,10493,18072.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10371,21869.8],[0,10371,21866.3],[0,10381,21869.8],
[0,10371,21873.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8216.3,21866.2],[1,8647.9,21866.9,9955,21869.1,10371,21869.8]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,18071.8],[0,10489.6,18071.1],[0,10495,18062],
[0,10496.4,18072.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8203.7,21918.7],[1,8226.9,21914.1,8250,21906.1,8269.4,21893],
[1,9812.9,20854.3,10426,18362.2,10493,18071.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,12726,21894.6],[0,12726,21891.1],[0,12736,21894.6],
[0,12726,21898.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8203.9,21919.3],[1,8883.6,21915.6,12075,21898.2,12726,21894.6]],0,
[0,"#0000ff"]],
[1,
[0,[0,10492,19862.9],[0,10488.7,19861.9],[0,10494.9,19853.3],
[0,10495.3,19863.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,23555.1],[1,8143.4,23558.3,8218.5,23558.6,8269.4,23525],
[1,9772.4,22533.7,10420,20147.6,10492,19862.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10388,23578.7],[0,10388,23575.2],[0,10398,23578.8],
[0,10388,23582.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,23552.3],[1,8333.1,23555,9947.6,23573.6,10388,23578.7]],0,
[0,"#0000ff"]],
[1,
[0,[0,8038.9,23552],[0,8038.9,23548.5],[0,8048.9,23552],
[0,8038.9,23555.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5542.7,23552],[1,5904.1,23552,7751.9,23552,8038.9,23552]],0,
[0,"#0000ff"]],
[1,
[0,[0,10404,18056.7],[0,10403.5,18053.2],[0,10413.9,18055.4],
[0,10404.5,18060.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5558,18188.6],[1,5884.7,18215.8,7194.5,18315.7,8269.4,18263],
[1,9099,18222.4,10096,18097.2,10404,18056.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10390,18052.6],[0,10389.7,18049.1],[0,10400,18051.8],
[0,10390.3,18056.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8162,18229.2],[1,8530.1,18200.1,9979.5,18085.2,10390,18052.6]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19806.8],[0,10496.4,19806.1],[0,10494.9,19816.6],
[0,10489.6,19807.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8146.4,16019.5],[1,8185.5,16020.3,8233.6,16027,8269.4,16051],
[1,9795.7,17069.9,10423,19517.1,10493,19806.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10448,13985],[0,10446.7,13981.8],[0,10457.3,13981.3],
[0,10449.3,13988.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8148.7,16024.3],[1,8186.3,16021.9,8232.1,16015,8269.4,15997],
[1,9406.9,15449.8,9290.5,14758,10332,14045],
[1,10369,14020,10414,13999,10448,13985]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19806.9],[0,10494.3,19805.9],[0,10494,19816.5],
[0,10487.7,19807.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8170.7,14611],[1,8205.1,14621,8242.3,14636,8269.4,14661],
[1,9146.8,15469.2,10377,19434,10491,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10474,11841],[0,10471.5,11838.5],[0,10481.1,11833.9],
[0,10476.5,11843.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8223.7,14587],[1,8239.7,14583,8255.3,14577,8269.4,14569],
[1,9545.5,13842,9361.4,13090,10332,11988],
[1,10380,11934,10440,11874,10474,11841]],
0,[0,"#0000ff"]],
[1,
[0,[0,10418,11125],[0,10417.3,11121.6],[0,10427.8,11123],
[0,10418.7,11128.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8126.4,11709],[1,8368,11638,9439.1,11327,10332,11140],
[1,10360,11134,10391,11129,10418,11125]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19807.1],[0,10496.3,19806.1],[0,10495.9,19816.7],
[0,10489.7,19808.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8153.4,11733],[1,8193.1,11741,8239.3,11757,8269.4,11789],
[1,8884.4,12438,10386,19314,10493,19807.1]],
0,[0,"#0000ff"]],
[1,[0,[0,10383,11812],[0,10383,11808.5],[0,10393,11812],[0,10383,11815.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8162.3,11727],[1,8528.7,11741,9961.7,11796,10383,11812]],0,
[0,"#0000ff"]],
[1,
[0,[0,10402,8156],[0,10401.7,8152.51],[0,10412,8155.09],
[0,10402.3,8159.49]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5548.1,8305],[1,5857.4,8315,7183.2,8351,8269.4,8311],
[1,9096.3,8280,10092,8186,10402,8156]],
0,[0,"#0000ff"]],
[1,
[0,[0,10395,8152],[0,10394.7,8148.52],[0,10405,8151],[0,10395.3,8155.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8148.3,8280],[1,8493.8,8260,9984.7,8175,10395,8152]],0,
[0,"#0000ff"]],
[1,
[0,[0,10439,18063.2],[0,10438,18059.9],[0,10448.6,18060.2],
[0,10440,18066.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5543.3,18778.6],[1,5928.7,18757.4,7991.5,18642.3,8269.4,18599],
[1,9145.6,18462.3,10181,18144.6,10439,18063.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10494,19863.4],[0,10490.6,19862.7],[0,10495.9,19853.6],
[0,10497.4,19864.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8173.2,24079.8],[1,8206.2,24076.8,8241.7,24068.4,8269.4,24049],
[1,9905.4,22901.9,10439,20171.3,10494,19863.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10494,19863.1],[0,10490.6,19862.4],[0,10495.9,19853.3],
[0,10497.4,19863.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8183.1,23970.5],[1,8213.1,23966.8,8244.4,23958.3,8269.4,23941],
[1,9877.9,22826,10435,20165.6,10494,19863.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10494,19863.5],[0,10490.6,19862.8],[0,10495.9,19853.7],
[0,10497.4,19864.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8179.6,24025],[1,8210.7,24021.6,8243.5,24013.1,8269.4,23995],
[1,9891.2,22864.3,10437,20169.9,10494,19863.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,7957.1,18816.5],[0,7957.38,18813],[0,7967.07,18817.3],
[0,7956.82,18820]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5554.6,18625.8],[1,5915.4,18654.4,7506.4,18780.8,7957.1,18816.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,7955.7,16983.7],[0,7955.15,16980.2],[0,7965.58,16982.1],
[0,7956.25,16987.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5558.2,18618],[1,5595,18614.8,5639.1,18607.9,5676.4,18593],
[1,6798.7,18143.5,6761.5,17453.3,7883.4,17003],
[1,7906.1,16993.9,7931.2,16987.8,7955.7,16983.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,19834.3],[0,10380,19830.8],[0,10390,19834.4],
[0,10380,19837.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5556.3,18624.6],[1,5593.1,18628.3,5637.8,18635,5676.4,18647],
[1,6724.4,18972.6,6819.6,19484.7,7883.4,19754],
[1,8126.8,19815.6,9899.3,19831.2,10380,19834.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10426,18061],[0,10425.2,18057.6],[0,10435.7,18058.8],
[0,10426.8,18064.4]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5558.5,18618.9],[1,5886.7,18613.3,7199.9,18583.7,8269.4,18454],
[1,9124,18350.4,10146,18124.6,10426,18061]],
0,[0,"#ee82ee"]],
[1,
[0,[0,5411.9,8119],[0,5410.89,8115.65],[0,5421.48,8116.13],
[0,5412.91,8122.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2991,9896],[1,3145.2,9751,4236.3,8737,5286.4,8170],
[1,5326.1,8149,5373.6,8131,5411.9,8119]],
0,[0,"#0000ff"]],
[1,
[0,[0,5430.6,18162.4],[0,5432,18159.2],[0,5439.77,18166.4],
[0,5429.2,18165.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3046.6,9921],[1,3082.8,9928,3124.2,9942,3151.4,9971],
[1,5713.2,12665,3092.6,15057,5286.4,18058],
[1,5322.9,18107.9,5386.1,18142.6,5430.6,18162.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10413,10044],[0,10413.7,10040.6],[0,10422.8,10046],
[0,10412.3,10047.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3040.4,9904],[1,3318.2,9865,4395,9719,5286.4,9673],
[1,6610.4,9604,6948.5,9559,8269.4,9673],
[1,9196.6,9753,9414.6,9877,10332,10031],
[1,10359,10035,10387,10040,10413,10044]],
0,[0,"#0000ff"]],
[1,
[0,[0,10371,16550.6],[0,10370.8,16547.1],[0,10381,16550.1],
[0,10371.2,16554.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3045.5,9921],[1,3081.6,9929,3123.4,9943,3151.4,9971],
[1,5351,12166,2775.9,14797.6,5286.4,16629],
[1,5353.4,16677.8,8186.6,16630.6,8269.4,16629],
[1,9069.5,16613.8,10030,16567.8,10371,16550.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,18044.4],[0,10380,18040.9],[0,10390,18044.4],
[0,10380,18047.9]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3046.6,9921],[1,3082.7,9928,3124.2,9942,3151.4,9971],
[1,5703.6,12651,2358.2,15756.5,5286.4,18020],
[1,5338.5,18060.3,9606.3,18047.1,10380,18044.4]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10395,10158],[0,10395.3,10154.5],[0,10405,10159],
[0,10394.7,10161.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3052.6,9915],[1,3539,9918,6145.3,9939,8269.4,10028],
[1,9089.2,10062,10077,10134,10395,10158]],
0,[0,"#0000ff"]],
[1,
[0,[0,10389,10102],[0,10389.3,10098.5],[0,10399,10103],
[0,10388.7,10105.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3052.6,9913],[1,3539.1,9906,6145.5,9875,8269.4,9957],
[1,9084.4,9989,10064,10073,10389,10102]],
0,[0,"#0000ff"]],
[1,[0,[0,10390,8147],[0,10390,8143.5],[0,10400,8147],[0,10390,8150.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,2988.7,9896],[1,3130.1,9744,4175.2,8647,5286.4,8276],
[1,5536.9,8192,9662.2,8153,10390,8147]],
0,[0,"#ee82ee"]],
[1,[0,[0,5395,827],[0,5395,823.5],[0,5405,827],[0,5395,830.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,2999.8,1034],[1,3239.4,1013,4984.1,863,5395,827]],0,[0,"#0000ff"]],
[1,[0,[0,5389.1,1088],[0,5389.1,1084.5],[0,5399.1,1088],[0,5389.1,1091.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,2999.8,1037],[1,3238.3,1042,4967.7,1079,5389.1,1088]],0,
[0,"#0000ff"]],
[1,[0,[0,5387.7,1036],[0,5387.7,1032.5],[0,5397.7,1036],[0,5387.7,1039.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,2999.8,1036],[1,3238,1036,4963.9,1036,5387.7,1036]],0,
[0,"#0000ff"]],
[1,[0,[0,2935,1036],[0,2935,1032.5],[0,2945,1036],[0,2935,1039.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,924.11,1036],[1,1298.2,1036,2688.5,1036,2935,1036]],0,
[0,"#0000ff"]],
[1,
[0,[0,10399,9881],[0,10399.7,9877.57],[0,10408.8,9882.96],
[0,10398.3,9884.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8162.2,9348],[1,8195.8,9353,8234.5,9358,8269.4,9365],
[1,9196.4,9543,9407.4,9682,10332,9869],
[1,10354,9873,10377,9878,10399,9881]],
0,[0,"#0000ff"]],
[1,
[0,[0,10399,9772],[0,10399.7,9768.57],[0,10408.8,9773.96],
[0,10398.3,9775.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8174.9,8970],[1,8205.5,8974,8239.1,8979,8269.4,8987],
[1,9218,9227,9390.2,9492,10332,9756],
[1,10354,9762,10377,9767,10399,9772]],
0,[0,"#0000ff"]],
[1,
[0,[0,5369.2,20844.6],[0,5368.71,20841.1],[0,5379.1,20843.2],
[0,5369.69,20848.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3024.8,21287],[1,3275.4,21234.6,4376.9,21006.5,5286.4,20857],
[1,5313.2,20852.6,5342,20848.3,5369.2,20844.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10474,19860.2],[0,10471.6,19857.6],[0,10481.3,19853.4],
[0,10476.4,19862.8]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3038.6,21298.5],[1,3639.8,21303.4,8137.9,21338.3,8269.4,21299],
[1,9304.6,20989.6,10305,20028.3,10474,19860.2]],
0,[0,"#ee82ee"]],
[1,
[0,[0,5401.6,23940],[0,5401.89,23936.5],[0,5411.57,23940.8],
[0,5401.31,23943.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2985.4,21315.7],[1,3140.7,21526.6,4643.1,23554.1,5286.4,23909],
[1,5321.3,23928.2,5364.6,23936.6,5401.6,23940]],
0,[0,"#0000ff"]],
[1,
[0,[0,5381.1,23981.6],[0,5381.56,23978.1],[0,5391.01,23982.9],
[0,5380.64,23985.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3080.2,23674.4],[1,3494.4,23729.7,4980.2,23928.1,5381.1,23981.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,5407.5,23932.7],[0,5407.89,23929.2],[0,5417.44,23933.8],
[0,5407.11,23936.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3092.2,23673.4],[1,3532.4,23722.7,5053.7,23893.1,5407.5,23932.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,5331.6,20839],[0,5330.74,20835.6],[0,5341.3,20836.6],
[0,5332.46,20842.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2980.8,23641.8],[1,3074.6,23439.4,3954.4,21600.6,5286.4,20857],
[1,5300.4,20849.2,5315.8,20843.4,5331.6,20839]],
0,[0,"#0000ff"]],
[1,
[0,[0,8001.7,23749.4],[0,8001.8,23745.9],[0,8011.7,23749.7],
[0,8001.6,23752.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5508.8,23661],[1,5756.2,23669.7,7605.2,23735.3,8001.7,23749.4]],0,
[0,"#0000ff"]],
[1,
[0,[0,8026.7,23644.3],[0,8026.67,23640.8],[0,8036.7,23644.2],
[0,8026.73,23647.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5508.8,23659.8],[1,5761.9,23658.3,7690.9,23646.4,8026.7,23644.3]],
0,[0,"#0000ff"]],
[1,[0,[0,5444,23660],[0,5444,23656.5],[0,5454,23660],[0,5444,23663.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3151.6,23660],[1,3676,23660,5187,23660,5444,23660]],0,
[0,"#0000ff"]],
[1,
[0,[0,10483,19861.7],[0,10480.1,19859.7],[0,10488.7,19853.5],
[0,10485.9,19863.7]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3015.2,23642.4],[1,3244.6,23548.6,4353.3,23100.2,5286.4,22812],
[1,6424,22460.7,6714.5,22380.8,7883.4,22155],
[1,8053.4,22122.2,8114.6,22180.5,8269.4,22103],
[1,9438.5,21518.1,10352,20075.5,10483,19861.7]],
0,[0,"#ee82ee"]],
[1,[0,[0,10409,13966],[0,10409,13962.5],[0,10419,13966],[0,10409,13969.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3046,13966],[1,3770,13966,9608.6,13966,10409,13966]],0,
[0,"#0000ff"]],
[1,[0,[0,10408,11483],[0,10408,11479.5],[0,10418,11483],[0,10408,11486.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2981.4,13948],[1,3079.5,13752,3975.9,12025,5286.4,11436],
[1,5771,11218,9751.9,11444,10408,11483]],
0,[0,"#0000ff"]],
[1,
[0,[0,10411,19849.1],[0,10410.5,19845.6],[0,10420.9,19847.6],
[0,10411.5,19852.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2976.3,13984],[1,3048.8,14323,4129.7,19296.3,5286.4,20096],
[1,5422.7,20190.2,8104,20105.6,8269.4,20096],
[1,9106.3,20047.2,10111,19896.2,10411,19849.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10392,12953],[0,10392.3,12949.5],[0,10402,12954],
[0,10391.7,12956.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2998.4,13949],[1,3179.7,13831,4277.8,13137,5286.4,12919],
[1,5801.5,12808,9693.7,12930,10392,12953]],
0,[0,"#0000ff"]],
[1,
[0,[0,5342.5,16014.9],[0,5343.2,16011.5],[0,5352.3,16016.9],
[0,5341.8,16018.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2985.7,13984],[1,3112.1,14152,4122.8,15464.8,5286.4,15997],
[1,5303.9,16005,5323.1,16010.8,5342.5,16014.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19863.1],[0,10487.7,19862.1],[0,10493.9,19853.5],
[0,10494.3,19864.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8136,23248],[1,8176.6,23247.9,8229.8,23242,8269.4,23217],
[1,9695.2,22316.3,10407,20135.6,10491,19863.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10409,23247.9],[0,10409,23244.4],[0,10419,23247.9],
[0,10409,23251.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8137.5,23244.1],[1,8465.5,23244.6,10017,23247.2,10409,23247.9]],0,
[0,"#0000ff"]],
[1,
[0,[0,10491,19863.1],[0,10487.7,19862.1],[0,10493.9,19853.5],
[0,10494.3,19864.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8111.4,23301.4],[1,8152.5,23303.6,8221.2,23301.7,8269.4,23271],
[1,9708.6,22354.5,10409,20138,10491,19863.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,12777,23273.3],[0,12777,23269.8],[0,12787,23273.3],
[0,12777,23276.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8112.1,23297.8],[1,8516.4,23295.7,12238,23276.2,12777,23273.3]],0,
[0,"#0000ff"]],
[1,
[0,[0,10465,19858],[0,10463,19855.1],[0,10473.2,19852.3],
[0,10467,19860.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5566.3,20885.4],[1,6004.5,20892.3,8000.5,20920.1,8269.4,20860],
[1,9225.7,20646.4,10263,19989.5,10465,19858]],
0,[0,"#0000ff"]],
[1,
[0,[0,10462,19857.7],[0,10460.2,19854.7],[0,10470.6,19852.6],
[0,10463.8,19860.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8140,20918],[1,8178.2,20913.2,8227.3,20905.2,8269.4,20892],
[1,9206.6,20598.5,10253,19983.2,10462,19857.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,2879.8,15431.2],[0,2879.28,15427.7],[0,2889.69,15429.7],
[0,2880.32,15434.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,886.23,15737.6],[1,1174.3,15693.3,2513.8,15487.5,2879.8,15431.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,2854.9,17329.3],[0,2855.53,17325.9],[0,2864.74,17331.1],
[0,2854.27,17332.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,846.61,15763.8],[1,971.37,15908.4,1847,16897.9,2793.4,17311],
[1,2812.6,17319.4,2833.8,17325.2,2854.9,17329.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10476,12040],[0,10473.5,12037.5],[0,10483.1,12032.9],
[0,10478.5,12042.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8152.7,14672],[1,8190.1,14662,8234.5,14647,8269.4,14623],
[1,9441.4,13829,9393.8,13256,10332,12196],
[1,10383,12139,10443,12074,10476,12040]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19807.2],[0,10494.3,19806.2],[0,10494,19816.8],
[0,10487.7,19808.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8220.6,14691],[1,8238.2,14697,8255,14704,8269.4,14715],
[1,9211.5,15430.5,10384,19434.3,10491,19807.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10485,19862],[0,10481.9,19860.3],[0,10489.9,19853.3],
[0,10488.1,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8169.4,22380.1],[1,8202.6,22376.8,8239.2,22369.2,8269.4,22353],
[1,9491.9,21697,10366,20089.8,10485,19862]],
0,[0,"#0000ff"]],
[1,
[0,[0,10492,19807],[0,10495.3,19806],[0,10494.9,19816.6],
[0,10488.7,19808]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8131.6,14266],[1,8173.6,14264,8230.6,14269,8269.4,14299],
[1,9267.3,15078.9,10393,19417.5,10492,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,10419,13976],[0,10418.7,13972.5],[0,10429,13975],
[0,10419.3,13979.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8130.7,14265],[1,8446.1,14225,10041,14024,10419,13976]],0,
[0,"#0000ff"]],
[1,[0,[0,5410.3,51],[0,5410.3,47.5],[0,5420.3,51.0001],[0,5410.3,54.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,2999.8,77],[1,3242.5,74,5029.7,55,5410.3,51]],0,[0,"#0000ff"]],
[1,
[0,[0,5429.2,103],[0,5429.54,99.5161],[0,5439.15,103.957],
[0,5428.86,106.484]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,2999.8,77],[1,3246.8,80,5093.6,100,5429.2,103]],0,[0,"#0000ff"]],
[1,[0,[0,2935.1,77],[0,2935.1,73.5],[0,2945.1,77.0001],[0,2935.1,80.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,895.21,77],[1,1219.8,77,2682.2,77,2935.1,77]],0,[0,"#0000ff"]],
[1,
[0,[0,10411,5495],[0,10411.7,5491.57],[0,10420.8,5496.96],
[0,10410.3,5498.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.4,4904],[1,8140.9,4909,8210.7,4919,8269.4,4932],
[1,9196.9,5132,9404.5,5283,10332,5481],
[1,10358,5486,10386,5491,10411,5495]],
0,[0,"#0000ff"]],
[1,
[0,[0,10409,4642],[0,10408.7,4638.52],[0,10419,4641],[0,10409.3,4645.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,4897],[1,8336.8,4871,9999.8,4687,10409,4642]],0,
[0,"#0000ff"]],
[1,[0,[0,8039,4900],[0,8039,4896.5],[0,8049,4900],[0,8039,4903.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5610.1,4900],[1,6090.8,4900,7767,4900,8039,4900]],0,[0,"#0000ff"]],
[1,
[0,[0,10426,4230],[0,10425.3,4226.57],[0,10435.8,4228.04],
[0,10426.7,4233.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8174.9,4726],[1,8205.3,4722,8238.8,4717,8269.4,4711],
[1,9194,4543,9412.4,4439,10332,4248],
[1,10363,4242,10397,4235,10426,4230]],
0,[0,"#0000ff"]],
[1,
[0,[0,10402,5550],[0,10402.3,5546.52],[0,10412,5551],[0,10401.7,5553.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8183.4,4749],[1,8211.6,4753,8241.9,4758,8269.4,4765],
[1,9218.1,5005,9386.3,5285,10332,5535],
[1,10355,5541,10379,5546,10402,5550]],
0,[0,"#0000ff"]],
[1,[0,[0,10409,3348],[0,10409,3344.5],[0,10419,3348],[0,10409,3351.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,3399],[1,8336.8,3394,9999.9,3357,10409,3348]],0,
[0,"#0000ff"]],
[1,
[0,[0,10417,2872],[0,10416.7,2868.52],[0,10427,2871],[0,10417.3,2875.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.7,3397],[1,8141.2,3393,8210.7,3384,8269.4,3373],
[1,9195.3,3200,9408.4,3070,10332,2887],
[1,10360,2882,10390,2876,10417,2872]],
0,[0,"#0000ff"]],
[1,[0,[0,10383,3297],[0,10383,3293.5],[0,10393,3297],[0,10383,3300.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,3399],[1,8332.2,3389,9933.9,3317,10383,3297]],0,
[0,"#0000ff"]],
[1,[0,[0,10433,3400],[0,10433,3396.5],[0,10443,3400],[0,10433,3403.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,3400],[1,8341.7,3400,10070,3400,10433,3400]],0,
[0,"#0000ff"]],
[1,[0,[0,8039,3401],[0,8039,3397.5],[0,8049,3401],[0,8039,3404.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5619.6,3454],[1,6112.3,3443,7768.8,3407,8039,3401]],0,
[0,"#0000ff"]],
[1,
[0,[0,7974.3,3174],[0,7974.64,3170.52],[0,7984.25,3174.99],
[0,7973.96,3177.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3054,3042],[1,3382.7,3040,4641.4,3033,5676.4,3062],
[1,6567.4,3087,7642.9,3153,7974.3,3174]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7985.4,1979],[0,7985.74,1975.52],[0,7995.35,1979.99],
[0,7985.06,1982.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3001.4,3026],[1,3192.6,2915,4295.4,2290,5286.4,2075],
[1,6325.5,1850,7632.8,1947,7985.4,1979]],
0,[0,"#0000ff"]],
[1,[0,[0,5367.3,3087],[0,5367.3,3083.5],[0,5377.3,3087],[0,5367.3,3090.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3053.8,3044],[1,3422.5,3051,4937.4,3079,5367.3,3087]],0,
[0,"#0000ff"]],
[1,
[0,[0,10413,11046],[0,10413.6,11042.6],[0,10422.8,11047.8],
[0,10412.4,11049.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3049.4,3037],[1,3084.3,3038,3123.9,3046,3151.4,3070],
[1,5708.2,5307,2694.6,8213,5286.4,10409],
[1,6304.8,11272,6943.9,10599,8269.4,10755],
[1,9106.5,10853,10116,11002,10413,11046]],
0,[0,"#0000ff"]],
[1,
[0,[0,10414,8133],[0,10414.3,8129.52],[0,10424,8134],[0,10413.7,8136.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5561.4,7893],[1,5893.8,7878,7199.1,7828,8269.4,7889],
[1,9109.1,7937,10118,8087,10414,8133]],
0,[0,"#0000ff"]],
[1,
[0,[0,10401,8137],[0,10401.3,8133.52],[0,10411,8138],[0,10400.7,8140.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8175.2,7925],[1,8567.1,7963,10010,8100,10401,8137]],0,
[0,"#0000ff"]],
[1,
[0,[0,10435,16780.4],[0,10434.1,16777],[0,10444.6,16777.7],
[0,10435.9,16783.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8111.8,17334.2],[1,8150.7,17329.7,8214.8,17321.5,8269.4,17311],
[1,9135.8,17144.2,10171,16855.6,10435,16780.4]],
0,[0,"#0000ff"]],
[1,[0,[0,15070,7678],[0,15070,7674.5],[0,15080,7678],[0,15070,7681.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12890,7819],[1,13188,7800,14802,7696,15070,7678]],0,[0,"#0000ff"]],
[1,
[0,[0,15070,7679],[0,15069.7,7675.52],[0,15080,7678],[0,15070.3,7682.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12883,7872],[1,13163,7848,14802,7703,15070,7679]],0,[0,"#0000ff"]],
[1,
[0,[0,10441,2697],[0,10441.3,2693.52],[0,10451,2698],[0,10440.7,2700.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8190.4,2677],[1,8619.1,2681,10126,2695,10441,2697]],0,
[0,"#0000ff"]],
[1,[0,[0,12762,2748],[0,12762,2744.5],[0,12772,2748],[0,12762,2751.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8190,2674],[1,8551.7,2668,9708.8,2653,10666,2671],
[1,11485,2686,12476,2734,12762,2748]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10487,19807.5],[0,10490.1,19805.9],[0,10491.7,19816.3],
[0,10483.9,19809.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8220.9,17037.9],[1,8237.9,17042.3,8254.5,17048.5,8269.4,17057],
[1,9551,17785.1,10379,19565.2,10487,19807.5]],
0,[0,"#0000ff"]],
[1,[0,[0,10363,17030],[0,10363,17026.5],[0,10373,17030],[0,10363,17033.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8237.3,17030],[1,8686,17030,9946,17030,10363,17030]],0,
[0,"#0000ff"]],
[1,
[0,[0,10367,9270],[0,10366,9266.65],[0,10376.6,9267.13],[0,10368,9273.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8231.8,17025.2],[1,8245.6,17020,8258.4,17012.8,8269.4,17003],
[1,10927,14652,7700,11670,10332,9291],
[1,10342,9282,10354,9275,10367,9270]],
0,[0,"#0000ff"]],
[1,
[0,[0,15070,7677],[0,15069.7,7673.52],[0,15080,7676],[0,15070.3,7680.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10595,7708],[1,10928,7709,12075,7710,13022,7703],
[1,13851,7697,14865,7680,15070,7677]],
0,[0,"#0000ff"]],
[1,
[0,[0,10494,19863.2],[0,10490.6,19862.5],[0,10496,19853.4],
[0,10497.4,19863.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8184.8,23916.2],[1,8214.3,23912.4,8244.8,23903.9,8269.4,23887],
[1,9863.9,22788.3,10433,20164.1,10494,19863.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10402,9881],[0,10402.3,9877.52],[0,10412,9882],[0,10401.7,9884.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.7,9449],[1,8141.1,9454,8210.5,9463,8269.4,9473],
[1,9190.5,9626,9413.1,9706,10332,9869],
[1,10355,9873,10379,9877,10402,9881]],
0,[0,"#0000ff"]],
[1,
[0,[0,10392,9773],[0,10392.3,9769.52],[0,10402,9774],[0,10391.7,9776.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,9450],[1,8141,9455,8210.3,9465,8269.4,9473],
[1,9085.5,9588,10069,9727,10392,9773]],
0,[0,"#0000ff"]],
[1,
[0,[0,10409,10045],[0,10409.7,10041.6],[0,10418.8,10047],
[0,10408.3,10048.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.5,9449],[1,8141,9453,8210.8,9461,8269.4,9473],
[1,9200,9663,9403.9,9831,10332,10031],
[1,10357,10036,10384,10041,10409,10045]],
0,[0,"#0000ff"]],
[1,
[0,[0,10439,9832],[0,10439.7,9828.57],[0,10448.8,9833.96],
[0,10438.3,9835.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,9450],[1,8141,9455,8210.4,9464,8269.4,9473],
[1,9188.2,9613,9415.2,9665,10332,9815],
[1,10368,9821,10407,9827,10439,9832]],
0,[0,"#0000ff"]],
[1,
[0,[0,8039.1,9449],[0,8038.76,9445.52],[0,8049.05,9448.02],
[0,8039.44,9452.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5577.4,10265],[1,5609.1,10260,5644.5,10255,5676.4,10247],
[1,6686.7,10002,6873.3,9718,7883.4,9473],
[1,7936.7,9460,7999.9,9453,8039.1,9449]],
0,[0,"#0000ff"]],
[1,
[0,[0,10404,9881],[0,10404.3,9877.52],[0,10414,9882],[0,10403.7,9884.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,9504],[1,8141,9509,8210.4,9518,8269.4,9527],
[1,9188.2,9667,9415.2,9719,10332,9869],
[1,10356,9873,10381,9877,10404,9881]],
0,[0,"#0000ff"]],
[1,
[0,[0,10410,10045],[0,10410.3,10041.5],[0,10420,10046],
[0,10409.7,10048.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.7,9503],[1,8141.3,9507,8210.8,9516,8269.4,9527],
[1,9196.4,9705,9407.4,9844,10332,10031],
[1,10357,10036,10385,10041,10410,10045]],
0,[0,"#0000ff"]],
[1,
[0,[0,10437,9833],[0,10437.6,9829.56],[0,10446.8,9834.79],
[0,10436.4,9836.44]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,9504],[1,8141,9509,8210.3,9519,8269.4,9527],
[1,9129.1,9648,10175,9796,10437,9833]],
0,[0,"#0000ff"]],
[1,
[0,[0,10392,11247],[0,10392.7,11243.6],[0,10401.8,11249],
[0,10391.3,11250.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,9499],[1,8142.1,9499,8214.1,9503,8269.4,9527],
[1,9357.1,10005,9257.1,10722,10332,11227],
[1,10351,11236,10372,11242,10392,11247]],
0,[0,"#0000ff"]],
[1,
[0,[0,8039.2,9503],[0,8038.86,9499.52],[0,8049.15,9502.01],
[0,8039.54,9506.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5576.3,10264],[1,5608.3,10260,5644.1,10254,5676.4,10247],
[1,6681.9,10015,6878.2,9759,7883.4,9527],
[1,7936.9,9515,8000,9507,8039.2,9503]],
0,[0,"#0000ff"]],
[1,
[0,[0,10417,9991],[0,10417.3,9987.52],[0,10427,9992],[0,10416.7,9994.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.5,9612],[1,8291.2,9643,9416.3,9828,10332,9977],
[1,10360,9981,10390,9986,10417,9991]],
0,[0,"#0000ff"]],
[1,
[0,[0,10390,9883],[0,10390.3,9879.52],[0,10400,9884],[0,10389.7,9886.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,9611],[1,8333.3,9639,9950.3,9831,10390,9883]],0,
[0,"#0000ff"]],
[1,
[0,[0,10412,10044],[0,10412.7,10040.6],[0,10421.8,10046],
[0,10411.3,10047.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.6,9612],[1,8141,9618,8210.4,9630,8269.4,9640],
[1,9188.3,9803,9413.3,9870,10332,10031],
[1,10358,10036,10387,10040,10412,10044]],
0,[0,"#0000ff"]],
[1,
[0,[0,10394,11246],[0,10394.7,11242.6],[0,10403.8,11248],
[0,10393.3,11249.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.4,9614],[1,8141.8,9624,8213.6,9644,8269.4,9673],
[1,9284.8,10208,9283.1,10762,10332,11227],
[1,10352,11235,10373,11242,10394,11246]],
0,[0,"#0000ff"]],
[1,
[0,[0,8039.3,9620],[0,8038.28,9616.65],[0,8048.87,9617.1],
[0,8040.32,9623.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5573.6,10264],[1,5606.2,10259,5643.1,10254,5676.4,10247],
[1,6651.6,10050,7818.4,9689,8039.3,9620]],
0,[0,"#0000ff"]],
[1,
[0,[0,10411,18029.8],[0,10411.6,18026.3],[0,10420.9,18031.4],
[0,10410.4,18033.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5586.5,10268],[1,5618.6,10271,5651.8,10280,5676.4,10301],
[1,8268.4,12522,5248.2,15487.7,7883.4,17657],
[1,7950,17711.8,8183.9,17684.1,8269.4,17695],
[1,8486.5,17722.7,10023,17967.8,10411,18029.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10405,18031.1],[0,10405.5,18027.6],[0,10414.9,18032.5],
[0,10404.5,18034.6]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5545.6,17632.2],[1,5850.3,17643.1,7181.7,17693.8,8269.4,17787],
[1,9099.2,17858.1,10098,17989.6,10405,18031.1]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8011.6,17630],[0,8011.6,17626.5],[0,8021.6,17630],
[0,8011.6,17633.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5546.2,17630],[1,5905.7,17630,7652.1,17630,8011.6,17630]],0,
[0,"#0000ff"]],
[1,
[0,[0,10396,10175],[0,10395.7,10171.5],[0,10406,10174],
[0,10396.3,10178.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5494.5,17612.2],[1,5528.4,17565.1,5620.8,17432.6,5676.4,17311],
[1,7018.1,14376,5362.3,12408,7883.4,10393],
[1,7896,10383,9913.2,10215,10396,10175]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10391,19826.2],[0,10391.3,19822.7],[0,10401,19827],
[0,10390.7,19829.7]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5505.5,17646.8],[1,5542.7,17672.9,5616.1,17725.1,5676.4,17772],
[1,6682.4,18554.1,6705.2,19116.9,7883.4,19602],
[1,7942.5,19626.3,9903.7,19786.7,10391,19826.2]],
0,[0,"#ee82ee"]],
[1,[0,[0,8039.2,7510],[0,8039.2,7506.5],[0,8049.2,7510],[0,8039.2,7513.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5546.2,7514],[1,5916.1,7513,7753.8,7510,8039.2,7510]],0,
[0,"#0000ff"]],
[1,
[0,[0,10435,24029.9],[0,10435.3,24026.4],[0,10445,24030.8],
[0,10434.7,24033.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8182.9,23816.1],[1,8598.3,23855.5,10104,23998.4,10435,24029.9]],0,
[0,"#0000ff"]],
[1,
[0,[0,10494,19863],[0,10490.6,19862.3],[0,10496,19853.2],
[0,10497.4,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8204.8,23804.7],[1,8227.7,23800,8250.3,23792,8269.4,23779],
[1,9836.7,22712.3,10430,20158.2,10494,19863]],
0,[0,"#0000ff"]],
[1,
[0,[0,10409,9937],[0,10409.3,9933.52],[0,10419,9938],[0,10408.7,9940.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8157.5,9401],[1,8192.1,9406,8232.9,9412,8269.4,9419],
[1,9196.4,9597,9407.4,9736,10332,9923],
[1,10357,9928,10384,9933,10409,9937]],
0,[0,"#0000ff"]],
[1,
[0,[0,8037.2,10184],[0,8037.2,10180.5],[0,8047.2,10184],
[0,8037.2,10187.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5616.4,10320],[1,6104,10293,7760.7,10200,8037.2,10184]],0,
[0,"#0000ff"]],
[1,
[0,[0,8005.4,10133],[0,8005.4,10129.5],[0,8015.4,10133],
[0,8005.4,10136.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5607,10318],[1,6066.9,10283,7650.5,10161,8005.4,10133]],0,
[0,"#0000ff"]],
[1,
[0,[0,10438,19816.2],[0,10439.1,19812.9],[0,10447.5,19819.3],
[0,10436.9,19819.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5563.2,11808],[1,5601.6,11809,5645.7,11817,5676.4,11843],
[1,8274.9,14071,5266.8,17015,7883.4,19222],
[1,7949.5,19277.7,8184.5,19253.1,8269.4,19269],
[1,9140.6,19431.9,10177,19737.7,10438,19816.2]],
0,[0,"#ee82ee"]],
[1,[0,[0,10388,11639],[0,10388,11635.5],[0,10398,11639],[0,10388,11642.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5565.1,11809],[1,5873.2,11784,6973.9,11697,7883.4,11664],
[1,8853.4,11629,10027,11636,10388,11639]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7952.1,11816],[0,7952.1,11812.5],[0,7962.1,11816],
[0,7952.1,11819.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5572.3,11816],[1,5963.1,11816,7502,11816,7952.1,11816]],0,
[0,"#0000ff"]],
[1,
[0,[0,10440,19815.6],[0,10441.1,19812.3],[0,10449.5,19818.6],
[0,10438.9,19818.9]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5563.2,11754],[1,5601.6,11755,5645.7,11763,5676.4,11789],
[1,8279.4,14023,5262.2,16971.9,7883.4,19184],
[1,7949.5,19239.7,8184.6,19214.4,8269.4,19231],
[1,9145.9,19402.1,10185,19732.5,10440,19815.6]],
0,[0,"#ee82ee"]],
[1,[0,[0,10388,11639],[0,10388,11635.5],[0,10398,11639],[0,10388,11642.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5565.9,11755],[1,5875.2,11732,6974.8,11652,7883.4,11626],
[1,8054.9,11621,8097.9,11625,8269.4,11626],
[1,9082.3,11629,10062,11636,10388,11639]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7953.2,11813],[0,7953.55,11809.5],[0,7963.15,11814],
[0,7952.85,11816.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5571.5,11764],[1,5961.4,11772,7504.1,11804,7953.2,11813]],0,
[0,"#0000ff"]],
[1,
[0,[0,10494,19806.5],[0,10497.4,19805.8],[0,10495.9,19816.3],
[0,10490.6,19807.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8171.2,15642.1],[1,8204.7,15645,8241.1,15653.3,8269.4,15673],
[1,9891.7,16804.3,10437,19500,10494,19806.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10456,13561],[0,10454.6,13557.8],[0,10465.1,13556.9],
[0,10457.4,13564.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8173.1,15644.3],[1,8205,15640.7,8239.9,15633.3,8269.4,15619],
[1,9412.7,15064,9322.4,14410,10332,13639],
[1,10372,13609,10421,13580,10456,13561]],
0,[0,"#0000ff"]],
[1,
[0,[0,10434,12975],[0,10433,12971.6],[0,10443.6,12972.1],
[0,10435,12978.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8132.2,13597],[1,8455.4,13510,10087,13069,10434,12975]],0,
[0,"#0000ff"]],
[1,[0,[0,10337,13544],[0,10337,13540.5],[0,10347,13544],[0,10337,13547.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8176.3,13609],[1,8550.8,13598,9873.6,13558,10337,13544]],0,
[0,"#0000ff"]],
[1,
[0,[0,10494,19806.9],[0,10497.4,19806.2],[0,10496,19816.7],
[0,10490.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8171.4,13606],[1,8205.5,13608,8242.2,13617,8269.4,13639],
[1,9356.8,14522,10406,19392.9,10494,19806.9]],
0,[0,"#0000ff"]],
[1,[0,[0,7931.7,8061],[0,7931.7,8057.5],[0,7941.7,8061],[0,7931.7,8064.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5580.4,8047],[1,5978,8049,7460.6,8058,7931.7,8061]],0,
[0,"#0000ff"]],
[1,
[0,[0,10396,8139],[0,10396.3,8135.51],[0,10406,8139.91],
[0,10395.7,8142.49]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5579.6,8044],[1,5938.9,8035,7216.4,8009,8269.4,8035],
[1,9090.3,8055,10080,8118,10396,8139]],
0,[0,"#ee82ee"]],
[1,
[0,[0,8006.9,9682],[0,8007.92,9678.65],[0,8016.47,9684.9],
[0,8005.88,9685.35]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5578,8050],[1,5610.1,8054,5645.6,8061,5676.4,8073],
[1,6793.9,8515,6812.2,9090,7883.4,9635],
[1,7922.6,9655,7969.3,9671,8006.9,9682]],
0,[0,"#0000ff"]],
[1,
[0,[0,10416,13958],[0,10416.3,13954.5],[0,10426,13959],
[0,10415.7,13961.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8114,13724],[1,8383.7,13751,10025,13918,10416,13958]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8114.1,13723],[1,8157,13729,8226.8,13744,8269.4,13785],
[1,9252,14740,10395,19401.9,10493,19806.9]],
0,[0,"#0000ff"]],
[1,[0,[0,12805,7170],[0,12805,7166.5],[0,12815,7170],[0,12805,7173.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8113,13725],[1,8155.5,13730,8225.6,13730,8269.4,13693],
[1,10541,11789,7999.1,9179,10332,7351],
[1,10358,7331,12495,7191,12805,7170]],
0,[0,"#0000ff"]],
[1,
[0,[0,15001,2404],[0,15000.7,2400.52],[0,15011,2403],[0,15001.3,2407.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12869,2454],[1,13089,2449,14586,2413,15001,2404]],0,[0,"#0000ff"]],
[1,
[0,[0,14962,2354],[0,14961.7,2350.52],[0,14972,2353],[0,14962.3,2357.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12869,2454],[1,13083,2444,14499,2376,14962,2354]],0,[0,"#0000ff"]],
[1,[0,[0,14980,2506],[0,14980,2502.5],[0,14990,2506],[0,14980,2509.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12869,2456],[1,13086,2461,14539,2495,14980,2506]],0,[0,"#0000ff"]],
[1,[0,[0,12805,2457],[0,12805,2453.5],[0,12815,2457],[0,12805,2460.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10626,2598],[1,11071,2569,12551,2474,12805,2457]],0,[0,"#0000ff"]],
[1,[0,[0,12761,2754],[0,12761,2750.5],[0,12771,2754],[0,12761,2757.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10572,2804],[1,10918,2796,12396,2762,12761,2754]],0,[0,"#0000ff"]],
[1,[0,[0,12761,2806],[0,12761,2802.5],[0,12771,2806],[0,12761,2809.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10572,2806],[1,10919,2806,12396,2806,12761,2806]],0,[0,"#0000ff"]],
[1,[0,[0,12733,6252],[0,12733,6248.5],[0,12743,6252],[0,12733,6255.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.5,6466],[1,8290.5,6438,9412.4,6276,10332,6227],
[1,10481,6219,10518,6226,10666,6227],
[1,11459,6232,12414,6247,12733,6252]],
0,[0,"#0000ff"]],
[1,
[0,[0,10415,6595],[0,10415.3,6591.52],[0,10425,6596],[0,10414.7,6598.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,6471],[1,8338,6484,10017,6574,10415,6595]],0,[0,"#0000ff"]],
[1,[0,[0,8038.8,6470],[0,8038.8,6466.5],[0,8048.8,6470],[0,8038.8,6473.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5580,6470],[1,6015.8,6470,7760.3,6470,8038.8,6470]],0,
[0,"#0000ff"]],
[1,
[0,[0,10392,12953],[0,10392.3,12949.5],[0,10402,12954],
[0,10391.7,12956.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3115.5,12936],[1,3478.3,12911,4463.8,12848,5286.4,12827],
[1,6612,12793,6943.9,12850,8269.4,12886],
[1,9086,12908,10071,12942,10392,12953]],
0,[0,"#0000ff"]],
[1,
[0,[0,10405,19847.9],[0,10404.5,19844.4],[0,10414.9,19846.5],
[0,10405.5,19851.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2976.9,12964],[1,3071.7,13345,4634.6,19584.6,5286.4,20058],
[1,5420.5,20155.4,8103.9,20066.3,8269.4,20058],
[1,9099.9,20016.6,10098,19888.9,10405,19847.9]],
0,[0,"#0000ff"]],
[1,[0,[0,10390,12957],[0,10390,12953.5],[0,10400,12957],[0,10390,12960.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5595.7,12946],[1,6270.6,12948,9729.4,12955,10390,12957]],0,
[0,"#0000ff"]],
[1,
[0,[0,10410,13962],[0,10410.3,13958.5],[0,10420,13963],
[0,10409.7,13965.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8188.8,13871],[1,8602.6,13888,10036,13947,10410,13962]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8189.7,13862],[1,8218.2,13866,8247,13875,8269.4,13893],
[1,9322.1,14736,10401,19401.3,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10456,12979],[0,10454.3,12975.9],[0,10464.7,12974.1],
[0,10457.7,12982.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8176,13857],[1,8206.3,13853,8239.5,13847,8269.4,13839],
[1,9184.7,13598,10233,13089,10456,12979]],
0,[0,"#0000ff"]],
[1,
[0,[0,12805,2283],[0,12805.3,2279.52],[0,12815,2284],[0,12804.7,2286.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8217.9,2154],[1,8608.1,2149,9732.4,2139,10666,2167],
[1,11534,2193,12595,2268,12805,2283]],
0,[0,"#0000ff"]],
[1,[0,[0,12805,2285],[0,12805,2281.5],[0,12815,2285],[0,12805,2288.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10633,2199],[1,11086,2217,12553,2275,12805,2285]],0,[0,"#0000ff"]],
[1,
[0,[0,5361.9,20816.6],[0,5362.28,20813.1],[0,5371.84,20817.7],
[0,5361.52,20820.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,2999.8,20551.1],[1,3233.4,20577.3,4898.3,20764.5,5361.9,20816.6]],
0,[0,"#0000ff"]],
[1,[0,[0,10394,12962],[0,10394,12958.5],[0,10404,12962],[0,10394,12965.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2999.7,20533],[1,3039,20510.1,3111.2,20462.7,3151.4,20403],
[1,4962.5,17719.7,2800.6,15512.9,5286.4,13439],
[1,6178.8,12694,6726.2,13240,7883.4,13133],
[1,8857.4,13043,10039,12980,10394,12962]],
0,[0,"#0000ff"]],
[1,
[0,[0,2935.2,20548],[0,2935.2,20544.5],[0,2945.2,20548],
[0,2935.2,20551.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,933.97,20548],[1,1322.1,20548,2691.3,20548,2935.2,20548]],0,
[0,"#0000ff"]],
[1,
[0,[0,5401.3,20811.8],[0,5402.06,20808.4],[0,5411.06,20814],
[0,5400.54,20815.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2999.5,20325.6],[1,3034.6,20330.4,3097.7,20339.4,3151.4,20349],
[1,4037.9,20507.2,5104.4,20744.8,5401.3,20811.8]],
0,[0,"#0000ff"]],
[1,[0,[0,10406,11485],[0,10406,11481.5],[0,10416,11485],[0,10406,11488.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2999.7,20326.4],[1,3038.6,20331,3109.8,20333.1,3151.4,20295],
[1,6116.4,17581.9,2131.6,13998,5286.4,11508],
[1,5495.3,11343,9721.5,11464,10406,11485]],
0,[0,"#0000ff"]],
[1,
[0,[0,2935.1,20325.9],[0,2934.76,20322.4],[0,2945.05,20324.9],
[0,2935.44,20329.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,919.35,20538.7],[1,1286.3,20500,2687.9,20352,2935.1,20325.9]],0,
[0,"#0000ff"]],
[1,
[0,[0,10477,19860.5],[0,10474.3,19858.3],[0,10483.2,19852.7],
[0,10479.7,19862.7]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,862.82,20565.2],[1,1043.3,20662.9,1969.5,21150.6,2793.4,21325],
[1,3091.1,21388,7979.7,21526.1,8269.4,21433],
[1,9331.2,21091.8,10316,20037.9,10477,19860.5]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10384,19829.4],[0,10384.2,19825.9],[0,10394,19829.9],
[0,10383.8,19832.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5585.9,18519.8],[1,5615.6,18523.8,5647.7,18529.9,5676.4,18539],
[1,6728.6,18872.6,6819.1,19385.5,7883.4,19678],
[1,8005.5,19711.6,9894.3,19805.5,10384,19829.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,7959.4,13464],[0,7958.71,13460.6],[0,7969.21,13462],
[0,7960.09,13467.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5595.7,18515.3],[1,5624.3,18511.2,5653.4,18502.4,5676.4,18485],
[1,7613.4,17024.6,5947.5,14954.8,7883.4,13493],
[1,7905.2,13477,7932.4,13468,7959.4,13464]],
0,[0,"#0000ff"]],
[1,
[0,[0,10487,19807.7],[0,10490.2,19806.3],[0,10491,19816.9],
[0,10483.8,19809.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8151.5,17081.9],[1,8189,17083.9,8233.9,17091,8269.4,17111],
[1,9538.7,17824.1,10377,19568.6,10487,19807.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10365,17033],[0,10364.9,17029.5],[0,10375,17032.8],
[0,10365.1,17036.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8151.6,17082.3],[1,8495.2,17074.7,9918.3,17043,10365,17033]],0,
[0,"#0000ff"]],
[1,
[0,[0,10484,12984],[0,10480.9,12982.3],[0,10488.9,12975.3],
[0,10487.1,12985.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8149,17089],[1,8187.9,17088.1,8234.7,17081.1,8269.4,17057],
[1,9850.3,15960.2,9398.8,14933.4,10332,13251],
[1,10387,13152,10454,13036,10484,12984]],
0,[0,"#0000ff"]],
[1,
[0,[0,10396,19824.5],[0,10396.4,19821],[0,10405.9,19825.6],
[0,10395.6,19828]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5503.7,17052],[1,5540.7,17082.2,5616.4,17145.2,5676.4,17203],
[1,6711,18199.4,6597.1,18924.8,7883.4,19564],
[1,7897.8,19571.2,9912.5,19775.6,10396,19824.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10370,17023.6],[0,10370.2,17020.1],[0,10380,17024.1],
[0,10369.8,17027.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5611,17025.6],[1,6008.3,17000.7,7244.5,16930.4,8269.4,16949],
[1,9068.2,16963.5,10027,17007.2,10370,17023.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10397,12964],[0,10396.7,12960.5],[0,10407,12963],
[0,10397.3,12967.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5497.8,17016],[1,5532.5,16977.3,5615.5,16882.8,5676.4,16797],
[1,6769.3,15257.8,6276.5,14159,7883.4,13168],
[1,7938,13134,9919,12997,10397,12964]],
0,[0,"#0000ff"]],
[1,
[0,[0,10369,17035.8],[0,10368.9,17032.3],[0,10379,17035.4],
[0,10369.1,17039.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8250.2,17130.3],[1,8711.8,17109.7,9961.3,17054,10369,17035.8]],0,
[0,"#0000ff"]],
[1,
[0,[0,10484,12984],[0,10480.9,12982.3],[0,10488.9,12975.3],
[0,10487.1,12985.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8236.9,17127.9],[1,8248.4,17123.5,8259.4,17118,8269.4,17111],
[1,9864.4,15997.5,9393.5,14954.6,10332,13251],
[1,10387,13152,10454,13036,10484,12984]],
0,[0,"#0000ff"]],
[1,
[0,[0,10485,19808.2],[0,10488.2,19806.8],[0,10489.1,19817.3],
[0,10481.8,19809.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8156.5,17154.5],[1,8193.1,17164.6,8235.6,17180.1,8269.4,17203],
[1,9446.1,18001.8,10359,19583.3,10485,19808.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10472,19860.1],[0,10469.7,19857.4],[0,10479.6,19853.6],
[0,10474.3,19862.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8179.8,21359.2],[1,8209.5,21354.4,8241.3,21347.2,8269.4,21336],
[1,9278.5,20934.9,10295,20023,10472,19860.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10386,18050.5],[0,10385.8,18047],[0,10396,18049.9],
[0,10386.2,18054]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8176.7,18176.3],[1,8565.7,18154.1,9974.1,18073.9,10386,18050.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10475,19809.6],[0,10477.5,19807.2],[0,10481.9,19816.9],
[0,10472.5,19812]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8178.5,18186.9],[1,8208.6,18190.8,8241,18197.5,8269.4,18209],
[1,9307.2,18628.9,10308,19636.9,10475,19809.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10411,18029.9],[0,10411.6,18026.4],[0,10420.9,18031.5],
[0,10410.4,18033.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8125.6,17638.1],[1,8164.6,17644.5,8220.5,17653.7,8269.4,17662],
[1,9186.8,17817,9414.8,17863.9,10332,18017],
[1,10358,18021.2,10386,18025.8,10411,18029.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10488,10194],[0,10484.8,10192.7],[0,10491.7,10184.7],
[0,10491.2,10195.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8129.4,17625.4],[1,8172.7,17618.9,8232.6,17603.2,8269.4,17565],
[1,10511,15238.3,9285.8,13651,10332,10594],
[1,10385,10441,10459,10261,10488,10194]],
0,[0,"#0000ff"]],
[1,
[0,[0,10480,19808.9],[0,10482.8,19806.8],[0,10486,19816.9],
[0,10477.2,19811]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8122.9,17639.6],[1,8163.7,17649.3,8223.3,17667.1,8269.4,17695],
[1,9350.7,18350.3,10331,19612.2,10480,19808.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10413,19849.6],[0,10412.4,19846.1],[0,10422.9,19847.9],
[0,10413.6,19853.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8167.7,20226.9],[1,8199.9,20221.6,8236.3,20215.5,8269.4,20210],
[1,9104.6,20070.5,10115,19899.9,10413,19849.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,18046.3],[0,10379.9,18042.8],[0,10390,18046.1],
[0,10380.1,18049.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8198.2,18087.7],[1,8613.3,18079.8,9969.2,18054.1,10380,18046.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10473,19809.9],[0,10475.3,19807.3],[0,10480.5,19816.5],
[0,10470.7,19812.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8138.9,18105.5],[1,8177.7,18116.5,8228,18133.1,8269.4,18155],
[1,9269.2,18682.2,10298,19642.7,10473,19809.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10479,19861.1],[0,10476.3,19858.8],[0,10485.5,19853.5],
[0,10481.7,19863.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8166.4,21807.4],[1,8200,21803.1,8237.6,21795,8269.4,21780],
[1,9362.5,21264.4,10330,20053.8,10479,19861.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,5393.1,18187.1],[0,5393.27,18183.6],[0,5403.09,18187.6],
[0,5392.93,18190.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2976.7,10484],[1,3068.7,10880,4636.2,17579.1,5286.4,18150],
[1,5315.3,18175.3,5356.2,18184.6,5393.1,18187.1]],
0,[0,"#0000ff"]],
[1,[0,[0,10393,10051],[0,10393,10047.5],[0,10403,10051],[0,10393,10054.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3020.9,10454],[1,3262.9,10396,4366.2,10141,5286.4,10055],
[1,7333,9864,9851.2,10014,10393,10051]],
0,[0,"#0000ff"]],
[1,
[0,[0,10403,8156],[0,10402.7,8152.52],[0,10413,8155],[0,10403.3,8159.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2984.8,10448],[1,3105.5,10276,4093.7,8903,5286.4,8430],
[1,5440.6,8369,8103.9,8342,8269.4,8332],
[1,9096.3,8284,10093,8187,10403,8156]],
0,[0,"#0000ff"]],
[1,
[0,[0,10393,19844.5],[0,10392.7,19841],[0,10403,19843.6],
[0,10393.3,19848]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2976.7,10484],[1,3084.2,10943,5182.2,19900.1,5286.4,19982],
[1,5416.7,20084.4,8103.8,19987.5,8269.4,19982],
[1,9087.7,19955.1,10072,19872.7,10393,19844.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10407,18057.3],[0,10406.5,18053.8],[0,10416.9,18055.9],
[0,10407.5,18060.8]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,2976.5,10484],[1,3065.5,10882,4594.5,17679,5286.4,18209],
[1,5549.6,18410.6,7938.3,18296.4,8269.4,18279],
[1,9101.9,18235.3,10102,18100.3,10407,18057.3]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10391,10172],[0,10390.7,10168.5],[0,10401,10171],
[0,10391.3,10175.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3035.8,10465],[1,3333.4,10462,4621.2,10447,5676.4,10409],
[1,5919.9,10400,9697.9,10207,10391,10172]],
0,[0,"#0000ff"]],
[1,
[0,[0,10377,10107],[0,10377.3,10103.5],[0,10387,10108],
[0,10376.7,10110.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3022.6,10455],[1,3268.2,10401,4369.9,10167,5286.4,10085],
[1,6607.1,9967,6943.7,10028,8269.4,10047],
[1,9073.4,10059,10040,10094,10377,10107]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19807.2],[0,10496.4,19806.5],[0,10495,19817],
[0,10489.6,19807.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8115.8,12340],[1,8158.7,12336,8227,12337,8269.4,12373],
[1,8901.5,12916,10384,19331.5,10493,19807.2]],
0,[0,"#0000ff"]],
[1,[0,[0,10387,12346],[0,10387,12342.5],[0,10397,12346],[0,10387,12349.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8118,12346],[1,8392.8,12346,9951.7,12346,10387,12346]],0,
[0,"#0000ff"]],
[1,
[0,[0,10439,12938],[0,10440,12934.6],[0,10448.6,12940.9],
[0,10438,12941.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8117,12350],[1,8156.2,12355,8217.2,12363,8269.4,12373],
[1,9141.7,12548,10180,12859,10439,12938]],
0,[0,"#0000ff"]],
[1,
[0,[0,10433,12024],[0,10432.7,12020.5],[0,10443,12023.1],
[0,10433.3,12027.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8116.5,12341],[1,8397.9,12302,10078,12073,10433,12024]],0,
[0,"#0000ff"]],
[1,[0,[0,10428,12016],[0,10428,12012.5],[0,10438,12016],[0,10428,12019.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8165.2,12037],[1,8550.8,12033,10078,12019,10428,12016]],0,
[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8207.5,12560],[1,8230.1,12565,8251.9,12574,8269.4,12589],
[1,8886.4,13115,10381,19336.7,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10390,12485],[0,10389.7,12481.5],[0,10400,12484],
[0,10390.3,12488.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8204.6,12558],[1,8630.3,12543,9992.8,12498,10390,12485]],0,
[0,"#0000ff"]],
[1,
[0,[0,10418,12943],[0,10418.7,12939.6],[0,10427.8,12945],
[0,10417.3,12946.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8170.2,12575],[1,8201.8,12579,8237.2,12584,8269.4,12589],
[1,9110.4,12717,10126,12892,10418,12943]],
0,[0,"#0000ff"]],
[1,
[0,[0,12761,12315],[0,12761.3,12311.5],[0,12771,12315.9],
[0,12760.7,12318.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8180.1,12131],[1,8530.1,12137,9700.2,12156,10666,12196],
[1,11485,12230,12475,12296,12761,12315]],
0,[0,"#0000ff"]],
[1,
[0,[0,10453,12936],[0,10454.4,12932.8],[0,10462.1,12940.1],
[0,10451.6,12939.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8167.5,12139],[1,8199.9,12143,8236.6,12149,8269.4,12157],
[1,9173,12380,10221,12834,10453,12936]],
0,[0,"#0000ff"]],
[1,
[0,[0,10437,18062.7],[0,10436,18059.3],[0,10446.6,18059.9],
[0,10438,18066.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8150.1,18653.4],[1,8186.2,18647.9,8230.2,18640.4,8269.4,18632],
[1,9137.7,18446,10175,18141,10437,18062.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10389,18034.8],[0,10389.7,18031.4],[0,10398.8,18036.7],
[0,10388.3,18038.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8185.8,16282.7],[1,8213.9,16286.7,8243.5,16293.6,8269.4,16305],
[1,9359.4,16786.3,9247.7,17524.1,10332,18017],
[1,10350,18025.1,10370,18030.7,10389,18034.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10466,15090.5],[0,10463.9,15087.7],[0,10474.1,15084.6],
[0,10468.1,15093.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8179.1,16270.4],[1,8208.7,16266.4,8240.8,16260.3,8269.4,16251],
[1,9230.8,15939.3,10269,15228.6,10466,15090.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10392,11056],[0,10392.7,11052.6],[0,10401.8,11058],
[0,10391.3,11059.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8159.4,7432],[1,8196.1,7442,8238.1,7457,8269.4,7483],
[1,9682.8,8637,8829,9998,10332,11032],
[1,10350,11044,10371,11051,10392,11056]],
0,[0,"#0000ff"]],
[1,
[0,[0,10409,7697],[0,10409.3,7693.52],[0,10419,7698],[0,10408.7,7700.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8176.3,7430],[1,8572.5,7477,10030,7652,10409,7697]],0,
[0,"#0000ff"]],
[1,
[0,[0,10429,6771],[0,10428.7,6767.52],[0,10439,6770],[0,10429.3,6774.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8179.1,7406],[1,8208.4,7402,8240.3,7397,8269.4,7391],
[1,9203.3,7191,9400.8,6999,10332,6789],
[1,10364,6782,10399,6776,10429,6771]],
0,[0,"#0000ff"]],
[1,
[0,[0,10408,6720],[0,10407.7,6716.52],[0,10418,6719],[0,10408.3,6723.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8180.7,7407],[1,8209.6,7403,8240.9,7397,8269.4,7391],
[1,9207.6,7178,9396.5,6958,10332,6735],
[1,10357,6729,10383,6724,10408,6720]],
0,[0,"#0000ff"]],
[1,
[0,[0,15070,7675],[0,15070.3,7671.52],[0,15080,7676],[0,15069.7,7678.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,8171,7431],[1,8480.5,7472,9491.4,7600,10332,7643],
[1,11526,7704,11827,7640,13022,7649],
[1,13851,7655,14865,7672,15070,7675]],
0,[0,"#ee82ee"]],
[1,
[0,[0,5364.8,8088],[0,5365.15,8084.52],[0,5374.75,8089],
[0,5364.45,8091.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3052.4,7848],[1,3417.9,7886,4931,8043,5364.8,8088]],0,
[0,"#0000ff"]],
[1,
[0,[0,10411,8133],[0,10411.7,8129.57],[0,10420.8,8134.96],
[0,10410.3,8136.43]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3060.8,7836],[1,3567.8,7817,6159.9,7729,8269.4,7866],
[1,8700.2,7894,10052,8083,10411,8133]],
0,[0,"#ee82ee"]],
[1,[0,[0,8039.1,7510],[0,8039.1,7506.5],[0,8049.1,7510],[0,8039.1,7513.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3045.7,7829],[1,3331.6,7788,4400.6,7640,5286.4,7579],
[1,6411.1,7502,7796,7508,8039.1,7510]],
0,[0,"#0000ff"]],
[1,
[0,[0,10420,24139.5],[0,10420.4,24136],[0,10429.9,24140.7],
[0,10419.6,24143]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8191.7,23873.7],[1,8612.8,23924,10063,24096.9,10420,24139.5]],0,
[0,"#0000ff"]],
[1,
[0,[0,10494,19863.3],[0,10490.6,19862.6],[0,10496,19853.5],
[0,10497.4,19864]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8232.4,23851.3],[1,8245.6,23846.7,8258.1,23840.7,8269.4,23833],
[1,9849.9,22750.6,10431,20162.5,10494,19863.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,12801,3757],[0,12802.7,3753.94],[0,12809.7,3761.86],
[0,12799.3,3760.06]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10553,2920],[1,10586,2924,10629,2931,10666,2941],
[1,11556,3181,12584,3655,12801,3757]],
0,[0,"#0000ff"]],
[1,[0,[0,12763,2757],[0,12763,2753.5],[0,12773,2757],[0,12763,2760.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10555,2910],[1,10866,2889,12397,2783,12763,2757]],0,[0,"#0000ff"]],
[1,
[0,[0,8039.1,5113],[0,8039.44,5109.52],[0,8049.05,5113.99],
[0,8038.76,5116.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5560.5,4996],[1,5961,5015,7757,5100,8039.1,5113]],0,[0,"#0000ff"]],
[1,
[0,[0,8038.9,4795],[0,8038.56,4791.52],[0,8048.85,4794.02],
[0,8039.24,4798.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5557.7,4986],[1,5952.4,4956,7755.7,4817,8038.9,4795]],0,
[0,"#ee82ee"]],
[1,[0,[0,8039.2,4992],[0,8039.2,4988.5],[0,8049.2,4992],[0,8039.2,4995.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5561.9,4992],[1,5965.2,4992,7757.7,4992,8039.2,4992]],0,
[0,"#ee82ee"]],
[1,
[0,[0,8004,23745.6],[0,8004.38,23742.1],[0,8013.94,23746.7],
[0,8003.62,23749.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5512.8,22853.5],[1,5716.9,22947.4,6880.6,23473,7883.4,23725],
[1,7922.7,23734.9,7967.5,23741.4,8004,23745.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10484,19862.1],[0,10480.9,19860.4],[0,10488.9,19853.4],
[0,10487.1,19863.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5519.4,22826.4],[1,5742.5,22752.8,6905.8,22376.2,7883.4,22191],
[1,8053,22158.9,8114.5,22224.2,8269.4,22148],
[1,9454.8,21564.7,10356,20080.8,10484,19862.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10492,19862.7],[0,10488.6,19862],[0,10494,19852.9],
[0,10495.4,19863.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8112.9,23355.5],[1,8154.2,23357.7,8221.9,23355.5,8269.4,23325],
[1,9722.7,22392.3,10412,20138.1,10492,19862.7]],
0,[0,"#0000ff"]],
[1,[0,[0,10393,23352],[0,10393,23348.5],[0,10403,23352],[0,10393,23355.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8113.5,23352],[1,8376.8,23352,9964.7,23352,10393,23352]],0,
[0,"#0000ff"]],
[1,
[0,[0,10449,13985],[0,10447.6,13981.8],[0,10458.1,13980.9],
[0,10450.4,13988.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8105.1,15971.2],[1,8144.2,15971.7,8215.4,15968.5,8269.4,15943],
[1,9395.9,15410.8,9299.1,14741,10332,14045],
[1,10369,14020,10415,13999,10449,13985]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19806.9],[0,10496.4,19806.2],[0,10495,19816.7],
[0,10489.6,19807.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8104.7,15966.7],[1,8144.8,15963.5,8219.2,15963.2,8269.4,15997],
[1,9809.4,17032,10425,19515.2,10493,19806.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10475,11284],[0,10472.5,11281.5],[0,10482.1,11276.9],
[0,10477.5,11286.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8143.2,16215.4],[1,8184,16207,8234.7,16190.7,8269.4,16159],
[1,9952,14620,9136,13402,10332,11461],
[1,10375,11392,10440,11321,10475,11284]],
0,[0,"#0000ff"]],
[1,
[0,[0,10397,16530.5],[0,10397.5,16527],[0,10406.9,16531.8],
[0,10396.5,16534]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8142.5,16232.7],[1,8477.5,16277,9988.5,16476.5,10397,16530.5]],0,
[0,"#0000ff"]],
[1,
[0,[0,10389,18034.9],[0,10389.7,18031.5],[0,10398.8,18036.8],
[0,10388.3,18038.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8152,16224.7],[1,8188.8,16227.5,8232.9,16234.5,8269.4,16251],
[1,9369.8,16747,9237.4,17509.3,10332,18017],
[1,10350,18025.1,10369,18030.8,10389,18034.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10391,8145],[0,10390.3,8141.57],[0,10400.8,8143.04],
[0,10391.7,8148.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8146.5,16217],[1,8187.7,16209.3,8237.8,16193,8269.4,16159],
[1,10767,13475,7623.2,10643,10332,8173],
[1,10349,8158,10370,8150,10391,8145]],
0,[0,"#0000ff"]],
[1,
[0,[0,10485,19861.8],[0,10482,19860.1],[0,10489.9,19853.1],
[0,10488,19863.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8156.8,22327],[1,8193,22324.4,8235.2,22317.1,8269.4,22299],
[1,9480.2,21657.7,10364,20086,10485,19861.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10419,13956],[0,10419.3,13952.5],[0,10429,13957],
[0,10418.7,13959.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8140.6,13674],[1,8478,13716,10045,13910,10419,13956]],0,
[0,"#0000ff"]],
[1,
[0,[0,10494,19806.7],[0,10497.4,19806],[0,10495.9,19816.5],
[0,10490.6,19807.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8150.4,15749.2],[1,8188.9,15750.2,8235,15757.3,8269.4,15781],
[1,9864.4,16880.2,10433,19505.7,10494,19806.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,12818,3802],[0,12815.5,3799.53],[0,12825.1,3794.93],
[0,12820.5,3804.47]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,10566,8690],[1,10600,8688,10638,8681,10666,8659],
[1,12442,7272,11501,5930,12662,4000],
[1,12709,3922,12781,3841,12818,3802]],
0,[0,"#0000ff"]],
[1,
[0,[0,10415,16084.3],[0,10414.6,16080.8],[0,10424.9,16083],
[0,10415.4,16087.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8147.6,17535.8],[1,8184.9,17532.8,8230.8,17525.9,8269.4,17511],
[1,9304.5,17111.2,9301.7,16515.8,10332,16105],
[1,10358,16094.6,10388,16088.2,10415,16084.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10408,18030.2],[0,10408.5,18026.7],[0,10417.9,18031.6],
[0,10407.5,18033.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8137.8,17547.4],[1,8175.8,17553.4,8225.6,17561.6,8269.4,17570],
[1,9190.9,17746.1,9410.6,17842.7,10332,18017],
[1,10357,18021.7,10384,18026.2,10408,18030.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10442,16061],[0,10443,16057.6],[0,10451.6,16063.8],
[0,10441,16064.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8141.9,15491.3],[1,8179.4,15496,8227.3,15502.7,8269.4,15511],
[1,9144.6,15682.9,10189,15986.2,10442,16061]],
0,[0,"#0000ff"]],
[1,
[0,[0,10456,12368],[0,10454.3,12364.9],[0,10464.7,12363.1],
[0,10457.7,12371.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8136.3,15474.1],[1,8177,15465,8230.3,15448.4,8269.4,15419],
[1,9553.4,14455,9178.2,13570,10332,12454],
[1,10369,12418,10420,12387,10456,12368]],
0,[0,"#0000ff"]],
[1,
[0,[0,10489,19807.2],[0,10492.2,19805.9],[0,10492.8,19816.4],
[0,10485.8,19808.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8145.1,15478.7],[1,8184.7,15479,8233.7,15485.7,8269.4,15511],
[1,9106.5,16104.6,10364,19466.8,10489,19807.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10413,8159],[0,10412.3,8155.57],[0,10422.8,8157.04],
[0,10413.7,8162.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5540.3,8850],[1,5809,8807,6946.3,8623,7883.4,8501],
[1,8054.6,8479,8098.2,8480,8269.4,8458],
[1,9105.6,8353,10115,8204,10413,8159]],
0,[0,"#0000ff"]],
[1,
[0,[0,8022.4,9774],[0,8023.45,9770.66],[0,8031.94,9777.01],
[0,8021.35,9777.34]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5521.3,8875],[1,5750.3,8959,6921.1,9391,7883.4,9727],
[1,7930.2,9743,7983.6,9761,8022.4,9774]],
0,[0,"#0000ff"]],
[1,
[0,[0,10485,19861.9],[0,10481.8,19860.4],[0,10489.2,19852.8],
[0,10488.2,19863.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8161.4,22272.5],[1,8196.5,22269.6,8236.6,22262.2,8269.4,22245],
[1,9467.9,21618.7,10360,20083.8,10485,19861.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10490,19862.9],[0,10486.8,19861.6],[0,10493.8,19853.7],
[0,10493.2,19864.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8146.8,23486.5],[1,8186.1,23477.2,8234.1,23461,8269.4,23433],
[1,9651,22337.6,10402,20135.3,10490,19862.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10462,23506.9],[0,10462,23503.4],[0,10472,23506.9],
[0,10462,23510.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8167,23498.3],[1,8570.1,23499.8,10193,23505.9,10462,23506.9]],0,
[0,"#0000ff"]],
[1,
[0,[0,10393,9177],[0,10392.7,9173.52],[0,10403,9176],[0,10393.3,9180.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,9283],[1,8334,9272,9959.4,9197,10393,9177]],0,
[0,"#0000ff"]],
[1,[0,[0,10365,9265],[0,10365,9261.5],[0,10375,9265],[0,10365,9268.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,9284],[1,8329.2,9282,9892.4,9269,10365,9265]],0,
[0,"#0000ff"]],
[1,[0,[0,8038.8,9284],[0,8038.8,9280.5],[0,8048.8,9284],[0,8038.8,9287.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5587.6,9284],[1,6035.6,9284,7761.7,9284,8038.8,9284]],0,
[0,"#0000ff"]],
[1,
[0,[0,10368,9259],[0,10368.3,9255.52],[0,10378,9260],[0,10367.7,9262.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8145.4,9179],[1,8478.5,9191,9923.5,9243,10368,9259]],0,
[0,"#0000ff"]],
[1,[0,[0,10390,9172],[0,10390,9168.5],[0,10400,9172],[0,10390,9175.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8146,9176],[1,8486,9175,9972.8,9173,10390,9172]],0,[0,"#0000ff"]],
[1,
[0,[0,10481,15618.5],[0,10478.1,15616.5],[0,10486.8,15610.3],
[0,10483.9,15620.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8147.4,17944.8],[1,8185.5,17934.5,8232.2,17918.5,8269.4,17895],
[1,9381.2,17193.1,10340,15825.5,10481,15618.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10472,19810],[0,10474.3,19807.3],[0,10479.6,19816.5],
[0,10469.7,19812.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8113.5,17977.3],[1,8153.2,17996.4,8217.5,18028.9,8269.4,18063],
[1,9232.8,18695.3,10290,19644.8,10472,19810]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,17039.8],[0,10379.7,17036.3],[0,10390,17039],
[0,10380.3,17043.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3019.9,16561.9],[1,3259.6,16631.1,4361.1,16940.9,5286.4,17061],
[1,6602,17231.8,6943.5,17205.1,8269.4,17165],
[1,9076.7,17140.6,10046,17066.6,10380,17039.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10392,14171],[0,10392.3,14167.5],[0,10402,14172],
[0,10391.7,14174.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2983.5,16530],[1,3096,16348.4,4055.1,14844.1,5286.4,14299],
[1,6244.7,13875,9733.7,14121,10392,14171]],
0,[0,"#0000ff"]],
[1,
[0,[0,10399,15577.7],[0,10399.5,15574.2],[0,10408.9,15579.2],
[0,10398.5,15581.2]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3006.4,16532],[1,3336.7,16378.1,6009.8,15170.7,8269.4,15312],
[1,8695.6,15338.7,10023,15524.4,10399,15577.7]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10421,19851.2],[0,10420.3,19847.8],[0,10430.8,19849.2],
[0,10421.7,19854.6]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,2976.9,16566.1],[1,3035.9,16802.9,3690.7,19297.6,5286.4,20172],
[1,5431.8,20251.6,8104.2,20184.4,8269.4,20172],
[1,9118.8,20108.2,10135,19909.5,10421,19851.2]],
0,[0,"#ee82ee"]],
[1,
[0,[0,5327.5,16548],[0,5327.5,16544.5],[0,5337.5,16548],
[0,5327.5,16551.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3046.5,16548],[1,3391.9,16548,4847.9,16548,5327.5,16548]],0,
[0,"#0000ff"]],
[1,
[0,[0,5361.8,16759.4],[0,5362.11,16755.9],[0,5371.76,16760.3],
[0,5361.49,16762.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3042.2,16554.2],[1,3388,16584.8,4920,16720.3,5361.8,16759.4]],0,
[0,"#0000ff"]],
[1,[0,[0,10428,12012],[0,10428,12008.5],[0,10438,12012],[0,10428,12015.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,2978.3,16529.8],[1,3052.8,16301.1,3836.4,13977,5286.4,12827],
[1,6369.4,11968,6887.4,11927,8269.4,11948],
[1,9119.2,11961,10151,12001,10428,12012]],
0,[0,"#0000ff"]],
[1,
[0,[0,10389,15604.3],[0,10388.6,15600.8],[0,10398.9,15603.2],
[0,10389.4,15607.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8180.9,15850.4],[1,8576.8,15806.2,9982.7,15649.6,10389,15604.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10391,14189],[0,10390.3,14185.6],[0,10400.8,14187],
[0,10391.7,14192.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8201.1,15854.4],[1,8224.4,15850.3,8248.1,15844.1,8269.4,15835],
[1,9343.6,15376.4,9263.2,14677,10332,14207],
[1,10351,14199,10371,14193,10391,14189]],
0,[0,"#0000ff"]],
[1,
[0,[0,10494,19807],[0,10497.4,19806.3],[0,10496,19816.8],
[0,10490.6,19807.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8211.8,15864.9],[1,8232.3,15869.7,8252.3,15877.3,8269.4,15889],
[1,9837.2,16956.3,10430,19511.6,10494,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19807],[0,10494.3,19806],[0,10493.9,19816.6],
[0,10487.7,19808]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8206.8,16443],[1,8228.9,16447.6,8250.7,16455.2,8269.4,16467],
[1,9692,17363.8,10406,19535.7,10491,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,12704,15272.7],[0,12704,15269.2],[0,12714,15272.6],
[0,12704,15276.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8189.3,16430.6],[1,8216,16426.6,8244,16421,8269.4,16413],
[1,9250.5,16104.7,9336.9,15623.1,10332,15365],
[1,10562,15305.5,12212,15279.3,12704,15272.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10376,17021.4],[0,10376.2,17017.9],[0,10386,17022.1],
[0,10375.8,17024.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5546.9,16448.6],[1,5584.8,16453.7,5633.4,16460.4,5676.4,16467],
[1,6659.5,16617,6896.1,16716.1,7883.4,16835],
[1,8132.5,16865,9890.2,16987.8,10376,17021.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,12740,15257],[0,12740.4,15253.5],[0,12749.9,15258.3],
[0,12739.6,15260.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5500.8,16422.6],[1,5660.2,16281.2,6774.9,15317.4,7883.4,15013],
[1,8845.2,14749,12119,15173,12740,15257]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7942.1,16542.4],[0,7942.24,16538.9],[0,7952.09,16542.8],
[0,7941.96,16545.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5554.6,16443],[1,5911.5,16457.9,7472.2,16522.9,7942.1,16542.4]],0,
[0,"#0000ff"]],
[1,
[0,[0,10422,19818.8],[0,10422.7,19815.4],[0,10431.8,19820.8],
[0,10421.3,19822.2]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5554.8,16437.1],[1,5593.3,16438.6,5640,16445.7,5676.4,16467],
[1,7076.4,17286.4,6476.7,18566.2,7883.4,19374],
[1,8033.3,19460.1,8098.6,19394.8,8269.4,19421],
[1,9117.1,19551.2,10136,19759.5,10422,19818.8]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10393,14063],[0,10393.3,14059.5],[0,10403,14063.9],
[0,10392.7,14066.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5499.7,16422.3],[1,5534.3,16388.8,5611.5,16314.1,5676.4,16251],
[1,6658.2,15297.7,6618.7,14627,7883.4,14104],
[1,8347.7,13912,9962.8,14028,10393,14063]],
0,[0,"#0000ff"]],
[1,
[0,[0,7924.3,16490.8],[0,7924.4,16487.3],[0,7934.3,16491.1],
[0,7924.2,16494.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5555.3,16441.5],[1,5909.1,16448.9,7434.5,16480.6,7924.3,16490.8]],
0,[0,"#0000ff"]],
[1,[0,[0,10428,12013],[0,10428,12009.5],[0,10438,12013],[0,10428,12016.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5503.6,16422.6],[1,5542.3,16391.4,5623.2,16322.4,5676.4,16251],
[1,6945.9,14548,6067.2,13113,7883.4,12011],
[1,7995.1,11943,10019,12001,10428,12013]],
0,[0,"#0000ff"]],
[1,
[0,[0,10493,19806.7],[0,10496.4,19806],[0,10494.9,19816.5],
[0,10489.6,19807.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8110.2,14759],[1,8152.4,14782.7,8224.3,14827.4,8269.4,14883],
[1,9704.6,16652.4,10417,19493.4,10493,19806.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10406,14085],[0,10405.3,14081.6],[0,10415.8,14083],
[0,10406.7,14088.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8180.9,14730],[1,8209.7,14726,8240.9,14721,8269.4,14715],
[1,9204.4,14511,9399.7,14313,10332,14099],
[1,10356,14094,10382,14089,10406,14085]],
0,[0,"#0000ff"]],
[1,
[0,[0,12744,15256.4],[0,12744.5,15252.9],[0,12753.9,15257.9],
[0,12743.5,15259.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8194.7,14751],[1,8561.9,14780,9714.6,14872.7,10666,14980],
[1,11470,15070.7,12437,15211.1,12744,15256.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,12705,15346.2],[0,12704.9,15342.7],[0,12715,15346],
[0,12705.1,15349.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8204.1,17863.3],[1,8226.8,17858.8,8249.5,17851.8,8269.4,17841],
[1,9500.3,17171.4,9071.6,16068.3,10332,15457],
[1,10440,15405,12196,15358.6,12705,15346.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10477,19809.5],[0,10479.6,19807.1],[0,10483.8,19816.8],
[0,10474.4,19811.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8142.9,17883.6],[1,8181.4,17894.3,8229.9,17910.6,8269.4,17933],
[1,9307.7,18521.3,10315,19627.9,10477,19809.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10366,17026.2],[0,10366.1,17022.7],[0,10376,17026.5],
[0,10365.9,17029.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5546.5,16502.7],[1,5584.4,16507.9,5633.2,16514.6,5676.4,16521],
[1,6658.7,16666.2,6896.4,16760.1,7883.4,16868],
[1,8831.2,16971.6,9979.8,17014.1,10366,17026.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,12708,15338.2],[0,12708.1,15334.7],[0,12718,15338.6],
[0,12707.9,15341.7]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5553.6,16490],[1,5590.9,16486.4,5636.9,16479.7,5676.4,16467],
[1,6730.8,16129.4,6808.3,15576.3,7883.4,15312],
[1,8362.7,15194.2,11962,15312.3,12708,15338.2]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7937.8,16545.1],[0,7937.87,16541.6],[0,7947.8,16545.3],
[0,7937.73,16548.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5555.3,16495.5],[1,5912.4,16503,7463,16535.2,7937.8,16545.1]],0,
[0,"#0000ff"]],
[1,
[0,[0,10416,19819.6],[0,10416.6,19816.2],[0,10425.8,19821.4],
[0,10415.4,19823]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5554.8,16491.1],[1,5593.3,16492.7,5640,16499.7,5676.4,16521],
[1,7072.6,17335.7,6480.6,18608.8,7883.4,19412],
[1,8033.4,19497.9,8098.4,19434.2,8269.4,19459],
[1,9110.4,19581,10123,19765.5,10416,19819.6]],
0,[0,"#ee82ee"]],
[1,[0,[0,10382,14124],[0,10382,14120.5],[0,10392,14124],[0,10382,14127.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5555.3,16495.2],[1,5593.3,16493.1,5639.3,16486.1,5676.4,16467],
[1,6944.9,15814.6,6574.3,14703,7883.4,14137],
[1,7999.3,14087,9888.5,14116,10382,14124]],
0,[0,"#0000ff"]],
[1,
[0,[0,7922.7,16494],[0,7922.7,16490.5],[0,7932.7,16494],
[0,7922.7,16497.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5555.6,16494],[1,5909.7,16494,7431.1,16494,7922.7,16494]],0,
[0,"#0000ff"]],
[1,[0,[0,10428,12016],[0,10428,12012.5],[0,10438,12016],[0,10428,12019.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5552.2,16499.6],[1,5592.1,16499.2,5640.8,16492.4,5676.4,16467],
[1,7445.3,15204,6051.3,13272,7883.4,12103],
[1,7938.6,12068,10013,12025,10428,12016]],
0,[0,"#0000ff"]],
[1,
[0,[0,12710,15337.1],[0,12710.1,15333.6],[0,12720,15337.5],
[0,12709.9,15340.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8211.6,15189],[1,8595.8,15197.8,9727.1,15224.5,10666,15256],
[1,11441,15281.9,12370,15322.1,12710,15337.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10399,14138],[0,10398.3,14134.6],[0,10408.8,14136],
[0,10399.7,14141.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8131.1,15169.4],[1,8170.1,15157.2,8223.5,15139.4,8269.4,15121],
[1,9209.3,14744,9364.7,14452,10332,14153],
[1,10354,14146,10377,14141,10399,14138]],
0,[0,"#0000ff"]],
[1,
[0,[0,10490,19807.2],[0,10493.3,19806.2],[0,10493,19816.8],
[0,10486.7,19808.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8100.7,15203.8],[1,8140.1,15233.6,8218.6,15297.2,8269.4,15365],
[1,9521.3,17036.3,10391,19517.9,10490,19807.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,10398,15577.8],[0,10398.5,15574.3],[0,10407.9,15579.2],
[0,10397.5,15581.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5601.8,16538.2],[1,5626.8,16534.2,5652.8,16528.7,5676.4,16521],
[1,6735.5,16174.9,6803.1,15604.5,7883.4,15332],
[1,8131.2,15269.5,9946.9,15515.3,10398,15577.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,10412,19820.6],[0,10412.6,19817.1],[0,10421.9,19822.2],
[0,10411.4,19824.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5618.9,16553.3],[1,5639.1,16557.9,5658.9,16564.8,5676.4,16575],
[1,7068.9,17384.9,6483.4,18653.3,7883.4,19450],
[1,7958.5,19492.7,8183.8,19484.4,8269.4,19496],
[1,9104.9,19609.3,10112,19771.8,10412,19820.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,12712,15277.8],[0,12711.8,15274.3],[0,12722,15277.2],
[0,12712.2,15281.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10527,15390.6],[1,10747,15379.2,12255,15301.3,12712,15277.8]],0,
[0,"#0000ff"]],
[1,
[0,[0,12705,15345.9],[0,12704.9,15342.4],[0,12715,15345.7],
[0,12705.1,15349.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10527,15391.4],[1,10746,15386.8,12241,15355.6,12705,15345.9]],0,
[0,"#0000ff"]],
[1,
[0,[0,10462,15396.1],[0,10461.6,15392.6],[0,10471.9,15394.9],
[0,10462.4,15399.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8194.7,16483.7],[1,8219.7,16479.8,8245.7,16474.4,8269.4,16467],
[1,9249.9,16159.9,9360,15755.7,10332,15424],
[1,10376,15409.2,10428,15400.6,10462,15396.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10491,19807],[0,10494.3,19806],[0,10493.9,19816.6],
[0,10487.7,19808]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8214.8,16498.9],[1,8234.1,16503.6,8252.9,16510.7,8269.4,16521],
[1,9678.7,17402.1,10404,19538.2,10491,19807]],
0,[0,"#0000ff"]],
[1,
[0,[0,10378,15582],[0,10378.3,15578.5],[0,10388,15582.8],
[0,10377.7,15585.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8103.6,15394.2],[1,8331.4,15413,9923,15544.4,10378,15582]],0,
[0,"#0000ff"]],
[1,
[0,[0,12705,15274.2],[0,12704.9,15270.7],[0,12715,15274],
[0,12705.1,15277.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8103.5,15391.3],[1,8291.2,15386.1,9416.4,15355.3,10332,15332],
[1,11238,15309,12327,15283.1,12705,15274.2]],
0,[0,"#0000ff"]],
[1,
[0,[0,8039.4,15397.5],[0,8038.78,15394.1],[0,8049.24,15395.7],
[0,8040.02,15400.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5605.4,18564.1],[1,5630.2,18559.6,5655.1,18551.9,5676.4,18539],
[1,7118.5,17667.8,6529.2,16459.2,7883.4,15457],
[1,7930.7,15422,7998.1,15405,8039.4,15397.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10382,19831],[0,10382.1,19827.5],[0,10392,19831.4],
[0,10381.9,19834.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5590.9,18574.7],[1,5619.2,18578.6,5649.3,18584.5,5676.4,18593],
[1,6726.5,18922.6,6819.3,19435.1,7883.4,19716],
[1,8005.6,19748.2,9888,19814.2,10382,19831]],
0,[0,"#0000ff"]],
[1,
[0,[0,10394,15578.7],[0,10394.4,15575.2],[0,10403.9,15579.9],
[0,10393.6,15582.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5594.7,16593.4],[1,5621.9,16589.4,5650.6,16583.6,5676.4,16575],
[1,6738.4,16223.6,6799.8,15642.6,7883.4,15365],
[1,8129.9,15301.9,9935.6,15521.4,10394,15578.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10406,19821.8],[0,10406.5,19818.3],[0,10415.9,19823.2],
[0,10405.5,19825.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5510.7,16619.7],[1,5550.5,16644.4,5623,16692.2,5676.4,16743],
[1,6811.3,17821.3,6513.3,18730.9,7883.4,19488],
[1,7959,19529.8,8183.7,19522.2,8269.4,19533],
[1,9099.2,19637.5,10101,19778.4,10406,19821.8]],
0,[0,"#0000ff"]],
[1,[0,[0,10483,19808.3],[0,10486,19806.6],[0,10488,19817],[0,10480,19810]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8098.3,16619.8],[1,8135.4,16650.7,8212.5,16717,8269.4,16781],
[1,9306.5,17947.2,10340,19580.8,10483,19808.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10462,15395.7],[0,10461.6,15392.2],[0,10471.9,15394.5],
[0,10462.4,15399.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8189.3,16593.3],[1,8216,16589.3,8244.1,16583.5,8269.4,16575],
[1,9264.8,16240.8,9345.8,15783.1,10332,15424],
[1,10376,15408.3,10428,15399.9,10462,15395.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10401,19822.9],[0,10401.4,19819.4],[0,10410.9,19824.1],
[0,10400.6,19826.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5496.5,16788.1],[1,5691.5,17021.4,7712.1,19436.5,7883.4,19526],
[1,7959.9,19565.9,8183.7,19558.2,8269.4,19568],
[1,9094.4,19662.3,10090,19784.5,10401,19822.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,15581.7],[0,10380.3,15578.2],[0,10390,15582.5],
[0,10379.7,15585.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5509,16752.4],[1,5738.7,16606.2,7336.9,15596.6,7883.4,15457],
[1,8126.9,15394.8,9900.4,15540.7,10380,15581.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10462,15395.9],[0,10461.6,15392.4],[0,10471.9,15394.7],
[0,10462.4,15399.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8188.9,16539],[1,8215.7,16535,8243.9,16529.3,8269.4,16521],
[1,9257.2,16200.4,9353.1,15769.4,10332,15424],
[1,10376,15408.8,10428,15400.3,10462,15395.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10490,19807.1],[0,10493.3,19806.1],[0,10493,19816.7],
[0,10486.7,19808.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8204.4,16550.7],[1,8227.3,16555.3,8249.9,16562.9,8269.4,16575],
[1,9665.6,17440.5,10401,19540.7,10490,19807.1]],
0,[0,"#0000ff"]],
[1,
[0,[0,10484,19862],[0,10480.9,19860.3],[0,10488.9,19853.3],
[0,10487.1,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8146.9,22217.1],[1,8185,22214,8231.9,22205.9,8269.4,22186],
[1,9446.3,21561.2,10354,20080.1,10484,19862]],
0,[0,"#0000ff"]],
[1,
[0,[0,10492,19862.7],[0,10488.7,19861.7],[0,10495,19853.1],
[0,10495.3,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8138.4,23410.2],[1,8178.7,23410,8230.8,23404,8269.4,23379],
[1,9736.2,22430.4,10414,20140.3,10492,19862.7]],
0,[0,"#0000ff"]],
[1,[0,[0,10421,23406],[0,10421,23402.5],[0,10431,23406],[0,10421,23409.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8140,23406],[1,8476.8,23406,10051,23406,10421,23406]],0,
[0,"#0000ff"]],
[1,[0,[0,12771,3774],[0,12771,3770.5],[0,12781,3774],[0,12771,3777.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10569,3673],[1,10912,3689,12425,3758,12771,3774]],0,[0,"#0000ff"]],
[1,[0,[0,15070,7676],[0,15070,7672.5],[0,15080,7676],[0,15070,7679.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12882,7676],[1,13158,7676,14801,7676,15070,7676]],0,[0,"#0000ff"]],
[1,[0,[0,12761,2750],[0,12761,2746.5],[0,12771,2750],[0,12761,2753.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10547,2699],[1,10839,2706,12387,2742,12761,2750]],0,[0,"#0000ff"]],
[1,[0,[0,10436,7431],[0,10436,7427.5],[0,10446,7431],[0,10436,7434.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8134.4,5391],[1,8174.3,5392,8227.3,5399,8269.4,5419],
[1,9413.9,5976,9193.9,6836,10332,7405],
[1,10364,7421,10404,7428,10436,7431]],
0,[0,"#0000ff"]],
[1,
[0,[0,10431,3858],[0,10430.7,3854.51],[0,10441,3857.09],
[0,10431.3,3861.49]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8134.4,5391],[1,8173.8,5389,8226.2,5382,8269.4,5365],
[1,9317.8,4945,9288.6,4312,10332,3881],
[1,10364,3868,10400,3861,10431,3858]],
0,[0,"#0000ff"]],
[1,
[0,[0,10401,11246],[0,10401.3,11242.5],[0,10411,11247],
[0,10400.7,11249.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8148.9,10938],[1,8497.6,10986,10001.3,11191,10401,11246]],0,
[0,"#0000ff"]],
[1,
[0,[0,10368,16536.6],[0,10369.2,16533.3],[0,10377.4,16540],
[0,10366.8,16539.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8157.1,10921],[1,8194.9,10922,8238.3,10930,8269.4,10955],
[1,10324,12607,8295.6,14842.9,10332,16517],
[1,10343,16525.5,10355,16531.9,10368,16536.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10407,10633],[0,10406.3,10629.6],[0,10416.8,10631],
[0,10407.7,10636.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8150.6,10919],[1,8504,10874,10016,10682,10407,10633]],0,
[0,"#0000ff"]],
[1,
[0,[0,10380,18041.6],[0,10380.8,18038.2],[0,10389.7,18043.9],
[0,10379.2,18045]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8155,10920],[1,8193.6,10921,8238.5,10928,8269.4,10955],
[1,10743,13093,7881.6,15852.5,10332,18017],
[1,10346,18028.9,10362,18036.6,10380,18041.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10392,8151],[0,10391.3,8147.57],[0,10401.8,8149.04],
[0,10392.7,8154.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8141.7,10916],[1,8181.3,10907,8231.5,10890,8269.4,10863],
[1,9495.1,9987,9038.9,8946,10332,8173],
[1,10350,8162,10371,8155,10392,8151]],
0,[0,"#0000ff"]],
[1,[0,[0,10374,11255],[0,10374,11251.5],[0,10384,11255],[0,10374,11258.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8162,11185],[1,8525.3,11196,9941.7,11241,10374,11255]],0,
[0,"#0000ff"]],
[1,
[0,[0,10368,16536.4],[0,10369.1,16533.1],[0,10377.5,16539.4],
[0,10366.9,16539.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8157.4,11175],[1,8195,11177,8238.3,11184,8269.4,11209],
[1,10254,12780,8364.7,14925.1,10332,16517],
[1,10343,16525.5,10355,16531.8,10368,16536.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,12744,10631],[0,12743.7,10627.5],[0,12754,10630.1],
[0,12744.3,10634.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8148.4,11172],[1,8428.3,11133,9471.4,10988,10332,10886],
[1,10814,10829,12342,10672,12744,10631]],
0,[0,"#0000ff"]],
[1,
[0,[0,10380,18041.4],[0,10380.8,18038],[0,10389.7,18043.8],
[0,10379.2,18044.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8154.9,11174],[1,8193.5,11175,8238.3,11182,8269.4,11209],
[1,10672,13265,7952.2,15936,10332,18017],
[1,10346,18028.8,10363,18036.5,10380,18041.4]],
0,[0,"#0000ff"]],
[1,
[0,[0,10391,8151],[0,10390.3,8147.57],[0,10400.8,8149.04],
[0,10391.7,8154.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8162.2,11185],[1,8197.7,11182,8237.7,11175,8269.4,11155],
[1,9641.4,10310,8969.5,9033,10332,8173],
[1,10350,8162,10370,8155,10391,8151]],
0,[0,"#0000ff"]],
[1,[0,[0,7968.7,3181],[0,7968.7,3177.5],[0,7978.7,3181],[0,7968.7,3184.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3054.7,3196],[1,3649.8,3194,7293.2,3183,7968.7,3181]],0,
[0,"#0000ff"]],
[1,
[0,[0,7968.7,3183],[0,7968.36,3179.52],[0,7978.65,3182.02],
[0,7969.04,3186.48]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5563,3218],[1,5942.9,3212,7537.7,3189,7968.7,3183]],0,
[0,"#0000ff"]],
[1,
[0,[0,10394,8153],[0,10393.3,8149.57],[0,10403.8,8151.04],
[0,10394.7,8156.43]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8144.6,10313],[1,8183.2,10303,8231.2,10287,8269.4,10263],
[1,9376.4,9571,9172.4,8771,10332,8173],
[1,10351,8163,10373,8157,10394,8153]],
0,[0,"#0000ff"]],
[1,
[0,[0,10367,16536.9],[0,10368.1,16533.6],[0,10376.5,16540],
[0,10365.9,16540.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8163.9,10340],[1,8200.6,10349,8241.3,10365,8269.4,10393],
[1,10300,12424,8141.5,14660,10332,16517],
[1,10343,16525.7,10355,16532.2,10367,16536.9]],
0,[0,"#0000ff"]],
[1,[0,[0,5437.2,1514],[0,5437.2,1510.5],[0,5447.2,1514],[0,5437.2,1517.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,880.5,1491],[1,1347.1,1494,4993.4,1512,5437.2,1514]],0,
[0,"#0000ff"]],
[1,[0,[0,5437,1513],[0,5437,1509.5],[0,5447,1513],[0,5437,1516.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,2999.8,1469],[1,3248.8,1473,5123.3,1507,5437,1513]],0,
[0,"#0000ff"]],
[1,
[0,[0,10484,19862],[0,10480.9,19860.3],[0,10488.9,19853.3],
[0,10487.1,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5532.6,22070.3],[1,5900.9,22079.3,8138.2,22131.6,8269.4,22077],
[1,9470.7,21577.5,10359,20081.6,10484,19862]],
0,[0,"#0000ff"]],
[1,
[0,[0,10482,19861.7],[0,10479.1,19859.7],[0,10487.8,19853.5],
[0,10484.9,19863.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8136.7,22049.3],[1,8176.3,22046.6,8228.2,22038.9,8269.4,22018],
[1,9410.8,21438.9,10345,20069.6,10482,19861.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10474,19859.9],[0,10471.5,19857.4],[0,10481,19852.8],
[0,10476.5,19862.4]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5544.5,21251.5],[1,5933.6,21266.8,8000.3,21343.9,8269.4,21265],
[1,9298.5,20963.4,10303,20024.9,10474,19859.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,10470,19859.3],[0,10467.8,19856.6],[0,10477.8,19853],
[0,10472.2,19862]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8130.3,21234.7],[1,8169.8,21230.9,8224.3,21222.9,8269.4,21206],
[1,9256.8,20836.9,10286,20011.2,10470,19859.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,8004.3,17230],[0,8004.3,17226.5],[0,8014.3,17230],
[0,8004.3,17233.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5508.8,17230],[1,5756.7,17230,7613.2,17230,8004.3,17230]],0,
[0,"#ee82ee"]],
[1,
[0,[0,7986.4,17282.1],[0,7986.47,17278.6],[0,7996.4,17282.3],
[0,7986.33,17285.6]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,5508.8,17230.6],[1,5753.2,17235.7,7560,17273.3,7986.4,17282.1]],0,
[0,"#ee82ee"]],
[1,
[0,[0,10388,16755.7],[0,10388.2,16752.2],[0,10398,16756.3],
[0,10387.8,16759.2]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5508.5,17223],[1,5701.6,17173.8,6893.2,16876.4,7883.4,16781],
[1,8849.2,16688,10025,16737,10388,16755.7]],
0,[0,"#ee82ee"]],
[1,[0,[0,5444,17230],[0,5444,17226.5],[0,5454,17230],[0,5444,17233.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,[0,[0,3008.9,17230],[1,3293.4,17230,5156,17230,5444,17230]],0,
[0,"#ee82ee"]],
[1,
[0,[0,8004.3,17231.5],[0,8004.23,17228],[0,8014.3,17231.3],
[0,8004.37,17235]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5508.8,17283.4],[1,5756.7,17278.3,7613.2,17239.6,8004.3,17231.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,7986.1,17284],[0,7986.1,17280.5],[0,7996.1,17284],
[0,7986.1,17287.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5508.8,17284],[1,5753.1,17284,7559,17284,7986.1,17284]],0,
[0,"#0000ff"]],
[1,
[0,[0,8030.3,17337],[0,8030.37,17333.5],[0,8040.3,17337.2],
[0,8030.23,17340.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5508.8,17284.6],[1,5762.8,17289.9,7705.2,17330.3,8030.3,17337]],0,
[0,"#0000ff"]],
[1,
[0,[0,5444,17283.2],[0,5444.07,17279.7],[0,5454,17283.4],
[0,5443.93,17286.7]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3008.9,17230.8],[1,3293.4,17236.9,5156,17277,5444,17283.2]],0,
[0,"#0000ff"]],
[1,
[0,[0,10454,18065.3],[0,10452.5,18062.1],[0,10463,18061],
[0,10455.5,18068.5]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5503.4,20262.5],[1,5673.4,20127.5,6804.1,19249.9,7883.4,18896],
[1,8047.5,18842.2,8101.3,18892.3,8269.4,18853],
[1,9177.8,18640.8,10224,18170.8,10454,18065.3]],
0,[0,"#ee82ee"]],
[1,
[0,[0,7962.4,18837.7],[0,7961.81,18834.2],[0,7972.26,18836],
[0,7962.99,18841.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5503.4,20262.5],[1,5674.2,20127.7,6808.9,19249.5,7883.4,18858],
[1,7908.3,18848.9,7936,18842.4,7962.4,18837.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,5381.8,20283.8],[0,5381.66,20280.3],[0,5391.79,20283.4],
[0,5381.94,20287.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,3072.3,20372.2],[1,3475.3,20356.8,4979.2,20299.2,5381.8,20283.8]],
0,[0,"#0000ff"]],
[1,
[0,[0,8011.9,18845.4],[0,8010.83,18842.1],[0,8021.42,18842.4],
[0,8012.97,18848.7]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3074.5,20376.6],[1,3537,20379.1,5424.6,20384.1,5676.4,20307],
[1,6789.6,19966.1,6839.4,19411.2,7883.4,18896],
[1,7924.8,18875.6,7973.7,18857.9,8011.9,18845.4]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10456,18065.8],[0,10454.4,18062.7],[0,10464.9,18061.3],
[0,10457.6,18068.9]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3074.6,20376.5],[1,3552.6,20378.8,5549.8,20385.9,5676.4,20348],
[1,6793.2,20014.1,6780.9,19309.4,7883.4,18931],
[1,8046.4,18875.1,8101.6,18934.9,8269.4,18896],
[1,9186.9,18683.4,10233,18176.9,10456,18065.8]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10457,19856.9],[0,10455.4,19853.8],[0,10465.9,19852.3],
[0,10458.6,19860]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3050.6,20387.6],[1,3343.6,20430.7,4405.3,20580.8,5286.4,20633],
[1,5948.2,20672.2,7616.7,20768.9,8269.4,20653],
[1,9193.6,20488.9,10237,19970,10457,19856.9]],
0,[0,"#0000ff"]],
[1,[0,[0,2873.5,1667],[0,2873.5,1663.5],[0,2883.5,1667],[0,2873.5,1670.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,936.87,1642],[1,1303.2,1647,2517.4,1662,2873.5,1667]],0,
[0,"#0000ff"]],
[1,[0,[0,7924.2,2156],[0,7924.2,2152.5],[0,7934.2,2156],[0,7924.2,2159.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5551.2,2156],[1,5897.2,2156,7432.3,2156,7924.2,2156]],0,
[0,"#0000ff"]],
[1,
[0,[0,12805,2282],[0,12805.3,2278.52],[0,12815,2283],[0,12804.7,2285.48]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5550.2,2153],[1,6000.2,2136,8572.9,2045,10666,2129],
[1,11535,2164,12594,2262,12805,2282]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10442,19815.5],[0,10443.1,19812.2],[0,10451.5,19818.6],
[0,10440.9,19818.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5549,2161],[1,5592.1,2167,5645.4,2183,5676.4,2221],
[1,10483,8049,2743.2,13539,7883.4,19075],
[1,8002.6,19203.4,8099.7,19111.6,8269.4,19155],
[1,9145,19378.7,10190,19729.4,10442,19815.5]],
0,[0,"#0000ff"]],
[1,
[0,[0,10478,19861],[0,10475.4,19858.7],[0,10484.6,19853.5],
[0,10480.6,19863.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8173.6,21714],[1,8205.2,21709.4,8239.8,21701.6,8269.4,21688],
[1,9344.2,21196.6,10323,20048.1,10478,19861]],
0,[0,"#0000ff"]],
[1,
[0,[0,10471,16568.6],[0,10468.8,16565.9],[0,10478.7,16562.2],
[0,10473.2,16571.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,8112.3,18349.1],[1,8151.8,18330,8216.8,18297,8269.4,18263],
[1,9225.3,17645.6,10287,16729.6,10471,16568.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,10404,18056.7],[0,10403.5,18053.2],[0,10413.9,18055.3],
[0,10404.5,18060.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8156.4,18355.4],[1,8519.2,18307.2,10011,18108.9,10404,18056.7]],0,
[0,"#0000ff"]],
[1,
[0,[0,10462,19812.2],[0,10463.8,19809.2],[0,10470.6,19817.3],
[0,10460.2,19815.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8104.9,18383.3],[1,8355.1,18534.9,10176,19639,10462,19812.2]],0,
[0,"#0000ff"]],
[1,
[0,[0,10483,19861.8],[0,10480,19860],[0,10488,19853.2],[0,10486,19863.6]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,3044.8,21727.1],[1,3329.8,21750.7,4402,21837.2,5286.4,21879],
[1,5617.6,21894.6,7961.4,22069.7,8269.4,21947],
[1,9440.9,21480.3,10351,20073.6,10483,19861.8]],
0,[0,"#ee82ee"]],
[1,
[0,[0,10398,17404.6],[0,10398.1,17401.1],[0,10408,17404.8],
[0,10397.9,17408.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3012.2,21705.6],[1,3051.6,21688.7,3111.5,21658.4,3151.4,21617],
[1,4553.2,20161.6,3595.6,18709.4,5286.4,17603],
[1,5729.2,17313.3,9707.9,17389.2,10398,17404.6]],
0,[0,"#0000ff"]],
[1,
[0,[0,7981.4,21537.7],[0,7981.33,21534.2],[0,7991.4,21537.5],
[0,7981.47,21541.2]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,3046.8,21716.8],[1,3334.9,21700.7,4404.7,21641.9,5286.4,21609],
[1,6343.4,21569.6,7626.3,21544.3,7981.4,21537.7]],
0,[0,"#0000ff"]],
[1,
[0,[0,10397,17408],[0,10397,17404.5],[0,10407,17407.9],[0,10397,17411.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8128.2,17429.5],[1,8431.7,17426.6,9982.1,17411.9,10397,17408]],0,
[0,"#0000ff"]],
[1,
[0,[0,7981.6,21534.3],[0,7981.67,21530.8],[0,7991.6,21534.5],
[0,7981.53,21537.8]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5632.6,21492.7],[1,6112.4,21501.2,7591.9,21527.4,7981.6,21534.3]],
0,[0,"#0000ff"]],
[1,
[0,[0,10477,19860.9],[0,10474.4,19858.5],[0,10483.7,19853.5],
[0,10479.6,19863.3]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5630.5,21494],[1,6172.3,21508,8018.9,21549,8269.4,21466],
[1,9335.5,21112.7,10317,20041.2,10477,19860.9]],
0,[0,"#ee82ee"]],
[1,
[0,[0,12710,18004.7],[0,12709.3,18001.3],[0,12719.8,18002.7],
[0,12710.7,18008.1]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5540.5,21473.3],[1,5579.7,21461.5,5632,21444.4,5676.4,21425],
[1,6701.6,20977.4,6873.8,20696.7,7883.4,20215],
[1,9089.8,19639.5,9456,19642,10666,19075],
[1,11576,18649.1,11709,18331.1,12662,18017],
[1,12677,18012,12694,18008,12710,18004.7]],
0,[0,"#0000ff"]],
[1,[0,[0,12659,17990],[0,12659,17986.5],[0,12669,17990],[0,12659,17993.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,10654,17990],[1,11069,17990,12212,17990,12659,17990]],0,
[0,"#0000ff"]],
[1,
[0,[0,7989.5,21544.8],[0,7989.15,21541.3],[0,7999.45,21543.8],
[0,7989.85,21548.3]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,5557.7,21790.3],[1,5933.9,21752.3,7590,21585.1,7989.5,21544.8]],0,
[0,"#0000ff"]],
[1,
[0,[0,10481,19861.3],[0,10478.2,19859.3],[0,10486.8,19853.2],
[0,10483.8,19863.3]],
[0,"#ee82ee"],[0,"#ee82ee"]],
[0,
[0,[0,5565.4,21798.1],[1,6017,21798.2,8140.1,21796.2,8269.4,21747],
[1,9392.5,21319.7,10337,20059.2,10481,19861.3]],
0,[0,"#ee82ee"]],
[1,
[0,[0,15101,18017.9],[0,15097.6,18017.2],[0,15103,18008.1],
[0,15104.4,18018.6]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,
[0,[0,5564.9,21800.6],[1,5600.3,21803.9,5641.4,21810.9,5676.4,21825],
[1,6801.8,22279.2,6729.5,23057.2,7883.4,23433],
[1,7951.3,23455.1,12964,23473.4,13022,23433],
[1,14042,22732.1,15016,18406.4,15101,18017.9]],
0,[0,"#0000ff"]],
[1,
[0,[0,15039,17972.5],[0,15039.9,17969.1],[0,15048.7,17975],
[0,15038.1,17975.9]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,12896,17420.9],[1,13201,17499.3,14701,17885.4,15039,17972.5]],0,
[0,"#0000ff"]],
[1,[0,[0,10371,11258],[0,10371,11254.5],[0,10381,11258],[0,10371,11261.5]],
[0,"#0000ff"],[0,"#0000ff"]],
[0,[0,[0,8163,11237],[1,8527.4,11240,9936.9,11254,10371,11258]],0,
[0,"#0000ff"]]]]
coinst-1.9.3/viewer/viewer_common.mli 0000644 0001750 0001750 00000005440 12657630652 016655 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
module F (M : sig
type color
type font
type text
val white : color
type ctx
val save : ctx -> unit
val restore : ctx -> unit
val scale : ctx -> sx:float -> sy:float -> unit
val translate : ctx -> tx:float -> ty:float -> unit
val set_line_width : ctx -> float -> unit
val begin_path : ctx -> unit
val close_path : ctx -> unit
val move_to : ctx -> x:float -> y:float -> unit
val line_to : ctx -> x:float -> y:float -> unit
val curve_to :
ctx ->
x1:float -> y1:float -> x2:float -> y2:float -> x3:float -> y3:float ->
unit
val arc :
ctx ->
xc:float -> yc:float -> radius:float -> angle1:float -> angle2:float ->
unit
val rectangle :
ctx -> x:float -> y:float -> width:float -> height:float -> unit
val fill : ctx -> color -> unit
val stroke : ctx -> color -> unit
val clip : ctx -> unit
val draw_text :
ctx -> float -> float -> text ->
font -> color option -> color option -> unit
type window
type drawable
type pixmap
val get_drawable : window -> drawable
val make_pixmap : window -> int -> int -> pixmap
val drawable_of_pixmap : pixmap -> drawable
val get_context : pixmap -> ctx
val put_pixmap :
dst:drawable ->
x:int -> y:int -> xsrc:int -> ysrc:int -> width:int -> height:int ->
pixmap -> unit
(****)
type rectangle = {x : int; y : int; width : int; height: int}
val compute_extents :
ctx ->
(color, font, text) Scene.element array ->
(float * float * float * float) array
end) : sig
type pixmap
val make_pixmap : unit -> pixmap
val invalidate_pixmap : pixmap -> unit
type st =
{ mutable bboxes : (float * float * float * float) array;
scene : (M.color, M.font, M.text) Scene.element array;
mutable zoom_factor : float;
st_x : float; st_y : float; st_width : float; st_height : float;
st_pixmap : pixmap }
val redraw :
st -> float -> float -> float ->
M.window -> M.rectangle -> int -> int -> int -> int -> unit
end
coinst-1.9.3/viewer/Makefile 0000644 0001750 0001750 00000003543 12657630652 014743 0 ustar mehdi mehdi
OCAMLC=ocamlfind ocamlc
OCAMLOPT=ocamlfind ocamlopt
OCAMLDEP=ocamlfind ocamldep
OCAMLYACC=ocamlyacc
OCAMLLEX=ocamllex
COMPFLAGS=-package str,cairo.lablgtk2,js_of_ocaml,js_of_ocaml.syntax -syntax camlp4o
DEPFLAGS=$(COMPFLAGS)
GENERATED=dot_parser.ml dot_lexer.ml
OBJS=scene.cmx scene_extents.cmx viewer_common.cmx viewer.cmx \
dot_file.cmx dot_parser.cmx dot_lexer.cmx dot_graph.cmx dot_render.cmx \
main.cmx
CONVERTER=scene.cmx scene_extents.cmx scene_json.cmx \
dot_file.cmx dot_parser.cmx dot_lexer.cmx dot_graph.cmx dot_render.cmx \
converter.cmx
OPTLINKFLAGS=-package str,cairo.lablgtk2 -linkpkg
JSOBJS=scene.cmo viewer_common.cmo viewer_js.cmo
LINKFLAGS=-package js_of_ocaml -linkpkg
all: coinst_viewer jsviewer.js coinst_converter
opt: all
byte: coinst_viewer.byte jsviewer.js coinst_converter.byte
coinst_viewer: $(OBJS)
$(OCAMLOPT) -o $@ $(OPTLINKFLAGS) $^
coinst_viewer.byte: $(OBJS:.cmx=.cmo)
$(OCAMLC) -o $@ $(OPTLINKFLAGS) $^
coinst_converter: $(CONVERTER)
$(OCAMLOPT) -o $@ $(OPTLINKFLAGS) $^
coinst_converter.byte: $(CONVERTER:.cmx=.cmo)
$(OCAMLC) -o $@ $(OPTLINKFLAGS) $^
jsviewer.js: jsviewer.byte
js_of_ocaml $^ -pretty
jsviewer.byte: $(JSOBJS)
$(OCAMLC) -o $@ $(LINKFLAGS) $^
realclean:: clean
rm -f dot_parser.ml dot_parser.mli dot_lexer.ml
clean::
rm -f coinst_converter coinst_viewer coinst_viewer.byte coinst_converter.byte
rm -f jsviewer.js jsviewer.byte
rm -f dot_lexer.ml dot_parser.ml
#####
clean::
find . -regex ".*\\.\(cm[toix].?\|o\|annot\)" | xargs rm -f
%.cmx: %.ml
$(OCAMLOPT) $(OPTCOMPFLAGS) $(COMPFLAGS) -c $<
%.cmi: %.mli
$(OCAMLC) $(COMPFLAGS) -c $<
%.cmo: %.ml
$(OCAMLC) $(COMPFLAGS) -c $<
%.ml: %.mly
$(OCAMLYACC) $<
%.mli: %.mly
$(OCAMLYACC) $<
%.ml: %.mll
$(OCAMLLEX) $<
depend: $(GENERATED)
find . -regex ".*\\.mli?" | xargs \
$(OCAMLDEP) $(DEPFLAGS) $$i \
> .depend
include .depend
coinst-1.9.3/viewer/dot_render.ml 0000644 0001750 0001750 00000043444 12657630652 015766 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
module G = Dot_graph
module IntMap = G.IntMap
module StringMap = G.StringMap
(****)
let convert (r, g, b) =
let c i = float i /. 255.99 in
(c r, c g, c b)
let named_colors =
let colors = Hashtbl.create 101 in
List.iter (fun (nm, v) -> Hashtbl.add colors nm (convert v))
["aliceblue", (240, 248, 255);
"antiquewhite", (250, 235, 215);
"aqua", ( 0, 255, 255);
"aquamarine", (127, 255, 212);
"azure", (240, 255, 255);
"beige", (245, 245, 220);
"bisque", (255, 228, 196);
"black", ( 0, 0, 0);
"blanchedalmond", (255, 235, 205);
"blue", ( 0, 0, 255);
"blueviolet", (138, 43, 226);
"brown", (165, 42, 42);
"burlywood", (222, 184, 135);
"cadetblue", ( 95, 158, 160);
"chartreuse", (127, 255, 0);
"chocolate", (210, 105, 30);
"coral", (255, 127, 80);
"cornflowerblue", (100, 149, 237);
"cornsilk", (255, 248, 220);
"crimson", (220, 20, 60);
"cyan", ( 0, 255, 255);
"darkblue", ( 0, 0, 139);
"darkcyan", ( 0, 139, 139);
"darkgoldenrod", (184, 134, 11);
"darkgray", (169, 169, 169);
"darkgreen", ( 0, 100, 0);
"darkgrey", (169, 169, 169);
"darkkhaki", (189, 183, 107);
"darkmagenta", (139, 0, 139);
"darkolivegreen", ( 85, 107, 47);
"darkorange", (255, 140, 0);
"darkorchid", (153, 50, 204);
"darkred", (139, 0, 0);
"darksalmon", (233, 150, 122);
"darkseagreen", (143, 188, 143);
"darkslateblue", ( 72, 61, 139);
"darkslategray", ( 47, 79, 79);
"darkslategrey", ( 47, 79, 79);
"darkturquoise", ( 0, 206, 209);
"darkviolet", (148, 0, 211);
"deeppink", (255, 20, 147);
"deepskyblue", ( 0, 191, 255);
"dimgray", (105, 105, 105);
"dimgrey", (105, 105, 105);
"dodgerblue", ( 30, 144, 255);
"firebrick", (178, 34, 34);
"floralwhite", (255, 250, 240);
"forestgreen", ( 34, 139, 34);
"fuchsia", (255, 0, 255);
"gainsboro", (220, 220, 220);
"ghostwhite", (248, 248, 255);
"gold", (255, 215, 0);
"goldenrod", (218, 165, 32);
"gray", (128, 128, 128);
"grey", (128, 128, 128);
"green", ( 0, 128, 0);
"greenyellow", (173, 255, 47);
"honeydew", (240, 255, 240);
"hotpink", (255, 105, 180);
"indianred", (205, 92, 92);
"indigo", ( 75, 0, 130);
"ivory", (255, 255, 240);
"khaki", (240, 230, 140);
"lavender", (230, 230, 250);
"lavenderblush", (255, 240, 245);
"lawngreen", (124, 252, 0);
"lemonchiffon", (255, 250, 205);
"lightblue", (173, 216, 230);
"lightcoral", (240, 128, 128);
"lightcyan", (224, 255, 255);
"lightgoldenrodyellow", (250, 250, 210);
"lightgray", (211, 211, 211);
"lightgreen", (144, 238, 144);
"lightgrey", (211, 211, 211);
"lightpink", (255, 182, 193);
"lightsalmon", (255, 160, 122);
"lightseagreen", ( 32, 178, 170);
"lightskyblue", (135, 206, 250);
"lightslategray", (119, 136, 153);
"lightslategrey", (119, 136, 153);
"lightsteelblue", (176, 196, 222);
"lightyellow", (255, 255, 224);
"lime", ( 0, 255, 0);
"limegreen", ( 50, 205, 50);
"linen", (250, 240, 230);
"magenta", (255, 0, 255);
"maroon", (128, 0, 0);
"mediumaquamarine", (102, 205, 170);
"mediumblue", ( 0, 0, 205);
"mediumorchid", (186, 85, 211);
"mediumpurple", (147, 112, 219);
"mediumseagreen", ( 60, 179, 113);
"mediumslateblue", (123, 104, 238);
"mediumspringgreen", ( 0, 250, 154);
"mediumturquoise", ( 72, 209, 204);
"mediumvioletred", (199, 21, 133);
"midnightblue", ( 25, 25, 112);
"mintcream", (245, 255, 250);
"mistyrose", (255, 228, 225);
"moccasin", (255, 228, 181);
"navajowhite", (255, 222, 173);
"navy", ( 0, 0, 128);
"oldlace", (253, 245, 230);
"olive", (128, 128, 0);
"olivedrab", (107, 142, 35);
"orange", (255, 165, 0);
"orangered", (255, 69, 0);
"orchid", (218, 112, 214);
"palegoldenrod", (238, 232, 170);
"palegreen", (152, 251, 152);
"paleturquoise", (175, 238, 238);
"palevioletred", (219, 112, 147);
"papayawhip", (255, 239, 213);
"peachpuff", (255, 218, 185);
"peru", (205, 133, 63);
"pink", (255, 192, 203);
"plum", (221, 160, 221);
"powderblue", (176, 224, 230);
"purple", (128, 0, 128);
"red", (255, 0, 0);
"rosybrown", (188, 143, 143);
"royalblue", ( 65, 105, 225);
"saddlebrown", (139, 69, 19);
"salmon", (250, 128, 114);
"sandybrown", (244, 164, 96);
"seagreen", ( 46, 139, 87);
"seashell", (255, 245, 238);
"sienna", (160, 82, 45);
"silver", (192, 192, 192);
"skyblue", (135, 206, 235);
"slateblue", (106, 90, 205);
"slategray", (112, 128, 144);
"slategrey", (112, 128, 144);
"snow", (255, 250, 250);
"springgreen", ( 0, 255, 127);
"steelblue", ( 70, 130, 180);
"tan", (210, 180, 140);
"teal", ( 0, 128, 128);
"thistle", (216, 191, 216);
"tomato", (255, 99, 71);
"turquoise", ( 64, 224, 208);
"violet", (238, 130, 238);
"wheat", (245, 222, 179);
"white", (255, 255, 255);
"whitesmoke", (245, 245, 245);
"yellow", (255, 255, 0);
"yellowgreen", (154, 205, 50)];
colors
let rgb_of_hsv h s v =
if s <= 0.0 then
(v, v, v)
else begin
let h = 6. *. if h >= 1. then 0. else h in
let i = truncate h in
let f = h -. float i in
let p = v *. (1. -. s) in
let q = v *. (1. -. s *. f) in
let t = v *. (1. -. s *. (1. -. f)) in
match i with
0 -> (v, t, p)
| 1 -> (q, v, p)
| 2 -> (p, v, t)
| 3 -> (p, q, v)
| 4 -> (t, p, v)
| 5 -> (v, p, q)
| _ -> assert false
end
let parse_color c =
if c = "none" then None else
if String.length c = 7 && c.[0] = '#' then begin
let conv s = int_of_string ("0x" ^ s) in
let c =
(conv (String.sub c 1 2),
conv (String.sub c 3 2),
conv (String.sub c 5 2))
in
Some (convert c)
end else
try
Scanf.sscanf c "%f,%f,%f" (fun h s v -> Some (rgb_of_hsv h s v))
with Scanf.Scan_failure _ | Failure _ | End_of_file | Invalid_argument _ ->
Some (try Hashtbl.find named_colors c
with Not_found -> Format.eprintf "%s@." c; assert false)
let convert (r, g, b) =
let c i = float i /. 255.99 in
(c r, c g, c b)
let named_colors =
let colors = Hashtbl.create 101 in
List.iter (fun (nm, v) -> Hashtbl.add colors nm (convert v))
["aliceblue", (240, 248, 255);
"antiquewhite", (250, 235, 215);
"aqua", ( 0, 255, 255);
"aquamarine", (127, 255, 212);
"azure", (240, 255, 255);
"beige", (245, 245, 220);
"bisque", (255, 228, 196);
"black", ( 0, 0, 0);
"blanchedalmond", (255, 235, 205);
"blue", ( 0, 0, 255);
"blueviolet", (138, 43, 226);
"brown", (165, 42, 42);
"burlywood", (222, 184, 135);
"cadetblue", ( 95, 158, 160);
"chartreuse", (127, 255, 0);
"chocolate", (210, 105, 30);
"coral", (255, 127, 80);
"cornflowerblue", (100, 149, 237);
"cornsilk", (255, 248, 220);
"crimson", (220, 20, 60);
"cyan", ( 0, 255, 255);
"darkblue", ( 0, 0, 139);
"darkcyan", ( 0, 139, 139);
"darkgoldenrod", (184, 134, 11);
"darkgray", (169, 169, 169);
"darkgreen", ( 0, 100, 0);
"darkgrey", (169, 169, 169);
"darkkhaki", (189, 183, 107);
"darkmagenta", (139, 0, 139);
"darkolivegreen", ( 85, 107, 47);
"darkorange", (255, 140, 0);
"darkorchid", (153, 50, 204);
"darkred", (139, 0, 0);
"darksalmon", (233, 150, 122);
"darkseagreen", (143, 188, 143);
"darkslateblue", ( 72, 61, 139);
"darkslategray", ( 47, 79, 79);
"darkslategrey", ( 47, 79, 79);
"darkturquoise", ( 0, 206, 209);
"darkviolet", (148, 0, 211);
"deeppink", (255, 20, 147);
"deepskyblue", ( 0, 191, 255);
"dimgray", (105, 105, 105);
"dimgrey", (105, 105, 105);
"dodgerblue", ( 30, 144, 255);
"firebrick", (178, 34, 34);
"floralwhite", (255, 250, 240);
"forestgreen", ( 34, 139, 34);
"fuchsia", (255, 0, 255);
"gainsboro", (220, 220, 220);
"ghostwhite", (248, 248, 255);
"gold", (255, 215, 0);
"goldenrod", (218, 165, 32);
"gray", (128, 128, 128);
"grey", (128, 128, 128);
"green", ( 0, 128, 0);
"greenyellow", (173, 255, 47);
"honeydew", (240, 255, 240);
"hotpink", (255, 105, 180);
"indianred", (205, 92, 92);
"indigo", ( 75, 0, 130);
"ivory", (255, 255, 240);
"khaki", (240, 230, 140);
"lavender", (230, 230, 250);
"lavenderblush", (255, 240, 245);
"lawngreen", (124, 252, 0);
"lemonchiffon", (255, 250, 205);
"lightblue", (173, 216, 230);
"lightcoral", (240, 128, 128);
"lightcyan", (224, 255, 255);
"lightgoldenrodyellow", (250, 250, 210);
"lightgray", (211, 211, 211);
"lightgreen", (144, 238, 144);
"lightgrey", (211, 211, 211);
"lightpink", (255, 182, 193);
"lightsalmon", (255, 160, 122);
"lightseagreen", ( 32, 178, 170);
"lightskyblue", (135, 206, 250);
"lightslategray", (119, 136, 153);
"lightslategrey", (119, 136, 153);
"lightsteelblue", (176, 196, 222);
"lightyellow", (255, 255, 224);
"lime", ( 0, 255, 0);
"limegreen", ( 50, 205, 50);
"linen", (250, 240, 230);
"magenta", (255, 0, 255);
"maroon", (128, 0, 0);
"mediumaquamarine", (102, 205, 170);
"mediumblue", ( 0, 0, 205);
"mediumorchid", (186, 85, 211);
"mediumpurple", (147, 112, 219);
"mediumseagreen", ( 60, 179, 113);
"mediumslateblue", (123, 104, 238);
"mediumspringgreen", ( 0, 250, 154);
"mediumturquoise", ( 72, 209, 204);
"mediumvioletred", (199, 21, 133);
"midnightblue", ( 25, 25, 112);
"mintcream", (245, 255, 250);
"mistyrose", (255, 228, 225);
"moccasin", (255, 228, 181);
"navajowhite", (255, 222, 173);
"navy", ( 0, 0, 128);
"oldlace", (253, 245, 230);
"olive", (128, 128, 0);
"olivedrab", (107, 142, 35);
"orange", (255, 165, 0);
"orangered", (255, 69, 0);
"orchid", (218, 112, 214);
"palegoldenrod", (238, 232, 170);
"palegreen", (152, 251, 152);
"paleturquoise", (175, 238, 238);
"palevioletred", (219, 112, 147);
"papayawhip", (255, 239, 213);
"peachpuff", (255, 218, 185);
"peru", (205, 133, 63);
"pink", (255, 192, 203);
"plum", (221, 160, 221);
"powderblue", (176, 224, 230);
"purple", (128, 0, 128);
"red", (255, 0, 0);
"rosybrown", (188, 143, 143);
"royalblue", ( 65, 105, 225);
"saddlebrown", (139, 69, 19);
"salmon", (250, 128, 114);
"sandybrown", (244, 164, 96);
"seagreen", ( 46, 139, 87);
"seashell", (255, 245, 238);
"sienna", (160, 82, 45);
"silver", (192, 192, 192);
"skyblue", (135, 206, 235);
"slateblue", (106, 90, 205);
"slategray", (112, 128, 144);
"slategrey", (112, 128, 144);
"snow", (255, 250, 250);
"springgreen", ( 0, 255, 127);
"steelblue", ( 70, 130, 180);
"tan", (210, 180, 140);
"teal", ( 0, 128, 128);
"thistle", (216, 191, 216);
"tomato", (255, 99, 71);
"turquoise", ( 64, 224, 208);
"violet", (238, 130, 238);
"wheat", (245, 222, 179);
"white", (255, 255, 255);
"whitesmoke", (245, 245, 245);
"yellow", (255, 255, 0);
"yellowgreen", (154, 205, 50)];
colors
(****)
let comma_re = Str.regexp ","
let semi_re = Str.regexp ";"
let wsp_re = Str.regexp "[\x20\x09\x0D\x0A]+"
let parse_float s = try float_of_string s with Failure _ -> raise Not_found
let parse_rectangle s =
match Str.split comma_re s with
[x1; y1; x2; y2] ->
(parse_float x1, -. parse_float y2,
parse_float x2, -. parse_float y1)
| _ ->
raise Not_found
let parse_point s =
match Str.split comma_re s with
[x; y] -> (parse_float x, -. parse_float y)
| _ -> raise Not_found
let start_point l = match l with x :: _ -> x | _ -> raise Not_found
let rec end_point l =
match l with [x] -> x | _ :: r -> end_point r | _ -> raise Not_found
let epsilon = 0.0001
let add_arrow scene (px, py) (ux, uy) color arrow_size (*XXX pen_width*) =
let dx = ux -. px in
let dy = uy -. py in
let s = 10. /. (sqrt (dx *. dx +. dy *. dy) +. epsilon) in
let dx = s *. if dx >= 0. then dx +. epsilon else dx -. epsilon in
let dy = s *. if dy >= 0. then dy +. epsilon else dy -. epsilon in
let arrow_width = 0.35 in
let vx = -. dy *. arrow_width in
let vy = dx *. arrow_width in
let qx = px +. dx in
let qy = py +. dy in
let l = [|(px, py); (px -. vx, py -. vy); (qx, qy); (px +. vx, py +. vy)|] in
Scene.add scene (Scene.Polygon (l, color, color, ""))
let rec render_spline_rec l =
match l with
[] ->
[]
| (x1, y1) :: (x2, y2) :: (x3, y3) :: r ->
Scene.Curve_to (x1, y1, x2, y2, x3, y3) :: render_spline_rec r
| _ ->
raise Not_found
let render_spline l =
match l with
(x, y) :: r -> Array.of_list (Scene.Move_to (x, y) :: render_spline_rec r)
| _ -> raise Not_found
let parse_spline scene s color arrow_size style =
let l = Str.split semi_re s in
List.iter
(fun s ->
let l = List.map (fun s -> Str.split comma_re s) (Str.split wsp_re s) in
let (endp, l) =
match l with
["e"; x; y] :: r -> Some (parse_float x, -. parse_float y), r
| _ -> None, l
in
let (startp, l) =
match l with
["s"; x; y] :: r -> Some (parse_float x, -. parse_float y), r
| _ -> None, l
in
let l =
List.map
(fun l ->
match l with
[x; y] -> (parse_float x, -. parse_float y)
| _ -> raise Not_found)
l
in
begin match endp with
Some u -> add_arrow scene (end_point l) u color arrow_size
| None -> ()
end;
begin match startp with
Some u -> add_arrow scene (start_point l) u color arrow_size
| None -> ()
end;
Scene.add scene (Scene.Path (render_spline l, None, color, style)))
l
let add_rect_margin (x1, y1, x2, y2) w =
(x1 -. w, y1 -. w, x2 +. w, y2 +. w)
let dpi = 72.
let f g =
let bbox = parse_rectangle (StringMap.find "bb" g.G.graph_attr) in
let margin =
try
parse_float (StringMap.find "margin" g.G.graph_attr)
with Not_found ->
4.
in
let bbox = add_rect_margin bbox margin in
let scene = Scene.make () in
IntMap.iter
(fun _ n ->
let (x, y) = parse_point (StringMap.find "pos" n.G.node_attr) in
let width =
dpi *. parse_float (StringMap.find "width" n.G.node_attr) in
let height =
dpi *. parse_float (StringMap.find "height" n.G.node_attr) in
let color =
parse_color
(try StringMap.find "color" n.G.node_attr with Not_found -> "black")
in
let shape =
try StringMap.find "shape" n.G.node_attr with Not_found -> "ellipse" in
(*XXX parse style *)
let style =
try
Str.split comma_re (StringMap.find "style" n.G.node_attr)
with Not_found ->
[]
in
let fillcolor =
if not (List.mem "filled" style) then None else
try
parse_color (StringMap.find "fillcolor" n.G.node_attr)
with Not_found ->
color
in
let line_style =
List.find (fun s -> s = "" || List.mem s style)
["dashed"; "dotted"; ""]
in
begin match shape with
"box" | "rect" | "rectangle" ->
let w2 = width /. 2. in
let h2 = height /. 2. in
Scene.add scene
(Scene.rectangle (x -. w2, y -. h2, x +. w2, y +. h2)
fillcolor color line_style)
| _ ->
Scene.add scene
(Scene.Ellipse
(x, y, width /. 2., height /. 2., fillcolor, color,
line_style))
end;
let font_color =
parse_color
(try StringMap.find "color" n.G.node_attr with Not_found -> "black")
in
let font_size =
try
parse_float (StringMap.find "fontsize" n.G.node_attr)
with Not_found ->
14.
in
let label =
(*XXX Parse...*)
try StringMap.find "label" n.G.node_attr with Not_found -> n.G.name
in
let font_family = "serif" in
Scene.add scene
(Scene.Text (x, y, label, (font_family, font_size),
font_color, None));
()
)
g.G.nodes.G.seq;
IntMap.iter
(fun _ e ->
(* Format.eprintf "%s -> %s@." e.G.tail.G.name e.G.head.G.name;*)
let color =
parse_color
(try StringMap.find "color" e.G.edge_attr with Not_found -> "black")
in
let arrow_size =
try
parse_float (StringMap.find "arrowsize" e.G.edge_attr)
with Not_found -> 1.
in
let style =
try StringMap.find "style" e.G.edge_attr with Not_found -> ""
in
parse_spline scene (StringMap.find "pos" e.G.edge_attr)
color arrow_size style;
())
g.G.edges.G.seq;
(bbox, scene)
coinst-1.9.3/viewer/dot_graph.mli 0000644 0001750 0001750 00000003231 12657630652 015747 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
module StringMap : Map.S with type key = string
module IntMap : Map.S with type key = int
type id
type 'a sequence =
{ mutable count : int;
mutable seq : 'a IntMap.t;
id : (id, 'a) Hashtbl.t }
type node =
{ name : string;
id : id;
mutable node_attr : string StringMap.t }
type edge =
{ head : node;
tail : node;
edge_id : id;
mutable edge_attr : string StringMap.t }
type graph =
{ graph_id : id;
graph_name : string option;
mutable graph_attr : string StringMap.t;
subgraphs : graph sequence;
nodes : node sequence;
edges : edge sequence;
parents : (id, graph) Hashtbl.t }
type info =
{ kind : [`Graph | `Digraph];
strict : bool }
val of_file_spec : Dot_file.t -> info * graph
val of_channel : in_channel -> info * graph
val from_lexbuf : Lexing.lexbuf -> info * graph
coinst-1.9.3/viewer/dot_parser.mly 0000644 0001750 0001750 00000006600 12657630652 016165 0 ustar mehdi mehdi /* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*/
%{
%}
%token EOF
%token NODE
%token EDGE
%token GRAPH
%token DIGRAPH
%token STRICT
%token SUBGRAPH
%token EDGEOP
%token ATOM
%token QATOM
%token LBRACE
%token RBRACE
%token LBRACKET
%token RBRACKET
%token SEMI
%token COMMA
%token COLON
%token EQUAL
%token PLUS
%start graph
%type graph
%%
graph: optstrict graphtype optgraphname body
{ { Dot_file.kind = $2; strict = $1;
graph = { Dot_file.graph_name = $3; body = $4 } } }
| EOF
{ raise End_of_file }
;
body: LBRACE optstmtlist RBRACE
{ $2 }
;
optgraphname:
atom
{ Some $1 }
| /* empty */
{ None }
;
optstrict:
STRICT
{ true }
| /* empty */
{ false }
;
graphtype:
GRAPH
{ `Graph }
| DIGRAPH
{ `Digraph }
;
optstmtlist:
stmtlist
{ List.rev $1 }
| /* empty */
{ [] }
stmtlist:
stmtlist stmt
{ $2 :: $1 }
| stmt
{ [$1] }
;
optsemi:
SEMI
{ }
| /* empty */
{ }
;
stmt:
attrstmt optsemi
{ `Attributes $1 }
| compound optsemi
{ `Compound $1 }
;
compound: simple rcompound optattr
{ ($1 :: $2, List.flatten (List.rev $3)) }
;
simple:
node
{ `Node $1 }
| subgraph
{ `Graph $1 }
;
rcompound:
EDGEOP simple rcompound
{ $2 :: $3 }
| /* empty */
{ [] }
;
node:
atom
{ { Dot_file.name = $1; port = None } }
| atom COLON atom
{ { Dot_file.name = $1; port = Some $3 } }
| atom COLON atom COLON atom
{ { Dot_file.name = $1; port = Some ($3 ^ ":" ^ $5) } }
;
attrstmt:
attrtype attrlist
{ ($1, List.flatten (List.rev $2)) }
| graphattrdefs
{ (`Graph, [$1]) }
;
attrtype:
GRAPH
{ `Graph }
| NODE
{ `Node }
| EDGE
{ `Edge }
;
optattr:
attrlist
{ $1 }
| /* empty */
{ [] }
;
attrlist: optattr LBRACKET optattrdefs RBRACKET
{ List.rev $3 :: $1 }
;
optattrdefs:
optattrdefs attrdefs
{ $2 :: $1 }
| /* empty */
{ [] }
;
attrdefs: attritem optseparator
{ $1 }
;
attritem:
attrassignment
{ $1 }
;
attrassignment: atom EQUAL atom
{ ($1, $3) }
| atom
{ ($1, "true") }
;
graphattrdefs: atom EQUAL atom
{ ($1, $3) }
;
subgraph: optsubghdr body
{ {Dot_file.graph_name = $1; body = $2} }
;
optsubghdr:
SUBGRAPH atom
{ Some $2 }
| SUBGRAPH
{ None }
| /* empty */
{ None }
;
optseparator:
| COMMA
{ }
| /*empty*/
{ }
;
atom:
ATOM
{ $1 }
| qatom
{ $1 }
;
qatom:
QATOM
{ $1 }
| qatom PLUS QATOM
{ $1 ^ $3 }
;
coinst-1.9.3/viewer/index.html 0000644 0001750 0001750 00000000604 12657630652 015273 0 ustar mehdi mehdi
Graph viewer
coinst-1.9.3/viewer/scene_svg.mli 0000644 0001750 0001750 00000000226 12657630652 015755 0 ustar mehdi mehdi
val format :
Format.formatter ->
(float * float * float * float) *
(float * float * float, string * float, string) Scene.element array -> unit
coinst-1.9.3/viewer/scene_svg.ml 0000644 0001750 0001750 00000003727 12657630652 015615 0 ustar mehdi mehdi
open Scene
let color c =
match c with
None ->
"none"
| Some (r, g, b) ->
let h v = truncate (v *. 255.99) in
Format.sprintf "#%02x%02x%02x" (h r) (h g) (h b)
let command c =
match c with
Move_to (x, y) ->
Format.sprintf "M%g,%g" x y
| Curve_to (x1, y1, x2, y2, x3, y3) ->
Format.sprintf "C%g,%g %g,%g %g,%g" x1 y1 x2 y2 x3 y3
let style s =
match s with
"dashed" -> " stroke-dasharray='5,2'"
| "dotted" -> " stroke-dasharray='1,3'"
| _ -> ""
let (>>) v f = f v
let comma_re = Str.regexp ","
let format f ((x1, y1, x2, y2), scene) =
Format.fprintf f "\n@?";
coinst-1.9.3/viewer/dot_file.ml 0000644 0001750 0001750 00000010144 12657630652 015415 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
type kind = [`Graph | `Digraph]
type attr_type = [`Graph | `Edge | `Node]
type attributes = (string * string) list
type node = { name : string; port : string option }
type graph = { graph_name : string option; body : statement list }
and compound = [`Node of node | `Graph of graph] list * attributes
and statement =
[`Attributes of attr_type * attributes | `Compound of compound]
type t = { kind : kind; strict : bool; graph : graph }
(****)
let graph' ?name body = { graph_name = name; body = body }
let graph kind ?(strict = false) name body =
{ kind = kind; strict = strict; graph = graph' ~name body }
let subgraph ?name body = `Graph (graph' ?name body)
let node ?port name = `Node { name = name; port = port }
(****)
let name_or_number_re =
Str.regexp
"^\\([a-zA-Z_][a-zA-Z_0-9]*\\|-?[0-9]+\\(\\.[0-9]*\\)?\\|\\.[0-9]+\\)$"
let keywords = ["node"; "edge"; "graph"; "digraph"; "subgraph"; "strict"]
let backslash_re = Str.regexp "\\\\"
let quote_re = Str.regexp "\""
let escape_string s =
Str.global_replace quote_re "\\\""
(Str.global_replace backslash_re "\\\\\\\\" s)
let need_quotes s =
not (Str.string_match name_or_number_re s 0) ||
List.mem (String.lowercase s) keywords
let print_atom f atom =
if need_quotes atom then
Format.fprintf f "\"%s\"" atom
else
Format.fprintf f "%s" atom
let print_node f node =
match node.port with
None -> print_atom f node.name
| Some port -> Format.fprintf f "%a:%s" print_atom node.name port
let print_attribute f (key, value) =
Format.fprintf f "@[<2>%a=@,%a@]" print_atom key print_atom value
let print_list pr f l =
match l with
[] -> ()
| x :: r -> pr f x; List.iter (fun x -> Format.fprintf f "@ %a" pr x) r
let print_attributes f (typ, l) =
Format.fprintf f "@[%s@ [@;<0 2>@["
(match typ with `Graph -> "graph" | `Edge -> "edge" | `Node -> "node");
print_list print_attribute f l;
Format.fprintf f "@]@,]@]"
let rec print_simple kind f s =
match s with
`Node node -> print_node f node
| `Graph graph -> print_subgraph kind f graph
and print_subgraph kind f graph =
Format.fprintf f "@[@[";
begin match graph.graph_name with
None -> ()
| Some n -> Format.fprintf f "subgraph@ %a@ " print_atom n
end;
Format.fprintf f "{@]@;<1 2>@[";
print_list (print_statement kind) f graph.body;
Format.fprintf f "@]@ }@]"
and print_statement kind f st =
match st with
`Attributes attrs -> print_attributes f attrs
| `Compound c -> print_compound kind f c
and print_compound kind f (c, l) =
let sep = match kind with `Graph -> "--" | `Digraph -> "->" in
Format.fprintf f "@[@[";
begin match c with
[] ->
assert false
| s :: r ->
print_simple kind f s;
List.iter
(fun s -> Format.fprintf f "@ %s@ %a" sep (print_simple kind) s) r
end;
Format.fprintf f "@]";
if l <> [] then begin
Format.fprintf f "@ [@;<0 2>@[";
print_list print_attribute f l;
Format.fprintf f "@]@,]"
end;
Format.fprintf f "@]"
let print f g =
Format.fprintf f "@[@[%s%s@ %a@ {@]@;<1 2>@["
(if g.strict then "strict " else "")
(if g.kind = `Digraph then "digraph" else "graph")
print_atom (match g.graph.graph_name with Some nm -> nm | None -> "graph");
print_list (print_statement g.kind) f g.graph.body;
Format.fprintf f "@]@ }@]@."
coinst-1.9.3/viewer/main.ml 0000644 0001750 0001750 00000002132 12657630652 014552 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
let _ =
let ch = if Array.length Sys.argv > 1 then open_in Sys.argv.(1) else stdin in
let (_, g) = Dot_graph.of_channel ch in
let (bbox, scene) = Dot_render.f g in
ignore (GMain.Main.init ());
Viewer.create (*~full_screen:true*) bbox scene;
GMain.main ()
coinst-1.9.3/viewer/dot_lexer.mll 0000644 0001750 0001750 00000007270 12657630652 015777 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
{
type graph_type = Graph | Digraph | Unknown
let graph_type = ref Unknown
let set_graph_type v = if !graph_type = Unknown then graph_type := v
let buffer = Buffer.create 256
let html_nest = ref 1
let reset () = graph_type := Unknown
}
let letter = ['A'-'Z' 'a'-'z' '_' '\128'-'\255']
let digit = ['0'-'9']
let name = letter (letter | digit) *
let number = '-'? ((digit+ ('.' digit*)?) | ('.' digit+))
let id = name | number
rule token =
parse
"/*"
{ comment lexbuf }
| "//" [^ '\n']*
| "#" [^ '\n']*
| [' ' '\t' '\r' '\n']+
{ token lexbuf }
| "->"
{ if !graph_type = Digraph then
Dot_parser.EDGEOP
else
exit 1 (*XXX*) }
| "--"
{ if !graph_type = Graph then
Dot_parser.EDGEOP
else
exit 1 (*XXX*) }
| name
{
let s = Lexing.lexeme lexbuf in
match String.lowercase s with
"node" -> Dot_parser.NODE
| "edge" -> Dot_parser.EDGE
| "graph" -> set_graph_type Graph; Dot_parser.GRAPH
| "digraph" -> set_graph_type Digraph; Dot_parser.DIGRAPH
| "strict" -> Dot_parser.STRICT
| "subgraph" -> Dot_parser.SUBGRAPH
| _ -> Dot_parser.ATOM s }
| number
{ Dot_parser.ATOM (Lexing.lexeme lexbuf) }
| '"'
{ qstring lexbuf }
| '<'
{ Buffer.add_char buffer '<';
html_nest := 1;
hstring lexbuf }
| '{'
{ Dot_parser.LBRACE }
| '}'
{ Dot_parser.RBRACE }
| '['
{ Dot_parser.LBRACKET }
| ']'
{ Dot_parser.RBRACKET }
| '='
{ Dot_parser.EQUAL }
| ':'
{ Dot_parser.COLON }
| ';'
{ Dot_parser.SEMI }
| ','
{ Dot_parser.COMMA }
| '+'
{ Dot_parser.PLUS }
| _
{ Format.eprintf "%s@." (Lexing.lexeme lexbuf); exit 1 (*XXX*) }
| eof
{ Dot_parser.EOF }
and comment =
parse
[^'*']*
{ comment lexbuf }
| '*'+ [^ '*' '/']*
{ comment lexbuf }
| '*'+ '/'
{ token lexbuf }
(*
| eof
*)
and qstring =
parse
'"'
{ let s = Buffer.contents buffer in
Buffer.clear buffer;
Dot_parser.QATOM s }
| "\\\""
{ Buffer.add_string buffer "\\\"";
qstring lexbuf }
| "\\\n"
{ qstring lexbuf }
| '\n'
{ Buffer.add_char buffer '\n';
qstring lexbuf }
| [^ '"' '\\']+ | '\\' [^'\n']
{ Buffer.add_string buffer (Lexing.lexeme lexbuf);
qstring lexbuf }
(*
| _
| eof
*)
and hstring =
parse
'>'
{ decr html_nest;
if !html_nest > 0 then hstring lexbuf else begin
Buffer.add_char buffer '>';
let s = Buffer.contents buffer in
Buffer.clear buffer;
Dot_parser.QATOM s
end }
| '<'
{ incr html_nest;
Buffer.add_char buffer '<';
hstring lexbuf }
| [^ '<' '>'] +
{ Buffer.add_string buffer (Lexing.lexeme lexbuf);
hstring lexbuf }
coinst-1.9.3/viewer/.depend 0000644 0001750 0001750 00000003214 12657630652 014536 0 ustar mehdi mehdi ./dot_file.cmo: ./dot_file.cmi
./dot_file.cmx: ./dot_file.cmi
./scene_extents.cmo: scene.cmi ./scene_extents.cmi
./scene_extents.cmx: scene.cmx ./scene_extents.cmi
./viewer_common.cmi: scene.cmi
./dot_lexer.cmo: dot_parser.cmi ./dot_lexer.cmi
./dot_lexer.cmx: dot_parser.cmx ./dot_lexer.cmi
./dot_graph.cmo: dot_parser.cmi dot_lexer.cmi dot_file.cmi ./dot_graph.cmi
./dot_graph.cmx: dot_parser.cmx dot_lexer.cmx dot_file.cmx ./dot_graph.cmi
./scene_json.cmo: scene.cmi ./scene_json.cmi
./scene_json.cmx: scene.cmx ./scene_json.cmi
./viewer.cmo: viewer_common.cmi scene_extents.cmi scene.cmi ./viewer.cmi
./viewer.cmx: viewer_common.cmx scene_extents.cmx scene.cmx ./viewer.cmi
./dot_render.cmi: scene.cmi dot_graph.cmi
./dot_parser.cmo: dot_file.cmi ./dot_parser.cmi
./dot_parser.cmx: dot_file.cmx ./dot_parser.cmi
./main.cmo: viewer.cmi dot_render.cmi dot_graph.cmi
./main.cmx: viewer.cmx dot_render.cmx dot_graph.cmx
./scene.cmo: ./scene.cmi
./scene.cmx: ./scene.cmi
./converter.cmo: scene_json.cmi scene_extents.cmi scene.cmi dot_render.cmi \
dot_graph.cmi
./converter.cmx: scene_json.cmx scene_extents.cmx scene.cmx dot_render.cmx \
dot_graph.cmx
./svg.cmo:
./svg.cmx:
./scene.cmi:
./scene_extents.cmi: scene.cmi
./viewer.cmi: scene.cmi
./scene_json.cmi: scene.cmi
./dot_file.cmi:
./dot_graph.cmi: dot_file.cmi
./viewer_common.cmo: scene.cmi ./viewer_common.cmi
./viewer_common.cmx: scene.cmx ./viewer_common.cmi
./dot_lexer.cmi: dot_parser.cmi
./dot_parser.cmi: dot_file.cmi
./viewer_js.cmo: viewer_common.cmi
./viewer_js.cmx: viewer_common.cmx
./dot_render.cmo: scene.cmi dot_graph.cmi ./dot_render.cmi
./dot_render.cmx: scene.cmx dot_graph.cmx ./dot_render.cmi
coinst-1.9.3/viewer/dot_file.mli 0000644 0001750 0001750 00000002677 12657630652 015602 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
type kind = [`Graph | `Digraph]
type attr_type = [`Graph | `Edge | `Node]
type attributes = (string * string) list
type node = { name : string; port : string option }
type graph = { graph_name : string option; body : statement list }
and compound = [`Node of node | `Graph of graph] list * attributes
and statement =
[`Attributes of attr_type * attributes | `Compound of compound]
type t = { kind : kind; strict : bool; graph : graph }
val node : ?port:string -> string -> [`Node of node | `Graph of graph]
val graph : kind -> ?strict:bool -> string -> statement list -> t
val print : Format.formatter -> t -> unit
coinst-1.9.3/viewer/viewer_js.ml 0000644 0001750 0001750 00000035550 12657630652 015635 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
type rect = {x : int; y : int; width : int; height: int}
module Html = Dom_html
let create_canvas w h =
let c = Html.createCanvas Html.document in
c##width <- w; c##height <- h; c
module Common = Viewer_common.F (struct
type font = Js.js_string Js.t
type color = Js.js_string Js.t
type text = Js.js_string Js.t
let white = Js.string "white"
type ctx = Html.canvasRenderingContext2D Js.t
let save ctx = ctx##save ()
let restore ctx = ctx##restore ()
let scale ctx ~sx ~sy = ctx##scale (sx, sy)
let translate ctx ~tx ~ty = ctx##translate (tx, ty)
let set_line_width ctx w = ctx##lineWidth <- w
let begin_path ctx = ctx##beginPath ()
let close_path ctx = ctx##closePath ()
let move_to ctx ~x ~y = ctx##moveTo (x, y)
let line_to ctx ~x ~y = ctx##lineTo (x, y)
let curve_to ctx ~x1 ~y1 ~x2 ~y2 ~x3 ~y3 =
ctx##bezierCurveTo (x1, y1, x2, y2, x3, y3)
let arc ctx ~xc ~yc ~radius ~angle1 ~angle2 =
ctx##arc (xc, yc, radius, angle1, angle2, Js._true)
let rectangle ctx ~x ~y ~width ~height = ctx##rect (x, y, width, height)
let fill ctx c = ctx##fillStyle <- c; ctx##fill ()
let stroke ctx c = ctx##strokeStyle <- c; ctx##stroke ()
let clip ctx = ctx##clip ()
let draw_text (ctx:ctx) x y txt font fill_color stroke_color =
ctx##font <- font;
ctx##textAlign <- Js.string "center";
ctx##textBaseline <- Js.string "middle";
begin match fill_color with
Some c -> ctx##fillStyle <- c; ctx##fillText (txt, x, y)
| None -> ()
end;
begin match stroke_color with
Some c -> ctx##strokeStyle <- c; ctx##strokeText (txt, x, y)
| None -> ()
end
type window = Html.canvasElement Js.t
type drawable = window * ctx
type pixmap = drawable
let get_drawable w =
let ctx = w##getContext(Html._2d_) in
ctx##lineWidth <- 2.;
(w, ctx)
let make_pixmap _ width height =
let c = Html.createCanvas Html.document in
c##width <- width; c##height <- height;
get_drawable c
let drawable_of_pixmap p = p
let get_context (p, c) = c
let put_pixmap ~dst:((p, c) :drawable) ~x ~y ~xsrc ~ysrc ~width ~height ((p, _) : pixmap)=
c##drawImage_fullFromCanvas (p, float xsrc, float ysrc, float width, float height, float x, float y, float width, float height)
(****)
type rectangle = rect = {x : int; y : int; width : int; height: int}
let compute_extents _ = assert false
end)
open Common
let redraw st s h v (canvas : Html.canvasElement Js.t) =
let width = canvas##width in
let height = canvas##height in
(*Firebug.console##time (Js.string "draw");*)
if width > 0 && height > 0 then
redraw st s h v canvas
{x = 0; y = 0; width = width; height = height} 0 0 width height
(*
begin try
ignore (canvas##getContext(Html._2d_)##getImageData (0., 0., 1., 1.))
with _ -> () end
*)
(*
;Firebug.console##timeEnd (Js.string "draw")
;Firebug.console##log_2 (Js.string "draw", Js.date##now())
*)
let (>>=) = Lwt.bind
let http_get url =
XmlHttpRequest.perform_raw_url url
>>= fun {XmlHttpRequest.code = cod; content = msg} ->
if cod = 0 || cod = 200
then Lwt.return msg
else fst (Lwt.wait ())
let json : < parse : Js.js_string Js.t -> 'a> Js.t = Js.Unsafe.variable "JSON"
class adjustment
?(value=0.) ?(lower=0.) ?(upper=100.)
?(step_incr=1.) ?(page_incr = 10.) ?(page_size = 10.) () =
object
val mutable _value = value method value = _value
val mutable _lower = lower method lower = _lower
val mutable _upper = upper method upper = _upper
val mutable _step_incr = step_incr method step_increment = _step_incr
val mutable _page_incr = page_incr method page_increment = _page_incr
val mutable _page_size = page_size method page_size = _page_size
method set_value v = _value <- v
method set_bounds ?lower ?upper ?step_incr ?page_incr ?page_size () =
begin match lower with Some v -> _lower <- v | None -> () end;
begin match upper with Some v -> _upper <- v | None -> () end;
begin match step_incr with Some v -> _step_incr <- v | None -> () end;
begin match page_incr with Some v -> _page_incr <- v | None -> () end;
begin match page_size with Some v -> _page_size <- v | None -> () end
end
let handle_drag element f =
let mx = ref 0 in
let my = ref 0 in
element##onmousedown <- Html.handler
(fun ev ->
mx := ev##clientX; my := ev##clientY;
element##style##cursor <- Js.string "move";
let c1 =
Html.addEventListener Html.document Html.Event.mousemove
(Html.handler
(fun ev ->
let x = ev##clientX and y = ev##clientY in
let x' = !mx and y' = !my in
mx := x; my := y;
f (x - x') (y - y');
Js._true))
Js._true
in
let c2 = ref Js.null in
c2 := Js.some
(Html.addEventListener Html.document Html.Event.mouseup
(Html.handler
(fun _ ->
Html.removeEventListener c1;
Js.Opt.iter !c2 Html.removeEventListener;
(* "auto" would be better, but does not seem to work
with Opera *)
element##style##cursor <- Js.string "";
Js._true))
Js._true);
(* We do not want to disable the default action on mouse down
(here, keyboard focus)
in this example. *)
Js._true)
let load () =
Js.Optdef.case ((Js.Unsafe.coerce Dom_html.window)##scene)
(fun () -> http_get "scene.json" >>= fun s ->
Lwt.return (json##parse (Js.string s)))
(fun s -> Lwt.return s)
let start () =
let doc = Html.document in
let page = doc##documentElement in
page##style##overflow <- Js.string "hidden";
doc##body##style##overflow <- Js.string "hidden";
doc##body##style##margin <- Js.string "0px";
let started = ref false in
let p = Html.createP doc in
p##innerHTML <- Js.string "Loading graph...";
p##style##display <- Js.string "none";
Dom.appendChild doc##body p;
ignore
(Lwt_js.sleep 0.5 >>= fun () ->
if not !started then p##style##display <- Js.string "inline";
Lwt.return ());
(*
Firebug.console##time(Js.string "loading");
*)
load () >>= fun ((x1, y1, x2, y2), bboxes, scene) ->
(*
Firebug.console##timeEnd(Js.string "loading");
Firebug.console##time(Js.string "init");
*)
started := true;
Dom.removeChild doc##body p;
let st =
{ bboxes = bboxes;
scene = scene;
zoom_factor = 1. /. 20.;
st_x = x1; st_y = y1; st_width = x2 -. x1; st_height = y2 -. y1;
st_pixmap = Common.make_pixmap () }
in
let canvas = create_canvas (page##clientWidth) (page##clientHeight) in
Dom.appendChild doc##body canvas;
let allocation () =
{x = 0; y = 0; width = canvas##width; height = canvas##height} in
let hadj = new adjustment () in
let vadj = new adjustment () in
let sadj =
new adjustment ~upper:20. ~step_incr:1. ~page_incr:0. ~page_size:0. () in
let zoom_steps = 8. in (* Number of steps to get a factor of 2 *)
let set_zoom_factor f =
let count = ceil (log f /. log 2. *. zoom_steps) in
let f = 2. ** (count /. zoom_steps) in
sadj#set_bounds ~upper:count ();
st.zoom_factor <- f
in
let get_scale () = 2. ** (sadj#value /. zoom_steps) /. st.zoom_factor in
let redraw_queued = ref false in
let update_view force =
(*
Firebug.console##log_2(Js.string "update", Js.date##now());
*)
let a = allocation () in
let scale = get_scale () in
let aw = ceil (float a.width /. scale) in
let ah = ceil (float a.height /. scale) in
hadj#set_bounds ~step_incr:(aw /. 20.) ~page_incr:(aw /. 2.)
~page_size:(min aw st.st_width) ~upper:st.st_width ();
let mv = st.st_width -. hadj#page_size in
if hadj#value < 0. then hadj#set_value 0.;
if hadj#value > mv then hadj#set_value mv;
vadj#set_bounds ~step_incr:(ah /. 20.) ~page_incr:(ah /. 2.)
~page_size:(min ah st.st_height) ~upper:st.st_height ();
let mv = st.st_height -. vadj#page_size in
if vadj#value < 0. then vadj#set_value 0.;
if vadj#value > mv then vadj#set_value mv;
if not !redraw_queued then begin
redraw_queued := true;
Html._requestAnimationFrame
(Js.wrap_callback (fun () ->
redraw_queued := false;
redraw st (get_scale ()) hadj#value vadj#value canvas))
end
(*
if force then redraw st (get_scale ()) hadj#value vadj#value canvas else
if not !redraw_queued then
ignore (redraw_queued := true;
(*
Firebug.console##log(Js.string "sleep");
*)
Lwt_js.yield() >>= fun () ->
redraw_queued := false;
redraw st (get_scale ()) hadj#value vadj#value canvas;
Lwt.return ())
*)
in
let a = allocation () in
let zoom_factor =
max (st.st_width /. float a.width)
(st.st_height /. float a.height)
in
set_zoom_factor zoom_factor;
let prev_scale = ref (get_scale ()) in
let rescale x y =
let scale = get_scale () in
let r = (1. -. !prev_scale /. scale) in
hadj#set_value (hadj#value +. hadj#page_size *. r *. x);
vadj#set_value (vadj#value +. vadj#page_size *. r *. y);
prev_scale := scale;
invalidate_pixmap st.st_pixmap;
update_view false
in
let size = 16 in
let height = 300 - size in
let points d = Js.string (Printf.sprintf "%dpx" d) in
let size_px = points size in
let pos = ref height in
let thumb = Html.createDiv doc in
let style = thumb##style in
style##position <- Js.string "absolute";
style##width <- size_px;
style##height <- size_px;
style##top <- points !pos;
style##left <- Js.string "0px";
style##margin <- Js.string "1px";
style##backgroundColor <- Js.string "black";
let slider = Html.createDiv doc in
let style = slider##style in
style##position <- Js.string "absolute";
style##width <- size_px;
style##height <- points (height + size);
style##border <- Js.string "2px solid black";
style##padding <- Js.string "1px";
style##top <- Js.string "10px";
style##left <- Js.string "10px";
Dom.appendChild slider thumb;
Dom.appendChild doc##body slider;
let set_slider_position pos' =
if pos' <> !pos then begin
thumb##style##top <- points pos';
pos := pos';
sadj#set_value (float (height - pos') *. sadj#upper /. float height);
rescale 0.5 0.5
end
in
handle_drag thumb
(fun dx dy ->
set_slider_position (min height (max 0 (!pos + dy))));
slider##onmousedown <- Html.handler
(fun ev ->
let ey = ev##clientY in
let (_, sy) = Dom_html.elementClientPosition slider in
set_slider_position (max 0 (min height (ey - sy - size / 2)));
Js._false);
let adjust_slider () =
let pos' =
height - truncate (sadj#value *. float height /. sadj#upper +. 0.5) in
thumb##style##top <- points pos';
pos := pos'
in
Html.window##onresize <- Html.handler
(fun _ ->
let page = doc##documentElement in
canvas##width <- page##clientWidth;
canvas##height <- page##clientHeight;
update_view true;
Js._true);
(* Drag the graph using the mouse *)
handle_drag canvas
(fun dx dy ->
let scale = get_scale () in
let offset a d =
a#set_value
(min (a#value -. float d /. scale) (a#upper -. a#page_size)) in
offset hadj dx;
offset vadj dy;
update_view true);
let bump_scale x y v =
let a = allocation () in
let x = x /. float a.width in
let y = y /. float a.height in
let prev = sadj#value in
let vl =
min (sadj#upper) (max (sadj#lower) (prev +. v *. sadj#step_increment)) in
if vl <> prev then begin
sadj#set_value vl;
adjust_slider ();
if x >= 0. && x <= 1. && y >= 0. && y <= 1. then
rescale x y
else
rescale 0.5 0.5
end;
Js._false
in
(* Zoom using the mouse wheel *)
ignore (Html.addMousewheelEventListener canvas
(fun ev ~dx ~dy ->
let (ex, ey) = Dom_html.elementClientPosition canvas in
let x = float (ev##clientX - ex) in
let y = float (ev##clientY - ey) in
if dy < 0 then
bump_scale x y 1.
else if dy > 0 then
bump_scale x y (-1.)
else
Js._false)
Js._true);
(*
Html.addEventListener Html.document Html.Event.keydown
(Html.handler
(fun e -> Firebug.console##log(e##keyCode);
Js._true))
Js._true;
*)
(*
Html.addEventListener Html.document Html.Event.keypress
(Html.handler
(fun e ->
Firebug.console##log(Js.string "press");
match e##keyCode with
| 37 -> (* left *)
Js._false
| 38 -> (* up *)
Js._false
| 39 -> (* right *)
Js._false
| 40 -> (* down *)
Js._false
| _ ->
Firebug.console##log(- 1- e##keyCode);
Js._true))
Js._true;
*)
let handle_key_event ev =
match ev##keyCode with
37 -> (* left *)
hadj#set_value (hadj#value -. hadj#step_increment);
update_view false;
Js._false
| 38 -> (* up *)
vadj#set_value (vadj#value -. vadj#step_increment);
update_view false;
Js._false
| 39 -> (* right *)
hadj#set_value (hadj#value +. hadj#step_increment);
update_view false;
Js._false
| 40 -> (* down *)
vadj#set_value (vadj#value +. vadj#step_increment);
update_view false;
Js._false
| _ ->
(*
Firebug.console##log_2(Js.string "keycode:", ev##keyCode);
*)
Js._true
in
let ignored_keycode = ref (-1) in
Html.document##onkeydown <-
(Html.handler
(fun e ->
ignored_keycode := e##keyCode;
handle_key_event e));
Html.document##onkeypress <-
(Html.handler
(fun e ->
let k = !ignored_keycode in
ignored_keycode := -1;
if e##keyCode = k then Js._true else handle_key_event e));
(*
Firebug.console##time(Js.string "initial drawing");
*)
update_view true;
(*
Firebug.console##timeEnd(Js.string "initial drawing");
Firebug.console##timeEnd(Js.string "init");
*)
Lwt.return ()
let _ =
Html.window##onload <- Html.handler (fun _ -> ignore (start ()); Js._false)
coinst-1.9.3/viewer/viewer.ml 0000644 0001750 0001750 00000033530 12657630652 015135 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
open Scene
let pi = 4. *. atan 1.
(****)
let path_extent ctx fill stroke =
if stroke <> None then Cairo.stroke_extents ctx
else Cairo.fill_extents ctx
let compute_extent ctx e =
Cairo.new_path ctx;
match e with
Path (cmd, fill, stroke, _) ->
Array.iter
(fun c ->
match c with
Move_to (x, y) ->
Cairo.move_to ctx x y
| Curve_to (x1, y1, x2, y2, x3, y3) ->
Cairo.curve_to ctx x1 y1 x2 y2 x3 y3)
cmd;
path_extent ctx fill stroke
| Ellipse (cx, cy, rx, ry, fill, stroke, _) ->
Cairo.save ctx;
Cairo.translate ctx cx cy;
Cairo.scale ctx rx ry;
Cairo.arc ctx 0. 0. 1. 0. (2. *. pi);
Cairo.restore ctx;
path_extent ctx fill stroke
| Polygon (points, fill, stroke, _) ->
Array.iteri
(fun i (x, y) ->
if i = 0 then Cairo.move_to ctx x y else Cairo.line_to ctx x y)
points;
Cairo.close_path ctx;
path_extent ctx fill stroke
| Text (x, y, txt, (font, font_size), fill, stroke) ->
Cairo.select_font_face ctx font
Cairo.FONT_SLANT_NORMAL Cairo.FONT_WEIGHT_NORMAL;
Cairo.set_font_size ctx font_size;
let ext = Cairo.text_extents ctx txt in
(x -. ext.Cairo.text_width /. 2. -. 5.,
y +. ext.Cairo.y_bearing -. 5.,
x +. ext.Cairo.text_width /. 2. +. 5.,
y +. ext.Cairo.y_bearing +. ext.Cairo.text_height +. 5.)
(****)
module Common = Viewer_common.F (struct
type font = string * float
type color = float * float * float
type text = string
let white = (1., 1., 1.)
type ctx = Cairo.t
let save = Cairo.save
let restore = Cairo.restore
let scale = Cairo.scale
let translate = Cairo.translate
let set_line_width = Cairo.set_line_width
let begin_path = Cairo.new_path
let close_path = Cairo.close_path
let move_to = Cairo.move_to
let line_to = Cairo.line_to
let curve_to = Cairo.curve_to
let arc = Cairo.arc
let rectangle = Cairo.rectangle
let fill ctx (r, g, b) =
Cairo.set_source_rgb ctx r g b; Cairo.fill_preserve ctx
let stroke ctx (r, g, b) =
Cairo.set_source_rgb ctx r g b; Cairo.stroke_preserve ctx
let clip = Cairo.clip
let perform_draw ctx fill_color stroke_color =
begin match fill_color with
Some c -> fill ctx c
| None -> ()
end;
begin match stroke_color with
Some c -> stroke ctx c
| None -> ()
end
let draw_text ctx x y txt (font, font_size) fill stroke =
Cairo.select_font_face ctx font
Cairo.FONT_SLANT_NORMAL Cairo.FONT_WEIGHT_NORMAL;
Cairo.set_font_size ctx font_size;
let fext = Cairo.font_extents ctx in
let ext = Cairo.text_extents ctx txt in
let dy = (fext.Cairo.ascent -. fext.Cairo.descent) /. 2. in
Cairo.move_to ctx
(x -. ext.Cairo.x_bearing -. ext.Cairo.text_width /. 2.) (y +. dy);
Cairo.show_text ctx txt;
perform_draw ctx fill stroke
type window = GMisc.drawing_area
type drawable = GDraw.drawable
type pixmap = GDraw.pixmap
let get_drawable w = new GDraw.drawable (w#misc#window)
let make_pixmap window width height =
GDraw.pixmap ~width ~height ~window ()
let drawable_of_pixmap p = (p : GDraw.pixmap :> GDraw.drawable)
let get_context p = Cairo_lablgtk.create p#pixmap
let put_pixmap ~(dst : GDraw.drawable) ~x ~y ~xsrc ~ysrc ~width ~height p =
dst#put_pixmap ~x ~y ~xsrc ~ysrc ~width ~height p#pixmap;
(****)
type rectangle = Gtk.rectangle = {x : int; y : int; width : int; height: int}
let compute_extents = Scene_extents.compute
end)
open Common
(****)
let set_visible w vis =
if vis then begin
if not w#misc#visible then w#misc#show ()
end else begin
if w#misc#visible then w#misc#hide ()
end
let scroll_view ?width ?height ?packing st =
let table = GPack.table ?width ?height ~columns:2 ~rows:2 ?packing () in
let hadj = GData.adjustment () in
let hbar =
GRange.scrollbar `HORIZONTAL ~adjustment:hadj
~packing:(table#attach ~left:0 ~top:1 ~fill:`BOTH ~expand:`NONE) () in
hbar#misc#hide ();
let vadj = GData.adjustment () in
let vbar =
GRange.scrollbar `VERTICAL ~adjustment:vadj
~packing:(table#attach ~left:1 ~top:0 ~fill:`BOTH ~expand:`NONE) () in
vbar#misc#hide ();
let display =
GMisc.drawing_area
~packing:(table#attach ~left:0 ~top:0 ~fill:`BOTH ~expand:`BOTH) () in
display#misc#set_can_focus true;
display#misc#set_double_buffered false;
let sadj =
GData.adjustment ~upper:20. ~step_incr:1. ~page_incr:1. ~page_size:0. () in
let zoom_steps = 8. in (* Number of steps to get a factor of 2 *)
let set_zoom_factor f =
let count = ceil (log f /. log 2. *. zoom_steps) in
let f = 2. ** (count /. zoom_steps) in
sadj#set_bounds ~upper:count ();
Format.eprintf "Factor: %f@." f;
st.zoom_factor <- f
in
let get_scale () = 2. ** (sadj#value /. zoom_steps) /. st.zoom_factor in
let update_scrollbars () =
let a = display#misc#allocation in
let scale = get_scale () in
let aw = ceil (float a.Gtk.width /. scale) in
let ah = ceil (float a.Gtk.height /. scale) in
hadj#set_bounds ~step_incr:(aw /. 20.) ~page_incr:(aw /. 2.)
~page_size:(min aw st.st_width) ~upper:st.st_width ();
let mv = st.st_width -. hadj#page_size in
if hadj#value > mv then hadj#set_value mv;
vadj#set_bounds ~step_incr:(ah /. 20.) ~page_incr:(ah /. 2.)
~page_size:(min ah st.st_height) ~upper:st.st_height ();
let mv = st.st_height -. vadj#page_size in
if vadj#value > mv then vadj#set_value mv;
set_visible hbar (aw < st.st_width);
set_visible vbar (ah < st.st_height)
in
let refresh () =
invalidate_pixmap st.st_pixmap;
GtkBase.Widget.queue_draw display#as_widget
in
ignore (display#event#connect#configure
(fun ev ->
prerr_endline "CONFIGURE";
update_scrollbars (); false));
ignore (display#event#connect#map
(fun ev ->
let a = display#misc#allocation in
Format.eprintf "alloc: %d %d@." a.Gtk.width a.Gtk.height;
let zoom_factor =
max (st.st_width /. float a.Gtk.width)
(st.st_height /. float a.Gtk.height)
in
set_zoom_factor zoom_factor;
refresh ();
update_scrollbars (); false));
display#event#add [`STRUCTURE];
ignore (display#event#connect#expose
(fun ev ->
let area = GdkEvent.Expose.area ev in
let x = Gdk.Rectangle.x area in
let y = Gdk.Rectangle.y area in
let width = Gdk.Rectangle.width area in
let height = Gdk.Rectangle.height area in
redraw st (get_scale ()) hadj#value vadj#value
display display#misc#allocation x y width height;
true));
ignore (hadj#connect#value_changed
(fun () -> GtkBase.Widget.queue_draw display#as_widget));
ignore (vadj#connect#value_changed
(fun () -> GtkBase.Widget.queue_draw display#as_widget));
let prev_scale = ref (get_scale ()) in
let zoom_center = ref (0.5, 0.5) in
ignore (sadj#connect#value_changed
(fun () ->
let scale = get_scale () in
let r = (1. -. !prev_scale /. scale) in
Format.eprintf "update@.";
hadj#set_value (hadj#value +. hadj#page_size *. r *. fst !zoom_center);
vadj#set_value (vadj#value +. vadj#page_size *. r *. snd !zoom_center);
prev_scale := scale;
refresh ();
update_scrollbars ()));
let bump_scale x y v =
let a = display#misc#allocation in
let x = x /. float a.Gtk.width in
let y = y /. float a.Gtk.height in
if x >= 0. && x <= 1. && y >= 0. && y <= 1. then
zoom_center := (x, y);
Format.eprintf "loc: %f %f@." x y;
sadj#set_value (sadj#value +. v *. sadj#step_increment);
Format.eprintf "reset@.";
zoom_center := (0.5, 0.5);
true
in
(* Zoom using the mouse wheel *)
ignore (display#event#connect#scroll
(fun ev ->
let x = GdkEvent.Scroll.x ev in
let y = GdkEvent.Scroll.y ev in
match GdkEvent.Scroll.direction ev with
`UP -> bump_scale x y 1.
| `DOWN -> bump_scale x y (-1.)
| _ -> false));
display#event#add [`SCROLL];
let pos = ref None in
ignore (display#event#connect#button_press
(fun ev ->
display#misc#grab_focus ();
if
GdkEvent.get_type ev = `BUTTON_PRESS && GdkEvent.Button.button ev = 1
then begin
pos := Some (GdkEvent.Button.x ev, GdkEvent.Button.y ev);
end;
false));
ignore (display#event#connect#button_release
(fun ev ->
if GdkEvent.Button.button ev = 1 then begin
pos := None;
end;
false));
ignore (display#event#connect#motion_notify
(fun ev ->
begin match !pos with
Some (x, y) ->
let (x', y') =
if GdkEvent.Motion.is_hint ev then
let (x', y') = display#misc#pointer in
(float x', float y')
else
(GdkEvent.Motion.x ev, GdkEvent.Motion.y ev)
in
let offset a d =
a#set_value (min (a#value +. d) (a#upper -. a#page_size)) in
let scale = get_scale () in
offset (hadj) ((x -. x') /. scale);
offset (vadj) ((y -. y') /. scale);
pos := Some (x', y')
| None ->
()
end;
false));
display#event#add
[`BUTTON_PRESS; `BUTTON_RELEASE; `BUTTON1_MOTION; `POINTER_MOTION_HINT];
ignore (display#event#connect#key_press
(fun ev ->
let keyval = GdkEvent.Key.keyval ev in
if
keyval = GdkKeysyms._Up
then begin
vadj#set_value (vadj#value -. vadj#step_increment);
update_scrollbars ();
true
end else if
keyval = GdkKeysyms._Down
then begin
vadj#set_value (vadj#value +. vadj#step_increment);
update_scrollbars ();
true
end else if
keyval = GdkKeysyms._Left
then begin
hadj#set_value (hadj#value -. hadj#step_increment);
update_scrollbars ();
true
end else if
keyval = GdkKeysyms._Right
then begin
hadj#set_value (hadj#value +. hadj#step_increment);
update_scrollbars ();
true
end else if
keyval = GdkKeysyms._Page_Up
then begin
vadj#set_value (vadj#value -. vadj#page_increment);
update_scrollbars ();
true
end else if
keyval = GdkKeysyms._Page_Down
then begin
vadj#set_value (vadj#value +. vadj#page_increment);
update_scrollbars ();
true
end else if
keyval = GdkKeysyms._0 || keyval = GdkKeysyms._agrave
then begin
let a = table#misc#allocation in
Format.eprintf "alloc: %d %d@." a.Gtk.width a.Gtk.height;
let zf =
max (st.st_width /. float a.Gtk.width)
(st.st_height /. float a.Gtk.height)
in
let v = ceil (log zf /. log 2. *. zoom_steps) in
Format.eprintf "ZOOM: %f %f %f@." zf v sadj#upper;
sadj#set_value (min sadj#upper (max 0. (sadj#upper -. v)));
true
end else if
keyval = GdkKeysyms._1 || keyval = GdkKeysyms._ampersand
then begin
sadj#set_value (sadj#upper);
true
end else if
keyval = GdkKeysyms._plus ||
keyval = GdkKeysyms._equal ||
keyval = GdkKeysyms._KP_Add
then begin
let (x, y) = display#misc#pointer in
bump_scale (float x) (float y) 1.
end else if
keyval = GdkKeysyms._minus ||
keyval = GdkKeysyms._KP_Subtract
then begin
let (x, y) = display#misc#pointer in
bump_scale (float x) (float y) (-1.)
end else
false));
display#event#add [`KEY_PRESS];
object
method scale_adjustment = sadj
end
let create ?(full_screen=false) (x1, y1, x2, y2) scene =
let st =
{ bboxes = [||]; scene = Scene.get scene; zoom_factor = 20.;
st_x = x1; st_y = y1; st_width = x2 -. x1; st_height = y2 -. y1;
st_pixmap = make_pixmap () } in
let initial_size = 600 in
let w = GWindow.window () in
ignore (w#connect#destroy GMain.quit);
let b = GPack.hbox ~packing:w#add () in
let f =
scroll_view ~width:initial_size ~height:initial_size
~packing:(b#pack ~expand:true) st in
ignore
(GRange.scale `VERTICAL ~inverted:true ~draw_value:false
~adjustment:(f#scale_adjustment) ~packing:b#pack ());
(*XXX Tooltips
area#misc#set_has_tooltip true;
ignore (area#misc#connect#query_tooltip (fun ~x ~y ~kbd tooltip ->
Format.eprintf "%d %d %b@." x y kbd; false));
*)
(* Full screen mode *)
let fullscreen = ref false in
let toggle_fullscreen () =
if !fullscreen then w#unfullscreen () else w#fullscreen ();
fullscreen := not !fullscreen;
true
in
if full_screen then ignore (toggle_fullscreen ());
ignore (w#event#connect#key_press
(fun ev ->
let keyval = GdkEvent.Key.keyval ev in
if keyval = GdkKeysyms._q || keyval = GdkKeysyms._Q then
exit 0
else if
keyval = GdkKeysyms._F11 ||
keyval = GdkKeysyms._F5 ||
(keyval = GdkKeysyms._Escape && !fullscreen) ||
keyval = GdkKeysyms._f || keyval = GdkKeysyms._F
then
toggle_fullscreen ()
else
false));
w#show ()
coinst-1.9.3/viewer/viewer.mli 0000644 0001750 0001750 00000001647 12657630652 015312 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
val create :
?full_screen:bool -> float * float * float * float -> Scene.cairo_t -> unit
coinst-1.9.3/viewer/scene_json.mli 0000644 0001750 0001750 00000002162 12657630652 016130 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
val rect_stringify : Format.formatter -> float * float * float * float -> unit
val rect_array_stringify :
Format.formatter -> (float * float * float * float) array -> unit
val stringify :
Format.formatter ->
(float * float * float, string * float, string) Scene.element array ->
unit
coinst-1.9.3/viewer/scene.ml 0000644 0001750 0001750 00000003263 12657630652 014731 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
type command =
Move_to of float * float
| Curve_to of float * float * float * float * float * float
type color = float * float * float
type ('color, 'font, 'text) element =
Path of command array * 'color option * 'color option * string
| Polygon of (float * float) array * 'color option * 'color option * string
| Ellipse of
float * float * float * float * 'color option * 'color option * string
| Text of float * float * 'text * 'font * 'color option * 'color option
(****)
let rectangle (x1, y1, x2, y2) fill stroke style =
Polygon ([|(x1, y1); (x2, y1); (x2, y2); (x1, y2)|], fill, stroke, style)
(****)
type ('color, 'font, 'text) t = ('color, 'font, 'text) element list ref
type cairo_t = (float * float * float, string * float, string) t
let make () = ref []
let add sc e = sc := e :: !sc
let get sc = Array.of_list (List.rev !sc)
coinst-1.9.3/viewer/dot_graph.ml 0000644 0001750 0001750 00000017507 12657630652 015611 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
module IntSet =
Set.Make (struct type t = int let compare (x : int) y = compare x y end)
module IntMap =
Map.Make (struct type t = int let compare (x : int) y = compare x y end)
type id = int
module IdMap = IntMap
let last_id = ref (-1)
let fresh_id () = incr last_id; !last_id
type 'a sequence =
{ mutable count : int;
mutable seq : 'a IntMap.t;
id : (id, 'a) Hashtbl.t }
let make_sequence () =
{ count = 0;
seq = IntMap.empty;
id = Hashtbl.create 17 }
let sequence_add s id v =
if not (Hashtbl.mem s.id id) then begin
let n = s.count in
s.count <- n + 1;
s.seq <- IntMap.add n v s.seq;
Hashtbl.add s.id id v
end
module StringMap = Map.Make (String)
type node =
{ name : string;
id : id;
mutable node_attr : string StringMap.t }
type edge =
{ head : node;
tail : node;
edge_id : id;
mutable edge_attr : string StringMap.t }
type def_attr =
{ mutable g_attr : string StringMap.t;
mutable n_attr : string StringMap.t;
mutable e_attr : string StringMap.t }
type graph =
{ graph_id : id;
graph_name : string option;
mutable graph_attr : string StringMap.t;
subgraphs : graph sequence;
nodes : node sequence;
edges : edge sequence;
parents : (id, graph) Hashtbl.t }
type info =
{ kind : [`Graph | `Digraph];
strict : bool }
type st =
{ st_info : info;
st_graphs : (string, graph) Hashtbl.t;
st_nodes : (string, node) Hashtbl.t;
st_edges : (string * string * string, edge) Hashtbl.t }
let make_def_attr () =
{ g_attr = StringMap.empty;
n_attr = StringMap.empty;
e_attr = StringMap.empty }
let clone_def_attr a =
{ g_attr = a.g_attr; n_attr = a.n_attr; e_attr = a.e_attr }
let rec all_parents s g =
if IntMap.mem g.graph_id s then s else
Hashtbl.fold (fun _ g s -> all_parents s g)
g.parents (IntMap.add g.graph_id g s)
let insert_graph parent g =
if not (IntMap.mem g.graph_id (all_parents IntMap.empty parent)) then begin
Hashtbl.add g.parents parent.graph_id parent;
sequence_add parent.subgraphs g.graph_id g
end
let make_graph parent name def_attrs =
let g =
{ graph_id = fresh_id ();
graph_name = name;
graph_attr = def_attrs.g_attr;
subgraphs = make_sequence ();
nodes = make_sequence ();
edges = make_sequence ();
parents = Hashtbl.create 17 }
in
begin match parent with
Some parent -> insert_graph parent g
| None -> ()
end;
g
let insert_node g n =
let p = all_parents IntMap.empty g in
IntMap.iter (fun _ g -> sequence_add g.nodes n.id n) p
let make_node g name def_attrs =
let node =
{ name = name;
id = fresh_id ();
node_attr = def_attrs.n_attr }
in
insert_node g node;
node
let insert_edge g e =
let p = all_parents IntMap.empty g in
IntMap.iter (fun _ g -> sequence_add g.edges e.edge_id e) p
let make_edge g n1 n2 attrs =
let edge =
{ tail = n1; head = n2;
edge_id = fresh_id ();
edge_attr = attrs }
in
insert_edge g edge;
edge
(****)
let find_graph st parent name def_attrs =
match name with
Some nm when Hashtbl.mem st.st_graphs nm ->
let g = Hashtbl.find st.st_graphs nm in
begin match parent with
Some parent -> insert_graph parent g
| None -> ()
end;
g
| _ ->
let g = make_graph parent name def_attrs in
begin match name with
Some nm -> Hashtbl.add st.st_graphs nm g
| None -> ()
end;
g
let find_node st g name def_attrs =
try
let n = Hashtbl.find st.st_nodes name in
insert_node g n;
n
with Not_found ->
let n = make_node g name def_attrs in
Hashtbl.add st.st_nodes name n;
n
let lookup_edge st n1 n2 key =
try
Hashtbl.find st.st_edges (n1.name, n2.name, key)
with Not_found when st.st_info.kind = `Graph ->
Hashtbl.find st.st_edges (n2.name, n1.name, key)
let find_edge st g n1 n2 key attrs =
let key = if st.st_info.strict then Some "" else key in
try
let key =
match key with
Some k -> k
| None -> raise Not_found
in
let e = lookup_edge st n1 n2 key in
insert_edge g e;
e
with Not_found ->
let e = make_edge g n1 n2 attrs in
begin match key with
Some key -> Hashtbl.add st.st_edges (n1.name, n2.name, key) e
| None -> ()
end;
e
(****)
let add_attributes def l =
List.fold_left (fun s (nm, v) -> StringMap.add nm v s) def l
let get_edges x =
match x with
`Node (n, p) ->
(IntMap.add 0 n IntMap.empty, p)
| `Graph gr ->
(gr.nodes.seq, None)
let opt_add nm v m =
match v with
Some v -> StringMap.add nm v m
| None -> m
let add_edge st g n1 p1 n2 p2 key attrs =
let attrs = opt_add "tailport" p1 (opt_add "headport" p2 attrs) in
ignore (find_edge st g n1 n2 key attrs)
let rec add_edges st g x r key attrs =
match r with
[] ->
()
| y :: r ->
let (s1, p1) = get_edges x in
let (s2, p2) = get_edges y in
IntMap.iter
(fun _ n1 ->
IntMap.iter
(fun _ n2 -> add_edge st g n1 p1 n2 p2 key attrs) s2)
s1;
add_edges st g y r key attrs
let rec compound_to_graph st g def_attr (c, attr) =
let c =
List.map
(fun s ->
match s with
`Node node ->
`Node (find_node st g node.Dot_file.name def_attr,
node.Dot_file.port)
| `Graph gr ->
`Graph (graph_def_to_graph st (Some g) def_attr gr))
c
in
match c with
[] ->
assert false
| [`Node (n, _)] ->
n.node_attr <- add_attributes n.node_attr attr
| [`Graph _] ->
()
| x :: r ->
let attrs = add_attributes def_attr.e_attr attr in
let key =
try Some (StringMap.find "key" attrs) with Not_found -> None
in
add_edges st g x r key attrs
and body_to_graph st g def_attr body =
List.iter
(fun stmt ->
match stmt with
`Compound c ->
compound_to_graph st g def_attr c
| `Attributes (typ, l) ->
match typ with
`Graph -> def_attr.g_attr <-
add_attributes def_attr.g_attr l
| `Node -> def_attr.n_attr <-
add_attributes def_attr.n_attr l
| `Edge -> def_attr.e_attr <-
add_attributes def_attr.e_attr l)
body
and graph_def_to_graph st g def_attr gr =
let g = find_graph st g gr.Dot_file.graph_name def_attr in
let def_attr = clone_def_attr def_attr in
body_to_graph st g def_attr gr.Dot_file.body;
g.graph_attr <- def_attr.g_attr;
g
let of_file_spec f =
let st =
{ st_info = { kind = f.Dot_file.kind; strict = f.Dot_file.strict };
st_graphs = Hashtbl.create 101;
st_nodes = Hashtbl.create 101;
st_edges = Hashtbl.create 101 }
in
(st.st_info, graph_def_to_graph st None (make_def_attr ()) f.Dot_file.graph)
let of_channel c =
Dot_lexer.reset ();
let g = Dot_parser.graph Dot_lexer.token (Lexing.from_channel c) in
of_file_spec g
let from_lexbuf lb =
Dot_lexer.reset ();
let g = Dot_parser.graph Dot_lexer.token lb in
of_file_spec g
coinst-1.9.3/viewer/scene.mli 0000644 0001750 0001750 00000003356 12657630652 015105 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
type command =
Move_to of float * float
| Curve_to of float * float * float * float * float * float
type color = float * float * float
type ('color, 'font, 'text) element =
Path of command array * 'color option * 'color option * string
| Polygon of (float * float) array * 'color option * 'color option * string
| Ellipse of
float * float * float * float * 'color option * 'color option * string
| Text of float * float * 'text * 'font * 'color option * 'color option
(****)
val rectangle :
float * float * float * float -> 'color option -> 'color option -> string ->
('color, 'font, 'text) element
(****)
type ('color, 'font, 'text) t
type cairo_t = (float * float * float, string * float, string) t
val make : unit -> ('color, 'font, 'text) t
val add : ('color, 'font, 'text) t -> ('color, 'font, 'text) element -> unit
val get : ('color, 'font, 'text) t -> ('color, 'font, 'text) element array
coinst-1.9.3/viewer/converter.ml 0000644 0001750 0001750 00000004153 12657630652 015642 0 ustar mehdi mehdi (* Graph viewer
* Copyright (C) 2010 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* This program is free software; you can redistribute it and/or modify
* it under the terms of the GNU General Public License as published by
* the Free Software Foundation; either version 2 of the License, or
* (at your option) any later version.
*
* This program is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
* GNU Lesser General Public License for more details.
*
* You should have received a copy of the GNU Lesser General Public License
* along with this program; if not, write to the Free Software
* Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
*)
open Scene
let offset_command x y c =
match c with
Move_to (x1, y1) ->
Move_to (x1 -. x, y1 -. y)
| Curve_to (x1, y1, x2, y2, x3, y3) ->
Curve_to (x1 -. x, y1 -. y, x2 -. x , y2 -. y, x3 -. x , y3 -. y)
let offset_element x y e =
match e with
Path (cmds, c1, c2, style) ->
Path (Array.map (fun c -> offset_command x y c) cmds, c1, c2, style)
| Polygon (pts, c1, c2, style) ->
Polygon
(Array.map (fun (x1, y1) -> (x1 -. x, y1 -. y)) pts, c1, c2, style)
| Ellipse (cx, cy, rx, ry, c1, c2, style) ->
Ellipse (cx -. x, cy -. y, rx, ry, c1, c2, style)
| Text (x1, y1, txt, font, c1, c2) ->
Text (x1 -. x, y1 -. y, txt, font, c1, c2)
let _ =
let ch = if Array.length Sys.argv > 1 then open_in Sys.argv.(1) else stdin in
let (_, g) = Dot_graph.of_channel ch in
let (bbox, scene) = Dot_render.f g in
let (x1, y1, x2, y2) = bbox in
let l = Scene.get scene in
let l = Array.map (fun e -> offset_element x1 y1 e) l in
let bbox = (0., 0., x2 -. x1, y2 -. y1) in
let i = Cairo.image_surface_create Cairo.FORMAT_ARGB32 1024 1024 in
let bboxes = Scene_extents.compute (Cairo.create i) l in
Format.printf "@[<1>[0,@,%a,@,%a,@,%a]@]@."
Scene_json.rect_stringify bbox
Scene_json.rect_array_stringify bboxes
Scene_json.stringify l
coinst-1.9.3/upgrade_main.ml 0000644 0001750 0001750 00000005034 12657630652 014764 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
(*
TODO (?)
- List broken new packages!
- Does it make sense to consider new packages as previously
installable, and report issues for them in a uniform way?
- Print equivalence classes
*)
let broken_sets = Upgrade_common.empty_break_set ()
let (file1,file2) =
("snapshots/updates/stable", "snapshots/updates/testing")
(*
("snapshots/updates/oldstable", "snapshots/updates/stable")
("/tmp/last_month", "/tmp/new")
*)
let _ =
let output_file = ref "/tmp/upgrade.html" in
let l = ref [] in
let popcon_file = ref None in
let spec =
Arg.align
["-o",
Arg.String (fun d -> output_file := d),
"FILE Write output to file FILE";
"--break",
Arg.String (Upgrade_common.allow_broken_sets broken_sets),
"SETS Ignore broken sets of packages of shape SETS";
"--popcon",
Arg.String (fun s -> popcon_file := Some s),
"FILE Use popcon data from FILE";
"--debug",
Arg.String Debug.set,
"NAME Activate debug option NAME"]
in
Arg.parse spec (fun f -> l := f :: !l)
("Usage: " ^ Sys.argv.(0) ^ " OPTIONS FILE1 FILE2\n\
Takes two Debian binary package control files as input and computes\n\
a core set of packages that were co-installable but are not anymore\n\
after upgrade.\n\
\n\
Options:");
let (file1, file2) =
match List.rev !l with
[] -> (file1, file2)
| [file1; file2] -> (file1, file2)
| _ ->
Format.eprintf
"Exactly two Debian binary package control files \
should be provided as input.@.";
exit 1
in
if Sys.command "dot -V 2> /dev/null" <> 0 then begin
Format.eprintf "Could not execute Graphviz 'dot' command.@.";
exit 1
end;
let dist1 = Upgrade.read_data file1 in
let dist2 = Upgrade.read_data file2 in
Upgrade.f broken_sets dist1 dist2 ?popcon_file:!popcon_file !output_file
coinst-1.9.3/deb_lib.mli 0000644 0001750 0001750 00000010161 12657630652 014057 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2005-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
type rel
type package_name
type version
type 'a dep = ('a * (rel * version) option) list
type deps = package_name dep list
type deb_reason =
R_conflict of int * int * (int * package_name dep) option
| R_depends of int * package_name dep
type p =
{ mutable num : int;
mutable package : package_name;
mutable version : version;
mutable source : package_name * version;
mutable section : string;
mutable architecture : string;
mutable depends : deps;
mutable recommends : deps;
mutable suggests : deps;
mutable enhances : deps;
mutable pre_depends : deps;
mutable provides : deps;
mutable conflicts : deps;
mutable breaks : deps;
mutable replaces : deps }
type deb_pool
include Api.S with type reason = deb_reason and type pool = deb_pool
type dict
val name_of_id : package_name -> string
val id_of_name : string -> package_name
val add_name : string -> package_name
val name_exists : string -> bool
val valid_directory : dict -> bool
(* Check whether the given dictionary is an extension of the current one *)
val set_dict : dict -> unit
val current_dict : unit -> dict
module PkgTbl : Hashtbl.S with type key = package_name
module PkgDenseTbl : sig
type 'a t
val create : 'a -> 'a t
val add : 'a t -> package_name -> 'a -> unit
val replace : 'a t -> package_name -> 'a -> unit
val find : 'a t -> package_name -> 'a
val mem : 'a t -> package_name -> bool
val remove : 'a t -> package_name -> unit
val iteri : (package_name -> 'a -> unit) -> 'a t -> unit
end
module PkgSet : Set.S with type elt = package_name
val find_package_by_num : pool -> int -> p
val find_packages_by_name : pool -> package_name -> p list
val has_package_of_name : pool -> package_name -> bool
val find_provided_packages : pool -> package_name -> p list
val iter_packages : pool -> (p -> unit) -> unit
val iter_packages_by_name : pool -> (package_name -> p list -> unit) -> unit
val pool_size : pool -> int
val package_name : pool -> int -> string
val resolve_package_dep :
pool -> package_name * (rel * version) option -> int list
val resolve_package_dep_raw :
pool -> package_name * (rel * version) option -> p list
val dep_can_be_satisfied :
pool -> package_name * (rel * version) option -> bool
val copy : pool -> pool
val merge : pool -> (p -> bool) -> pool -> unit
val only_latest : pool -> pool
val add_package : pool -> p -> int
val remove_package : pool -> p -> unit
val replace_package : pool -> p -> p -> unit
val parse_version : string -> version
val print_version : Format.formatter -> version -> unit
val compare_version : version -> version -> int
val string_of_version : version -> string
type s =
{ mutable s_name : package_name;
mutable s_version : version;
mutable s_section : string;
mutable s_binary : package_name list;
mutable s_extra_source : bool }
type s_pool
val find_source_by_name : s_pool -> package_name -> s
val has_source : s_pool -> package_name -> bool
val iter_sources : (s -> unit) -> s_pool -> unit
val remove_source : s_pool -> package_name -> unit
val add_source : s_pool -> s -> unit
val new_src_pool : unit -> s_pool
val parse_src_packages : s_pool -> in_channel -> unit
val src_only_latest : s_pool -> s_pool
val generate_rules_restricted : pool -> Util.IntSet.t -> Solver.state
val print_package_dependency : Format.formatter -> string dep list -> unit
coinst-1.9.3/quotient.mli 0000644 0001750 0001750 00000004337 12657630652 014357 0 ustar mehdi mehdi (* Co-installability tools
* http://coinst.irill.org/
* Copyright (C) 2010-2011 Jérôme Vouillon
* Laboratoire PPS - CNRS Université Paris Diderot
*
* These programs are free software; you can redistribute them and/or
* modify them under the terms of the GNU General Public License as
* published by the Free Software Foundation; either version 2 of the
* License, or (at your option) any later version.
*
* This program is distributed in the hope that it will be useful, but
* WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Lesser General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this program. If not, see .
*)
module S (R : Repository.S) : sig
module type S = sig
open R
type t
val perform : pool -> ?packages:PSet.t -> Formula.t PTbl.t -> t
val trivial : pool -> t
val subset : pool -> PSet.t -> t
val from_partition : pool -> PSet.t -> Package.t list list -> t
val formula : t -> Formula.t -> Formula.t
val dependencies : t -> dependencies -> dependencies
val conflicts : t -> Conflict.t -> Conflict.t
val package_set : t -> PSet.t -> PSet.t
val iter : (Package.t -> unit) -> t -> unit
val print : t -> dependencies -> unit
val print_class : t -> Format.formatter -> Package.t -> unit
val clss : t -> Package.t -> PSet.t
val class_size : t -> Package.t -> int
val pool : t -> pool
end
end
module F (R : Repository.S) : sig
open R
type t
val perform : pool -> ?packages:PSet.t -> Formula.t PTbl.t -> t
val trivial : pool -> t
val subset : pool -> PSet.t -> t
val from_partition : pool -> PSet.t -> Package.t list list -> t
val formula : t -> Formula.t -> Formula.t
val dependencies : t -> dependencies -> dependencies
val conflicts : t -> Conflict.t -> Conflict.t
val package_set : t -> PSet.t -> PSet.t
val iter : (Package.t -> unit) -> t -> unit
val print : t -> dependencies -> unit
val print_class : t -> Format.formatter -> Package.t -> unit
val clss : t -> Package.t -> PSet.t
val class_size : t -> Package.t -> int
val pool : t -> pool
end