diff options
58 files changed, 4938 insertions, 3550 deletions
| diff --git a/.travis.yml b/.travis.yml index 282f1302..6c03b451 100644 --- a/.travis.yml +++ b/.travis.yml @@ -11,8 +11,6 @@ addons:  cache: packages  repos:    CRAN: https://cloud.r-project.org -r_github_packages: -  - saemixdevelopment/saemixextension@master  script:    - R CMD build .    - R CMD check --no-tests mkin_*.tar.gz diff --git a/DESCRIPTION b/DESCRIPTION index dd57aefa..15871070 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@  Package: mkin  Type: Package  Title: Kinetic Evaluation of Chemical Degradation Data -Version: 1.0.1 +Version: 1.0.1.9000  Date: 2021-02-06  Authors@R: c(    person("Johannes", "Ranke", role = c("aut", "cre", "cph"), @@ -19,9 +19,10 @@ Description: Calculation routines based on the FOCUS Kinetics Report (2006,    particular purpose.  Depends: R (>= 2.15.1), parallel  Imports: stats, graphics, methods, deSolve, R6, inline (>= 0.3.17), numDeriv, -  lmtest, pkgbuild, nlme (>= 3.1-151), purrr +  lmtest, pkgbuild, nlme (>= 3.1-151), purrr, saemix (>= 3.1.9000)  Suggests: knitr, rbenchmark, tikzDevice, testthat, rmarkdown, covr, vdiffr,    benchmarkme, tibble, stats4 +Remotes: github::saemixdevelopment/saemixextension  License: GPL  LazyLoad: yes  LazyData: yes @@ -30,11 +30,15 @@ S3method(print,mkinmod)  S3method(print,mmkin)  S3method(print,nafta)  S3method(print,nlme.mmkin) +S3method(print,saem.mmkin)  S3method(print,summary.mkinfit)  S3method(print,summary.nlme.mmkin) +S3method(print,summary.saem.mmkin)  S3method(residuals,mkinfit) +S3method(saem,mmkin)  S3method(summary,mkinfit)  S3method(summary,nlme.mmkin) +S3method(summary,saem.mmkin)  S3method(update,mkinfit)  S3method(update,mmkin)  S3method(update,nlme.mmkin) @@ -86,6 +90,9 @@ export(parms)  export(plot_err)  export(plot_res)  export(plot_sep) +export(saem) +export(saemix_data) +export(saemix_model)  export(sigma_twocomp)  export(transform_odeparms)  import(deSolve) @@ -126,5 +133,6 @@ importFrom(stats,residuals)  importFrom(stats,rnorm)  importFrom(stats,shapiro.test)  importFrom(stats,update) +importFrom(stats,vcov)  importFrom(utils,getFromNamespace)  importFrom(utils,write.table) @@ -1,3 +1,13 @@ +# mkin 1.0.1.9000 + +- Switch to a versioning scheme where the fourth version component indicates development versions + +- Reintroduce the interface to the current development version of saemix, in particular: + +- 'saemix_model' and 'saemix_data': Helper functions to set up nonlinear mixed-effects models for mmkin row objects + +- 'saem': generic function to fit saemix models using 'saemix_model' and 'saemix_data', with a generator 'saem.mmkin', summary and plot methods +  # mkin 1.0.1  - 'confint.mmkin', 'nlme.mmkin', 'transform_odeparms': Fix example code in dontrun sections that failed with current defaults diff --git a/R/endpoints.R b/R/endpoints.R index b5872e68..f1f47581 100644 --- a/R/endpoints.R +++ b/R/endpoints.R @@ -10,8 +10,8 @@  #' Additional DT50 values are calculated from the FOMC DT90 and k1 and k2 from  #' HS and DFOP, as well as from Eigenvalues b1 and b2 of any SFORB models  #' -#' @param fit An object of class [mkinfit] or [nlme.mmkin]  -#'  or another object that has list components +#' @param fit An object of class [mkinfit], [nlme.mmkin] or +#'  [saem.mmkin]. Or another object that has list components  #'  mkinmod containing an [mkinmod] degradation model, and two numeric vectors,  #'  bparms.optim and bparms.fixed, that contain parameter values  #'  for that model. @@ -20,8 +20,8 @@  #'   and, if applicable, a vector of formation fractions named ff  #'   and, if the SFORB model was in use, a vector of eigenvalues  #'   of these SFORB models, equivalent to DFOP rate constants -#' @note The function is used internally by [summary.mkinfit] -#'   and [summary.nlme.mmkin] +#' @note The function is used internally by [summary.mkinfit], +#'   [summary.nlme.mmkin] and [summary.saem.mmkin].  #' @author Johannes Ranke  #' @examples  #' diff --git a/R/plot.mixed.mmkin.R b/R/plot.mixed.mmkin.R index 5a0b7412..1674d855 100644 --- a/R/plot.mixed.mmkin.R +++ b/R/plot.mixed.mmkin.R @@ -2,7 +2,7 @@ utils::globalVariables("ds")  #' Plot predictions from a fitted nonlinear mixed model obtained via an mmkin row object  #' -#' @param x An object of class [mixed.mmkin], [nlme.mmkin] +#' @param x An object of class [mixed.mmkin], [saem.mmkin] or [nlme.mmkin]  #' @param i A numeric index to select datasets for which to plot the individual predictions,  #'   in case plots get too large  #' @inheritParams plot.mkinfit @@ -39,6 +39,15 @@ utils::globalVariables("ds")  #' f_nlme <- nlme(f, control = list(pnlsMaxIter = 120, tolerance = 1e-3))  #' plot(f_nlme)  #' +#' f_saem <- saem(f, transformations = "saemix") +#' plot(f_saem) +#' +#' # We can overlay the two variants if we generate predictions +#' pred_nlme <- mkinpredict(dfop_sfo, +#'   f_nlme$bparms.optim[-1], +#'   c(parent = f_nlme$bparms.optim[[1]], A1 = 0), +#'   seq(0, 180, by = 0.2)) +#' plot(f_saem, pred_over = list(nlme = pred_nlme))  #' }  #' @export  plot.mixed.mmkin <- function(x, @@ -82,6 +91,18 @@ plot.mixed.mmkin <- function(x,        type = ifelse(standardized, "pearson", "response"))    } +  if (inherits(x, "saem.mmkin")) { +    if (x$transformations == "saemix") backtransform = FALSE +    degparms_i <- saemix::psi(x$so) +    rownames(degparms_i) <- ds_names +    degparms_i_names <- setdiff(x$so@results@name.fixed, names(fit_1$errparms)) +    colnames(degparms_i) <- degparms_i_names +    residual_type = ifelse(standardized, "standardized", "residual") +    residuals <- x$data[[residual_type]] +    degparms_pop <- x$so@results@fixed.effects +    names(degparms_pop) <- degparms_i_names +  } +    degparms_fixed <- fit_1$fixed$value    names(degparms_fixed) <- rownames(fit_1$fixed)    degparms_all <- cbind(as.matrix(degparms_i), diff --git a/R/saem.R b/R/saem.R new file mode 100644 index 00000000..fd2a77b4 --- /dev/null +++ b/R/saem.R @@ -0,0 +1,512 @@ +utils::globalVariables(c("predicted", "std")) + +#' Fit nonlinear mixed models with SAEM +#' +#' This function uses [saemix::saemix()] as a backend for fitting nonlinear mixed +#' effects models created from [mmkin] row objects using the Stochastic Approximation +#' Expectation Maximisation algorithm (SAEM). +#' +#' An mmkin row object is essentially a list of mkinfit objects that have been +#' obtained by fitting the same model to a list of datasets using [mkinfit]. +#' +#' Starting values for the fixed effects (population mean parameters, argument +#' psi0 of [saemix::saemixModel()] are the mean values of the parameters found +#' using [mmkin]. +#' +#' @param object An [mmkin] row object containing several fits of the same +#'   [mkinmod] model to different datasets +#' @param verbose Should we print information about created objects of +#'   type [saemix::SaemixModel] and [saemix::SaemixData]? +#' @param transformations Per default, all parameter transformations are done +#'   in mkin. If this argument is set to 'saemix', parameter transformations +#'   are done in 'saemix' for the supported cases. Currently this is only +#'   supported in cases where the initial concentration of the parent is not fixed, +#'   SFO or DFOP is used for the parent and there is either no metabolite or one. +#' @param degparms_start Parameter values given as a named numeric vector will +#'   be used to override the starting values obtained from the 'mmkin' object. +#' @param solution_type Possibility to specify the solution type in case the +#'   automatic choice is not desired +#' @param quiet Should we suppress the messages saemix prints at the beginning +#'   and the end of the optimisation process? +#' @param control Passed to [saemix::saemix] +#' @param \dots Further parameters passed to [saemix::saemixModel]. +#' @return An S3 object of class 'saem.mmkin', containing the fitted +#'   [saemix::SaemixObject] as a list component named 'so'. The +#'   object also inherits from 'mixed.mmkin'. +#' @seealso [summary.saem.mmkin] [plot.mixed.mmkin] +#' @examples +#' \dontrun{ +#' ds <- lapply(experimental_data_for_UBA_2019[6:10], +#'  function(x) subset(x$data[c("name", "time", "value")])) +#' names(ds) <- paste("Dataset", 6:10) +#' f_mmkin_parent_p0_fixed <- mmkin("FOMC", ds, +#'   state.ini = c(parent = 100), fixed_initials = "parent", quiet = TRUE) +#' f_saem_p0_fixed <- saem(f_mmkin_parent_p0_fixed) +#' +#' f_mmkin_parent <- mmkin(c("SFO", "FOMC", "DFOP"), ds, quiet = TRUE) +#' f_saem_sfo <- saem(f_mmkin_parent["SFO", ]) +#' f_saem_fomc <- saem(f_mmkin_parent["FOMC", ]) +#' f_saem_dfop <- saem(f_mmkin_parent["DFOP", ]) +#' +#' # The returned saem.mmkin object contains an SaemixObject, therefore we can use +#' # functions from saemix +#' library(saemix) +#' compare.saemix(list(f_saem_sfo$so, f_saem_fomc$so, f_saem_dfop$so)) +#' plot(f_saem_fomc$so, plot.type = "convergence") +#' plot(f_saem_fomc$so, plot.type = "individual.fit") +#' plot(f_saem_fomc$so, plot.type = "npde") +#' plot(f_saem_fomc$so, plot.type = "vpc") +#' +#' f_mmkin_parent_tc <- update(f_mmkin_parent, error_model = "tc") +#' f_saem_fomc_tc <- saem(f_mmkin_parent_tc["FOMC", ]) +#' compare.saemix(list(f_saem_fomc$so, f_saem_fomc_tc$so)) +#' +#' sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"), +#'   A1 = mkinsub("SFO")) +#' fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"), +#'   A1 = mkinsub("SFO")) +#' dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), +#'   A1 = mkinsub("SFO")) +#' # The following fit uses analytical solutions for SFO-SFO and DFOP-SFO, +#' # and compiled ODEs for FOMC that are much slower +#' f_mmkin <- mmkin(list( +#'     "SFO-SFO" = sfo_sfo, "FOMC-SFO" = fomc_sfo, "DFOP-SFO" = dfop_sfo), +#'   ds, quiet = TRUE) +#' # saem fits of SFO-SFO and DFOP-SFO to these data take about five seconds +#' # each on this system, as we use analytical solutions written for saemix. +#' # When using the analytical solutions written for mkin this took around +#' # four minutes +#' f_saem_sfo_sfo <- saem(f_mmkin["SFO-SFO", ]) +#' f_saem_dfop_sfo <- saem(f_mmkin["DFOP-SFO", ]) +#' # We can use print, plot and summary methods to check the results +#' print(f_saem_dfop_sfo) +#' plot(f_saem_dfop_sfo) +#' summary(f_saem_dfop_sfo, data = TRUE) +#' +#' # The following takes about 6 minutes +#' #f_saem_dfop_sfo_deSolve <- saem(f_mmkin["DFOP-SFO", ], solution_type = "deSolve", +#' #  control = list(nbiter.saemix = c(200, 80), nbdisplay = 10)) +#' +#' #saemix::compare.saemix(list( +#' #  f_saem_dfop_sfo$so, +#' #  f_saem_dfop_sfo_deSolve$so)) +#' +#' # If the model supports it, we can also use eigenvalue based solutions, which +#' # take a similar amount of time +#' #f_saem_sfo_sfo_eigen <- saem(f_mmkin["SFO-SFO", ], solution_type = "eigen", +#' #  control = list(nbiter.saemix = c(200, 80), nbdisplay = 10)) +#' } +#' @export +saem <- function(object, ...) UseMethod("saem") + +#' @rdname saem +#' @export +saem.mmkin <- function(object, +  transformations = c("mkin", "saemix"), +  degparms_start = numeric(), +  solution_type = "auto", +  control = list(displayProgress = FALSE, print = FALSE, +    save = FALSE, save.graphs = FALSE), +  verbose = FALSE, quiet = FALSE, ...) +{ +  transformations <- match.arg(transformations) +  m_saemix <- saemix_model(object, verbose = verbose, +    degparms_start = degparms_start, solution_type = solution_type, +    transformations = transformations, ...) +  d_saemix <- saemix_data(object, verbose = verbose) + +  fit_time <- system.time({ +    utils::capture.output(f_saemix <- saemix::saemix(m_saemix, d_saemix, control), split = !quiet) +  }) + +  transparms_optim <- f_saemix@results@fixed.effects +  names(transparms_optim) <- f_saemix@results@name.fixed + +  if (transformations == "mkin") { +    bparms_optim <- backtransform_odeparms(transparms_optim, +      object[[1]]$mkinmod, +      object[[1]]$transform_rates, +      object[[1]]$transform_fractions) +  } else { +    bparms_optim <- transparms_optim +  } + +  return_data <- nlme_data(object) + +  return_data$predicted <- f_saemix@model@model( +    psi = saemix::psi(f_saemix), +    id = as.numeric(return_data$ds), +    xidep = return_data[c("time", "name")]) + +  return_data <- transform(return_data, +    residual = predicted - value, +    std = sigma_twocomp(predicted, +      f_saemix@results@respar[1], f_saemix@results@respar[2])) +  return_data <- transform(return_data, +    standardized = residual / std) + +  result <- list( +    mkinmod = object[[1]]$mkinmod, +    mmkin = object, +    solution_type = object[[1]]$solution_type, +    transformations = transformations, +    transform_rates = object[[1]]$transform_rates, +    transform_fractions = object[[1]]$transform_fractions, +    so = f_saemix, +    time = fit_time, +    mean_dp_start = attr(m_saemix, "mean_dp_start"), +    bparms.optim = bparms_optim, +    bparms.fixed = object[[1]]$bparms.fixed, +    data = return_data, +    err_mod = object[[1]]$err_mod, +    date.fit = date(), +    saemixversion = as.character(utils::packageVersion("saemix")), +    mkinversion = as.character(utils::packageVersion("mkin")), +    Rversion = paste(R.version$major, R.version$minor, sep=".") +  ) + +  class(result) <- c("saem.mmkin", "mixed.mmkin") +  return(result) +} + +#' @export +#' @rdname saem +#' @param x An saem.mmkin object to print +#' @param digits Number of digits to use for printing +print.saem.mmkin <- function(x, digits = max(3, getOption("digits") - 3), ...) { +  cat( "Kinetic nonlinear mixed-effects model fit by SAEM" ) +  cat("\nStructural model:\n") +  diffs <- x$mmkin[[1]]$mkinmod$diffs +  nice_diffs <- gsub("^(d.*) =", "\\1/dt =", diffs) +  writeLines(strwrap(nice_diffs, exdent = 11)) +  cat("\nData:\n") +  cat(nrow(x$data), "observations of", +    length(unique(x$data$name)), "variable(s) grouped in", +    length(unique(x$data$ds)), "datasets\n") + +  cat("\nLikelihood computed by importance sampling\n") +  print(data.frame( +      AIC = AIC(x$so, type = "is"), +      BIC = BIC(x$so, type = "is"), +      logLik = logLik(x$so, type = "is"), +      row.names = " "), digits = digits) + +  cat("\nFitted parameters:\n") +  conf.int <- x$so@results@conf.int[c("estimate", "lower", "upper")] +  rownames(conf.int) <- x$so@results@conf.int[["name"]] +  print(conf.int, digits = digits) + +  invisible(x) +} + +#' @rdname saem +#' @return An [saemix::SaemixModel] object. +#' @export +saemix_model <- function(object, solution_type = "auto", transformations = c("mkin", "saemix"), +  degparms_start = numeric(), verbose = FALSE, ...) +{ +  if (nrow(object) > 1) stop("Only row objects allowed") + +  mkin_model <- object[[1]]$mkinmod + +  degparms_optim <-  mean_degparms(object) +  if (transformations == "saemix") { +    degparms_optim <- backtransform_odeparms(degparms_optim, +      object[[1]]$mkinmod, +      object[[1]]$transform_rates, +      object[[1]]$transform_fractions) +  } +  degparms_fixed <- object[[1]]$bparms.fixed + +  # Transformations are done in the degradation function +  transform.par = rep(0, length(degparms_optim)) + +  odeini_optim_parm_names <- grep('_0$', names(degparms_optim), value = TRUE) +  odeini_fixed_parm_names <- grep('_0$', names(degparms_fixed), value = TRUE) + +  odeparms_fixed_names <- setdiff(names(degparms_fixed), odeini_fixed_parm_names) +  odeparms_fixed <- degparms_fixed[odeparms_fixed_names] + +  odeini_fixed <- degparms_fixed[odeini_fixed_parm_names] +  names(odeini_fixed) <- gsub('_0$', '', odeini_fixed_parm_names) + +  model_function <- FALSE + +  # Model functions with analytical solutions +  # Fixed parameters, use_of_ff = "min" and turning off sinks currently not supported here +  # In general, we need to consider exactly how the parameters in mkinfit were specified, +  # as the parameters are currently mapped by position in these solutions +  sinks <- sapply(mkin_model$spec, function(x) x$sink) +  if (length(odeparms_fixed) == 0 & mkin_model$use_of_ff == "max" & all(sinks)) { +    # Parent only +    if (length(mkin_model$spec) == 1) { +      parent_type <- mkin_model$spec[[1]]$type +      if (length(odeini_fixed) == 1) { +        if (parent_type == "SFO") { +          stop("saemix needs at least two parameters to work on.") +        } +        if (parent_type == "FOMC") { +          model_function <- function(psi, id, xidep) { +            odeini_fixed / (xidep[, "time"]/exp(psi[id, 2]) + 1)^exp(psi[id, 1]) +          } +        } +        if (parent_type == "DFOP") { +          model_function <- function(psi, id, xidep) { +            g <- plogis(psi[id, 3]) +            t <- xidep[, "time"] +            odeini_fixed * (g * exp(- exp(psi[id, 1]) * t) + +              (1 - g) * exp(- exp(psi[id, 2]) * t)) +          } +        } +        if (parent_type == "HS") { +          model_function <- function(psi, id, xidep) { +            tb <- exp(psi[id, 3]) +            t <- xidep[, "time"] +            k1 = exp(psi[id, 1]) +            odeini_fixed * ifelse(t <= tb, +              exp(- k1 * t), +              exp(- k1 * tb) * exp(- exp(psi[id, 2]) * (t - tb))) +          } +        } +      } else { +        if (parent_type == "SFO") { +          if (transformations == "mkin") { +            model_function <- function(psi, id, xidep) { +              psi[id, 1] * exp( - exp(psi[id, 2]) * xidep[, "time"]) +            } +          } else { +            model_function <- function(psi, id, xidep) { +              psi[id, 1] * exp( - psi[id, 2] * xidep[, "time"]) +            } +            transform.par = c(0, 1) +          } +        } +        if (parent_type == "FOMC") { +          model_function <- function(psi, id, xidep) { +            psi[id, 1] / (xidep[, "time"]/exp(psi[id, 3]) + 1)^exp(psi[id, 2]) +          } +        } +        if (parent_type == "DFOP") { +          if (transformations == "mkin") { +            model_function <- function(psi, id, xidep) { +              g <- plogis(psi[id, 4]) +              t <- xidep[, "time"] +              psi[id, 1] * (g * exp(- exp(psi[id, 2]) * t) + +                (1 - g) * exp(- exp(psi[id, 3]) * t)) +            } +          } else { +            model_function <- function(psi, id, xidep) { +              g <- psi[id, 4] +              t <- xidep[, "time"] +              psi[id, 1] * (g * exp(- psi[id, 2] * t) + +                (1 - g) * exp(- psi[id, 3] * t)) +            } +            transform.par = c(0, 1, 1, 3) +          } +        } +        if (parent_type == "HS") { +          model_function <- function(psi, id, xidep) { +            tb <- exp(psi[id, 4]) +            t <- xidep[, "time"] +            k1 = exp(psi[id, 2]) +            psi[id, 1] * ifelse(t <= tb, +              exp(- k1 * t), +              exp(- k1 * tb) * exp(- exp(psi[id, 3]) * (t - tb))) +          } +        } +      } +    } + +    # Parent with one metabolite +    # Parameter names used in the model functions are as in +    # https://nbviewer.jupyter.org/urls/jrwb.de/nb/Symbolic%20ODE%20solutions%20for%20mkin.ipynb +    types <- unname(sapply(mkin_model$spec, function(x) x$type)) +    if (length(mkin_model$spec) == 2 &! "SFORB" %in% types ) { +      # Initial value for the metabolite (n20) must be fixed +      if (names(odeini_fixed) == names(mkin_model$spec)[2]) { +        n20 <- odeini_fixed +        parent_name <- names(mkin_model$spec)[1] +        if (identical(types, c("SFO", "SFO"))) { +          if (transformations == "mkin") { +            model_function <- function(psi, id, xidep) { +              t <- xidep[, "time"] +              n10 <- psi[id, 1] +              k1 <- exp(psi[id, 2]) +              k2 <- exp(psi[id, 3]) +              f12 <- plogis(psi[id, 4]) +              ifelse(xidep[, "name"] == parent_name, +                n10 * exp(- k1 * t), +                (((k2 - k1) * n20 - f12 * k1 * n10) * exp(- k2 * t)) / (k2 - k1) + +                  (f12 * k1 * n10 * exp(- k1 * t)) / (k2 - k1) +              ) +            } +          } else { +            model_function <- function(psi, id, xidep) { +              t <- xidep[, "time"] +              n10 <- psi[id, 1] +              k1 <- psi[id, 2] +              k2 <- psi[id, 3] +              f12 <- psi[id, 4] +              ifelse(xidep[, "name"] == parent_name, +                n10 * exp(- k1 * t), +                (((k2 - k1) * n20 - f12 * k1 * n10) * exp(- k2 * t)) / (k2 - k1) + +                  (f12 * k1 * n10 * exp(- k1 * t)) / (k2 - k1) +              ) +            } +            transform.par = c(0, 1, 1, 3) +          } +        } +        if (identical(types, c("DFOP", "SFO"))) { +          if (transformations == "mkin") { +            model_function <- function(psi, id, xidep) { +              t <- xidep[, "time"] +              n10 <- psi[id, 1] +              k2 <- exp(psi[id, 2]) +              f12 <- plogis(psi[id, 3]) +              l1 <- exp(psi[id, 4]) +              l2 <- exp(psi[id, 5]) +              g <- plogis(psi[id, 6]) +              ifelse(xidep[, "name"] == parent_name, +                n10 * (g * exp(- l1 * t) + (1 - g) * exp(- l2 * t)), +                ((f12 * g - f12) * l2 * n10 * exp(- l2 * t)) / (l2 - k2) - +                  (f12 * g * l1 * n10 * exp(- l1 * t)) / (l1 - k2) + +                  ((((l1 - k2) * l2 - k2 * l1 + k2^2) * n20 + +                      ((f12 * l1 + (f12 * g - f12) * k2) * l2 - +                        f12 * g * k2 * l1) * n10) * exp( - k2 * t)) / +                  ((l1 - k2) * l2 - k2 * l1 + k2^2) +              ) +            } +          } else { +            model_function <- function(psi, id, xidep) { +              t <- xidep[, "time"] +              n10 <- psi[id, 1] +              k2 <- psi[id, 2] +              f12 <- psi[id, 3] +              l1 <- psi[id, 4] +              l2 <- psi[id, 5] +              g <- psi[id, 6] +              ifelse(xidep[, "name"] == parent_name, +                n10 * (g * exp(- l1 * t) + (1 - g) * exp(- l2 * t)), +                ((f12 * g - f12) * l2 * n10 * exp(- l2 * t)) / (l2 - k2) - +                  (f12 * g * l1 * n10 * exp(- l1 * t)) / (l1 - k2) + +                  ((((l1 - k2) * l2 - k2 * l1 + k2^2) * n20 + +                      ((f12 * l1 + (f12 * g - f12) * k2) * l2 - +                        f12 * g * k2 * l1) * n10) * exp( - k2 * t)) / +                  ((l1 - k2) * l2 - k2 * l1 + k2^2) +              ) +            } +            transform.par = c(0, 1, 3, 1, 1, 3) +          } +        } +      } +    } +  } + +  if (is.function(model_function) & solution_type == "auto") { +    solution_type = "analytical saemix" +  } else { + +    if (solution_type == "auto") +      solution_type <- object[[1]]$solution_type + +    model_function <- function(psi, id, xidep) { + +      uid <- unique(id) + +      res_list <- lapply(uid, function(i) { + +        transparms_optim <- as.numeric(psi[i, ]) # psi[i, ] is a dataframe when called in saemix.predict +        names(transparms_optim) <- names(degparms_optim) + +        odeini_optim <- transparms_optim[odeini_optim_parm_names] +        names(odeini_optim) <- gsub('_0$', '', odeini_optim_parm_names) + +        odeini <- c(odeini_optim, odeini_fixed)[names(mkin_model$diffs)] + +        ode_transparms_optim_names <- setdiff(names(transparms_optim), odeini_optim_parm_names) +        odeparms_optim <- backtransform_odeparms(transparms_optim[ode_transparms_optim_names], mkin_model, +          transform_rates = object[[1]]$transform_rates, +          transform_fractions = object[[1]]$transform_fractions) +        odeparms <- c(odeparms_optim, odeparms_fixed) + +        xidep_i <- subset(xidep, id == i) + +        if (solution_type == "analytical") { +          out_values <- mkin_model$deg_func(xidep_i, odeini, odeparms) +        } else { + +          i_time <- xidep_i$time +          i_name <- xidep_i$name + +          out_wide <- mkinpredict(mkin_model, +            odeparms = odeparms, odeini = odeini, +            solution_type = solution_type, +            outtimes = sort(unique(i_time)), +            na_stop = FALSE +          ) + +          out_index <- cbind(as.character(i_time), as.character(i_name)) +          out_values <- out_wide[out_index] +        } +        return(out_values) +      }) +      res <- unlist(res_list) +      return(res) +    } +  } + +  error.model <- switch(object[[1]]$err_mod, +    const = "constant", +    tc = "combined", +    obs = "constant") + +  if (object[[1]]$err_mod == "obs") { +    warning("The error model 'obs' (variance by variable) can currently not be transferred to an saemix model") +  } + +  error.init <- switch(object[[1]]$err_mod, +    const = c(a = mean(sapply(object, function(x) x$errparms)), b = 1), +    tc = c(a = mean(sapply(object, function(x) x$errparms[1])), +      b = mean(sapply(object, function(x) x$errparms[2]))), +    obs = c(a = mean(sapply(object, function(x) x$errparms)), b = 1)) + +  degparms_psi0 <- degparms_optim +  degparms_psi0[names(degparms_start)] <- degparms_start +  psi0_matrix <- matrix(degparms_psi0, nrow = 1) +  colnames(psi0_matrix) <- names(degparms_psi0) + +  res <- saemix::saemixModel(model_function, +    psi0 = psi0_matrix, +    "Mixed model generated from mmkin object", +    transform.par = transform.par, +    error.model = error.model, +    verbose = verbose +  ) +  attr(res, "mean_dp_start") <- degparms_optim +  return(res) +} + +#' @rdname saem +#' @return An [saemix::SaemixData] object. +#' @export +saemix_data <- function(object, verbose = FALSE, ...) { +  if (nrow(object) > 1) stop("Only row objects allowed") +  ds_names <- colnames(object) + +  ds_list <- lapply(object, function(x) x$data[c("time", "variable", "observed")]) +  names(ds_list) <- ds_names +  ds_saemix_all <- purrr::map_dfr(ds_list, function(x) x, .id = "ds") +  ds_saemix <- data.frame(ds = ds_saemix_all$ds, +    name = as.character(ds_saemix_all$variable), +    time = ds_saemix_all$time, +    value = ds_saemix_all$observed, +    stringsAsFactors = FALSE) + +  res <- saemix::saemixData(ds_saemix, +    name.group = "ds", +    name.predictors = c("time", "name"), +    name.response = "value", +    verbose = verbose, +    ...) +  return(res) +} diff --git a/R/summary.saem.mmkin.R b/R/summary.saem.mmkin.R new file mode 100644 index 00000000..e92c561c --- /dev/null +++ b/R/summary.saem.mmkin.R @@ -0,0 +1,268 @@ +#' Summary method for class "saem.mmkin" +#' +#' Lists model equations, initial parameter values, optimised parameters +#' for fixed effects (population), random effects (deviations from the +#' population mean) and residual error model, as well as the resulting +#' endpoints such as formation fractions and DT50 values. Optionally +#' (default is FALSE), the data are listed in full. +#' +#' @param object an object of class [saem.mmkin] +#' @param x an object of class [summary.saem.mmkin] +#' @param data logical, indicating whether the full data should be included in +#'   the summary. +#' @param verbose Should the summary be verbose? +#' @param distimes logical, indicating whether DT50 and DT90 values should be +#'   included. +#' @param digits Number of digits to use for printing +#' @param \dots optional arguments passed to methods like \code{print}. +#' @return The summary function returns a list based on the [saemix::SaemixObject] +#'   obtained in the fit, with at least the following additional components +#'   \item{saemixversion, mkinversion, Rversion}{The saemix, mkin and R versions used} +#'   \item{date.fit, date.summary}{The dates where the fit and the summary were +#'     produced} +#'   \item{diffs}{The differential equations used in the degradation model} +#'   \item{use_of_ff}{Was maximum or minimum use made of formation fractions} +#'   \item{data}{The data} +#'   \item{confint_trans}{Transformed parameters as used in the optimisation, with confidence intervals} +#'   \item{confint_back}{Backtransformed parameters, with confidence intervals if available} +#'   \item{confint_errmod}{Error model parameters with confidence intervals} +#'   \item{ff}{The estimated formation fractions derived from the fitted +#'      model.} +#'   \item{distimes}{The DT50 and DT90 values for each observed variable.} +#'   \item{SFORB}{If applicable, eigenvalues of SFORB components of the model.} +#'   The print method is called for its side effect, i.e. printing the summary. +#' @importFrom stats predict vcov +#' @author Johannes Ranke for the mkin specific parts +#'   saemix authors for the parts inherited from saemix. +#' @examples +#' # Generate five datasets following DFOP-SFO kinetics +#' sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) +#' dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "m1"), +#'  m1 = mkinsub("SFO"), quiet = TRUE) +#' set.seed(1234) +#' k1_in <- rlnorm(5, log(0.1), 0.3) +#' k2_in <- rlnorm(5, log(0.02), 0.3) +#' g_in <- plogis(rnorm(5, qlogis(0.5), 0.3)) +#' f_parent_to_m1_in <- plogis(rnorm(5, qlogis(0.3), 0.3)) +#' k_m1_in <- rlnorm(5, log(0.02), 0.3) +#' +#' pred_dfop_sfo <- function(k1, k2, g, f_parent_to_m1, k_m1) { +#'   mkinpredict(dfop_sfo, +#'     c(k1 = k1, k2 = k2, g = g, f_parent_to_m1 = f_parent_to_m1, k_m1 = k_m1), +#'     c(parent = 100, m1 = 0), +#'     sampling_times) +#' } +#' +#' ds_mean_dfop_sfo <- lapply(1:5, function(i) { +#'   mkinpredict(dfop_sfo, +#'     c(k1 = k1_in[i], k2 = k2_in[i], g = g_in[i], +#'       f_parent_to_m1 = f_parent_to_m1_in[i], k_m1 = k_m1_in[i]), +#'     c(parent = 100, m1 = 0), +#'     sampling_times) +#' }) +#' names(ds_mean_dfop_sfo) <- paste("ds", 1:5) +#' +#' ds_syn_dfop_sfo <- lapply(ds_mean_dfop_sfo, function(ds) { +#'   add_err(ds, +#'     sdfunc = function(value) sqrt(1^2 + value^2 * 0.07^2), +#'     n = 1)[[1]] +#' }) +#' +#' \dontrun{ +#' # Evaluate using mmkin and saem +#' f_mmkin_dfop_sfo <- mmkin(list(dfop_sfo), ds_syn_dfop_sfo, +#'   quiet = TRUE, error_model = "tc", cores = 5) +#' f_saem_dfop_sfo <- saem(f_mmkin_dfop_sfo) +#' summary(f_saem_dfop_sfo, data = TRUE) +#' } +#' +#' @export +summary.saem.mmkin <- function(object, data = FALSE, verbose = FALSE, distimes = TRUE, ...) { + +  mod_vars <- names(object$mkinmod$diffs) + +  pnames <- names(object$mean_dp_start) +  np <- length(pnames) + +  conf.int <- object$so@results@conf.int +  rownames(conf.int) <- conf.int$name +  confint_trans <- as.matrix(conf.int[pnames, c("estimate", "lower", "upper")]) +  colnames(confint_trans)[1] <- "est." + +  # In case objects were produced by earlier versions of saem +  if (is.null(object$transformations)) object$transformations <- "mkin" + +  if (object$transformations == "mkin") { +    bp <- backtransform_odeparms(confint_trans[, "est."], object$mkinmod, +      object$transform_rates, object$transform_fractions) +    bpnames <- names(bp) + +    # Transform boundaries of CI for one parameter at a time, +    # with the exception of sets of formation fractions (single fractions are OK). +    f_names_skip <- character(0) +    for (box in mod_vars) { # Figure out sets of fractions to skip +      f_names <- grep(paste("^f", box, sep = "_"), pnames, value = TRUE) +      n_paths <- length(f_names) +      if (n_paths > 1) f_names_skip <- c(f_names_skip, f_names) +    } + +    confint_back <- matrix(NA, nrow = length(bp), ncol = 3, +      dimnames = list(bpnames, colnames(confint_trans))) +    confint_back[, "est."] <- bp + +    for (pname in pnames) { +      if (!pname %in% f_names_skip) { +        par.lower <- confint_trans[pname, "lower"] +        par.upper <- confint_trans[pname, "upper"] +        names(par.lower) <- names(par.upper) <- pname +        bpl <- backtransform_odeparms(par.lower, object$mkinmod, +                                              object$transform_rates, +                                              object$transform_fractions) +        bpu <- backtransform_odeparms(par.upper, object$mkinmod, +                                              object$transform_rates, +                                              object$transform_fractions) +        confint_back[names(bpl), "lower"] <- bpl +        confint_back[names(bpu), "upper"] <- bpu +      } +    } +  } else { +    confint_back <- confint_trans +  } + +  #  Correlation of fixed effects (inspired by summary.nlme) +  varFix <- vcov(object$so)[1:np, 1:np] +  stdFix <- sqrt(diag(varFix)) +  object$corFixed <- array( +    t(varFix/stdFix)/stdFix, +    dim(varFix), +    list(pnames, pnames)) + +  # Random effects +  rnames <- paste0("SD.", pnames) +  confint_ranef <- as.matrix(conf.int[rnames, c("estimate", "lower", "upper")]) +  colnames(confint_ranef)[1] <- "est." + +  # Error model +  enames <- if (object$err_mod == "const") "a.1" else c("a.1", "b.1") +  confint_errmod <- as.matrix(conf.int[enames, c("estimate", "lower", "upper")]) +  colnames(confint_errmod)[1] <- "est." + + +  object$confint_trans <- confint_trans +  object$confint_ranef <- confint_ranef +  object$confint_errmod <- confint_errmod +  object$confint_back <- confint_back + +  object$date.summary = date() +  object$use_of_ff = object$mkinmod$use_of_ff +  object$error_model_algorithm = object$mmkin_orig[[1]]$error_model_algorithm +  err_mod = object$mmkin_orig[[1]]$err_mod + +  object$diffs <- object$mkinmod$diffs +  object$print_data <- data # boolean: Should we print the data? +  so_pred <- object$so@results@predictions + +  names(object$data)[4] <- "observed" # rename value to observed + +  object$verbose <- verbose + +  object$fixed <- object$mmkin_orig[[1]]$fixed +  object$AIC = AIC(object$so) +  object$BIC = BIC(object$so) +  object$logLik = logLik(object$so, method = "is") + +  ep <- endpoints(object) +  if (length(ep$ff) != 0) +    object$ff <- ep$ff +  if (distimes) object$distimes <- ep$distimes +  if (length(ep$SFORB) != 0) object$SFORB <- ep$SFORB +  class(object) <- c("summary.saem.mmkin") +  return(object) +} + +#' @rdname summary.saem.mmkin +#' @export +print.summary.saem.mmkin <- function(x, digits = max(3, getOption("digits") - 3), verbose = x$verbose, ...) { +  cat("saemix version used for fitting:     ", x$saemixversion, "\n") +  cat("mkin version used for pre-fitting: ", x$mkinversion, "\n") +  cat("R version used for fitting:        ", x$Rversion, "\n") + +  cat("Date of fit:    ", x$date.fit, "\n") +  cat("Date of summary:", x$date.summary, "\n") + +  cat("\nEquations:\n") +  nice_diffs <- gsub("^(d.*) =", "\\1/dt =", x[["diffs"]]) +  writeLines(strwrap(nice_diffs, exdent = 11)) + +  cat("\nData:\n") +  cat(nrow(x$data), "observations of", +    length(unique(x$data$name)), "variable(s) grouped in", +    length(unique(x$data$ds)), "datasets\n") + +  cat("\nModel predictions using solution type", x$solution_type, "\n") + +  cat("\nFitted in", x$time[["elapsed"]],  "s using", paste(x$so@options$nbiter.saemix, collapse = ", "), "iterations\n") + +  cat("\nVariance model: ") +  cat(switch(x$err_mod, +    const = "Constant variance", +    obs = "Variance unique to each observed variable", +    tc = "Two-component variance function"), "\n") + +  cat("\nMean of starting values for individual parameters:\n") +  print(x$mean_dp_start, digits = digits) + +  cat("\nFixed degradation parameter values:\n") +  if(length(x$fixed$value) == 0) cat("None\n") +  else print(x$fixed, digits = digits) + +  cat("\nResults:\n\n") +  cat("Likelihood computed by importance sampling\n") +  print(data.frame(AIC = x$AIC, BIC = x$BIC, logLik = x$logLik, +      row.names = " "), digits = digits) + +  cat("\nOptimised parameters:\n") +  print(x$confint_trans, digits = digits) + +  if (nrow(x$confint_trans) > 1) { +    corr <- x$corFixed +    class(corr) <- "correlation" +    print(corr, title = "\nCorrelation:", ...) +  } + +  cat("\nRandom effects:\n") +  print(x$confint_ranef, digits = digits) + +  cat("\nVariance model:\n") +  print(x$confint_errmod, digits = digits) + +  if (x$transformations == "mkin") { +    cat("\nBacktransformed parameters:\n") +    print(x$confint_back, digits = digits) +  } + +  printSFORB <- !is.null(x$SFORB) +  if(printSFORB){ +    cat("\nEstimated Eigenvalues of SFORB model(s):\n") +    print(x$SFORB, digits = digits,...) +  } + +  printff <- !is.null(x$ff) +  if(printff){ +    cat("\nResulting formation fractions:\n") +    print(data.frame(ff = x$ff), digits = digits,...) +  } + +  printdistimes <- !is.null(x$distimes) +  if(printdistimes){ +    cat("\nEstimated disappearance times:\n") +    print(x$distimes, digits = digits,...) +  } + +  if (x$print_data){ +    cat("\nData:\n") +    print(format(x$data, digits = digits, ...), row.names = FALSE) +  } + +  invisible(x) +} diff --git a/_pkgdown.yml b/_pkgdown.yml index f632ddb0..5cfaeedf 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -1,8 +1,8 @@  url: https://pkgdown.jrwb.de/mkin  development: -  mode: release -  version_label: default +  mode: devel +  version_label: info  template:    bootswatch: spacelab @@ -39,10 +39,13 @@ reference:      desc: Create and work with nonlinear mixed effects models      contents:        - nlme.mmkin +      - saem.mmkin        - plot.mixed.mmkin        - summary.nlme.mmkin +      - summary.saem.mmkin        - nlme_function        - get_deg_func +      - saemix_model        - mixed    - title: Datasets and known results      contents: @@ -6,5 +6,5 @@  * creating vignettes ... OK  * checking for LF line-endings in source and make files and shell scripts  * checking for empty or unneeded directories -* building ‘mkin_1.0.1.tar.gz’ +* building ‘mkin_1.0.1.9000.tar.gz’ @@ -5,10 +5,15 @@  * using options ‘--no-tests --as-cran’  * checking for file ‘mkin/DESCRIPTION’ ... OK  * checking extension type ... Package -* this is package ‘mkin’ version ‘1.0.1’ +* this is package ‘mkin’ version ‘1.0.1.9000’  * package encoding: UTF-8 -* checking CRAN incoming feasibility ... Note_to_CRAN_maintainers +* checking CRAN incoming feasibility ... NOTE  Maintainer: ‘Johannes Ranke <jranke@uni-bremen.de>’ + +Version contains large components (1.0.1.9000) + +Unknown, possibly mis-spelled, fields in DESCRIPTION: +  ‘Remotes’  * checking package namespace information ... OK  * checking package dependencies ... OK  * checking if this is a source package ... OK @@ -67,5 +72,9 @@ Maintainer: ‘Johannes Ranke <jranke@uni-bremen.de>’  * checking for detritus in the temp directory ... OK  * DONE -Status: OK +Status: 1 NOTE +See +  ‘/home/jranke/git/mkin/mkin.Rcheck/00check.log’ +for details. + diff --git a/docs/dev/404.html b/docs/dev/404.html index bea38406..5f29faf2 100644 --- a/docs/dev/404.html +++ b/docs/dev/404.html @@ -71,7 +71,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="https://pkgdown.jrwb.de/mkin/index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> diff --git a/docs/dev/articles/index.html b/docs/dev/articles/index.html index 6daa6960..441d49c0 100644 --- a/docs/dev/articles/index.html +++ b/docs/dev/articles/index.html @@ -71,7 +71,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> diff --git a/docs/dev/authors.html b/docs/dev/authors.html index d592b39f..9641eec0 100644 --- a/docs/dev/authors.html +++ b/docs/dev/authors.html @@ -71,7 +71,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -147,15 +147,15 @@        </li>        <li>          <p><strong>Katrin Lindenberger</strong>. Contributor.  -        </p> +        <br /><small>contributed to mkinresplot()</small></p>        </li>        <li>          <p><strong>René Lehmann</strong>. Contributor.  -        </p> +        <br /><small>ilr() and invilr()</small></p>        </li>        <li>          <p><strong>Eurofins Regulatory AG</strong>. Copyright holder.  -        </p> +        <br /><small>copyright for some of the contributions of JR 2012-2014</small></p>        </li>      </ul> diff --git a/docs/dev/index.html b/docs/dev/index.html index a4399963..8888633d 100644 --- a/docs/dev/index.html +++ b/docs/dev/index.html @@ -38,7 +38,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -147,7 +147,7 @@  <li>Three different error models can be selected using the argument <code>error_model</code> to the <a href="https://pkgdown.jrwb.de/mkin/reference/mkinfit.html"><code>mkinfit</code></a> function.</li>  <li>The ‘variance by variable’ error model which is often fitted using Iteratively Reweighted Least Squares (IRLS) should now be specified as <code>error_model = "obs"</code>.</li>  <li>A two-component error model similar to the one proposed by <a href="https://pkgdown.jrwb.de/mkin/reference/sigma_twocomp.html">Rocke and Lorenzato</a> can be selected using the argument <code>error_model = "tc"</code>.</li> -<li>Nonlinear mixed-effects models can be created from fits of the same degradation model to different datasets for the same compound by using the <a href="https://pkgdown.jrwb.de/mkin/reference/nlme.mmkin.html">nlme.mmkin</a> method.</li> +<li>Nonlinear mixed-effects models can be created from fits of the same degradation model to different datasets for the same compound by using the <a href="https://pkgdown.jrwb.de/mkin/reference/nlme.mmkin.html">nlme.mmkin</a> method. Note that the convergence of the nlme fits depends on the quality of the data. Convergence is better for simple models and data for many groups (e.g. soils).</li>  </ul>  </div>  <div id="gui" class="section level2"> diff --git a/docs/dev/news/index.html b/docs/dev/news/index.html index c3597efe..998917f2 100644 --- a/docs/dev/news/index.html +++ b/docs/dev/news/index.html @@ -71,7 +71,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -141,13 +141,36 @@        <small>Source: <a href='https://github.com/jranke/mkin/blob/master/NEWS.md'><code>NEWS.md</code></a></small>      </div> -    <div id="mkin-0-9-50-4-unreleased" class="section level1"> -<h1 class="page-header" data-toc-text="0.9.50.4"> -<a href="#mkin-0-9-50-4-unreleased" class="anchor"></a>mkin 0.9.50.4 (unreleased)<small> Unreleased </small> +    <div id="mkin-1019000" class="section level1"> +<h1 class="page-header" data-toc-text="1.0.1.9000"> +<a href="#mkin-1019000" class="anchor"></a>mkin 1.0.1.9000<small> Unreleased </small>  </h1> -<div id="general-new-features" class="section level2"> +<ul> +<li><p>Switch to a versioning scheme where the fourth version component indicates development versions</p></li> +<li><p>Reintroduce the interface to the current development version of saemix, in particular:</p></li> +<li><p>‘saemix_model’ and ‘saemix_data’: Helper functions to set up nonlinear mixed-effects models for mmkin row objects</p></li> +<li><p>‘saem’: generic function to fit saemix models using ‘saemix_model’ and ‘saemix_data’, with a generator ‘saem.mmkin’, summary and plot methods</p></li> +</ul> +</div> +    <div id="mkin-101" class="section level1"> +<h1 class="page-header" data-toc-text="1.0.1"> +<a href="#mkin-101" class="anchor"></a>mkin 1.0.1<small> Unreleased </small> +</h1> +<ul> +<li><p>‘confint.mmkin’, ‘nlme.mmkin’, ‘transform_odeparms’: Fix example code in dontrun sections that failed with current defaults</p></li> +<li><p>‘logLik.mkinfit’: Improve example code to avoid warnings and show convenient syntax</p></li> +<li><p>‘mkinresplot’: Re-add Katrin Lindenberger as coauthor who was accidentally removed long ago</p></li> +<li><p>Remove tests relying on non-convergence of the FOMC fit to the FOCUS A dataset as this is platform dependent (revealed by the new additional tests on CRAN, thanks!)</p></li> +<li><p>Increase test tolerance for some parameter comparisons that also proved to be platform dependent</p></li> +</ul> +</div> +    <div id="mkin-100" class="section level1"> +<h1 class="page-header" data-toc-text="1.0.0"> +<a href="#mkin-100" class="anchor"></a>mkin 1.0.0<small> 2021-02-03 </small> +</h1> +<div id="general" class="section level2">  <h2 class="hasAnchor"> -<a href="#general-new-features" class="anchor"></a>General new features</h2> +<a href="#general" class="anchor"></a>General</h2>  <ul>  <li><p>‘mkinmod’ models gain arguments ‘name’ and ‘dll_dir’ which, in conjunction with a current version of the ‘inline’ package, make it possible to still use the DLL used for fast ODE solutions with ‘deSolve’ after saving and restoring the ‘mkinmod’ object.</p></li>  <li><p>‘mkindsg’ R6 class for groups of ‘mkinds’ datasets with metadata</p></li> @@ -156,6 +179,8 @@  <li><p>‘focus_soil_moisture’ FOCUS default soil moisture data</p></li>  <li><p>‘update’ method for ‘mmkin’ objects</p></li>  <li><p>‘transform_odeparms’, ‘backtransform_odeparms’: Use logit transformation for solitary fractions like the g parameter of the DFOP model, or formation fractions for a pathway to only one target variable</p></li> +<li><p>‘plot.mmkin’: Add a ylab argument, making it possible to customize the y axis label of the panels on the left without affecting the residual plots. Reduce legend size and vertical distance between panels</p></li> +<li><p>‘plot.mkinfit’: Change default ylab from “Observed” to “Residue”. Pass xlab to residual plot if show_residuals is TRUE.</p></li>  </ul>  </div>  <div id="mixed-effects-models" class="section level2"> @@ -163,18 +188,14 @@  <a href="#mixed-effects-models" class="anchor"></a>Mixed-effects models</h2>  <ul>  <li><p>‘mixed.mmkin’ New container for mmkin objects for plotting with the ‘plot.mixed.mmkin’ method</p></li> -<li><p>‘plot.mixed.mmkin’ method used for ‘nlme.mmkin’ and ‘saem.mmkin’, both inheriting from ‘mixed.mmkin’ (currently virtual)</p></li> +<li><p>‘plot.mixed.mmkin’ method used for ‘nlme.mmkin’ inheriting from ‘mixed.mmkin’ (currently virtual)</p></li>  <li><p>‘plot’, ‘summary’ and ‘print’ methods for ‘nlme.mmkin’ objects</p></li> -<li><p>Add the current development version of the saemix package as a second, optional backend for mixed-effects models</p></li> -<li><p>DESCRIPTION: Additional_repositories entry pointing to my drat repository on github for a suitable saemix version</p></li> -<li><p>‘saemix_model’, ‘saemix_data’: Helper functions to fit nonlinear mixed-effects models for mmkin row objects.</p></li> -<li><p>‘saem’ generic function to fit saemix models using ‘saemix_model’ and ‘saemix_data’, with a generator ‘saem.mmkin’, summary and plot methods</p></li>  </ul>  </div>  </div> -    <div id="mkin-0-9-50-3-2020-10-08" class="section level1"> +    <div id="mkin-09503-2020-10-08" class="section level1">  <h1 class="page-header" data-toc-text="0.9.50.3"> -<a href="#mkin-0-9-50-3-2020-10-08" class="anchor"></a>mkin 0.9.50.3 (2020-10-08)<small> 2020-10-08 </small> +<a href="#mkin-09503-2020-10-08" class="anchor"></a>mkin 0.9.50.3 (2020-10-08)<small> 2020-10-08 </small>  </h1>  <ul>  <li><p>‘parms’: Add a method for mmkin objects</p></li> @@ -188,18 +209,18 @@  <li><p>‘endpoints’: Back-calculate DT50 value from DT90 also for the biphasic models DFOP, HS and SFORB</p></li>  </ul>  </div> -    <div id="mkin-0-9-50-2-2020-05-12" class="section level1"> +    <div id="mkin-09502-2020-05-12" class="section level1">  <h1 class="page-header" data-toc-text="0.9.50.2"> -<a href="#mkin-0-9-50-2-2020-05-12" class="anchor"></a>mkin 0.9.50.2 (2020-05-12)<small> 2020-05-12 </small> +<a href="#mkin-09502-2020-05-12" class="anchor"></a>mkin 0.9.50.2 (2020-05-12)<small> 2020-05-12 </small>  </h1>  <ul>  <li><p>Increase tolerance for a platform specific test results on the Solaris test machine on CRAN</p></li>  <li><p>Updates and corrections (using the spelling package) to the documentation</p></li>  </ul>  </div> -    <div id="mkin-0-9-50-1-2020-05-11" class="section level1"> +    <div id="mkin-09501-2020-05-11" class="section level1">  <h1 class="page-header" data-toc-text="0.9.50.1"> -<a href="#mkin-0-9-50-1-2020-05-11" class="anchor"></a>mkin 0.9.50.1 (2020-05-11)<small> 2020-05-11 </small> +<a href="#mkin-09501-2020-05-11" class="anchor"></a>mkin 0.9.50.1 (2020-05-11)<small> 2020-05-11 </small>  </h1>  <ul>  <li><p>Support SFORB with formation fractions</p></li> @@ -207,17 +228,17 @@  <li><p>Improve performance by a) avoiding expensive calls in the cost function like merge() and data.frame(), and b) by implementing analytical solutions for SFO-SFO and DFOP-SFO</p></li>  </ul>  </div> -    <div id="mkin-0-9-49-11-2020-04-20" class="section level1"> +    <div id="mkin-094911-2020-04-20" class="section level1">  <h1 class="page-header" data-toc-text="0.9.49.11"> -<a href="#mkin-0-9-49-11-2020-04-20" class="anchor"></a>mkin 0.9.49.11 (2020-04-20)<small> 2020-04-20 </small> +<a href="#mkin-094911-2020-04-20" class="anchor"></a>mkin 0.9.49.11 (2020-04-20)<small> 2020-04-20 </small>  </h1>  <ul>  <li>Increase a test tolerance to make it pass on all CRAN check machines</li>  </ul>  </div> -    <div id="mkin-0-9-49-10-2020-04-18" class="section level1"> +    <div id="mkin-094910-2020-04-18" class="section level1">  <h1 class="page-header" data-toc-text="0.9.49.10"> -<a href="#mkin-0-9-49-10-2020-04-18" class="anchor"></a>mkin 0.9.49.10 (2020-04-18)<small> 2020-04-18 </small> +<a href="#mkin-094910-2020-04-18" class="anchor"></a>mkin 0.9.49.10 (2020-04-18)<small> 2020-04-18 </small>  </h1>  <ul>  <li><p>‘nlme.mmkin’: An nlme method for mmkin row objects and an associated S3 class with print, plot, anova and endpoint methods</p></li> @@ -228,18 +249,18 @@  <li><p>‘summary.mkinfit’: Add AIC, BIC and log likelihood to the summary</p></li>  </ul>  </div> -    <div id="mkin-0-9-49-9-2020-03-31" class="section level1"> +    <div id="mkin-09499-2020-03-31" class="section level1">  <h1 class="page-header" data-toc-text="0.9.49.9"> -<a href="#mkin-0-9-49-9-2020-03-31" class="anchor"></a>mkin 0.9.49.9 (2020-03-31)<small> 2020-03-31 </small> +<a href="#mkin-09499-2020-03-31" class="anchor"></a>mkin 0.9.49.9 (2020-03-31)<small> 2020-03-31 </small>  </h1>  <ul>  <li><p>‘mkinmod’: Use pkgbuild::has_compiler instead of Sys.which(‘gcc’), as the latter will often fail even if Rtools are installed</p></li>  <li><p>‘mkinds’: Use roxygen for documenting fields and methods of this R6 class</p></li>  </ul>  </div> -    <div id="mkin-0-9-49-8-2020-01-09" class="section level1"> +    <div id="mkin-09498-2020-01-09" class="section level1">  <h1 class="page-header" data-toc-text="0.9.49.8"> -<a href="#mkin-0-9-49-8-2020-01-09" class="anchor"></a>mkin 0.9.49.8 (2020-01-09)<small> 2020-01-09 </small> +<a href="#mkin-09498-2020-01-09" class="anchor"></a>mkin 0.9.49.8 (2020-01-09)<small> 2020-01-09 </small>  </h1>  <ul>  <li><p>‘aw’: Generic function for calculating Akaike weights, methods for mkinfit objects and mmkin columns</p></li> @@ -249,18 +270,18 @@  <li><p>‘confint.mkinfit’: Make the quadratic approximation the default, as the likelihood profiling takes a lot of time, especially if the fit has more than three parameters</p></li>  </ul>  </div> -    <div id="mkin-0-9-49-7-2019-11-01" class="section level1"> +    <div id="mkin-09497-2019-11-01" class="section level1">  <h1 class="page-header" data-toc-text="0.9.49.7"> -<a href="#mkin-0-9-49-7-2019-11-01" class="anchor"></a>mkin 0.9.49.7 (2019-11-01)<small> 2019-11-02 </small> +<a href="#mkin-09497-2019-11-01" class="anchor"></a>mkin 0.9.49.7 (2019-11-01)<small> 2019-11-02 </small>  </h1>  <ul>  <li><p>Fix a bug introduced in 0.9.49.6 that occurred if the direct optimisation yielded a higher likelihood than the three-step optimisation in the d_3 algorithm, which caused the fitted parameters of the three-step optimisation to be returned instead of the parameters of the direct optimisation</p></li>  <li><p>Add a ‘nobs’ method for mkinfit objects, enabling the default ‘BIC’ method from the stats package. Also, add a ‘BIC’ method for mmkin column objects.</p></li>  </ul>  </div> -    <div id="mkin-0-9-49-6-2019-10-31" class="section level1"> +    <div id="mkin-09496-2019-10-31" class="section level1">  <h1 class="page-header" data-toc-text="0.9.49.6"> -<a href="#mkin-0-9-49-6-2019-10-31" class="anchor"></a>mkin 0.9.49.6 (2019-10-31)<small> 2019-10-31 </small> +<a href="#mkin-09496-2019-10-31" class="anchor"></a>mkin 0.9.49.6 (2019-10-31)<small> 2019-10-31 </small>  </h1>  <ul>  <li><p>Implement a likelihood ratio test as a method for ‘lrtest’ from the lmtest package</p></li> @@ -278,9 +299,9 @@  <li><p>Support summarizing ‘mkinfit’ objects generated with versions < 0.9.49.5</p></li>  </ul>  </div> -    <div id="mkin-0-9-49-5-2019-07-04" class="section level1"> +    <div id="mkin-09495-2019-07-04" class="section level1">  <h1 class="page-header" data-toc-text="0.9.49.5"> -<a href="#mkin-0-9-49-5-2019-07-04" class="anchor"></a>mkin 0.9.49.5 (2019-07-04)<small> 2019-07-04 </small> +<a href="#mkin-09495-2019-07-04" class="anchor"></a>mkin 0.9.49.5 (2019-07-04)<small> 2019-07-04 </small>  </h1>  <ul>  <li><p>Several algorithms for minimization of the negative log-likelihood for non-constant error models (two-component and variance by variable). In the case the error model is constant variance, least squares is used as this is more stable. The default algorithm ‘d_3’ tries direct minimization and a three-step procedure, and returns the model with the highest likelihood.</p></li> @@ -297,9 +318,9 @@  <li><p>Add example datasets obtained from risk assessment reports published by the European Food Safety Agency.</p></li>  </ul>  </div> -    <div id="mkin-0-9-48-1-2019-03-04" class="section level1"> +    <div id="mkin-09481-2019-03-04" class="section level1">  <h1 class="page-header" data-toc-text="0.9.48.1"> -<a href="#mkin-0-9-48-1-2019-03-04" class="anchor"></a>mkin 0.9.48.1 (2019-03-04)<small> 2019-03-04 </small> +<a href="#mkin-09481-2019-03-04" class="anchor"></a>mkin 0.9.48.1 (2019-03-04)<small> 2019-03-04 </small>  </h1>  <ul>  <li><p>Add the function ‘logLik.mkinfit’ which makes it possible to calculate an AIC for mkinfit objects</p></li> @@ -314,9 +335,9 @@  <li><p>‘nafta’: Add evaluations according to the NAFTA guidance</p></li>  </ul>  </div> -    <div id="mkin-0-9-47-5-2018-09-14" class="section level1"> +    <div id="mkin-09475-2018-09-14" class="section level1">  <h1 class="page-header" data-toc-text="0.9.47.5"> -<a href="#mkin-0-9-47-5-2018-09-14" class="anchor"></a>mkin 0.9.47.5 (2018-09-14)<small> 2018-09-14 </small> +<a href="#mkin-09475-2018-09-14" class="anchor"></a>mkin 0.9.47.5 (2018-09-14)<small> 2018-09-14 </small>  </h1>  <ul>  <li><p>Make the two-component error model stop in cases where it is inadequate to avoid nls crashes on windows</p></li> @@ -324,27 +345,27 @@  <li><p>Exclude more example code from testing on CRAN to avoid NOTES from long execution times</p></li>  </ul>  </div> -    <div id="mkin-0-9-47-3" class="section level1"> +    <div id="mkin-09473" class="section level1">  <h1 class="page-header" data-toc-text="0.9.47.3"> -<a href="#mkin-0-9-47-3" class="anchor"></a>mkin 0.9.47.3<small> Unreleased </small> +<a href="#mkin-09473" class="anchor"></a>mkin 0.9.47.3<small> Unreleased </small>  </h1>  <ul>  <li><p>‘mkinfit’: Improve fitting the error model for reweight.method = ‘tc’. Add ‘manual’ to possible arguments for ‘weight’</p></li>  <li><p>Test that FOCUS_2006_C can be evaluated with DFOP and reweight.method = ‘tc’</p></li>  </ul>  </div> -    <div id="mkin-0-9-47-2-2018-07-19" class="section level1"> +    <div id="mkin-09472-2018-07-19" class="section level1">  <h1 class="page-header" data-toc-text="0.9.47.2"> -<a href="#mkin-0-9-47-2-2018-07-19" class="anchor"></a>mkin 0.9.47.2 (2018-07-19)<small> 2018-07-19 </small> +<a href="#mkin-09472-2018-07-19" class="anchor"></a>mkin 0.9.47.2 (2018-07-19)<small> 2018-07-19 </small>  </h1>  <ul>  <li><p>‘sigma_twocomp’: Rename ‘sigma_rl’ to ‘sigma_twocomp’ as the Rocke and Lorenzato model assumes lognormal distribution for large y. Correct references to the Rocke and Lorenzato model accordingly.</p></li>  <li><p>‘mkinfit’: Use 1.1 as starting value for N parameter of IORE models to obtain convergence in more difficult cases. Show parameter names when ‘trace_parms’ is ‘TRUE’.</p></li>  </ul>  </div> -    <div id="mkin-0-9-47-1-2018-02-06" class="section level1"> +    <div id="mkin-09471-2018-02-06" class="section level1">  <h1 class="page-header" data-toc-text="0.9.47.1"> -<a href="#mkin-0-9-47-1-2018-02-06" class="anchor"></a>mkin 0.9.47.1 (2018-02-06)<small> 2018-02-06 </small> +<a href="#mkin-09471-2018-02-06" class="anchor"></a>mkin 0.9.47.1 (2018-02-06)<small> 2018-02-06 </small>  </h1>  <ul>  <li><p>Skip some tests on CRAN and winbuilder to avoid timeouts</p></li> @@ -355,27 +376,27 @@  <li><p>‘summary.mkinfit’: Show versions of mkin and R used for fitting (not the ones used for the summary) if the fit was generated with mkin >= 0.9.47.1</p></li>  </ul>  </div> -    <div id="mkin-0-9-46-3-2017-11-16" class="section level1"> +    <div id="mkin-09463-2017-11-16" class="section level1">  <h1 class="page-header" data-toc-text="0.9.46.3"> -<a href="#mkin-0-9-46-3-2017-11-16" class="anchor"></a>mkin 0.9.46.3 (2017-11-16)<small> 2017-11-16 </small> +<a href="#mkin-09463-2017-11-16" class="anchor"></a>mkin 0.9.46.3 (2017-11-16)<small> 2017-11-16 </small>  </h1>  <ul>  <li><p><code>README.md</code>, <code>vignettes/mkin.Rmd</code>: URLs were updated</p></li>  <li><p><code>synthetic_data_for_UBA</code>: Add the code used to generate the data in the interest of reproducibility</p></li>  </ul>  </div> -    <div id="mkin-0-9-46-2-2017-10-10" class="section level1"> +    <div id="mkin-09462-2017-10-10" class="section level1">  <h1 class="page-header" data-toc-text="0.9.46.2"> -<a href="#mkin-0-9-46-2-2017-10-10" class="anchor"></a>mkin 0.9.46.2 (2017-10-10)<small> 2017-10-10 </small> +<a href="#mkin-09462-2017-10-10" class="anchor"></a>mkin 0.9.46.2 (2017-10-10)<small> 2017-10-10 </small>  </h1>  <ul>  <li><p>Converted the vignette FOCUS_Z from tex/pdf to markdown/html</p></li>  <li><p><code>DESCRIPTION</code>: Add ORCID</p></li>  </ul>  </div> -    <div id="mkin-0-9-46-1-2017-09-14" class="section level1"> +    <div id="mkin-09461-2017-09-14" class="section level1">  <h1 class="page-header" data-toc-text="0.9.46.1"> -<a href="#mkin-0-9-46-1-2017-09-14" class="anchor"></a>mkin 0.9.46.1 (2017-09-14)<small> 2017-09-14 </small> +<a href="#mkin-09461-2017-09-14" class="anchor"></a>mkin 0.9.46.1 (2017-09-14)<small> 2017-09-14 </small>  </h1>  <ul>  <li><p><code>plot.mkinfit</code>: Fix scaling of residual plots for the case of separate plots for each observed variable</p></li> @@ -383,17 +404,17 @@  <li><p>Documentation updates</p></li>  </ul>  </div> -    <div id="mkin-0-9-46-2017-07-24" class="section level1"> +    <div id="mkin-0946-2017-07-24" class="section level1">  <h1 class="page-header" data-toc-text="0.9.46"> -<a href="#mkin-0-9-46-2017-07-24" class="anchor"></a>mkin 0.9.46 (2017-07-24)<small> 2017-07-29 </small> +<a href="#mkin-0946-2017-07-24" class="anchor"></a>mkin 0.9.46 (2017-07-24)<small> 2017-07-29 </small>  </h1>  <ul>  <li>Remove <code>test_FOMC_ill-defined.R</code> as it is too platform dependent</li>  </ul>  </div> -    <div id="mkin-0-9-45-2-2017-07-24" class="section level1"> +    <div id="mkin-09452-2017-07-24" class="section level1">  <h1 class="page-header" data-toc-text="0.9.45.2"> -<a href="#mkin-0-9-45-2-2017-07-24" class="anchor"></a>mkin 0.9.45.2 (2017-07-24)<small> 2017-07-22 </small> +<a href="#mkin-09452-2017-07-24" class="anchor"></a>mkin 0.9.45.2 (2017-07-24)<small> 2017-07-22 </small>  </h1>  <ul>  <li><p>Rename <code>twa</code> to <code>max_twa_parent</code> to avoid conflict with <code>twa</code> from my <code>pfm</code> package</p></li> @@ -402,9 +423,9 @@  <li><p>Switch from <code>microbenchmark</code> to <code>rbenchmark</code> as the former is not supported on all platforms</p></li>  </ul>  </div> -    <div id="mkin-0-9-45-1-2016-12-20" class="section level1"> +    <div id="mkin-09451-2016-12-20" class="section level1">  <h1 class="page-header" data-toc-text="0.9.45.1"> -<a href="#mkin-0-9-45-1-2016-12-20" class="anchor"></a>mkin 0.9.45.1 (2016-12-20)<small> Unreleased </small> +<a href="#mkin-09451-2016-12-20" class="anchor"></a>mkin 0.9.45.1 (2016-12-20)<small> Unreleased </small>  </h1>  <div id="new-features" class="section level2">  <h2 class="hasAnchor"> @@ -414,9 +435,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-45-2016-12-08" class="section level1"> +    <div id="mkin-0945-2016-12-08" class="section level1">  <h1 class="page-header" data-toc-text="0.9.45"> -<a href="#mkin-0-9-45-2016-12-08" class="anchor"></a>mkin 0.9.45 (2016-12-08)<small> 2016-12-08 </small> +<a href="#mkin-0945-2016-12-08" class="anchor"></a>mkin 0.9.45 (2016-12-08)<small> 2016-12-08 </small>  </h1>  <div id="minor-changes" class="section level2">  <h2 class="hasAnchor"> @@ -428,9 +449,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-44-2016-06-29" class="section level1"> +    <div id="mkin-0944-2016-06-29" class="section level1">  <h1 class="page-header" data-toc-text="0.9.44"> -<a href="#mkin-0-9-44-2016-06-29" class="anchor"></a>mkin 0.9.44 (2016-06-29)<small> 2016-06-29 </small> +<a href="#mkin-0944-2016-06-29" class="anchor"></a>mkin 0.9.44 (2016-06-29)<small> 2016-06-29 </small>  </h1>  <div id="bug-fixes" class="section level2">  <h2 class="hasAnchor"> @@ -440,9 +461,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-43-2016-06-28" class="section level1"> +    <div id="mkin-0943-2016-06-28" class="section level1">  <h1 class="page-header" data-toc-text="0.9.43"> -<a href="#mkin-0-9-43-2016-06-28" class="anchor"></a>mkin 0.9.43 (2016-06-28)<small> 2016-06-28 </small> +<a href="#mkin-0943-2016-06-28" class="anchor"></a>mkin 0.9.43 (2016-06-28)<small> 2016-06-28 </small>  </h1>  <div id="major-changes" class="section level2">  <h2 class="hasAnchor"> @@ -479,9 +500,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-42-2016-03-25" class="section level1"> +    <div id="mkin-0942-2016-03-25" class="section level1">  <h1 class="page-header" data-toc-text="0.9.42"> -<a href="#mkin-0-9-42-2016-03-25" class="anchor"></a>mkin 0.9.42 (2016-03-25)<small> 2016-03-25 </small> +<a href="#mkin-0942-2016-03-25" class="anchor"></a>mkin 0.9.42 (2016-03-25)<small> 2016-03-25 </small>  </h1>  <div id="major-changes-1" class="section level2">  <h2 class="hasAnchor"> @@ -500,9 +521,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-41-2015-11-09" class="section level1"> +    <div id="mkin-09-41-2015-11-09" class="section level1">  <h1 class="page-header" data-toc-text="0.9-41"> -<a href="#mkin-0-9-41-2015-11-09" class="anchor"></a>mkin 0.9-41 (2015-11-09)<small> 2015-11-09 </small> +<a href="#mkin-09-41-2015-11-09" class="anchor"></a>mkin 0.9-41 (2015-11-09)<small> 2015-11-09 </small>  </h1>  <div id="minor-changes-3" class="section level2">  <h2 class="hasAnchor"> @@ -523,9 +544,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-40-2015-07-21" class="section level1"> +    <div id="mkin-09-40-2015-07-21" class="section level1">  <h1 class="page-header" data-toc-text="0.9-40"> -<a href="#mkin-0-9-40-2015-07-21" class="anchor"></a>mkin 0.9-40 (2015-07-21)<small> 2015-07-21 </small> +<a href="#mkin-09-40-2015-07-21" class="anchor"></a>mkin 0.9-40 (2015-07-21)<small> 2015-07-21 </small>  </h1>  <div id="bug-fixes-3" class="section level2">  <h2 class="hasAnchor"> @@ -544,9 +565,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-39-2015-06-26" class="section level1"> +    <div id="mkin-09-39-2015-06-26" class="section level1">  <h1 class="page-header" data-toc-text="0.9-39"> -<a href="#mkin-0-9-39-2015-06-26" class="anchor"></a>mkin 0.9-39 (2015-06-26)<small> 2015-06-26 </small> +<a href="#mkin-09-39-2015-06-26" class="anchor"></a>mkin 0.9-39 (2015-06-26)<small> 2015-06-26 </small>  </h1>  <div id="major-changes-2" class="section level2">  <h2 class="hasAnchor"> @@ -565,9 +586,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-38-2015-06-24" class="section level1"> +    <div id="mkin-09-38-2015-06-24" class="section level1">  <h1 class="page-header" data-toc-text="0.9-38"> -<a href="#mkin-0-9-38-2015-06-24" class="anchor"></a>mkin 0.9-38 (2015-06-24)<small> 2015-06-23 </small> +<a href="#mkin-09-38-2015-06-24" class="anchor"></a>mkin 0.9-38 (2015-06-24)<small> 2015-06-23 </small>  </h1>  <div id="minor-changes-4" class="section level2">  <h2 class="hasAnchor"> @@ -586,9 +607,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-36-2015-06-21" class="section level1"> +    <div id="mkin-09-36-2015-06-21" class="section level1">  <h1 class="page-header" data-toc-text="0.9-36"> -<a href="#mkin-0-9-36-2015-06-21" class="anchor"></a>mkin 0.9-36 (2015-06-21)<small> 2015-06-21 </small> +<a href="#mkin-09-36-2015-06-21" class="anchor"></a>mkin 0.9-36 (2015-06-21)<small> 2015-06-21 </small>  </h1>  <div id="major-changes-3" class="section level2">  <h2 class="hasAnchor"> @@ -608,9 +629,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-35-2015-05-15" class="section level1"> +    <div id="mkin-09-35-2015-05-15" class="section level1">  <h1 class="page-header" data-toc-text="0.9-35"> -<a href="#mkin-0-9-35-2015-05-15" class="anchor"></a>mkin 0.9-35 (2015-05-15)<small> 2015-05-15 </small> +<a href="#mkin-09-35-2015-05-15" class="anchor"></a>mkin 0.9-35 (2015-05-15)<small> 2015-05-15 </small>  </h1>  <div id="major-changes-4" class="section level2">  <h2 class="hasAnchor"> @@ -640,9 +661,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-34-2014-11-22" class="section level1"> +    <div id="mkin-09-34-2014-11-22" class="section level1">  <h1 class="page-header" data-toc-text="0.9-34"> -<a href="#mkin-0-9-34-2014-11-22" class="anchor"></a>mkin 0.9-34 (2014-11-22)<small> 2014-11-22 </small> +<a href="#mkin-09-34-2014-11-22" class="anchor"></a>mkin 0.9-34 (2014-11-22)<small> 2014-11-22 </small>  </h1>  <div id="new-features-2" class="section level2">  <h2 class="hasAnchor"> @@ -662,9 +683,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-33-2014-10-22" class="section level1"> +    <div id="mkin-09-33-2014-10-22" class="section level1">  <h1 class="page-header" data-toc-text="0.9-33"> -<a href="#mkin-0-9-33-2014-10-22" class="anchor"></a>mkin 0.9-33 (2014-10-22)<small> 2014-10-12 </small> +<a href="#mkin-09-33-2014-10-22" class="anchor"></a>mkin 0.9-33 (2014-10-22)<small> 2014-10-12 </small>  </h1>  <div id="new-features-3" class="section level2">  <h2 class="hasAnchor"> @@ -695,9 +716,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-32-2014-07-24" class="section level1"> +    <div id="mkin-09-32-2014-07-24" class="section level1">  <h1 class="page-header" data-toc-text="0.9-32"> -<a href="#mkin-0-9-32-2014-07-24" class="anchor"></a>mkin 0.9-32 (2014-07-24)<small> 2014-07-24 </small> +<a href="#mkin-09-32-2014-07-24" class="anchor"></a>mkin 0.9-32 (2014-07-24)<small> 2014-07-24 </small>  </h1>  <div id="new-features-4" class="section level2">  <h2 class="hasAnchor"> @@ -705,7 +726,7 @@  <ul>  <li><p>The number of degrees of freedom is difficult to define in the case of ilr transformation of formation fractions. Now for each source compartment the number of ilr parameters (=number of optimised parameters) is divided by the number of pathways to metabolites (=number of affected data series) which leads to fractional degrees of freedom in some cases.</p></li>  <li><p>The default for the initial value for the first state value is now taken from the mean of the observations at time zero, if available.</p></li> -<li><p>The kinetic model can alternatively be specified with a shorthand name for parent only degradation models, e.g. <code>SFO</code>, or <code>DFOP</code>.</p></li> +<li><p>The kinetic model can alternatively be specified with a shorthand name for parent only degradation models, e.g. <code>SFO</code>, or <code>DFOP</code>.</p></li>  <li><p>Optimisation method, number of model evaluations and time elapsed during optimisation are given in the summary of mkinfit objects.</p></li>  <li><p>The maximum number of iterations in the optimisation algorithm can be specified using the argument <code>maxit.modFit</code> to the mkinfit function.</p></li>  <li><p>mkinfit gives a warning when the fit does not converge (does not apply to SANN method). This warning is included in the summary.</p></li> @@ -732,9 +753,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-31-2014-07-14" class="section level1"> +    <div id="mkin-09-31-2014-07-14" class="section level1">  <h1 class="page-header" data-toc-text="0.9-31"> -<a href="#mkin-0-9-31-2014-07-14" class="anchor"></a>mkin 0.9-31 (2014-07-14)<small> 2014-07-14 </small> +<a href="#mkin-09-31-2014-07-14" class="anchor"></a>mkin 0.9-31 (2014-07-14)<small> 2014-07-14 </small>  </h1>  <div id="bug-fixes-9" class="section level2">  <h2 class="hasAnchor"> @@ -744,9 +765,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-30-2014-07-11" class="section level1"> +    <div id="mkin-09-30-2014-07-11" class="section level1">  <h1 class="page-header" data-toc-text="0.9-30"> -<a href="#mkin-0-9-30-2014-07-11" class="anchor"></a>mkin 0.9-30 (2014-07-11)<small> 2014-07-11 </small> +<a href="#mkin-09-30-2014-07-11" class="anchor"></a>mkin 0.9-30 (2014-07-11)<small> 2014-07-11 </small>  </h1>  <div id="new-features-5" class="section level2">  <h2 class="hasAnchor"> @@ -759,7 +780,7 @@  <h2 class="hasAnchor">  <a href="#major-changes-5" class="anchor"></a>Major changes</h2>  <ul> -<li><p>The original and the transformed parameters now have different names (e.g. <code>k_parent</code> and <code>log_k_parent</code>. They also differ in how many they are when we have formation fractions but no pathway to sink.</p></li> +<li><p>The original and the transformed parameters now have different names (e.g. <code>k_parent</code> and <code>log_k_parent</code>. They also differ in how many they are when we have formation fractions but no pathway to sink.</p></li>  <li><p>The order of some of the information blocks in <code>print.summary.mkinfit.R()</code> has been ordered in a more logical way.</p></li>  </ul>  </div> @@ -776,9 +797,9 @@  </ul>  </div>  </div> -    <div id="mkin-0-9-29-2014-06-27" class="section level1"> +    <div id="mkin-09-29-2014-06-27" class="section level1">  <h1 class="page-header" data-toc-text="0.9-29"> -<a href="#mkin-0-9-29-2014-06-27" class="anchor"></a>mkin 0.9-29 (2014-06-27)<small> 2014-06-27 </small> +<a href="#mkin-09-29-2014-06-27" class="anchor"></a>mkin 0.9-29 (2014-06-27)<small> 2014-06-27 </small>  </h1>  <ul>  <li><p>R/mkinresplot.R: Make it possible to specify <code>xlim</code></p></li> @@ -786,9 +807,9 @@  <li><p>R/endpoints.R, man/endpoints.Rd: Calculate additional (pseudo)-DT50 values for FOMC, DFOP, HS and SFORB. Avoid calculation of formation fractions from rate constants when they are directly fitted</p></li>  </ul>  </div> -    <div id="mkin-0-9-28-2014-05-20" class="section level1"> +    <div id="mkin-09-28-2014-05-20" class="section level1">  <h1 class="page-header" data-toc-text="0.9-28"> -<a href="#mkin-0-9-28-2014-05-20" class="anchor"></a>mkin 0.9-28 (2014-05-20)<small> 2014-05-20 </small> +<a href="#mkin-09-28-2014-05-20" class="anchor"></a>mkin 0.9-28 (2014-05-20)<small> 2014-05-20 </small>  </h1>  <ul>  <li><p>Do not backtransform confidence intervals for formation fractions if more than one compound is formed, as such parameters only define the pathways as a set</p></li> @@ -796,9 +817,9 @@  <li><p>Correct ‘isotropic’ into ‘isometric’ for the ilr transformation</p></li>  </ul>  </div> -    <div id="mkin-0-9-27-2014-05-10" class="section level1"> +    <div id="mkin-09-27-2014-05-10" class="section level1">  <h1 class="page-header" data-toc-text="0.9-27"> -<a href="#mkin-0-9-27-2014-05-10" class="anchor"></a>mkin 0.9-27 (2014-05-10)<small> 2014-05-10 </small> +<a href="#mkin-09-27-2014-05-10" class="anchor"></a>mkin 0.9-27 (2014-05-10)<small> 2014-05-10 </small>  </h1>  <ul>  <li><p>Fork the GUI into a separate package <a href="https://github.com/jranke/gmkin">gmkin</a></p></li> @@ -820,9 +841,9 @@  <li><p>Add gmkin workspace datasets FOCUS_2006_gmkin and FOCUS_2006_Z_gmkin</p></li>  </ul>  </div> -    <div id="mkin-0-9-24-2013-11-06" class="section level1"> +    <div id="mkin-09-24-2013-11-06" class="section level1">  <h1 class="page-header" data-toc-text="0.9-24"> -<a href="#mkin-0-9-24-2013-11-06" class="anchor"></a>mkin 0.9-24 (2013-11-06)<small> 2013-11-06 </small> +<a href="#mkin-09-24-2013-11-06" class="anchor"></a>mkin 0.9-24 (2013-11-06)<small> 2013-11-06 </small>  </h1>  <ul>  <li><p>Bugfix re-enabling the fixing of any combination of initial values for state variables</p></li> @@ -830,9 +851,9 @@  <li><p>Backtransform fixed ODE parameters for the summary</p></li>  </ul>  </div> -    <div id="mkin-0-9-22-2013-10-26" class="section level1"> +    <div id="mkin-09-22-2013-10-26" class="section level1">  <h1 class="page-header" data-toc-text="0.9-22"> -<a href="#mkin-0-9-22-2013-10-26" class="anchor"></a>mkin 0.9-22 (2013-10-26)<small> 2013-10-26 </small> +<a href="#mkin-09-22-2013-10-26" class="anchor"></a>mkin 0.9-22 (2013-10-26)<small> 2013-10-26 </small>  </h1>  <ul>  <li><p>Get rid of the optimisation step in <code>mkinerrmin</code> - this was unnecessary. Thanks to KinGUII for the inspiration - actually this is equation 6-2 in FOCUS kinetics p. 91 that I had overlooked originally</p></li> diff --git a/docs/dev/pkgdown.yml b/docs/dev/pkgdown.yml index 2963e810..f9b16e29 100644 --- a/docs/dev/pkgdown.yml +++ b/docs/dev/pkgdown.yml @@ -1,4 +1,4 @@ -pandoc: 2.2.1 +pandoc: 2.9.2.1  pkgdown: 1.6.1  pkgdown_sha: ~  articles: @@ -10,7 +10,7 @@ articles:    web_only/NAFTA_examples: NAFTA_examples.html    web_only/benchmarks: benchmarks.html    web_only/compiled_models: compiled_models.html -last_built: 2021-01-25T13:41Z +last_built: 2021-02-06T17:26Z  urls:    reference: https://pkgdown.jrwb.de/mkin/reference    article: https://pkgdown.jrwb.de/mkin/articles diff --git a/docs/dev/reference/Rplot001.png b/docs/dev/reference/Rplot001.pngBinary files differ index bca41e2c..17a35806 100644 --- a/docs/dev/reference/Rplot001.png +++ b/docs/dev/reference/Rplot001.png diff --git a/docs/dev/reference/Rplot003.png b/docs/dev/reference/Rplot003.pngBinary files differ index ff6bc722..2b011ec1 100644 --- a/docs/dev/reference/Rplot003.png +++ b/docs/dev/reference/Rplot003.png diff --git a/docs/dev/reference/Rplot005.png b/docs/dev/reference/Rplot005.pngBinary files differ index 5e675828..8c91d61e 100644 --- a/docs/dev/reference/Rplot005.png +++ b/docs/dev/reference/Rplot005.png diff --git a/docs/dev/reference/Rplot006.png b/docs/dev/reference/Rplot006.pngBinary files differ index da52f580..730a7481 100644 --- a/docs/dev/reference/Rplot006.png +++ b/docs/dev/reference/Rplot006.png diff --git a/docs/dev/reference/confint.mkinfit.html b/docs/dev/reference/confint.mkinfit.html index 515a7c9e..89bb3d89 100644 --- a/docs/dev/reference/confint.mkinfit.html +++ b/docs/dev/reference/confint.mkinfit.html @@ -79,7 +79,7 @@ method of Venzon and Moolgavkar (1988)." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -128,7 +128,7 @@ method of Venzon and Moolgavkar (1988)." />        <ul class="nav navbar-nav navbar-right">          <li>    <a href="https://github.com/jranke/mkin/"> -    <span class="fab fa fab fa-github fa-lg"></span> +    <span class="fab fa-github fa-lg"></span>    </a>  </li> @@ -273,68 +273,69 @@ Profile-Likelihood Based Confidence Intervals, Applied Statistics, 37,  <span class='kw'>if</span> <span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/identical.html'>identical</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/Sys.getenv.html'>Sys.getenv</a></span><span class='op'>(</span><span class='st'>"NOT_CRAN"</span><span class='op'>)</span>, <span class='st'>"true"</span><span class='op'>)</span><span class='op'>)</span> <span class='op'>{</span>    <span class='va'>n_cores</span> <span class='op'><-</span> <span class='fu'>parallel</span><span class='fu'>::</span><span class='fu'><a href='https://rdrr.io/r/parallel/detectCores.html'>detectCores</a></span><span class='op'>(</span><span class='op'>)</span> <span class='op'>-</span> <span class='fl'>1</span>  <span class='op'>}</span> <span class='kw'>else</span> <span class='op'>{</span> - <span class='va'>n_cores</span> <span class='op'><-</span> <span class='fl'>1</span> +  <span class='va'>n_cores</span> <span class='op'><-</span> <span class='fl'>1</span>  <span class='op'>}</span>  <span class='kw'>if</span> <span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/Sys.getenv.html'>Sys.getenv</a></span><span class='op'>(</span><span class='st'>"TRAVIS"</span><span class='op'>)</span> <span class='op'>!=</span> <span class='st'>""</span><span class='op'>)</span> <span class='va'>n_cores</span> <span class='op'>=</span> <span class='fl'>1</span>  <span class='kw'>if</span> <span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/Sys.info.html'>Sys.info</a></span><span class='op'>(</span><span class='op'>)</span><span class='op'>[</span><span class='st'>"sysname"</span><span class='op'>]</span> <span class='op'>==</span> <span class='st'>"Windows"</span><span class='op'>)</span> <span class='va'>n_cores</span> <span class='op'>=</span> <span class='fl'>1</span> -<span class='va'>SFO_SFO</span> <span class='op'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span><span class='op'>(</span>parent <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span>, <span class='st'>"m1"</span><span class='op'>)</span>, m1 <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span><span class='op'>)</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +<span class='va'>SFO_SFO</span> <span class='op'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span><span class='op'>(</span>parent <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span>, <span class='st'>"m1"</span><span class='op'>)</span>, m1 <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span><span class='op'>)</span>, +  use_of_ff <span class='op'>=</span> <span class='st'>"min"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='va'>SFO_SFO.ff</span> <span class='op'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span><span class='op'>(</span>parent <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span>, <span class='st'>"m1"</span><span class='op'>)</span>, m1 <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span><span class='op'>)</span>,    use_of_ff <span class='op'>=</span> <span class='st'>"max"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='va'>f_d_1</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO</span>, <span class='fu'><a href='https://rdrr.io/r/base/subset.html'>subset</a></span><span class='op'>(</span><span class='va'>FOCUS_2006_D</span>, <span class='va'>value</span> <span class='op'>!=</span> <span class='fl'>0</span><span class='op'>)</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='fu'><a href='https://rdrr.io/r/base/system.time.html'>system.time</a></span><span class='op'>(</span><span class='va'>ci_profile</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_1</span>, method <span class='op'>=</span> <span class='st'>"profile"</span>, cores <span class='op'>=</span> <span class='fl'>1</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span><span class='op'>)</span>  </div><div class='output co'>#>    user  system elapsed  -#>   3.900   0.929   3.548 </div><div class='input'><span class='co'># Using more cores does not save much time here, as parent_0 takes up most of the time</span> +#>   4.258   0.916   3.889 </div><div class='input'><span class='co'># Using more cores does not save much time here, as parent_0 takes up most of the time</span>  <span class='co'># If we additionally exclude parent_0 (the confidence of which is often of</span> -<span class='co'># minor interest), we get a nice performance improvement from about 50</span> -<span class='co'># seconds to about 12 seconds if we use at least four cores</span> +<span class='co'># minor interest), we get a nice performance improvement if we use at least 4 cores</span>  <span class='fu'><a href='https://rdrr.io/r/base/system.time.html'>system.time</a></span><span class='op'>(</span><span class='va'>ci_profile_no_parent_0</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_1</span>, method <span class='op'>=</span> <span class='st'>"profile"</span>,    <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"k_parent_sink"</span>, <span class='st'>"k_parent_m1"</span>, <span class='st'>"k_m1_sink"</span>, <span class='st'>"sigma"</span><span class='op'>)</span>, cores <span class='op'>=</span> <span class='va'>n_cores</span><span class='op'>)</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='message'>Profiling the likelihood</span></div><div class='output co'>#> <span class='warning'>Warning: scheduled cores 3, 2, 1 encountered errors in user code, all values of the jobs will be affected</span></div><div class='output co'>#> <span class='error'>Error in dimnames(x) <- dn: length of 'dimnames' [2] not equal to array extent</span></div><div class='output co'>#> <span class='message'>Timing stopped at: 0.009 0.034 0.257</span></div><div class='input'><span class='va'>ci_profile</span> -</div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       96.456003640 1.027703e+02 -#> k_parent        0.090911032 1.071578e-01 -#> k_m1            0.003892606 6.702775e-03 -#> f_parent_to_m1  0.471328495 5.611550e-01 -#> sigma           2.535612399 3.985263e+00</div><div class='input'><span class='va'>ci_quadratic_transformed</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_1</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span><span class='op'>)</span> +</div><div class='output co'>#> <span class='message'>Profiling the likelihood</span></div><div class='output co'>#>    user  system elapsed  +#>   1.459   0.088   0.907 </div><div class='input'><span class='va'>ci_profile</span> +</div><div class='output co'>#>                       2.5%        97.5% +#> parent_0      96.456003640 1.027703e+02 +#> k_parent_sink  0.040762501 5.549764e-02 +#> k_parent_m1    0.046786482 5.500879e-02 +#> k_m1_sink      0.003892605 6.702778e-03 +#> sigma          2.535612399 3.985263e+00</div><div class='input'><span class='va'>ci_quadratic_transformed</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_1</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span><span class='op'>)</span>  <span class='va'>ci_quadratic_transformed</span> -</div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       96.403833585 102.79311650 -#> k_parent        0.090823771   0.10725430 -#> k_m1            0.004012219   0.00689755 -#> f_parent_to_m1  0.469118824   0.55959615 -#> sigma           2.396089689   3.85491806</div><div class='input'><span class='va'>ci_quadratic_untransformed</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_1</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span>, transformed <span class='op'>=</span> <span class='cn'>FALSE</span><span class='op'>)</span> +</div><div class='output co'>#>                       2.5%        97.5% +#> parent_0      96.403841640 1.027931e+02 +#> k_parent_sink  0.041033378 5.596269e-02 +#> k_parent_m1    0.046777902 5.511931e-02 +#> k_m1_sink      0.004012217 6.897547e-03 +#> sigma          2.396089689 3.854918e+00</div><div class='input'><span class='va'>ci_quadratic_untransformed</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_1</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span>, transformed <span class='op'>=</span> <span class='cn'>FALSE</span><span class='op'>)</span>  <span class='va'>ci_quadratic_untransformed</span> -</div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       96.403833589 1.027931e+02 -#> k_parent        0.090491913 1.069035e-01 -#> k_m1            0.003835485 6.685823e-03 -#> f_parent_to_m1  0.469113477 5.598387e-01 -#> sigma           2.396089689 3.854918e+00</div><div class='input'><span class='co'># Against the expectation based on Bates and Watts (1988), the confidence</span> +</div><div class='output co'>#>                       2.5%        97.5% +#> parent_0      96.403841645 102.79312449 +#> k_parent_sink  0.040485331   0.05535491 +#> k_parent_m1    0.046611582   0.05494364 +#> k_m1_sink      0.003835483   0.00668582 +#> sigma          2.396089689   3.85491806</div><div class='input'><span class='co'># Against the expectation based on Bates and Watts (1988), the confidence</span>  <span class='co'># intervals based on the internal parameter transformation are less</span>  <span class='co'># congruent with the likelihood based intervals. Note the superiority of the</span>  <span class='co'># interval based on the untransformed fit for k_m1_sink</span>  <span class='va'>rel_diffs_transformed</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/MathFun.html'>abs</a></span><span class='op'>(</span><span class='op'>(</span><span class='va'>ci_quadratic_transformed</span> <span class='op'>-</span> <span class='va'>ci_profile</span><span class='op'>)</span><span class='op'>/</span><span class='va'>ci_profile</span><span class='op'>)</span>  <span class='va'>rel_diffs_untransformed</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/MathFun.html'>abs</a></span><span class='op'>(</span><span class='op'>(</span><span class='va'>ci_quadratic_untransformed</span> <span class='op'>-</span> <span class='va'>ci_profile</span><span class='op'>)</span><span class='op'>/</span><span class='va'>ci_profile</span><span class='op'>)</span>  <span class='va'>rel_diffs_transformed</span> <span class='op'><</span> <span class='va'>rel_diffs_untransformed</span> -</div><div class='output co'>#>                 2.5% 97.5% -#> parent_0       FALSE FALSE -#> k_parent        TRUE  TRUE -#> k_m1           FALSE FALSE -#> f_parent_to_m1  TRUE FALSE -#> sigma           TRUE FALSE</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/Round.html'>signif</a></span><span class='op'>(</span><span class='va'>rel_diffs_transformed</span>, <span class='fl'>3</span><span class='op'>)</span> -</div><div class='output co'>#>                    2.5%    97.5% -#> parent_0       0.000541 0.000222 -#> k_parent       0.000960 0.000900 -#> k_m1           0.030700 0.029100 -#> f_parent_to_m1 0.004690 0.002780 -#> sigma          0.055000 0.032700</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/Round.html'>signif</a></span><span class='op'>(</span><span class='va'>rel_diffs_untransformed</span>, <span class='fl'>3</span><span class='op'>)</span> -</div><div class='output co'>#>                    2.5%    97.5% -#> parent_0       0.000541 0.000222 -#> k_parent       0.004610 0.002370 -#> k_m1           0.014700 0.002530 -#> f_parent_to_m1 0.004700 0.002350 -#> sigma          0.055000 0.032700</div><div class='input'> +</div><div class='output co'>#>                2.5% 97.5% +#> parent_0      FALSE FALSE +#> k_parent_sink  TRUE FALSE +#> k_parent_m1    TRUE FALSE +#> k_m1_sink     FALSE FALSE +#> sigma         FALSE FALSE</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/Round.html'>signif</a></span><span class='op'>(</span><span class='va'>rel_diffs_transformed</span>, <span class='fl'>3</span><span class='op'>)</span> +</div><div class='output co'>#>                   2.5%    97.5% +#> parent_0      0.000541 0.000222 +#> k_parent_sink 0.006650 0.008380 +#> k_parent_m1   0.000183 0.002010 +#> k_m1_sink     0.030700 0.029100 +#> sigma         0.055000 0.032700</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/Round.html'>signif</a></span><span class='op'>(</span><span class='va'>rel_diffs_untransformed</span>, <span class='fl'>3</span><span class='op'>)</span> +</div><div class='output co'>#>                   2.5%    97.5% +#> parent_0      0.000541 0.000222 +#> k_parent_sink 0.006800 0.002570 +#> k_parent_m1   0.003740 0.001180 +#> k_m1_sink     0.014700 0.002530 +#> sigma         0.055000 0.032700</div><div class='input'>  <span class='co'># Investigate a case with formation fractions</span>  <span class='va'>f_d_2</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO.ff</span>, <span class='fu'><a href='https://rdrr.io/r/base/subset.html'>subset</a></span><span class='op'>(</span><span class='va'>FOCUS_2006_D</span>, <span class='va'>value</span> <span class='op'>!=</span> <span class='fl'>0</span><span class='op'>)</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> @@ -348,14 +349,14 @@ Profile-Likelihood Based Confidence Intervals, Applied Statistics, 37,  #> sigma           2.535612399 3.985263e+00</div><div class='input'><span class='va'>ci_quadratic_transformed_ff</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_2</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span><span class='op'>)</span>  <span class='va'>ci_quadratic_transformed_ff</span>  </div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       96.403833585 102.79311650 +#> parent_0       96.403833578 102.79311649  #> k_parent        0.090823771   0.10725430  #> k_m1            0.004012219   0.00689755  #> f_parent_to_m1  0.469118824   0.55959615  #> sigma           2.396089689   3.85491806</div><div class='input'><span class='va'>ci_quadratic_untransformed_ff</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_d_2</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span>, transformed <span class='op'>=</span> <span class='cn'>FALSE</span><span class='op'>)</span>  <span class='va'>ci_quadratic_untransformed_ff</span>  </div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       96.403833589 1.027931e+02 +#> parent_0       96.403833583 1.027931e+02  #> k_parent        0.090491913 1.069035e-01  #> k_m1            0.003835485 6.685823e-03  #> f_parent_to_m1  0.469113477 5.598387e-01 @@ -373,15 +374,15 @@ Profile-Likelihood Based Confidence Intervals, Applied Statistics, 37,  #> f_parent_to_m1  TRUE FALSE  #> sigma           TRUE FALSE</div><div class='input'><span class='va'>rel_diffs_transformed_ff</span>  </div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       0.0005408689 0.0002217234 +#> parent_0       0.0005408690 0.0002217233  #> k_parent       0.0009598532 0.0009001864 -#> k_m1           0.0307283044 0.0290588365 -#> f_parent_to_m1 0.0046881768 0.0027780063 +#> k_m1           0.0307283041 0.0290588361 +#> f_parent_to_m1 0.0046881769 0.0027780063  #> sigma          0.0550252516 0.0327066836</div><div class='input'><span class='va'>rel_diffs_untransformed_ff</span>  </div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       0.0005408689 0.0002217233 -#> k_parent       0.0046102155 0.0023732281 -#> k_m1           0.0146740688 0.0025291817 +#> parent_0       0.0005408689 0.0002217232 +#> k_parent       0.0046102156 0.0023732281 +#> k_m1           0.0146740690 0.0025291820  #> f_parent_to_m1 0.0046995211 0.0023457712  #> sigma          0.0550252516 0.0327066836</div><div class='input'>  <span class='co'># The profiling for the following fit does not finish in a reasonable time,</span> @@ -395,18 +396,18 @@ Profile-Likelihood Based Confidence Intervals, Applied Statistics, 37,    error_model_algorithm <span class='op'>=</span> <span class='st'>"direct"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_tc_2</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span><span class='op'>)</span>  </div><div class='output co'>#>                        2.5%        97.5% -#> parent_0       94.596126334 106.19944007 -#> k_M1            0.037605408   0.04490759 -#> k_M2            0.008568739   0.01087675 -#> f_parent_to_M1  0.021463787   0.62023881 -#> f_parent_to_M2  0.015166531   0.37975349 -#> k1              0.273897467   0.33388084 -#> k2              0.018614555   0.02250379 -#> g               0.671943606   0.73583278 -#> sigma_low       0.251283766   0.83992113 -#> rsd_high        0.040411014   0.07662005</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_tc_2</span>, <span class='st'>"parent_0"</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span><span class='op'>)</span> +#> parent_0       94.596039609 106.19954892 +#> k_M1            0.037605368   0.04490762 +#> k_M2            0.008568731   0.01087676 +#> f_parent_to_M1  0.021462489   0.62023882 +#> f_parent_to_M2  0.015165617   0.37975348 +#> k1              0.273897348   0.33388101 +#> k2              0.018614554   0.02250378 +#> g               0.671943411   0.73583305 +#> sigma_low       0.251283495   0.83992077 +#> rsd_high        0.040411024   0.07662008</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/stats/confint.html'>confint</a></span><span class='op'>(</span><span class='va'>f_tc_2</span>, <span class='st'>"parent_0"</span>, method <span class='op'>=</span> <span class='st'>"quadratic"</span><span class='op'>)</span>  </div><div class='output co'>#>              2.5%    97.5% -#> parent_0 94.59613 106.1994</div><div class='input'><span class='co'># }</span> +#> parent_0 94.59604 106.1995</div><div class='input'><span class='co'># }</span>  </div></pre>    </div>    <div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar"> diff --git a/docs/dev/reference/endpoints.html b/docs/dev/reference/endpoints.html index db702c2e..a13e11a7 100644 --- a/docs/dev/reference/endpoints.html +++ b/docs/dev/reference/endpoints.html @@ -78,7 +78,7 @@ advantage that the SFORB model can also be used for metabolites." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -127,7 +127,7 @@ advantage that the SFORB model can also be used for metabolites." />        <ul class="nav navbar-nav navbar-right">          <li>    <a href="https://github.com/jranke/mkin/"> -    <span class="fab fa fab fa-github fa-lg"></span> +    <span class="fab fa-github fa-lg"></span>    </a>  </li> diff --git a/docs/dev/reference/index.html b/docs/dev/reference/index.html index e038ef5c..7e98aa50 100644 --- a/docs/dev/reference/index.html +++ b/docs/dev/reference/index.html @@ -71,7 +71,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -175,7 +175,7 @@        </tr><tr>          <td> -          <p><code><a href="mmkin.html">mmkin()</a></code> </p> +          <p><code><a href="mmkin.html">mmkin()</a></code> <code><a href="mmkin.html">print(<i><mmkin></i>)</a></code> </p>          </td>          <td><p>Fit one or more kinetic models with one or more state variables to one or  more datasets</p></td> @@ -297,12 +297,6 @@ of an mmkin object</p></td>            <p><code><a href="AIC.mmkin.html">AIC(<i><mmkin></i>)</a></code> <code><a href="AIC.mmkin.html">BIC(<i><mmkin></i>)</a></code> </p>          </td>          <td><p>Calculate the AIC for a column of an mmkin object</p></td> -      </tr><tr> -         -        <td> -          <p><code><a href="print.mmkin.html">print(<i><mmkin></i>)</a></code> </p> -        </td> -        <td><p>Print method for mmkin objects</p></td>        </tr>      </tbody><tbody>        <tr> diff --git a/docs/dev/reference/logLik.mkinfit.html b/docs/dev/reference/logLik.mkinfit.html index 66539dbd..82c0654f 100644 --- a/docs/dev/reference/logLik.mkinfit.html +++ b/docs/dev/reference/logLik.mkinfit.html @@ -76,7 +76,7 @@ the error model." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -125,7 +125,7 @@ the error model." />        <ul class="nav navbar-nav navbar-right">          <li>    <a href="https://github.com/jranke/mkin/"> -    <span class="fab fa fab fa-github fa-lg"></span> +    <span class="fab fa-github fa-lg"></span>    </a>  </li> @@ -196,11 +196,11 @@ and the fitted error model parameters.</p>      parent <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span>, to <span class='op'>=</span> <span class='st'>"m1"</span><span class='op'>)</span>,      m1 <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span><span class='op'>)</span>    <span class='op'>)</span> -</div><div class='output co'>#> <span class='message'>Temporary DLL for differentials generated and loaded</span></div><div class='input'>  <span class='va'>d_t</span> <span class='op'><-</span> <span class='va'>FOCUS_2006_D</span> +</div><div class='output co'>#> <span class='message'>Temporary DLL for differentials generated and loaded</span></div><div class='input'>  <span class='va'>d_t</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/subset.html'>subset</a></span><span class='op'>(</span><span class='va'>FOCUS_2006_D</span>, <span class='va'>value</span> <span class='op'>!=</span> <span class='fl'>0</span><span class='op'>)</span>    <span class='va'>f_nw</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>sfo_sfo</span>, <span class='va'>d_t</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> <span class='co'># no weighting (weights are unity)</span> -</div><div class='output co'>#> <span class='warning'>Warning: Observations with value of zero were removed from the data</span></div><div class='input'>  <span class='va'>f_obs</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>sfo_sfo</span>, <span class='va'>d_t</span>, error_model <span class='op'>=</span> <span class='st'>"obs"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='warning'>Warning: Observations with value of zero were removed from the data</span></div><div class='input'>  <span class='va'>f_tc</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>sfo_sfo</span>, <span class='va'>d_t</span>, error_model <span class='op'>=</span> <span class='st'>"tc"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='warning'>Warning: Observations with value of zero were removed from the data</span></div><div class='input'>  <span class='fu'><a href='https://rdrr.io/r/stats/AIC.html'>AIC</a></span><span class='op'>(</span><span class='va'>f_nw</span>, <span class='va'>f_obs</span>, <span class='va'>f_tc</span><span class='op'>)</span> +  <span class='va'>f_obs</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span><span class='op'>(</span><span class='va'>f_nw</span>, error_model <span class='op'>=</span> <span class='st'>"obs"</span><span class='op'>)</span> +  <span class='va'>f_tc</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span><span class='op'>(</span><span class='va'>f_nw</span>, error_model <span class='op'>=</span> <span class='st'>"tc"</span><span class='op'>)</span> +  <span class='fu'><a href='https://rdrr.io/r/stats/AIC.html'>AIC</a></span><span class='op'>(</span><span class='va'>f_nw</span>, <span class='va'>f_obs</span>, <span class='va'>f_tc</span><span class='op'>)</span>  </div><div class='output co'>#>       df      AIC  #> f_nw   5 204.4486  #> f_obs  6 205.8727 diff --git a/docs/dev/reference/mkinresplot.html b/docs/dev/reference/mkinresplot.html index 4b2f6bea..2e10d5f6 100644 --- a/docs/dev/reference/mkinresplot.html +++ b/docs/dev/reference/mkinresplot.html @@ -75,7 +75,7 @@ argument show_residuals = TRUE." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -124,7 +124,7 @@ argument show_residuals = TRUE." />        <ul class="nav navbar-nav navbar-right">          <li>    <a href="https://github.com/jranke/mkin/"> -    <span class="fab fa fab fa-github fa-lg"></span> +    <span class="fab fa-github fa-lg"></span>    </a>  </li> @@ -242,7 +242,7 @@ lines of the mkinfit object, and <code><a href='plot.mkinfit.html'>plot_res</a><  combining the plot of the fit and the residual plot.</p></div>      <h2 class="hasAnchor" id="author"><a class="anchor" href="#author"></a>Author</h2> -    <p>Johannes Ranke</p> +    <p>Johannes Ranke and Katrin Lindenberger</p>      <h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>      <pre class="examples"><div class='input'> diff --git a/docs/dev/reference/mmkin-1.png b/docs/dev/reference/mmkin-1.pngBinary files differ index 7b7da90a..0db3379f 100644 --- a/docs/dev/reference/mmkin-1.png +++ b/docs/dev/reference/mmkin-1.png diff --git a/docs/dev/reference/mmkin-2.png b/docs/dev/reference/mmkin-2.pngBinary files differ index ce2b2af4..024a9892 100644 --- a/docs/dev/reference/mmkin-2.png +++ b/docs/dev/reference/mmkin-2.png diff --git a/docs/dev/reference/mmkin-3.png b/docs/dev/reference/mmkin-3.pngBinary files differ index bb96f1b2..a23d7cb9 100644 --- a/docs/dev/reference/mmkin-3.png +++ b/docs/dev/reference/mmkin-3.png diff --git a/docs/dev/reference/mmkin-4.png b/docs/dev/reference/mmkin-4.pngBinary files differ index 351b21aa..89975db5 100644 --- a/docs/dev/reference/mmkin-4.png +++ b/docs/dev/reference/mmkin-4.png diff --git a/docs/dev/reference/mmkin-5.png b/docs/dev/reference/mmkin-5.pngBinary files differ index c1c05eea..a2f34983 100644 --- a/docs/dev/reference/mmkin-5.png +++ b/docs/dev/reference/mmkin-5.png diff --git a/docs/dev/reference/mmkin.html b/docs/dev/reference/mmkin.html index 651eb9a6..65c91adf 100644 --- a/docs/dev/reference/mmkin.html +++ b/docs/dev/reference/mmkin.html @@ -75,7 +75,7 @@ datasets specified in its first two arguments." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -124,7 +124,7 @@ datasets specified in its first two arguments." />        <ul class="nav navbar-nav navbar-right">          <li>    <a href="https://github.com/jranke/mkin/"> -    <span class="fab fa fab fa-github fa-lg"></span> +    <span class="fab fa-github fa-lg"></span>    </a>  </li> @@ -158,7 +158,10 @@ datasets specified in its first two arguments.</p>    cores <span class='op'>=</span> <span class='fu'>parallel</span><span class='fu'>::</span><span class='fu'><a href='https://rdrr.io/r/parallel/detectCores.html'>detectCores</a></span><span class='op'>(</span><span class='op'>)</span>,    cluster <span class='op'>=</span> <span class='cn'>NULL</span>,    <span class='va'>...</span> -<span class='op'>)</span></pre> +<span class='op'>)</span> + +<span class='co'># S3 method for mmkin</span> +<span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>x</span>, <span class='va'>...</span><span class='op'>)</span></pre>      <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>      <table class="ref-arguments"> @@ -189,7 +192,11 @@ for parallel execution.</p></td>      </tr>      <tr>        <th>...</th> -      <td><p>Further arguments that will be passed to <code><a href='mkinfit.html'>mkinfit</a></code>.</p></td> +      <td><p>Not used.</p></td> +    </tr> +    <tr> +      <th>x</th> +      <td><p>An mmkin object.</p></td>      </tr>      </table> @@ -227,19 +234,19 @@ plotting.</p></div>  <span class='va'>time_default</span>  </div><div class='output co'>#>    user  system elapsed  -#>   4.968   0.427   1.342 </div><div class='input'><span class='va'>time_1</span> +#>   4.438   0.334   1.640 </div><div class='input'><span class='va'>time_1</span>  </div><div class='output co'>#>    user  system elapsed  -#>   5.365   0.000   5.368 </div><div class='input'> +#>   5.535   0.004   5.539 </div><div class='input'>  <span class='fu'><a href='endpoints.html'>endpoints</a></span><span class='op'>(</span><span class='va'>fits.0</span><span class='op'>[[</span><span class='st'>"SFO_lin"</span>, <span class='fl'>2</span><span class='op'>]</span><span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> $ff  #>   parent_M1 parent_sink       M1_M2     M1_sink  -#>   0.7340478   0.2659522   0.7505687   0.2494313  +#>   0.7340481   0.2659519   0.7505683   0.2494317   #>   #> $distimes  #>             DT50       DT90  #> parent  0.877769   2.915885 -#> M1      2.325746   7.725960 -#> M2     33.720083 112.015691 +#> M1      2.325744   7.725956 +#> M2     33.720100 112.015749  #> </div><div class='input'>  <span class='co'># plot.mkinfit handles rows or columns of mmkin result objects</span>  <span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>fits.0</span><span class='op'>[</span><span class='fl'>1</span>, <span class='op'>]</span><span class='op'>)</span> @@ -266,12 +273,10 @@ plotting.</p></div>  #>       dataset  #> model  A  B  C  D   #>   SFO  OK OK OK OK -#>   FOMC C  OK OK OK +#>   FOMC OK OK OK OK  #>   DFOP OK OK OK OK  #>  -#> OK: No warnings -#> C: Optimisation did not converge: -#> false convergence (8)</div><div class='input'><span class='co'># We get false convergence for the FOMC fit to FOCUS_2006_A because this</span> +#> OK: No warnings</div><div class='input'><span class='co'># We get false convergence for the FOMC fit to FOCUS_2006_A because this</span>  <span class='co'># dataset is really SFO, and the FOMC fit is overparameterised</span>  <span class='fu'>stopCluster</span><span class='op'>(</span><span class='va'>cl</span><span class='op'>)</span>  <span class='co'># }</span> diff --git a/docs/dev/reference/nlme.mmkin-1.png b/docs/dev/reference/nlme.mmkin-1.pngBinary files differ index 25bebeca..9186c135 100644 --- a/docs/dev/reference/nlme.mmkin-1.png +++ b/docs/dev/reference/nlme.mmkin-1.png diff --git a/docs/dev/reference/nlme.mmkin-2.png b/docs/dev/reference/nlme.mmkin-2.pngBinary files differ index c314c149..d395fe02 100644 --- a/docs/dev/reference/nlme.mmkin-2.png +++ b/docs/dev/reference/nlme.mmkin-2.png diff --git a/docs/dev/reference/nlme.mmkin-3.png b/docs/dev/reference/nlme.mmkin-3.pngBinary files differ index a40b7cad..40518a59 100644 --- a/docs/dev/reference/nlme.mmkin-3.png +++ b/docs/dev/reference/nlme.mmkin-3.png diff --git a/docs/dev/reference/nlme.mmkin.html b/docs/dev/reference/nlme.mmkin.html index a4d7070a..2649c111 100644 --- a/docs/dev/reference/nlme.mmkin.html +++ b/docs/dev/reference/nlme.mmkin.html @@ -74,7 +74,7 @@ have been obtained by fitting the same model to a list of datasets." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -123,7 +123,7 @@ have been obtained by fitting the same model to a list of datasets." />        <ul class="nav navbar-nav navbar-right">          <li>    <a href="https://github.com/jranke/mkin/"> -    <span class="fab fa fab fa-github fa-lg"></span> +    <span class="fab fa-github fa-lg"></span>    </a>  </li> @@ -262,6 +262,12 @@ parameters taken from the mmkin object are used</p></td>      <p>Upon success, a fitted 'nlme.mmkin' object, which is an nlme object  with additional elements. It also inherits from 'mixed.mmkin'.</p> +    <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> + +    <p>Note that the convergence of the nlme algorithms depends on the quality +of the data. In degradation kinetics, we often only have few datasets +(e.g. data for few soils) and complicated degradation models, which may +make it impossible to obtain convergence with nlme.</p>      <h2 class="hasAnchor" id="note"><a class="anchor" href="#note"></a>Note</h2>      <p>As the object inherits from <a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme::nlme</a>, there is a wealth of @@ -284,7 +290,7 @@ methods that will automatically work on 'nlme.mmkin' objects, such as    <span class='fu'><a href='https://rdrr.io/r/stats/anova.html'>anova</a></span><span class='op'>(</span><span class='va'>f_nlme_sfo</span>, <span class='va'>f_nlme_dfop</span><span class='op'>)</span>  </div><div class='output co'>#>             Model df      AIC      BIC    logLik   Test  L.Ratio p-value  #> f_nlme_sfo      1  5 625.0539 637.5529 -307.5269                         -#> f_nlme_dfop     2  9 495.1270 517.6253 -238.5635 1 vs 2 137.9268  <.0001</div><div class='input'>  <span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop</span><span class='op'>)</span> +#> f_nlme_dfop     2  9 495.1270 517.6253 -238.5635 1 vs 2 137.9269  <.0001</div><div class='input'>  <span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop</span><span class='op'>)</span>  </div><div class='output co'>#> Kinetic nonlinear mixed-effects model fit by maximum likelihood  #>   #> Structural model: @@ -312,7 +318,7 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  </div><div class='img'><img src='nlme.mmkin-1.png' alt='' width='700' height='433' /></div><div class='input'>  <span class='fu'><a href='endpoints.html'>endpoints</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop</span><span class='op'>)</span>  </div><div class='output co'>#> $distimes  #>            DT50     DT90 DT50back  DT50_k1  DT50_k2 -#> parent 10.79857 100.7937 30.34192 4.193937 43.85442 +#> parent 10.79857 100.7937 30.34193 4.193938 43.85443  #> </div><div class='input'>    <span class='va'>ds_2</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/lapply.html'>lapply</a></span><span class='op'>(</span><span class='va'>experimental_data_for_UBA_2019</span><span class='op'>[</span><span class='fl'>6</span><span class='op'>:</span><span class='fl'>10</span><span class='op'>]</span>,     <span class='kw'>function</span><span class='op'>(</span><span class='va'>x</span><span class='op'>)</span> <span class='va'>x</span><span class='op'>$</span><span class='va'>data</span><span class='op'>[</span><span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"name"</span>, <span class='st'>"time"</span>, <span class='st'>"value"</span><span class='op'>)</span><span class='op'>]</span><span class='op'>)</span> @@ -335,16 +341,17 @@ methods that will automatically work on 'nlme.mmkin' objects, such as    <span class='co'># f_nlme_sfo_sfo_ff <- nlme(f_2["SFO-SFO-ff", ])</span>    <span class='co'>#plot(f_nlme_sfo_sfo_ff)</span> -  <span class='co'># With the log-Cholesky parameterization, this converges in 11</span> -  <span class='co'># iterations and around 100 seconds, but without tweaking control</span> -  <span class='co'># parameters (with pdDiag, increasing the tolerance and pnlsMaxIter was</span> -  <span class='co'># necessary)</span> -  <span class='va'>f_nlme_dfop_sfo</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f_2</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in nlme.formula(model = value ~ (mkin::get_deg_func())(name, time,     parent_0, log_k_A1, f_parent_qlogis, log_k1, log_k2, g_qlogis),     data = structure(list(ds = structure(c(1L, 1L, 1L, 1L, 1L,     1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L,     1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L,     1L, 1L, 1L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L,     2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L,     2L, 2L, 2L, 2L, 2L, 2L, 2L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L,     3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L,     3L, 3L, 3L, 3L, 3L, 3L, 3L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L,     4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L,     4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L,     5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L,     5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L    ), .Label = c("1", "2", "3", "4", "5"), class = c("ordered",     "factor")), name = c("parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "A1", "A1", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1"), time = c(0, 0, 3, 3, 6, 6, 10, 10, 20, 20, 34, 34,     55, 55, 90, 90, 112, 112, 132, 132, 3, 3, 6, 6, 10, 10, 20,     20, 34, 34, 55, 55, 90, 90, 112, 112, 132, 132, 0, 0, 3,     3, 7, 7, 14, 14, 30, 30, 60, 60, 90, 90, 120, 120, 180, 180,     3, 3, 7, 7, 14, 14, 30, 30, 60, 60, 90, 90, 120, 120, 180,     180, 0, 0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70,     70, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 0,     0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 91,     91, 120, 120, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70,     70, 91, 91, 120, 120, 0, 0, 8, 8, 14, 14, 21, 21, 41, 41,     63, 63, 91, 91, 120, 120, 8, 8, 14, 14, 21, 21, 41, 41, 63,     63, 91, 91, 120, 120), value = c(97.2, 96.4, 71.1, 69.2,     58.1, 56.6, 44.4, 43.4, 33.3, 29.2, 17.6, 18, 10.5, 9.3,     4.5, 4.7, 3, 3.4, 2.3, 2.7, 4.3, 4.6, 7, 7.2, 8.2, 8, 11,     13.7, 11.5, 12.7, 14.9, 14.5, 12.1, 12.3, 9.9, 10.2, 8.8,     7.8, 93.6, 92.3, 87, 82.2, 74, 73.9, 64.2, 69.5, 54, 54.6,     41.1, 38.4, 32.5, 35.5, 28.1, 29, 26.5, 27.6, 3.9, 3.1, 6.9,     6.6, 10.4, 8.3, 14.4, 13.7, 22.1, 22.3, 27.5, 25.4, 28, 26.6,     25.8, 25.3, 91.9, 90.8, 64.9, 66.2, 43.5, 44.1, 18.3, 18.1,     10.2, 10.8, 4.9, 3.3, 1.6, 1.5, 1.1, 0.9, 9.6, 7.7, 15, 15.1,     21.2, 21.1, 19.7, 18.9, 17.5, 15.9, 9.5, 9.8, 6.2, 6.1, 99.8,     98.3, 77.1, 77.2, 59, 58.1, 27.4, 29.2, 19.1, 29.6, 10.1,     18.2, 4.5, 9.1, 2.3, 2.9, 2, 1.8, 2, 2.2, 4.2, 3.9, 7.4,     7.9, 14.5, 13.7, 14.2, 12.2, 13.7, 13.2, 13.6, 15.4, 10.4,     11.6, 10, 9.5, 9.1, 9, 96.1, 94.3, 73.9, 73.9, 69.4, 73.1,     65.6, 65.3, 55.9, 54.4, 47, 49.3, 44.7, 46.7, 42.1, 41.3,     3.3, 3.4, 3.9, 2.9, 6.4, 7.2, 9.1, 8.5, 11.7, 12, 13.3, 13.2,     14.3, 12.1)), row.names = c(NA, -170L), class = c("nfnGroupedData",     "nfGroupedData", "groupedData", "data.frame"), formula = value ~         time | ds, FUN = function (x)     max(x, na.rm = TRUE), order.groups = FALSE), start = list(        fixed = c(parent_0 = 93.8101519326534, log_k_A1 = -9.76474551635931,         f_parent_qlogis = -0.971114801595408, log_k1 = -1.87993711571859,         log_k2 = -4.27081421366622, g_qlogis = 0.135644115277507        ), random = list(ds = structure(c(2.56569977430371, -3.49441920289139,         -3.32614443321494, 4.35347873814922, -0.0986148763466161,         4.65850590018027, 1.8618544764481, 6.12693257601545,         4.91792724701579, -17.5652201996596, -0.466203822618637,         0.746660653597927, 0.282193987271096, -0.42053488943072,         -0.142115928819667, 0.369240076779088, -1.38985563501659,         1.02592753494098, 0.73090914081534, -0.736221117518819,         0.768170629350299, -1.89347658079869, 1.72168783460352,         0.844607177798114, -1.44098906095325, -0.377731855445672,         0.168180098477565, 0.469683412912104, 0.500717664434525,         -0.760849320378522), .Dim = 5:6, .Dimnames = list(c("1",         "2", "3", "4", "5"), c("parent_0", "log_k_A1", "f_parent_qlogis",         "log_k1", "log_k2", "g_qlogis"))))), fixed = list(parent_0 ~         1, log_k_A1 ~ 1, f_parent_qlogis ~ 1, log_k1 ~ 1, log_k2 ~         1, g_qlogis ~ 1), random = structure(numeric(0), class = c("pdDiag",     "pdMat"), formula = structure(list(parent_0 ~ 1, log_k_A1 ~         1, f_parent_qlogis ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~         1), class = "listForm"), Dimnames = list(NULL, NULL))): maximum number of iterations (maxIter = 50) reached without convergence</span></div><div class='output co'>#> <span class='message'>Timing stopped at: 49.95 16.5 44.08</span></div><div class='input'> +  <span class='co'># For the following, we need to increase pnlsMaxIter and the tolerance</span> +  <span class='co'># to get convergence</span> +  <span class='va'>f_nlme_dfop_sfo</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f_2</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span>, +    control <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>pnlsMaxIter <span class='op'>=</span> <span class='fl'>120</span>, tolerance <span class='op'>=</span> <span class='fl'>5e-4</span><span class='op'>)</span><span class='op'>)</span> +    <span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop_sfo</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in plot(f_nlme_dfop_sfo): object 'f_nlme_dfop_sfo' not found</span></div><div class='input'> +</div><div class='img'><img src='nlme.mmkin-3.png' alt='' width='700' height='433' /></div><div class='input'>    <span class='fu'><a href='https://rdrr.io/r/stats/anova.html'>anova</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop_sfo</span>, <span class='va'>f_nlme_sfo_sfo</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in anova(f_nlme_dfop_sfo, f_nlme_sfo_sfo): object 'f_nlme_dfop_sfo' not found</span></div><div class='input'> +</div><div class='output co'>#>                 Model df       AIC       BIC    logLik   Test  L.Ratio p-value +#> f_nlme_dfop_sfo     1 13  843.8548  884.6201 -408.9274                         +#> f_nlme_sfo_sfo      2  9 1085.1821 1113.4043 -533.5910 1 vs 2 249.3273  <.0001</div><div class='input'>    <span class='fu'><a href='endpoints.html'>endpoints</a></span><span class='op'>(</span><span class='va'>f_nlme_sfo_sfo</span><span class='op'>)</span>  </div><div class='output co'>#> $ff  #> parent_sink   parent_A1     A1_sink  @@ -355,7 +362,15 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  #> parent 19.13518  63.5657  #> A1     66.02155 219.3189  #> </div><div class='input'>  <span class='fu'><a href='endpoints.html'>endpoints</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop_sfo</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in endpoints(f_nlme_dfop_sfo): object 'f_nlme_dfop_sfo' not found</span></div><div class='input'> +</div><div class='output co'>#> $ff +#>   parent_A1 parent_sink  +#>   0.2768575   0.7231425  +#>  +#> $distimes +#>             DT50     DT90 DT50back  DT50_k1  DT50_k2 +#> parent  11.07091 104.6320 31.49737 4.462384 46.20825 +#> A1     162.30492 539.1653       NA       NA       NA +#> </div><div class='input'>    <span class='kw'>if</span> <span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='fu'>findFunction</span><span class='op'>(</span><span class='st'>"varConstProp"</span><span class='op'>)</span><span class='op'>)</span> <span class='op'>></span> <span class='fl'>0</span><span class='op'>)</span> <span class='op'>{</span> <span class='co'># tc error model for nlme available</span>      <span class='co'># Attempts to fit metabolite kinetics with the tc error model are possible,</span>      <span class='co'># but need tweeking of control values and sometimes do not converge</span> @@ -381,7 +396,7 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  #> Fixed effects:  #>  list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~ 1)   #> parent_0   log_k1   log_k2 g_qlogis  -#> 94.04775 -1.82340 -4.16715  0.05685  +#> 94.04774 -1.82340 -4.16716  0.05686   #>   #> Random effects:  #>  Formula: list(parent_0 ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~ 1) @@ -395,10 +410,8 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  #>  Formula: ~fitted(.)   #>  Parameter estimates:  #>      const       prop  -#> 2.23224114 0.01262341 </div><div class='input'> -  <span class='va'>f_2_obs</span> <span class='op'><-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='st'>"SFO-SFO"</span> <span class='op'>=</span> <span class='va'>m_sfo_sfo</span>, -   <span class='st'>"DFOP-SFO"</span> <span class='op'>=</span> <span class='va'>m_dfop_sfo</span><span class='op'>)</span>, -    <span class='va'>ds_2</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span>, error_model <span class='op'>=</span> <span class='st'>"obs"</span><span class='op'>)</span> +#> 2.23223147 0.01262395 </div><div class='input'> +  <span class='va'>f_2_obs</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span><span class='op'>(</span><span class='va'>f_2</span>, error_model <span class='op'>=</span> <span class='st'>"obs"</span><span class='op'>)</span>    <span class='va'>f_nlme_sfo_sfo_obs</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f_2_obs</span><span class='op'>[</span><span class='st'>"SFO-SFO"</span>, <span class='op'>]</span><span class='op'>)</span>    <span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>f_nlme_sfo_sfo_obs</span><span class='op'>)</span>  </div><div class='output co'>#> Kinetic nonlinear mixed-effects model fit by maximum likelihood @@ -429,18 +442,21 @@ methods that will automatically work on 'nlme.mmkin' objects, such as  #>  Formula: ~1 | name   #>  Parameter estimates:  #>    parent        A1  -#> 1.0000000 0.2050003 </div><div class='input'>  <span class='va'>f_nlme_dfop_sfo_obs</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f_2_obs</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in nlme.formula(model = value ~ (mkin::get_deg_func())(name, time,     parent_0, log_k_A1, f_parent_qlogis, log_k1, log_k2, g_qlogis),     data = structure(list(ds = structure(c(1L, 1L, 1L, 1L, 1L,     1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L,     1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L, 1L,     1L, 1L, 1L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L,     2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L, 2L,     2L, 2L, 2L, 2L, 2L, 2L, 2L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L,     3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L, 3L,     3L, 3L, 3L, 3L, 3L, 3L, 3L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L,     4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L,     4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L, 4L,     5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L,     5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L, 5L    ), .Label = c("1", "2", "3", "4", "5"), class = c("ordered",     "factor")), name = c("parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "A1", "A1", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1", "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "parent", "parent",     "parent", "parent", "parent", "parent", "A1", "A1", "A1",     "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1", "A1",     "A1"), time = c(0, 0, 3, 3, 6, 6, 10, 10, 20, 20, 34, 34,     55, 55, 90, 90, 112, 112, 132, 132, 3, 3, 6, 6, 10, 10, 20,     20, 34, 34, 55, 55, 90, 90, 112, 112, 132, 132, 0, 0, 3,     3, 7, 7, 14, 14, 30, 30, 60, 60, 90, 90, 120, 120, 180, 180,     3, 3, 7, 7, 14, 14, 30, 30, 60, 60, 90, 90, 120, 120, 180,     180, 0, 0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70,     70, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 0,     0, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70, 70, 91,     91, 120, 120, 1, 1, 3, 3, 8, 8, 14, 14, 27, 27, 48, 48, 70,     70, 91, 91, 120, 120, 0, 0, 8, 8, 14, 14, 21, 21, 41, 41,     63, 63, 91, 91, 120, 120, 8, 8, 14, 14, 21, 21, 41, 41, 63,     63, 91, 91, 120, 120), value = c(97.2, 96.4, 71.1, 69.2,     58.1, 56.6, 44.4, 43.4, 33.3, 29.2, 17.6, 18, 10.5, 9.3,     4.5, 4.7, 3, 3.4, 2.3, 2.7, 4.3, 4.6, 7, 7.2, 8.2, 8, 11,     13.7, 11.5, 12.7, 14.9, 14.5, 12.1, 12.3, 9.9, 10.2, 8.8,     7.8, 93.6, 92.3, 87, 82.2, 74, 73.9, 64.2, 69.5, 54, 54.6,     41.1, 38.4, 32.5, 35.5, 28.1, 29, 26.5, 27.6, 3.9, 3.1, 6.9,     6.6, 10.4, 8.3, 14.4, 13.7, 22.1, 22.3, 27.5, 25.4, 28, 26.6,     25.8, 25.3, 91.9, 90.8, 64.9, 66.2, 43.5, 44.1, 18.3, 18.1,     10.2, 10.8, 4.9, 3.3, 1.6, 1.5, 1.1, 0.9, 9.6, 7.7, 15, 15.1,     21.2, 21.1, 19.7, 18.9, 17.5, 15.9, 9.5, 9.8, 6.2, 6.1, 99.8,     98.3, 77.1, 77.2, 59, 58.1, 27.4, 29.2, 19.1, 29.6, 10.1,     18.2, 4.5, 9.1, 2.3, 2.9, 2, 1.8, 2, 2.2, 4.2, 3.9, 7.4,     7.9, 14.5, 13.7, 14.2, 12.2, 13.7, 13.2, 13.6, 15.4, 10.4,     11.6, 10, 9.5, 9.1, 9, 96.1, 94.3, 73.9, 73.9, 69.4, 73.1,     65.6, 65.3, 55.9, 54.4, 47, 49.3, 44.7, 46.7, 42.1, 41.3,     3.3, 3.4, 3.9, 2.9, 6.4, 7.2, 9.1, 8.5, 11.7, 12, 13.3, 13.2,     14.3, 12.1)), row.names = c(NA, -170L), class = c("nfnGroupedData",     "nfGroupedData", "groupedData", "data.frame"), formula = value ~         time | ds, FUN = function (x)     max(x, na.rm = TRUE), order.groups = FALSE), start = list(        fixed = c(parent_0 = 93.4272167134207, log_k_A1 = -9.71590717106959,         f_parent_qlogis = -0.953712099744438, log_k1 = -1.95256957646888,         log_k2 = -4.42919226610318, g_qlogis = 0.193023137298073        ), random = list(ds = structure(c(2.85557330683041, -3.87630303729395,         -2.78062140212751, 4.82042042600536, -1.01906929341432,         4.613992019697, 2.05871276943309, 6.0766404049189, 4.86471337131288,         -17.6140585653619, -0.480721175257541, 0.773079218835614,         0.260464433006093, -0.440615012802434, -0.112207463781733,         0.445812953745225, -1.49588630006094, 1.13602040717272,         0.801850880762046, -0.887797941619048, 0.936480292463262,         -2.43093808171905, 1.91256225793793, 0.984827519864443,         -1.40293198854659, -0.455176326336681, 0.376355651864385,         0.343919720700401, 0.46329187713133, -0.728390923359434        ), .Dim = 5:6, .Dimnames = list(c("1", "2", "3", "4",         "5"), c("parent_0", "log_k_A1", "f_parent_qlogis", "log_k1",         "log_k2", "g_qlogis"))))), fixed = list(parent_0 ~ 1,         log_k_A1 ~ 1, f_parent_qlogis ~ 1, log_k1 ~ 1, log_k2 ~             1, g_qlogis ~ 1), random = structure(numeric(0), class = c("pdDiag",     "pdMat"), formula = structure(list(parent_0 ~ 1, log_k_A1 ~         1, f_parent_qlogis ~ 1, log_k1 ~ 1, log_k2 ~ 1, g_qlogis ~         1), class = "listForm"), Dimnames = list(NULL, NULL)),     weights = structure(numeric(0), formula = ~1 | name, class = c("varIdent",     "varFunc"))): maximum number of iterations (maxIter = 50) reached without convergence</span></div><div class='output co'>#> <span class='message'>Timing stopped at: 59.38 16.5 53.5</span></div><div class='input'> -  <span class='va'>f_2_tc</span> <span class='op'><-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='st'>"SFO-SFO"</span> <span class='op'>=</span> <span class='va'>m_sfo_sfo</span>, -   <span class='st'>"DFOP-SFO"</span> <span class='op'>=</span> <span class='va'>m_dfop_sfo</span><span class='op'>)</span>, -    <span class='va'>ds_2</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span>, error_model <span class='op'>=</span> <span class='st'>"tc"</span><span class='op'>)</span> -  <span class='co'># f_nlme_sfo_sfo_tc <- nlme(f_2_tc["SFO-SFO", ]) # stops with error message</span> -  <span class='va'>f_nlme_dfop_sfo_tc</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f_2_tc</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='warning'>Warning: longer object length is not a multiple of shorter object length</span></div><div class='output co'>#> <span class='error'>Error in X[, fmap[[nm]]] <- gradnm: number of items to replace is not a multiple of replacement length</span></div><div class='output co'>#> <span class='message'>Timing stopped at: 6.363 2.688 5.469</span></div><div class='input'>  <span class='co'># We get warnings about false convergence in the LME step in several iterations</span> -  <span class='co'># but as the last such warning occurs in iteration 25 and we have 28 iterations</span> -  <span class='co'># we can ignore these</span> -  <span class='fu'><a href='https://rdrr.io/r/stats/anova.html'>anova</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop_sfo</span>, <span class='va'>f_nlme_dfop_sfo_obs</span>, <span class='va'>f_nlme_dfop_sfo_tc</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in anova(f_nlme_dfop_sfo, f_nlme_dfop_sfo_obs, f_nlme_dfop_sfo_tc): object 'f_nlme_dfop_sfo' not found</span></div><div class='input'> +#> 1.0000000 0.2049995 </div><div class='input'>  <span class='va'>f_nlme_dfop_sfo_obs</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/nlme/man/nlme.html'>nlme</a></span><span class='op'>(</span><span class='va'>f_2_obs</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span>, +    control <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>pnlsMaxIter <span class='op'>=</span> <span class='fl'>120</span>, tolerance <span class='op'>=</span> <span class='fl'>5e-4</span><span class='op'>)</span><span class='op'>)</span> + +  <span class='va'>f_2_tc</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span><span class='op'>(</span><span class='va'>f_2</span>, error_model <span class='op'>=</span> <span class='st'>"tc"</span><span class='op'>)</span> +  <span class='co'># f_nlme_sfo_sfo_tc <- nlme(f_2_tc["SFO-SFO", ]) # No convergence with 50 iterations</span> +  <span class='co'># f_nlme_dfop_sfo_tc <- nlme(f_2_tc["DFOP-SFO", ],</span> +  <span class='co'>#  control = list(pnlsMaxIter = 120, tolerance = 5e-4)) # Error in X[, fmap[[nm]]] <- gradnm</span> + +  <span class='fu'><a href='https://rdrr.io/r/stats/anova.html'>anova</a></span><span class='op'>(</span><span class='va'>f_nlme_dfop_sfo</span>, <span class='va'>f_nlme_dfop_sfo_obs</span><span class='op'>)</span> +</div><div class='output co'>#>                     Model df      AIC      BIC    logLik   Test  L.Ratio +#> f_nlme_dfop_sfo         1 13 843.8548 884.6201 -408.9274                 +#> f_nlme_dfop_sfo_obs     2 14 817.5338 861.4350 -394.7669 1 vs 2 28.32093 +#>                     p-value +#> f_nlme_dfop_sfo             +#> f_nlme_dfop_sfo_obs  <.0001</div><div class='input'>  <span class='co'># }</span>  </div></pre>    </div> diff --git a/docs/dev/reference/plot.mixed.mmkin-1.png b/docs/dev/reference/plot.mixed.mmkin-1.pngBinary files differ index 5cb33214..9c9a2211 100644 --- a/docs/dev/reference/plot.mixed.mmkin-1.png +++ b/docs/dev/reference/plot.mixed.mmkin-1.png diff --git a/docs/dev/reference/plot.mixed.mmkin-2.png b/docs/dev/reference/plot.mixed.mmkin-2.pngBinary files differ index c0d67204..0f66ff0f 100644 --- a/docs/dev/reference/plot.mixed.mmkin-2.png +++ b/docs/dev/reference/plot.mixed.mmkin-2.png diff --git a/docs/dev/reference/plot.mixed.mmkin-3.png b/docs/dev/reference/plot.mixed.mmkin-3.pngBinary files differ index 5e00afe6..34212f1c 100644 --- a/docs/dev/reference/plot.mixed.mmkin-3.png +++ b/docs/dev/reference/plot.mixed.mmkin-3.png diff --git a/docs/dev/reference/plot.mixed.mmkin-4.png b/docs/dev/reference/plot.mixed.mmkin-4.pngBinary files differ index 6a5f3b9c..c1450d24 100644 --- a/docs/dev/reference/plot.mixed.mmkin-4.png +++ b/docs/dev/reference/plot.mixed.mmkin-4.png diff --git a/docs/dev/reference/plot.mixed.mmkin.html b/docs/dev/reference/plot.mixed.mmkin.html index 55c411e7..601e1554 100644 --- a/docs/dev/reference/plot.mixed.mmkin.html +++ b/docs/dev/reference/plot.mixed.mmkin.html @@ -72,7 +72,7 @@        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -161,7 +161,7 @@    maxabs <span class='op'>=</span> <span class='st'>"auto"</span>,    ncol.legend <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/ifelse.html'>ifelse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'><=</span> <span class='fl'>3</span>, <span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'>+</span> <span class='fl'>1</span>, <span class='fu'><a href='https://rdrr.io/r/base/ifelse.html'>ifelse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'><=</span> <span class='fl'>8</span>, <span class='fl'>3</span>, <span class='fl'>4</span><span class='op'>)</span><span class='op'>)</span>,    nrow.legend <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/Round.html'>ceiling</a></span><span class='op'>(</span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span> <span class='op'>+</span> <span class='fl'>1</span><span class='op'>)</span><span class='op'>/</span><span class='va'>ncol.legend</span><span class='op'>)</span>, -  rel.height.legend <span class='op'>=</span> <span class='fl'>0.03</span> <span class='op'>+</span> <span class='fl'>0.08</span> <span class='op'>*</span> <span class='va'>nrow.legend</span>, +  rel.height.legend <span class='op'>=</span> <span class='fl'>0.02</span> <span class='op'>+</span> <span class='fl'>0.07</span> <span class='op'>*</span> <span class='va'>nrow.legend</span>,    rel.height.bottom <span class='op'>=</span> <span class='fl'>1.1</span>,    pch_ds <span class='op'>=</span> <span class='fl'>1</span><span class='op'>:</span><span class='fu'><a href='https://rdrr.io/r/base/length.html'>length</a></span><span class='op'>(</span><span class='va'>i</span><span class='op'>)</span>,    col_ds <span class='op'>=</span> <span class='va'>pch_ds</span> <span class='op'>+</span> <span class='fl'>1</span>, @@ -283,10 +283,10 @@ corresponding model prediction lines for the different datasets.</p></td>  </div><div class='img'><img src='plot.mixed.mmkin-2.png' alt='' width='700' height='433' /></div><div class='input'>  <span class='va'>f_saem</span> <span class='op'><-</span> <span class='fu'><a href='saem.html'>saem</a></span><span class='op'>(</span><span class='va'>f</span>, transformations <span class='op'>=</span> <span class='st'>"saemix"</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Dec 21 05:58:23 2020" +#> [1] "Sat Feb  6 18:29:17 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Dec 21 05:58:30 2020"</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f_saem</span><span class='op'>)</span> +#> [1] "Sat Feb  6 18:29:23 2021"</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span><span class='op'>(</span><span class='va'>f_saem</span><span class='op'>)</span>  </div><div class='img'><img src='plot.mixed.mmkin-3.png' alt='' width='700' height='433' /></div><div class='input'>  <span class='co'># We can overlay the two variants if we generate predictions</span>  <span class='va'>pred_nlme</span> <span class='op'><-</span> <span class='fu'><a href='mkinpredict.html'>mkinpredict</a></span><span class='op'>(</span><span class='va'>dfop_sfo</span>, diff --git a/docs/dev/reference/saem-3.png b/docs/dev/reference/saem-3.pngBinary files differ index 6a32cda1..4474b1f1 100644 --- a/docs/dev/reference/saem-3.png +++ b/docs/dev/reference/saem-3.png diff --git a/docs/dev/reference/saem-5.png b/docs/dev/reference/saem-5.pngBinary files differ index 6e6e0f91..27ed3f8f 100644 --- a/docs/dev/reference/saem-5.png +++ b/docs/dev/reference/saem-5.png diff --git a/docs/dev/reference/saem.html b/docs/dev/reference/saem.html index 59589378..4578db2a 100644 --- a/docs/dev/reference/saem.html +++ b/docs/dev/reference/saem.html @@ -74,7 +74,7 @@ Expectation Maximisation algorithm (SAEM)." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -261,27 +261,27 @@ using <a href='mmkin.html'>mmkin</a>.</p>    state.ini <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span>parent <span class='op'>=</span> <span class='fl'>100</span><span class='op'>)</span>, fixed_initials <span class='op'>=</span> <span class='st'>"parent"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='va'>f_saem_p0_fixed</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent_p0_fixed</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 25 14:41:42 2021" +#> [1] "Sat Feb  6 18:29:26 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 25 14:41:43 2021"</div><div class='input'> +#> [1] "Sat Feb  6 18:29:27 2021"</div><div class='input'>  <span class='va'>f_mmkin_parent</span> <span class='op'><-</span> <span class='fu'><a href='mmkin.html'>mmkin</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"SFO"</span>, <span class='st'>"FOMC"</span>, <span class='st'>"DFOP"</span><span class='op'>)</span>, <span class='va'>ds</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  <span class='va'>f_saem_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"SFO"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 25 14:41:45 2021" +#> [1] "Sat Feb  6 18:29:28 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 25 14:41:46 2021"</div><div class='input'><span class='va'>f_saem_fomc</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"FOMC"</span>, <span class='op'>]</span><span class='op'>)</span> +#> [1] "Sat Feb  6 18:29:30 2021"</div><div class='input'><span class='va'>f_saem_fomc</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"FOMC"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 25 14:41:47 2021" +#> [1] "Sat Feb  6 18:29:30 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 25 14:41:49 2021"</div><div class='input'><span class='va'>f_saem_dfop</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"DFOP"</span>, <span class='op'>]</span><span class='op'>)</span> +#> [1] "Sat Feb  6 18:29:32 2021"</div><div class='input'><span class='va'>f_saem_dfop</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent</span><span class='op'>[</span><span class='st'>"DFOP"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 25 14:41:49 2021" +#> [1] "Sat Feb  6 18:29:32 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 25 14:41:52 2021"</div><div class='input'> +#> [1] "Sat Feb  6 18:29:35 2021"</div><div class='input'>  <span class='co'># The returned saem.mmkin object contains an SaemixObject, therefore we can use</span>  <span class='co'># functions from saemix</span>  <span class='kw'><a href='https://rdrr.io/r/base/library.html'>library</a></span><span class='op'>(</span><span class='va'>saemix</span><span class='op'>)</span> @@ -324,10 +324,10 @@ using <a href='mmkin.html'>mmkin</a>.</p>  <span class='va'>f_mmkin_parent_tc</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/stats/update.html'>update</a></span><span class='op'>(</span><span class='va'>f_mmkin_parent</span>, error_model <span class='op'>=</span> <span class='st'>"tc"</span><span class='op'>)</span>  <span class='va'>f_saem_fomc_tc</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin_parent_tc</span><span class='op'>[</span><span class='st'>"FOMC"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 25 14:41:55 2021" +#> [1] "Sat Feb  6 18:29:37 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 25 14:42:00 2021"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/compare.saemix.html'>compare.saemix</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='va'>f_saem_fomc</span><span class='op'>$</span><span class='va'>so</span>, <span class='va'>f_saem_fomc_tc</span><span class='op'>$</span><span class='va'>so</span><span class='op'>)</span><span class='op'>)</span> +#> [1] "Sat Feb  6 18:29:42 2021"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/compare.saemix.html'>compare.saemix</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span><span class='va'>f_saem_fomc</span><span class='op'>$</span><span class='va'>so</span>, <span class='va'>f_saem_fomc_tc</span><span class='op'>$</span><span class='va'>so</span><span class='op'>)</span><span class='op'>)</span>  </div><div class='output co'>#> <span class='error'>Error in compare.saemix(list(f_saem_fomc$so, f_saem_fomc_tc$so)): 'compare.saemix' requires at least two models.</span></div><div class='input'>  <span class='va'>sfo_sfo</span> <span class='op'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span><span class='op'>(</span>parent <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span>, <span class='st'>"A1"</span><span class='op'>)</span>,    A1 <span class='op'>=</span> <span class='fu'><a href='mkinmod.html'>mkinsub</a></span><span class='op'>(</span><span class='st'>"SFO"</span><span class='op'>)</span><span class='op'>)</span> @@ -346,15 +346,15 @@ using <a href='mmkin.html'>mmkin</a>.</p>  <span class='co'># four minutes</span>  <span class='va'>f_saem_sfo_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin</span><span class='op'>[</span><span class='st'>"SFO-SFO"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 25 14:42:02 2021" +#> [1] "Sat Feb  6 18:29:44 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 25 14:42:07 2021"</div><div class='input'><span class='va'>f_saem_dfop_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span><span class='op'>)</span> +#> [1] "Sat Feb  6 18:29:48 2021"</div><div class='input'><span class='va'>f_saem_dfop_sfo</span> <span class='op'><-</span> <span class='fu'>saem</span><span class='op'>(</span><span class='va'>f_mmkin</span><span class='op'>[</span><span class='st'>"DFOP-SFO"</span>, <span class='op'>]</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 25 14:42:08 2021" +#> [1] "Sat Feb  6 18:29:49 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 25 14:42:17 2021"</div><div class='input'><span class='co'># We can use print, plot and summary methods to check the results</span> +#> [1] "Sat Feb  6 18:29:57 2021"</div><div class='input'><span class='co'># We can use print, plot and summary methods to check the results</span>  <span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>f_saem_dfop_sfo</span><span class='op'>)</span>  </div><div class='output co'>#> Kinetic nonlinear mixed-effects model fit by SAEM  #> Structural model: @@ -395,10 +395,10 @@ using <a href='mmkin.html'>mmkin</a>.</p>  #> SD.g_qlogis          0.44771 -0.86417  1.7596</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/plot-SaemixObject-method.html'>plot</a></span><span class='op'>(</span><span class='va'>f_saem_dfop_sfo</span><span class='op'>)</span>  </div><div class='img'><img src='saem-5.png' alt='' width='700' height='433' /></div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>f_saem_dfop_sfo</span>, data <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  </div><div class='output co'>#> saemix version used for fitting:      3.1.9000  -#> mkin version used for pre-fitting:  0.9.50.4  +#> mkin version used for pre-fitting:  1.0.1.9000   #> R version used for fitting:         4.0.3  -#> Date of fit:     Mon Jan 25 14:42:18 2021  -#> Date of summary: Mon Jan 25 14:42:18 2021  +#> Date of fit:     Sat Feb  6 18:29:57 2021  +#> Date of summary: Sat Feb  6 18:29:58 2021   #>   #> Equations:  #> d_parent/dt = - ((k1 * g * exp(-k1 * time) + k2 * (1 - g) * exp(-k2 * @@ -413,7 +413,7 @@ using <a href='mmkin.html'>mmkin</a>.</p>  #>   #> Model predictions using solution type analytical   #>  -#> Fitted in 9.954 s using 300, 100 iterations +#> Fitted in 8.539 s using 300, 100 iterations  #>   #> Variance model: Constant variance   #>  @@ -489,12 +489,12 @@ using <a href='mmkin.html'>mmkin</a>.</p>  #>   Dataset 6 parent    3     69.2  71.32042  2.12042 1.883     1.125873  #>   Dataset 6 parent    6     58.1  56.45256 -1.64744 1.883    -0.874739  #>   Dataset 6 parent    6     56.6  56.45256 -0.14744 1.883    -0.078288 -#>   Dataset 6 parent   10     44.4  44.48523  0.08523 1.883     0.045256 +#>   Dataset 6 parent   10     44.4  44.48523  0.08523 1.883     0.045257  #>   Dataset 6 parent   10     43.4  44.48523  1.08523 1.883     0.576224  #>   Dataset 6 parent   20     33.3  29.75774 -3.54226 1.883    -1.880826  #>   Dataset 6 parent   20     29.2  29.75774  0.55774 1.883     0.296141  #>   Dataset 6 parent   34     17.6  19.35710  1.75710 1.883     0.932966 -#>   Dataset 6 parent   34     18.0  19.35710  1.35710 1.883     0.720578 +#>   Dataset 6 parent   34     18.0  19.35710  1.35710 1.883     0.720579  #>   Dataset 6 parent   55     10.5  10.48443 -0.01557 1.883    -0.008266  #>   Dataset 6 parent   55      9.3  10.48443  1.18443 1.883     0.628895  #>   Dataset 6 parent   90      4.5   3.78622 -0.71378 1.883    -0.378995 @@ -560,9 +560,9 @@ using <a href='mmkin.html'>mmkin</a>.</p>  #>   Dataset 8 parent    1     64.9  67.73197  2.83197 1.883     1.503686  #>   Dataset 8 parent    1     66.2  67.73197  1.53197 1.883     0.813428  #>   Dataset 8 parent    3     43.5  41.58448 -1.91552 1.883    -1.017081 -#>   Dataset 8 parent    3     44.1  41.58448 -2.51552 1.883    -1.335661 +#>   Dataset 8 parent    3     44.1  41.58448 -2.51552 1.883    -1.335662  #>   Dataset 8 parent    8     18.3  19.62286  1.32286 1.883     0.702395 -#>   Dataset 8 parent    8     18.1  19.62286  1.52286 1.883     0.808589 +#>   Dataset 8 parent    8     18.1  19.62286  1.52286 1.883     0.808588  #>   Dataset 8 parent   14     10.2  10.77819  0.57819 1.883     0.306999  #>   Dataset 8 parent   14     10.8  10.77819 -0.02181 1.883    -0.011582  #>   Dataset 8 parent   27      4.9   3.26977 -1.63023 1.883    -0.865599 @@ -575,13 +575,13 @@ using <a href='mmkin.html'>mmkin</a>.</p>  #>   Dataset 8     A1    1      7.7   7.61539 -0.08461 1.883    -0.044923  #>   Dataset 8     A1    3     15.0  15.47954  0.47954 1.883     0.254622  #>   Dataset 8     A1    3     15.1  15.47954  0.37954 1.883     0.201525 -#>   Dataset 8     A1    8     21.2  20.22616 -0.97384 1.883    -0.517076 +#>   Dataset 8     A1    8     21.2  20.22616 -0.97384 1.883    -0.517075  #>   Dataset 8     A1    8     21.1  20.22616 -0.87384 1.883    -0.463979  #>   Dataset 8     A1   14     19.7  20.00067  0.30067 1.883     0.159645  #>   Dataset 8     A1   14     18.9  20.00067  1.10067 1.883     0.584419 -#>   Dataset 8     A1   27     17.5  16.38142 -1.11858 1.883    -0.593929 -#>   Dataset 8     A1   27     15.9  16.38142  0.48142 1.883     0.255619 -#>   Dataset 8     A1   48      9.5  10.25357  0.75357 1.883     0.400123 +#>   Dataset 8     A1   27     17.5  16.38142 -1.11858 1.883    -0.593928 +#>   Dataset 8     A1   27     15.9  16.38142  0.48142 1.883     0.255620 +#>   Dataset 8     A1   48      9.5  10.25357  0.75357 1.883     0.400124  #>   Dataset 8     A1   48      9.8  10.25357  0.45357 1.883     0.240833  #>   Dataset 8     A1   70      6.2   5.95728 -0.24272 1.883    -0.128878  #>   Dataset 8     A1   70      6.1   5.95728 -0.14272 1.883    -0.075781 @@ -622,7 +622,7 @@ using <a href='mmkin.html'>mmkin</a>.</p>  #>   Dataset 9     A1   91     10.0  10.09177  0.09177 1.883     0.048727  #>   Dataset 9     A1   91      9.5  10.09177  0.59177 1.883     0.314211  #>   Dataset 9     A1  120      9.1   7.91379 -1.18621 1.883    -0.629841 -#>   Dataset 9     A1  120      9.0   7.91379 -1.08621 1.883    -0.576745 +#>   Dataset 9     A1  120      9.0   7.91379 -1.08621 1.883    -0.576744  #>  Dataset 10 parent    0     96.1  93.65257 -2.44743 1.883    -1.299505  #>  Dataset 10 parent    0     94.3  93.65257 -0.64743 1.883    -0.343763  #>  Dataset 10 parent    8     73.9  77.85906  3.95906 1.883     2.102132 diff --git a/docs/dev/reference/summary.saem.mmkin.html b/docs/dev/reference/summary.saem.mmkin.html index 722415fb..93e1365d 100644 --- a/docs/dev/reference/summary.saem.mmkin.html +++ b/docs/dev/reference/summary.saem.mmkin.html @@ -76,7 +76,7 @@ endpoints such as formation fractions and DT50 values. Optionally        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -260,15 +260,15 @@ saemix authors for the parts inherited from saemix.</p>    quiet <span class='op'>=</span> <span class='cn'>TRUE</span>, error_model <span class='op'>=</span> <span class='st'>"tc"</span>, cores <span class='op'>=</span> <span class='fl'>5</span><span class='op'>)</span>  <span class='va'>f_saem_dfop_sfo</span> <span class='op'><-</span> <span class='fu'><a href='saem.html'>saem</a></span><span class='op'>(</span><span class='va'>f_mmkin_dfop_sfo</span><span class='op'>)</span>  </div><div class='output co'>#> Running main SAEM algorithm -#> [1] "Mon Jan 11 12:42:40 2021" +#> [1] "Sat Feb  6 18:30:00 2021"  #> ....  #>     Minimisation finished -#> [1] "Mon Jan 11 12:42:53 2021"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>f_saem_dfop_sfo</span>, data <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +#> [1] "Sat Feb  6 18:30:11 2021"</div><div class='input'><span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>f_saem_dfop_sfo</span>, data <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>  </div><div class='output co'>#> saemix version used for fitting:      3.1.9000  -#> mkin version used for pre-fitting:  0.9.50.4  +#> mkin version used for pre-fitting:  1.0.1.9000   #> R version used for fitting:         4.0.3  -#> Date of fit:     Mon Jan 11 12:42:54 2021  -#> Date of summary: Mon Jan 11 12:42:54 2021  +#> Date of fit:     Sat Feb  6 18:30:12 2021  +#> Date of summary: Sat Feb  6 18:30:12 2021   #>   #> Equations:  #> d_parent/dt = - ((k1 * g * exp(-k1 * time) + k2 * (1 - g) * exp(-k2 * @@ -283,7 +283,7 @@ saemix authors for the parts inherited from saemix.</p>  #>   #> Model predictions using solution type analytical   #>  -#> Fitted in 13.298 s using 300, 100 iterations +#> Fitted in 11.769 s using 300, 100 iterations  #>   #> Variance model: Two-component variance function   #>  @@ -291,7 +291,7 @@ saemix authors for the parts inherited from saemix.</p>  #>        parent_0        log_k_m1 f_parent_qlogis          log_k1          log_k2   #>       101.65645        -4.05368        -0.94311        -2.35943        -4.07006   #>        g_qlogis  -#>        -0.01133  +#>        -0.01132   #>   #> Fixed degradation parameter values:  #> None @@ -299,232 +299,232 @@ saemix authors for the parts inherited from saemix.</p>  #> Results:  #>   #> Likelihood computed by importance sampling -#>   AIC   BIC logLik -#>   830 824.5   -401 +#>     AIC   BIC logLik +#>   829.3 823.9 -400.7  #>   #> Optimised parameters: -#>                     est.  lower    upper -#> parent_0        101.4423 97.862 105.0224 -#> log_k_m1         -4.0703 -4.191  -3.9495 -#> f_parent_qlogis  -0.9539 -1.313  -0.5949 -#> log_k1           -2.9724 -3.811  -2.1342 -#> log_k2           -3.4977 -4.206  -2.7895 -#> g_qlogis         -0.0449 -1.116   1.0262 +#>                      est.  lower    upper +#> parent_0        101.29457 97.855 104.7344 +#> log_k_m1         -4.06337 -4.182  -3.9445 +#> f_parent_qlogis  -0.94546 -1.307  -0.5841 +#> log_k1           -2.98794 -3.844  -2.1321 +#> log_k2           -3.47891 -4.253  -2.7050 +#> g_qlogis         -0.03211 -1.157   1.0931  #>   #> Correlation:   #>                 prnt_0 lg_k_1 f_prn_ log_k1 log_k2 -#> log_k_m1        -0.207                             -#> f_parent_qlogis -0.148  0.202                      -#> log_k1           0.040 -0.038 -0.022               -#> log_k2           0.022 -0.015 -0.009  0.001        -#> g_qlogis        -0.012  0.005  0.011 -0.173 -0.130 +#> log_k_m1        -0.202                             +#> f_parent_qlogis -0.145  0.195                      +#> log_k1           0.094 -0.099 -0.049               +#> log_k2          -0.042  0.056  0.024 -0.097        +#> g_qlogis        -0.005  0.000  0.007 -0.160 -0.113  #>   #> Random effects: -#>                       est.   lower  upper -#> SD.parent_0        2.88564 -0.5163 6.2876 -#> SD.log_k_m1        0.08502 -0.0427 0.2127 -#> SD.f_parent_qlogis 0.38857  0.1350 0.6421 -#> SD.log_k1          0.92338  0.3296 1.5172 -#> SD.log_k2          0.78644  0.2817 1.2912 -#> SD.g_qlogis        0.34614 -0.8727 1.5650 +#>                       est.    lower  upper +#> SD.parent_0        2.70085 -0.64980 6.0515 +#> SD.log_k_m1        0.08408 -0.04023 0.2084 +#> SD.f_parent_qlogis 0.39215  0.13695 0.6473 +#> SD.log_k1          0.89280  0.27466 1.5109 +#> SD.log_k2          0.82387  0.26388 1.3838 +#> SD.g_qlogis        0.36468 -0.86978 1.5991  #>   #> Variance model:  #>        est.   lower   upper -#> a.1 0.65859 0.49250 0.82469 -#> b.1 0.06411 0.05006 0.07817 +#> a.1 0.65724 0.49361 0.82086 +#> b.1 0.06434 0.05034 0.07835  #>   #> Backtransformed parameters:  #>                     est.    lower     upper -#> parent_0       101.44231 97.86220 105.02241 -#> k_m1             0.01707  0.01513   0.01926 -#> f_parent_to_m1   0.27811  0.21201   0.35551 -#> k1               0.05118  0.02213   0.11834 -#> k2               0.03027  0.01491   0.06145 -#> g                0.48878  0.24675   0.73618 +#> parent_0       101.29457 97.85477 104.73437 +#> k_m1             0.01719  0.01526   0.01936 +#> f_parent_to_m1   0.27980  0.21302   0.35798 +#> k1               0.05039  0.02141   0.11859 +#> k2               0.03084  0.01422   0.06687 +#> g                0.49197  0.23916   0.74896  #>   #> Resulting formation fractions:  #>                 ff -#> parent_m1   0.2781 -#> parent_sink 0.7219 +#> parent_m1   0.2798 +#> parent_sink 0.7202  #>   #> Estimated disappearance times:  #>         DT50   DT90 DT50back DT50_k1 DT50_k2 -#> parent 17.53  61.64    18.55   13.54    22.9 -#> m1     40.60 134.88       NA      NA      NA +#> parent 17.49  61.05    18.38   13.76   22.47 +#> m1     40.32 133.94       NA      NA      NA  #>   #> Data: -#>    ds   name time observed  predicted   residual    std standardized -#>  ds 1 parent    0     89.8  9.869e+01   8.894553 6.3618     1.398124 -#>  ds 1 parent    0    104.1  9.869e+01  -5.405447 6.3618    -0.849676 -#>  ds 1 parent    1     88.7  9.413e+01   5.426448 6.0706     0.893897 -#>  ds 1 parent    1     95.5  9.413e+01  -1.373552 6.0706    -0.226265 -#>  ds 1 parent    3     81.8  8.576e+01   3.961821 5.5377     0.715422 -#>  ds 1 parent    3     94.5  8.576e+01  -8.738179 5.5377    -1.577932 -#>  ds 1 parent    7     71.5  7.168e+01   0.184828 4.6429     0.039809 -#>  ds 1 parent    7     70.3  7.168e+01   1.384828 4.6429     0.298270 -#>  ds 1 parent   14     54.2  5.351e+01  -0.688235 3.4934    -0.197008 -#>  ds 1 parent   14     49.6  5.351e+01   3.911765 3.4934     1.119747 -#>  ds 1 parent   28     31.5  3.209e+01   0.590445 2.1603     0.273322 -#>  ds 1 parent   28     28.8  3.209e+01   3.290445 2.1603     1.523177 -#>  ds 1 parent   60     12.1  1.272e+01   0.618158 1.0481     0.589761 -#>  ds 1 parent   60     13.6  1.272e+01  -0.881842 1.0481    -0.841332 -#>  ds 1 parent   90      6.2  6.085e+00  -0.115212 0.7655    -0.150512 -#>  ds 1 parent   90      8.3  6.085e+00  -2.215212 0.7655    -2.893953 -#>  ds 1 parent  120      2.2  3.009e+00   0.809439 0.6863     1.179470 -#>  ds 1 parent  120      2.4  3.009e+00   0.609439 0.6863     0.888041 -#>  ds 1     m1    1      0.3  1.129e+00   0.828817 0.6626     1.250938 -#>  ds 1     m1    1      0.2  1.129e+00   0.928817 0.6626     1.401869 -#>  ds 1     m1    3      2.2  3.141e+00   0.940880 0.6887     1.366187 -#>  ds 1     m1    3      3.0  3.141e+00   0.140880 0.6887     0.204562 -#>  ds 1     m1    7      6.5  6.326e+00  -0.174162 0.7735    -0.225175 -#>  ds 1     m1    7      5.0  6.326e+00   1.325838 0.7735     1.714181 -#>  ds 1     m1   14     10.2  9.883e+00  -0.317417 0.9139    -0.347326 -#>  ds 1     m1   14      9.5  9.883e+00   0.382583 0.9139     0.418631 -#>  ds 1     m1   28     12.2  1.251e+01   0.309856 1.0378     0.298572 -#>  ds 1     m1   28     13.4  1.251e+01  -0.890144 1.0378    -0.857726 -#>  ds 1     m1   60     11.8  1.086e+01  -0.940009 0.9584    -0.980812 -#>  ds 1     m1   60     13.2  1.086e+01  -2.340009 0.9584    -2.441581 -#>  ds 1     m1   90      6.6  7.823e+00   1.222977 0.8278     1.477332 -#>  ds 1     m1   90      9.3  7.823e+00  -1.477023 0.8278    -1.784214 -#>  ds 1     m1  120      3.5  5.315e+00   1.815201 0.7415     2.447906 -#>  ds 1     m1  120      5.4  5.315e+00  -0.084799 0.7415    -0.114356 -#>  ds 2 parent    0    118.0  1.031e+02 -14.876736 6.6443    -2.239038 -#>  ds 2 parent    0     99.8  1.031e+02   3.323264 6.6443     0.500171 -#>  ds 2 parent    1     90.2  9.757e+01   7.371379 6.2902     1.171891 -#>  ds 2 parent    1     94.6  9.757e+01   2.971379 6.2902     0.472386 -#>  ds 2 parent    3     96.1  8.788e+01  -8.222746 5.6724    -1.449599 -#>  ds 2 parent    3     78.4  8.788e+01   9.477254 5.6724     1.670758 -#>  ds 2 parent    7     77.9  7.293e+01  -4.972272 4.7218    -1.053054 -#>  ds 2 parent    7     77.7  7.293e+01  -4.772272 4.7218    -1.010697 -#>  ds 2 parent   14     56.0  5.602e+01   0.016773 3.6513     0.004594 -#>  ds 2 parent   14     54.7  5.602e+01   1.316773 3.6513     0.360633 -#>  ds 2 parent   28     36.6  3.855e+01   1.945779 2.5575     0.760803 -#>  ds 2 parent   28     36.8  3.855e+01   1.745779 2.5575     0.682603 -#>  ds 2 parent   60     22.1  2.101e+01  -1.086693 1.4996    -0.724663 -#>  ds 2 parent   60     24.7  2.101e+01  -3.686693 1.4996    -2.458475 -#>  ds 2 parent   90     12.4  1.246e+01   0.058759 1.0353     0.056757 -#>  ds 2 parent   90     10.8  1.246e+01   1.658759 1.0353     1.602256 -#>  ds 2 parent  120      6.8  7.406e+00   0.606226 0.8119     0.746659 -#>  ds 2 parent  120      7.9  7.406e+00  -0.493774 0.8119    -0.608157 -#>  ds 2     m1    1      1.3  1.438e+00   0.138236 0.6650     0.207869 -#>  ds 2     m1    3      3.7  3.879e+00   0.178617 0.7040     0.253726 -#>  ds 2     m1    3      4.7  3.879e+00  -0.821383 0.7040    -1.166780 -#>  ds 2     m1    7      8.1  7.389e+00  -0.710951 0.8113    -0.876337 -#>  ds 2     m1    7      7.9  7.389e+00  -0.510951 0.8113    -0.629812 -#>  ds 2     m1   14     10.1  1.069e+01   0.593533 0.9507     0.624328 -#>  ds 2     m1   14     10.3  1.069e+01   0.393533 0.9507     0.413951 -#>  ds 2     m1   28     10.7  1.240e+01   1.703647 1.0325     1.649956 -#>  ds 2     m1   28     12.2  1.240e+01   0.203647 1.0325     0.197229 -#>  ds 2     m1   60     10.7  1.055e+01  -0.147672 0.9442    -0.156405 -#>  ds 2     m1   60     12.5  1.055e+01  -1.947672 0.9442    -2.062848 -#>  ds 2     m1   90      9.1  8.010e+00  -1.090041 0.8351    -1.305210 -#>  ds 2     m1   90      7.4  8.010e+00   0.609959 0.8351     0.730362 -#>  ds 2     m1  120      6.1  5.793e+00  -0.306797 0.7561    -0.405759 -#>  ds 2     m1  120      4.5  5.793e+00   1.293203 0.7561     1.710347 -#>  ds 3 parent    0    106.2  1.035e+02  -2.712344 6.6675    -0.406801 -#>  ds 3 parent    0    106.9  1.035e+02  -3.412344 6.6675    -0.511788 -#>  ds 3 parent    1    107.4  9.548e+01 -11.924044 6.1566    -1.936801 -#>  ds 3 parent    1     96.1  9.548e+01  -0.624044 6.1566    -0.101362 -#>  ds 3 parent    3     79.4  8.246e+01   3.056105 5.3274     0.573662 -#>  ds 3 parent    3     82.6  8.246e+01  -0.143895 5.3274    -0.027010 -#>  ds 3 parent    7     63.9  6.489e+01   0.991141 4.2122     0.235304 -#>  ds 3 parent    7     62.4  6.489e+01   2.491141 4.2122     0.591416 -#>  ds 3 parent   14     51.0  4.869e+01  -2.306824 3.1906    -0.723013 -#>  ds 3 parent   14     47.1  4.869e+01   1.593176 3.1906     0.499338 -#>  ds 3 parent   28     36.1  3.480e+01  -1.304261 2.3260    -0.560722 -#>  ds 3 parent   28     36.6  3.480e+01  -1.804261 2.3260    -0.775679 -#>  ds 3 parent   60     20.1  1.988e+01  -0.221952 1.4346    -0.154719 -#>  ds 3 parent   60     19.8  1.988e+01   0.078048 1.4346     0.054406 -#>  ds 3 parent   90     11.3  1.194e+01   0.642458 1.0099     0.636132 -#>  ds 3 parent   90     10.7  1.194e+01   1.242458 1.0099     1.230224 -#>  ds 3 parent  120      8.2  7.176e+00  -1.023847 0.8034    -1.274423 -#>  ds 3 parent  120      7.3  7.176e+00  -0.123847 0.8034    -0.154158 -#>  ds 3     m1    0      0.8  8.527e-13  -0.800000 0.6586    -1.214712 -#>  ds 3     m1    1      1.8  1.856e+00   0.055925 0.6693     0.083562 -#>  ds 3     m1    1      2.3  1.856e+00  -0.444075 0.6693    -0.663537 -#>  ds 3     m1    3      4.2  4.780e+00   0.580164 0.7264     0.798676 -#>  ds 3     m1    3      4.1  4.780e+00   0.680164 0.7264     0.936340 -#>  ds 3     m1    7      6.8  8.410e+00   1.609920 0.8512     1.891455 -#>  ds 3     m1    7     10.1  8.410e+00  -1.690080 0.8512    -1.985633 -#>  ds 3     m1   14     11.4  1.098e+01  -0.424444 0.9638    -0.440389 -#>  ds 3     m1   14     12.8  1.098e+01  -1.824444 0.9638    -1.892979 -#>  ds 3     m1   28     11.5  1.142e+01  -0.079336 0.9848    -0.080558 -#>  ds 3     m1   28     10.6  1.142e+01   0.820664 0.9848     0.833311 -#>  ds 3     m1   60      7.5  9.110e+00   1.610231 0.8803     1.829222 -#>  ds 3     m1   60      8.6  9.110e+00   0.510231 0.8803     0.579622 -#>  ds 3     m1   90      7.3  6.799e+00  -0.501085 0.7898    -0.634463 -#>  ds 3     m1   90      8.1  6.799e+00  -1.301085 0.7898    -1.647404 -#>  ds 3     m1  120      5.3  4.868e+00  -0.431505 0.7288    -0.592064 -#>  ds 3     m1  120      3.8  4.868e+00   1.068495 0.7288     1.466073 -#>  ds 4 parent    0    104.7  9.926e+01  -5.444622 6.3975    -0.851049 -#>  ds 4 parent    0     88.3  9.926e+01  10.955378 6.3975     1.712436 -#>  ds 4 parent    1     94.2  9.618e+01   1.978413 6.2013     0.319030 -#>  ds 4 parent    1     94.6  9.618e+01   1.578413 6.2013     0.254527 -#>  ds 4 parent    3     78.1  9.037e+01  12.268550 5.8311     2.103985 -#>  ds 4 parent    3     96.5  9.037e+01  -6.131450 5.8311    -1.051508 -#>  ds 4 parent    7     76.2  7.999e+01   3.794958 5.1708     0.733918 -#>  ds 4 parent    7     77.8  7.999e+01   2.194958 5.1708     0.424489 -#>  ds 4 parent   14     70.8  6.518e+01  -5.624996 4.2301    -1.329742 -#>  ds 4 parent   14     67.3  6.518e+01  -2.124996 4.2301    -0.502346 -#>  ds 4 parent   28     43.1  4.462e+01   1.517860 2.9354     0.517085 -#>  ds 4 parent   28     45.1  4.462e+01  -0.482140 2.9354    -0.164249 -#>  ds 4 parent   60     21.3  2.130e+01  -0.003305 1.5159    -0.002180 -#>  ds 4 parent   60     23.5  2.130e+01  -2.203305 1.5159    -1.453435 -#>  ds 4 parent   90     11.8  1.180e+01   0.002834 1.0032     0.002825 -#>  ds 4 parent   90     12.1  1.180e+01  -0.297166 1.0032    -0.296226 -#>  ds 4 parent  120      7.0  6.868e+00  -0.132251 0.7922    -0.166937 -#>  ds 4 parent  120      6.2  6.868e+00   0.667749 0.7922     0.842879 -#>  ds 4     m1    0      1.6  0.000e+00  -1.600000 0.6586    -2.429424 -#>  ds 4     m1    1      0.9  6.826e-01  -0.217363 0.6600    -0.329315 -#>  ds 4     m1    3      3.7  1.935e+00  -1.765082 0.6702    -2.633768 -#>  ds 4     m1    3      2.0  1.935e+00  -0.065082 0.6702    -0.097112 -#>  ds 4     m1    7      3.6  4.035e+00   0.434805 0.7076     0.614501 -#>  ds 4     m1    7      3.8  4.035e+00   0.234805 0.7076     0.331845 -#>  ds 4     m1   14      7.1  6.652e+00  -0.448187 0.7846    -0.571220 -#>  ds 4     m1   14      6.6  6.652e+00   0.051813 0.7846     0.066036 -#>  ds 4     m1   28      9.5  9.156e+00  -0.343805 0.8822    -0.389696 -#>  ds 4     m1   28      9.3  9.156e+00  -0.143805 0.8822    -0.163000 -#>  ds 4     m1   60      8.3  8.848e+00   0.547762 0.8692     0.630185 -#>  ds 4     m1   60      9.0  8.848e+00  -0.152238 0.8692    -0.175146 -#>  ds 4     m1   90      6.6  6.674e+00   0.073979 0.7854     0.094194 -#>  ds 4     m1   90      7.7  6.674e+00  -1.026021 0.7854    -1.306390 -#>  ds 4     m1  120      3.7  4.668e+00   0.967537 0.7234     1.337503 -#>  ds 4     m1  120      3.5  4.668e+00   1.167537 0.7234     1.613979 -#>  ds 5 parent    0    110.4  1.022e+02  -8.170986 6.5872    -1.240433 -#>  ds 5 parent    0    112.1  1.022e+02  -9.870986 6.5872    -1.498509 -#>  ds 5 parent    1     93.5  9.513e+01   1.630764 6.1346     0.265832 -#>  ds 5 parent    1     91.0  9.513e+01   4.130764 6.1346     0.673359 -#>  ds 5 parent    3     71.0  8.296e+01  11.964279 5.3597     2.232268 -#>  ds 5 parent    3     89.7  8.296e+01  -6.735721 5.3597    -1.256735 -#>  ds 5 parent    7     60.4  6.495e+01   4.547441 4.2157     1.078684 -#>  ds 5 parent    7     59.1  6.495e+01   5.847441 4.2157     1.387053 -#>  ds 5 parent   14     56.5  4.626e+01 -10.241319 3.0380    -3.371047 -#>  ds 5 parent   14     47.0  4.626e+01  -0.741319 3.0380    -0.244014 -#>  ds 5 parent   28     30.2  3.026e+01   0.058478 2.0487     0.028544 -#>  ds 5 parent   28     23.9  3.026e+01   6.358478 2.0487     3.103661 -#>  ds 5 parent   60     17.0  1.792e+01   0.919046 1.3242     0.694024 -#>  ds 5 parent   60     18.7  1.792e+01  -0.780954 1.3242    -0.589742 -#>  ds 5 parent   90     11.3  1.187e+01   0.573917 1.0066     0.570144 -#>  ds 5 parent   90     11.9  1.187e+01  -0.026083 1.0066    -0.025912 -#>  ds 5 parent  120      9.0  7.898e+00  -1.102089 0.8307    -1.326622 -#>  ds 5 parent  120      8.1  7.898e+00  -0.202089 0.8307    -0.243261 -#>  ds 5     m1    0      0.7 -1.421e-14  -0.700000 0.6586    -1.062873 -#>  ds 5     m1    1      3.0  3.144e+00   0.143526 0.6887     0.208390 -#>  ds 5     m1    1      2.6  3.144e+00   0.543526 0.6887     0.789161 -#>  ds 5     m1    3      5.1  8.390e+00   3.290265 0.8504     3.869277 -#>  ds 5     m1    3      7.5  8.390e+00   0.890265 0.8504     1.046932 -#>  ds 5     m1    7     16.5  1.566e+01  -0.841368 1.2007    -0.700751 -#>  ds 5     m1    7     19.0  1.566e+01  -3.341368 1.2007    -2.782928 -#>  ds 5     m1   14     22.9  2.188e+01  -1.017753 1.5498    -0.656687 -#>  ds 5     m1   14     23.2  2.188e+01  -1.317753 1.5498    -0.850257 -#>  ds 5     m1   28     22.2  2.386e+01   1.655914 1.6652     0.994399 -#>  ds 5     m1   28     24.4  2.386e+01  -0.544086 1.6652    -0.326731 -#>  ds 5     m1   60     15.5  1.859e+01   3.091124 1.3618     2.269915 -#>  ds 5     m1   60     19.8  1.859e+01  -1.208876 1.3618    -0.887718 -#>  ds 5     m1   90     14.9  1.372e+01  -1.176815 1.0990    -1.070784 -#>  ds 5     m1   90     14.2  1.372e+01  -0.476815 1.0990    -0.433854 -#>  ds 5     m1  120     10.9  9.961e+00  -0.938796 0.9174    -1.023332 -#>  ds 5     m1  120     10.4  9.961e+00  -0.438796 0.9174    -0.478308</div><div class='input'><span class='co'># }</span> +#>    ds   name time observed  predicted  residual    std standardized +#>  ds 1 parent    0     89.8  9.878e+01   8.98039 6.3899      1.40541 +#>  ds 1 parent    0    104.1  9.878e+01  -5.31961 6.3899     -0.83251 +#>  ds 1 parent    1     88.7  9.422e+01   5.52084 6.0981      0.90533 +#>  ds 1 parent    1     95.5  9.422e+01  -1.27916 6.0981     -0.20976 +#>  ds 1 parent    3     81.8  8.587e+01   4.06752 5.5641      0.73103 +#>  ds 1 parent    3     94.5  8.587e+01  -8.63248 5.5641     -1.55147 +#>  ds 1 parent    7     71.5  7.180e+01   0.29615 4.6662      0.06347 +#>  ds 1 parent    7     70.3  7.180e+01   1.49615 4.6662      0.32063 +#>  ds 1 parent   14     54.2  5.360e+01  -0.59602 3.5112     -0.16975 +#>  ds 1 parent   14     49.6  5.360e+01   4.00398 3.5112      1.14035 +#>  ds 1 parent   28     31.5  3.213e+01   0.62529 2.1691      0.28828 +#>  ds 1 parent   28     28.8  3.213e+01   3.32529 2.1691      1.53306 +#>  ds 1 parent   60     12.1  1.271e+01   0.60718 1.0490      0.57879 +#>  ds 1 parent   60     13.6  1.271e+01  -0.89282 1.0490     -0.85108 +#>  ds 1 parent   90      6.2  6.080e+00  -0.12020 0.7649     -0.15716 +#>  ds 1 parent   90      8.3  6.080e+00  -2.22020 0.7649     -2.90279 +#>  ds 1 parent  120      2.2  3.011e+00   0.81059 0.6852      1.18302 +#>  ds 1 parent  120      2.4  3.011e+00   0.61059 0.6852      0.89113 +#>  ds 1     m1    1      0.3  1.131e+00   0.83071 0.6613      1.25628 +#>  ds 1     m1    1      0.2  1.131e+00   0.93071 0.6613      1.40750 +#>  ds 1     m1    3      2.2  3.147e+00   0.94691 0.6877      1.37688 +#>  ds 1     m1    3      3.0  3.147e+00   0.14691 0.6877      0.21361 +#>  ds 1     m1    7      6.5  6.341e+00  -0.15949 0.7736     -0.20618 +#>  ds 1     m1    7      5.0  6.341e+00   1.34051 0.7736      1.73290 +#>  ds 1     m1   14     10.2  9.910e+00  -0.28991 0.9157     -0.31659 +#>  ds 1     m1   14      9.5  9.910e+00   0.41009 0.9157      0.44783 +#>  ds 1     m1   28     12.2  1.255e+01   0.34690 1.0410      0.33323 +#>  ds 1     m1   28     13.4  1.255e+01  -0.85310 1.0410     -0.81949 +#>  ds 1     m1   60     11.8  1.087e+01  -0.92713 0.9599     -0.96586 +#>  ds 1     m1   60     13.2  1.087e+01  -2.32713 0.9599     -2.42434 +#>  ds 1     m1   90      6.6  7.813e+00   1.21254 0.8274      1.46541 +#>  ds 1     m1   90      9.3  7.813e+00  -1.48746 0.8274     -1.79766 +#>  ds 1     m1  120      3.5  5.295e+00   1.79489 0.7403      2.42457 +#>  ds 1     m1  120      5.4  5.295e+00  -0.10511 0.7403     -0.14198 +#>  ds 2 parent    0    118.0  1.074e+02 -10.63436 6.9396     -1.53242 +#>  ds 2 parent    0     99.8  1.074e+02   7.56564 6.9396      1.09021 +#>  ds 2 parent    1     90.2  1.012e+02  10.96486 6.5425      1.67594 +#>  ds 2 parent    1     94.6  1.012e+02   6.56486 6.5425      1.00342 +#>  ds 2 parent    3     96.1  9.054e+01  -5.56014 5.8627     -0.94839 +#>  ds 2 parent    3     78.4  9.054e+01  12.13986 5.8627      2.07069 +#>  ds 2 parent    7     77.9  7.468e+01  -3.21805 4.8501     -0.66350 +#>  ds 2 parent    7     77.7  7.468e+01  -3.01805 4.8501     -0.62226 +#>  ds 2 parent   14     56.0  5.748e+01   1.47774 3.7563      0.39340 +#>  ds 2 parent   14     54.7  5.748e+01   2.77774 3.7563      0.73948 +#>  ds 2 parent   28     36.6  3.996e+01   3.36317 2.6541      1.26717 +#>  ds 2 parent   28     36.8  3.996e+01   3.16317 2.6541      1.19182 +#>  ds 2 parent   60     22.1  2.132e+01  -0.78225 1.5210     -0.51430 +#>  ds 2 parent   60     24.7  2.132e+01  -3.38225 1.5210     -2.22369 +#>  ds 2 parent   90     12.4  1.215e+01  -0.25010 1.0213     -0.24487 +#>  ds 2 parent   90     10.8  1.215e+01   1.34990 1.0213      1.32169 +#>  ds 2 parent  120      6.8  6.931e+00   0.13105 0.7943      0.16500 +#>  ds 2 parent  120      7.9  6.931e+00  -0.96895 0.7943     -1.21994 +#>  ds 2     m1    1      1.3  1.519e+00   0.21924 0.6645      0.32995 +#>  ds 2     m1    3      3.7  4.049e+00   0.34891 0.7070      0.49351 +#>  ds 2     m1    3      4.7  4.049e+00  -0.65109 0.7070     -0.92094 +#>  ds 2     m1    7      8.1  7.565e+00  -0.53526 0.8179     -0.65448 +#>  ds 2     m1    7      7.9  7.565e+00  -0.33526 0.8179     -0.40993 +#>  ds 2     m1   14     10.1  1.071e+01   0.60614 0.9521      0.63663 +#>  ds 2     m1   14     10.3  1.071e+01   0.40614 0.9521      0.42657 +#>  ds 2     m1   28     10.7  1.224e+01   1.54440 1.0260      1.50526 +#>  ds 2     m1   28     12.2  1.224e+01   0.04440 1.0260      0.04327 +#>  ds 2     m1   60     10.7  1.056e+01  -0.14005 0.9453     -0.14815 +#>  ds 2     m1   60     12.5  1.056e+01  -1.94005 0.9453     -2.05226 +#>  ds 2     m1   90      9.1  8.089e+00  -1.01088 0.8384     -1.20577 +#>  ds 2     m1   90      7.4  8.089e+00   0.68912 0.8384      0.82197 +#>  ds 2     m1  120      6.1  5.855e+00  -0.24463 0.7576     -0.32292 +#>  ds 2     m1  120      4.5  5.855e+00   1.35537 0.7576      1.78911 +#>  ds 3 parent    0    106.2  1.095e+02   3.30335 7.0765      0.46680 +#>  ds 3 parent    0    106.9  1.095e+02   2.60335 7.0765      0.36788 +#>  ds 3 parent    1    107.4  9.939e+01  -8.01282 6.4287     -1.24641 +#>  ds 3 parent    1     96.1  9.939e+01   3.28718 6.4287      0.51133 +#>  ds 3 parent    3     79.4  8.365e+01   4.24698 5.4222      0.78326 +#>  ds 3 parent    3     82.6  8.365e+01   1.04698 5.4222      0.19309 +#>  ds 3 parent    7     63.9  6.405e+01   0.14704 4.1732      0.03523 +#>  ds 3 parent    7     62.4  6.405e+01   1.64704 4.1732      0.39467 +#>  ds 3 parent   14     51.0  4.795e+01  -3.04985 3.1546     -0.96681 +#>  ds 3 parent   14     47.1  4.795e+01   0.85015 3.1546      0.26950 +#>  ds 3 parent   28     36.1  3.501e+01  -1.09227 2.3465     -0.46549 +#>  ds 3 parent   28     36.6  3.501e+01  -1.59227 2.3465     -0.67858 +#>  ds 3 parent   60     20.1  2.012e+01   0.02116 1.4520      0.01457 +#>  ds 3 parent   60     19.8  2.012e+01   0.32116 1.4520      0.22119 +#>  ds 3 parent   90     11.3  1.206e+01   0.76096 1.0170      0.74826 +#>  ds 3 parent   90     10.7  1.206e+01   1.36096 1.0170      1.33825 +#>  ds 3 parent  120      8.2  7.230e+00  -0.97022 0.8052     -1.20493 +#>  ds 3 parent  120      7.3  7.230e+00  -0.07022 0.8052     -0.08721 +#>  ds 3     m1    0      0.8 -5.684e-13  -0.80000 0.6572     -1.21722 +#>  ds 3     m1    1      1.8  2.045e+00   0.24538 0.6703      0.36608 +#>  ds 3     m1    1      2.3  2.045e+00  -0.25462 0.6703     -0.37987 +#>  ds 3     m1    3      4.2  5.136e+00   0.93594 0.7356      1.27228 +#>  ds 3     m1    3      4.1  5.136e+00   1.03594 0.7356      1.40822 +#>  ds 3     m1    7      6.8  8.674e+00   1.87438 0.8623      2.17381 +#>  ds 3     m1    7     10.1  8.674e+00  -1.42562 0.8623     -1.65335 +#>  ds 3     m1   14     11.4  1.083e+01  -0.56746 0.9580     -0.59233 +#>  ds 3     m1   14     12.8  1.083e+01  -1.96746 0.9580     -2.05369 +#>  ds 3     m1   28     11.5  1.098e+01  -0.51762 0.9651     -0.53637 +#>  ds 3     m1   28     10.6  1.098e+01   0.38238 0.9651      0.39623 +#>  ds 3     m1   60      7.5  8.889e+00   1.38911 0.8713      1.59436 +#>  ds 3     m1   60      8.6  8.889e+00   0.28911 0.8713      0.33183 +#>  ds 3     m1   90      7.3  6.774e+00  -0.52608 0.7886     -0.66708 +#>  ds 3     m1   90      8.1  6.774e+00  -1.32608 0.7886     -1.68150 +#>  ds 3     m1  120      5.3  4.954e+00  -0.34584 0.7305     -0.47345 +#>  ds 3     m1  120      3.8  4.954e+00   1.15416 0.7305      1.58004 +#>  ds 4 parent    0    104.7  9.957e+01  -5.13169 6.4403     -0.79681 +#>  ds 4 parent    0     88.3  9.957e+01  11.26831 6.4403      1.74966 +#>  ds 4 parent    1     94.2  9.644e+01   2.23888 6.2400      0.35879 +#>  ds 4 parent    1     94.6  9.644e+01   1.83888 6.2400      0.29469 +#>  ds 4 parent    3     78.1  9.054e+01  12.43946 5.8627      2.12180 +#>  ds 4 parent    3     96.5  9.054e+01  -5.96054 5.8627     -1.01669 +#>  ds 4 parent    7     76.2  8.004e+01   3.83771 5.1918      0.73919 +#>  ds 4 parent    7     77.8  8.004e+01   2.23771 5.1918      0.43101 +#>  ds 4 parent   14     70.8  6.511e+01  -5.69246 4.2406     -1.34238 +#>  ds 4 parent   14     67.3  6.511e+01  -2.19246 4.2406     -0.51702 +#>  ds 4 parent   28     43.1  4.454e+01   1.43744 2.9401      0.48890 +#>  ds 4 parent   28     45.1  4.454e+01  -0.56256 2.9401     -0.19134 +#>  ds 4 parent   60     21.3  2.132e+01   0.02005 1.5211      0.01318 +#>  ds 4 parent   60     23.5  2.132e+01  -2.17995 1.5211     -1.43310 +#>  ds 4 parent   90     11.8  1.182e+01   0.02167 1.0053      0.02156 +#>  ds 4 parent   90     12.1  1.182e+01  -0.27833 1.0053     -0.27687 +#>  ds 4 parent  120      7.0  6.852e+00  -0.14780 0.7914     -0.18675 +#>  ds 4 parent  120      6.2  6.852e+00   0.65220 0.7914      0.82408 +#>  ds 4     m1    0      1.6 -5.684e-14  -1.60000 0.6572     -2.43444 +#>  ds 4     m1    1      0.9  6.918e-01  -0.20821 0.6587     -0.31607 +#>  ds 4     m1    3      3.7  1.959e+00  -1.74131 0.6692     -2.60204 +#>  ds 4     m1    3      2.0  1.959e+00  -0.04131 0.6692     -0.06173 +#>  ds 4     m1    7      3.6  4.076e+00   0.47590 0.7076      0.67252 +#>  ds 4     m1    7      3.8  4.076e+00   0.27590 0.7076      0.38989 +#>  ds 4     m1   14      7.1  6.698e+00  -0.40189 0.7859     -0.51135 +#>  ds 4     m1   14      6.6  6.698e+00   0.09811 0.7859      0.12483 +#>  ds 4     m1   28      9.5  9.175e+00  -0.32492 0.8835     -0.36779 +#>  ds 4     m1   28      9.3  9.175e+00  -0.12492 0.8835     -0.14141 +#>  ds 4     m1   60      8.3  8.818e+00   0.51810 0.8683      0.59671 +#>  ds 4     m1   60      9.0  8.818e+00  -0.18190 0.8683     -0.20949 +#>  ds 4     m1   90      6.6  6.645e+00   0.04480 0.7841      0.05713 +#>  ds 4     m1   90      7.7  6.645e+00  -1.05520 0.7841     -1.34581 +#>  ds 4     m1  120      3.7  4.648e+00   0.94805 0.7221      1.31293 +#>  ds 4     m1  120      3.5  4.648e+00   1.14805 0.7221      1.58991 +#>  ds 5 parent    0    110.4  1.026e+02  -7.81752 6.6333     -1.17853 +#>  ds 5 parent    0    112.1  1.026e+02  -9.51752 6.6333     -1.43482 +#>  ds 5 parent    1     93.5  9.560e+01   2.10274 6.1865      0.33989 +#>  ds 5 parent    1     91.0  9.560e+01   4.60274 6.1865      0.74399 +#>  ds 5 parent    3     71.0  8.356e+01  12.55799 5.4165      2.31846 +#>  ds 5 parent    3     89.7  8.356e+01  -6.14201 5.4165     -1.13394 +#>  ds 5 parent    7     60.4  6.550e+01   5.09732 4.2653      1.19506 +#>  ds 5 parent    7     59.1  6.550e+01   6.39732 4.2653      1.49984 +#>  ds 5 parent   14     56.5  4.641e+01 -10.09145 3.0576     -3.30044 +#>  ds 5 parent   14     47.0  4.641e+01  -0.59145 3.0576     -0.19344 +#>  ds 5 parent   28     30.2  2.982e+01  -0.37647 2.0284     -0.18560 +#>  ds 5 parent   28     23.9  2.982e+01   5.92353 2.0284      2.92028 +#>  ds 5 parent   60     17.0  1.754e+01   0.53981 1.3060      0.41332 +#>  ds 5 parent   60     18.7  1.754e+01  -1.16019 1.3060     -0.88834 +#>  ds 5 parent   90     11.3  1.175e+01   0.45050 1.0018      0.44969 +#>  ds 5 parent   90     11.9  1.175e+01  -0.14950 1.0018     -0.14923 +#>  ds 5 parent  120      9.0  7.915e+00  -1.08476 0.8315     -1.30462 +#>  ds 5 parent  120      8.1  7.915e+00  -0.18476 0.8315     -0.22220 +#>  ds 5     m1    0      0.7  0.000e+00  -0.70000 0.6572     -1.06507 +#>  ds 5     m1    1      3.0  3.062e+00   0.06170 0.6861      0.08992 +#>  ds 5     m1    1      2.6  3.062e+00   0.46170 0.6861      0.67290 +#>  ds 5     m1    3      5.1  8.209e+00   3.10938 0.8432      3.68760 +#>  ds 5     m1    3      7.5  8.209e+00   0.70938 0.8432      0.84130 +#>  ds 5     m1    7     16.5  1.544e+01  -1.05567 1.1914     -0.88605 +#>  ds 5     m1    7     19.0  1.544e+01  -3.55567 1.1914     -2.98436 +#>  ds 5     m1   14     22.9  2.181e+01  -1.08765 1.5498     -0.70181 +#>  ds 5     m1   14     23.2  2.181e+01  -1.38765 1.5498     -0.89539 +#>  ds 5     m1   28     22.2  2.404e+01   1.83624 1.6805      1.09270 +#>  ds 5     m1   28     24.4  2.404e+01  -0.36376 1.6805     -0.21647 +#>  ds 5     m1   60     15.5  1.875e+01   3.25390 1.3741      2.36805 +#>  ds 5     m1   60     19.8  1.875e+01  -1.04610 1.3741     -0.76131 +#>  ds 5     m1   90     14.9  1.380e+01  -1.09507 1.1050     -0.99102 +#>  ds 5     m1   90     14.2  1.380e+01  -0.39507 1.1050     -0.35753 +#>  ds 5     m1  120     10.9  1.002e+01  -0.88429 0.9205     -0.96069 +#>  ds 5     m1  120     10.4  1.002e+01  -0.38429 0.9205     -0.41749</div><div class='input'><span class='co'># }</span>  </div></pre>    </div> diff --git a/docs/dev/reference/transform_odeparms.html b/docs/dev/reference/transform_odeparms.html index 46b66073..6e19505f 100644 --- a/docs/dev/reference/transform_odeparms.html +++ b/docs/dev/reference/transform_odeparms.html @@ -77,7 +77,7 @@ the ilr transformation is used." />        </button>        <span class="navbar-brand">          <a class="navbar-link" href="../index.html">mkin</a> -        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">0.9.50.4</span> +        <span class="version label label-info" data-toggle="tooltip" data-placement="bottom" title="In-development version">1.0.1.9000</span>        </span>      </div> @@ -126,7 +126,7 @@ the ilr transformation is used." />        <ul class="nav navbar-nav navbar-right">          <li>    <a href="https://github.com/jranke/mkin/"> -    <span class="fab fa fab fa-github fa-lg"></span> +    <span class="fab fa-github fa-lg"></span>    </a>  </li> @@ -231,50 +231,64 @@ This is no problem for the internal use in <a href='mkinfit.html'>mkinfit</a>.</      <pre class="examples"><div class='input'>  <span class='va'>SFO_SFO</span> <span class='op'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span><span class='op'>(</span>    parent <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>type <span class='op'>=</span> <span class='st'>"SFO"</span>, to <span class='op'>=</span> <span class='st'>"m1"</span>, sink <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>, -  m1 <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>type <span class='op'>=</span> <span class='st'>"SFO"</span><span class='op'>)</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='message'>Temporary DLL for differentials generated and loaded</span></div><div class='input'><span class='co'># Fit the model to the FOCUS example dataset D using defaults</span> -<span class='va'>fit</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO</span>, <span class='va'>FOCUS_2006_D</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='warning'>Warning: Observations with value of zero were removed from the data</span></div><div class='input'><span class='va'>fit.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit</span><span class='op'>)</span> +  m1 <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>type <span class='op'>=</span> <span class='st'>"SFO"</span><span class='op'>)</span>, use_of_ff <span class='op'>=</span> <span class='st'>"min"</span><span class='op'>)</span> +</div><div class='output co'>#> <span class='message'>Temporary DLL for differentials generated and loaded</span></div><div class='input'> +<span class='co'># Fit the model to the FOCUS example dataset D using defaults</span> +<span class='va'>FOCUS_D</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/subset.html'>subset</a></span><span class='op'>(</span><span class='va'>FOCUS_2006_D</span>, <span class='va'>value</span> <span class='op'>!=</span> <span class='fl'>0</span><span class='op'>)</span> <span class='co'># remove zero values to avoid warning</span> +<span class='va'>fit</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO</span>, <span class='va'>FOCUS_D</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +<span class='va'>fit.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit</span><span class='op'>)</span>  <span class='co'># Transformed and backtransformed parameters</span>  <span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.s</span><span class='op'>$</span><span class='va'>par</span>, <span class='fl'>3</span><span class='op'>)</span> -</div><div class='output co'>#>                 Estimate Std. Error  Lower  Upper -#> parent_0         99.5985     1.5702 96.404 102.79 -#> log_k_parent     -2.3157     0.0409 -2.399  -2.23 -#> log_k_m1         -5.2475     0.1332 -5.518  -4.98 -#> f_parent_qlogis   0.0579     0.0893 -0.124   0.24 -#> sigma             3.1255     0.3585  2.396   3.85</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.s</span><span class='op'>$</span><span class='va'>bpar</span>, <span class='fl'>3</span><span class='op'>)</span> -</div><div class='output co'>#>                Estimate se_notrans t value   Pr(>t)    Lower    Upper -#> parent_0       99.59848    1.57022   63.43 2.30e-36 96.40383 102.7931 -#> k_parent        0.09870    0.00403   24.47 4.96e-23  0.09082   0.1073 -#> k_m1            0.00526    0.00070    7.51 6.16e-09  0.00401   0.0069 -#> f_parent_to_m1  0.51448    0.02230   23.07 3.10e-22  0.46912   0.5596 -#> sigma           3.12550    0.35852    8.72 2.24e-10  2.39609   3.8549</div><div class='input'> +</div><div class='output co'>#>                   Estimate Std. Error Lower  Upper +#> parent_0             99.60     1.5702 96.40 102.79 +#> log_k_parent_sink    -3.04     0.0763 -3.19  -2.88 +#> log_k_parent_m1      -2.98     0.0403 -3.06  -2.90 +#> log_k_m1_sink        -5.25     0.1332 -5.52  -4.98 +#> sigma                 3.13     0.3585  2.40   3.85</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.s</span><span class='op'>$</span><span class='va'>bpar</span>, <span class='fl'>3</span><span class='op'>)</span> +</div><div class='output co'>#>               Estimate se_notrans t value   Pr(>t)    Lower    Upper +#> parent_0      99.59848    1.57022   63.43 2.30e-36 96.40384 102.7931 +#> k_parent_sink  0.04792    0.00365   13.11 6.13e-15  0.04103   0.0560 +#> k_parent_m1    0.05078    0.00205   24.80 3.27e-23  0.04678   0.0551 +#> k_m1_sink      0.00526    0.00070    7.51 6.16e-09  0.00401   0.0069 +#> sigma          3.12550    0.35852    8.72 2.24e-10  2.39609   3.8549</div><div class='input'>  <span class='co'># \dontrun{</span> -<span class='co'># Compare to the version without transforming rate parameters</span> -<span class='va'>fit.2</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO</span>, <span class='va'>FOCUS_2006_D</span>, transform_rates <span class='op'>=</span> <span class='cn'>FALSE</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='warning'>Warning: Observations with value of zero were removed from the data</span></div><div class='output co'>#> <span class='error'>Error in if (cost < cost.current) {    assign("cost.current", cost, inherits = TRUE)    if (!quiet)         cat(ifelse(OLS, "Sum of squared residuals", "Negative log-likelihood"),             " at call ", calls, ": ", signif(cost.current, 6),             "\n", sep = "")}: missing value where TRUE/FALSE needed</span></div><div class='output co'>#> <span class='message'>Timing stopped at: 0.006 0 0.005</span></div><div class='input'><span class='va'>fit.2.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit.2</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in h(simpleError(msg, call)): error in evaluating the argument 'object' in selecting a method for function 'summary': object 'fit.2' not found</span></div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.2.s</span><span class='op'>$</span><span class='va'>par</span>, <span class='fl'>3</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in h(simpleError(msg, call)): error in evaluating the argument 'x' in selecting a method for function 'print': object 'fit.2.s' not found</span></div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.2.s</span><span class='op'>$</span><span class='va'>bpar</span>, <span class='fl'>3</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='error'>Error in h(simpleError(msg, call)): error in evaluating the argument 'x' in selecting a method for function 'print': object 'fit.2.s' not found</span></div><div class='input'><span class='co'># }</span> +<span class='co'># Compare to the version without transforming rate parameters (does not work</span> +<span class='co'># with analytical solution, we get NA values for m1 in predictions)</span> +<span class='va'>fit.2</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO</span>, <span class='va'>FOCUS_D</span>, transform_rates <span class='op'>=</span> <span class='cn'>FALSE</span>, +  solution_type <span class='op'>=</span> <span class='st'>"deSolve"</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +<span class='va'>fit.2.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit.2</span><span class='op'>)</span> +<span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.2.s</span><span class='op'>$</span><span class='va'>par</span>, <span class='fl'>3</span><span class='op'>)</span> +</div><div class='output co'>#>               Estimate Std. Error    Lower    Upper +#> parent_0      99.59848    1.57022 96.40384 1.03e+02 +#> k_parent_sink  0.04792    0.00365  0.04049 5.54e-02 +#> k_parent_m1    0.05078    0.00205  0.04661 5.49e-02 +#> k_m1_sink      0.00526    0.00070  0.00384 6.69e-03 +#> sigma          3.12550    0.35852  2.39609 3.85e+00</div><div class='input'><span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.2.s</span><span class='op'>$</span><span class='va'>bpar</span>, <span class='fl'>3</span><span class='op'>)</span> +</div><div class='output co'>#>               Estimate se_notrans t value   Pr(>t)    Lower    Upper +#> parent_0      99.59848    1.57022   63.43 2.30e-36 96.40384 1.03e+02 +#> k_parent_sink  0.04792    0.00365   13.11 6.13e-15  0.04049 5.54e-02 +#> k_parent_m1    0.05078    0.00205   24.80 3.27e-23  0.04661 5.49e-02 +#> k_m1_sink      0.00526    0.00070    7.51 6.16e-09  0.00384 6.69e-03 +#> sigma          3.12550    0.35852    8.72 2.24e-10  2.39609 3.85e+00</div><div class='input'><span class='co'># }</span>  <span class='va'>initials</span> <span class='op'><-</span> <span class='va'>fit</span><span class='op'>$</span><span class='va'>start</span><span class='op'>$</span><span class='va'>value</span>  <span class='fu'><a href='https://rdrr.io/r/base/names.html'>names</a></span><span class='op'>(</span><span class='va'>initials</span><span class='op'>)</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/colnames.html'>rownames</a></span><span class='op'>(</span><span class='va'>fit</span><span class='op'>$</span><span class='va'>start</span><span class='op'>)</span>  <span class='va'>transformed</span> <span class='op'><-</span> <span class='va'>fit</span><span class='op'>$</span><span class='va'>start_transformed</span><span class='op'>$</span><span class='va'>value</span>  <span class='fu'><a href='https://rdrr.io/r/base/names.html'>names</a></span><span class='op'>(</span><span class='va'>transformed</span><span class='op'>)</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/r/base/colnames.html'>rownames</a></span><span class='op'>(</span><span class='va'>fit</span><span class='op'>$</span><span class='va'>start_transformed</span><span class='op'>)</span>  <span class='fu'>transform_odeparms</span><span class='op'>(</span><span class='va'>initials</span>, <span class='va'>SFO_SFO</span><span class='op'>)</span> -</div><div class='output co'>#>        parent_0    log_k_parent        log_k_m1 f_parent_qlogis  -#>      100.750000       -2.302585       -2.301586        0.000000 </div><div class='input'><span class='fu'>backtransform_odeparms</span><span class='op'>(</span><span class='va'>transformed</span>, <span class='va'>SFO_SFO</span><span class='op'>)</span> -</div><div class='output co'>#>       parent_0       k_parent           k_m1 f_parent_to_m1  -#>       100.7500         0.1000         0.1001         0.5000 </div><div class='input'> +</div><div class='output co'>#>          parent_0 log_k_parent_sink   log_k_parent_m1     log_k_m1_sink  +#>        100.750000         -2.302585         -2.301586         -2.300587 </div><div class='input'><span class='fu'>backtransform_odeparms</span><span class='op'>(</span><span class='va'>transformed</span>, <span class='va'>SFO_SFO</span><span class='op'>)</span> +</div><div class='output co'>#>      parent_0 k_parent_sink   k_parent_m1     k_m1_sink  +#>      100.7500        0.1000        0.1001        0.1002 </div><div class='input'>  <span class='co'># \dontrun{</span> -<span class='co'># The case of formation fractions</span> +<span class='co'># The case of formation fractions (this is now the default)</span>  <span class='va'>SFO_SFO.ff</span> <span class='op'><-</span> <span class='fu'><a href='mkinmod.html'>mkinmod</a></span><span class='op'>(</span>    parent <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>type <span class='op'>=</span> <span class='st'>"SFO"</span>, to <span class='op'>=</span> <span class='st'>"m1"</span>, sink <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>,    m1 <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/list.html'>list</a></span><span class='op'>(</span>type <span class='op'>=</span> <span class='st'>"SFO"</span><span class='op'>)</span>,    use_of_ff <span class='op'>=</span> <span class='st'>"max"</span><span class='op'>)</span>  </div><div class='output co'>#> <span class='message'>Temporary DLL for differentials generated and loaded</span></div><div class='input'> -<span class='va'>fit.ff</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO.ff</span>, <span class='va'>FOCUS_2006_D</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='warning'>Warning: Observations with value of zero were removed from the data</span></div><div class='input'><span class='va'>fit.ff.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit.ff</span><span class='op'>)</span> +<span class='va'>fit.ff</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO.ff</span>, <span class='va'>FOCUS_D</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +<span class='va'>fit.ff.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit.ff</span><span class='op'>)</span>  <span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.ff.s</span><span class='op'>$</span><span class='va'>par</span>, <span class='fl'>3</span><span class='op'>)</span>  </div><div class='output co'>#>                 Estimate Std. Error  Lower  Upper  #> parent_0         99.5985     1.5702 96.404 102.79 @@ -299,8 +313,8 @@ This is no problem for the internal use in <a href='mkinfit.html'>mkinfit</a>.</    use_of_ff <span class='op'>=</span> <span class='st'>"max"</span><span class='op'>)</span>  </div><div class='output co'>#> <span class='message'>Temporary DLL for differentials generated and loaded</span></div><div class='input'> -<span class='va'>fit.ff.2</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO.ff.2</span>, <span class='va'>FOCUS_2006_D</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> -</div><div class='output co'>#> <span class='warning'>Warning: Observations with value of zero were removed from the data</span></div><div class='input'><span class='va'>fit.ff.2.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit.ff.2</span><span class='op'>)</span> +<span class='va'>fit.ff.2</span> <span class='op'><-</span> <span class='fu'><a href='mkinfit.html'>mkinfit</a></span><span class='op'>(</span><span class='va'>SFO_SFO.ff.2</span>, <span class='va'>FOCUS_D</span>, quiet <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span> +<span class='va'>fit.ff.2.s</span> <span class='op'><-</span> <span class='fu'><a href='https://rdrr.io/pkg/saemix/man/summary-methods.html'>summary</a></span><span class='op'>(</span><span class='va'>fit.ff.2</span><span class='op'>)</span>  <span class='fu'><a href='https://rdrr.io/r/base/print.html'>print</a></span><span class='op'>(</span><span class='va'>fit.ff.2.s</span><span class='op'>$</span><span class='va'>par</span>, <span class='fl'>3</span><span class='op'>)</span>  </div><div class='output co'>#>              Estimate Std. Error Lower Upper  #> parent_0        84.79      3.012 78.67 90.91 diff --git a/docs/dev/sitemap.xml b/docs/dev/sitemap.xml index ecf68e50..27f0e392 100644 --- a/docs/dev/sitemap.xml +++ b/docs/dev/sitemap.xml @@ -175,9 +175,6 @@      <loc>https://pkgdown.jrwb.de/mkin/reference/plot.nafta.html</loc>    </url>    <url> -    <loc>https://pkgdown.jrwb.de/mkin/reference/print.mmkin.html</loc> -  </url> -  <url>      <loc>https://pkgdown.jrwb.de/mkin/reference/reexports.html</loc>    </url>    <url> diff --git a/man/endpoints.Rd b/man/endpoints.Rd index 0b225e62..72487717 100644 --- a/man/endpoints.Rd +++ b/man/endpoints.Rd @@ -8,8 +8,8 @@ with mkinfit}  endpoints(fit)  }  \arguments{ -\item{fit}{An object of class \link{mkinfit} or \link{nlme.mmkin} -or another object that has list components +\item{fit}{An object of class \link{mkinfit}, \link{nlme.mmkin} or +\link{saem.mmkin}. Or another object that has list components  mkinmod containing an \link{mkinmod} degradation model, and two numeric vectors,  bparms.optim and bparms.fixed, that contain parameter values  for that model.} @@ -32,8 +32,8 @@ Additional DT50 values are calculated from the FOMC DT90 and k1 and k2 from  HS and DFOP, as well as from Eigenvalues b1 and b2 of any SFORB models  }  \note{ -The function is used internally by \link{summary.mkinfit} -and \link{summary.nlme.mmkin} +The function is used internally by \link{summary.mkinfit}, +\link{summary.nlme.mmkin} and \link{summary.saem.mmkin}.  }  \examples{ diff --git a/man/plot.mixed.mmkin.Rd b/man/plot.mixed.mmkin.Rd index 87a82286..b1200729 100644 --- a/man/plot.mixed.mmkin.Rd +++ b/man/plot.mixed.mmkin.Rd @@ -27,7 +27,7 @@  )  }  \arguments{ -\item{x}{An object of class \link{mixed.mmkin}, \link{nlme.mmkin}} +\item{x}{An object of class \link{mixed.mmkin}, \link{saem.mmkin} or \link{nlme.mmkin}}  \item{i}{A numeric index to select datasets for which to plot the individual predictions,  in case plots get too large} @@ -94,6 +94,15 @@ plot(f[, 3:4], standardized = TRUE)  f_nlme <- nlme(f, control = list(pnlsMaxIter = 120, tolerance = 1e-3))  plot(f_nlme) +f_saem <- saem(f, transformations = "saemix") +plot(f_saem) + +# We can overlay the two variants if we generate predictions +pred_nlme <- mkinpredict(dfop_sfo, +  f_nlme$bparms.optim[-1], +  c(parent = f_nlme$bparms.optim[[1]], A1 = 0), +  seq(0, 180, by = 0.2)) +plot(f_saem, pred_over = list(nlme = pred_nlme))  }  }  \author{ diff --git a/man/saem.Rd b/man/saem.Rd new file mode 100644 index 00000000..d5a8f17e --- /dev/null +++ b/man/saem.Rd @@ -0,0 +1,155 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/saem.R +\name{saem} +\alias{saem} +\alias{saem.mmkin} +\alias{print.saem.mmkin} +\alias{saemix_model} +\alias{saemix_data} +\title{Fit nonlinear mixed models with SAEM} +\usage{ +saem(object, ...) + +\method{saem}{mmkin}( +  object, +  transformations = c("mkin", "saemix"), +  degparms_start = numeric(), +  solution_type = "auto", +  control = list(displayProgress = FALSE, print = FALSE, save = FALSE, save.graphs = +    FALSE), +  verbose = FALSE, +  quiet = FALSE, +  ... +) + +\method{print}{saem.mmkin}(x, digits = max(3, getOption("digits") - 3), ...) + +saemix_model( +  object, +  solution_type = "auto", +  transformations = c("mkin", "saemix"), +  degparms_start = numeric(), +  verbose = FALSE, +  ... +) + +saemix_data(object, verbose = FALSE, ...) +} +\arguments{ +\item{object}{An \link{mmkin} row object containing several fits of the same +\link{mkinmod} model to different datasets} + +\item{\dots}{Further parameters passed to \link[saemix:saemixModel]{saemix::saemixModel}.} + +\item{transformations}{Per default, all parameter transformations are done +in mkin. If this argument is set to 'saemix', parameter transformations +are done in 'saemix' for the supported cases. Currently this is only +supported in cases where the initial concentration of the parent is not fixed, +SFO or DFOP is used for the parent and there is either no metabolite or one.} + +\item{degparms_start}{Parameter values given as a named numeric vector will +be used to override the starting values obtained from the 'mmkin' object.} + +\item{solution_type}{Possibility to specify the solution type in case the +automatic choice is not desired} + +\item{control}{Passed to \link[saemix:saemix]{saemix::saemix}} + +\item{verbose}{Should we print information about created objects of +type \link[saemix:SaemixModel-class]{saemix::SaemixModel} and \link[saemix:SaemixData-class]{saemix::SaemixData}?} + +\item{quiet}{Should we suppress the messages saemix prints at the beginning +and the end of the optimisation process?} + +\item{x}{An saem.mmkin object to print} + +\item{digits}{Number of digits to use for printing} +} +\value{ +An S3 object of class 'saem.mmkin', containing the fitted +\link[saemix:SaemixObject-class]{saemix::SaemixObject} as a list component named 'so'. The +object also inherits from 'mixed.mmkin'. + +An \link[saemix:SaemixModel-class]{saemix::SaemixModel} object. + +An \link[saemix:SaemixData-class]{saemix::SaemixData} object. +} +\description{ +This function uses \code{\link[saemix:saemix]{saemix::saemix()}} as a backend for fitting nonlinear mixed +effects models created from \link{mmkin} row objects using the Stochastic Approximation +Expectation Maximisation algorithm (SAEM). +} +\details{ +An mmkin row object is essentially a list of mkinfit objects that have been +obtained by fitting the same model to a list of datasets using \link{mkinfit}. + +Starting values for the fixed effects (population mean parameters, argument +psi0 of \code{\link[saemix:saemixModel]{saemix::saemixModel()}} are the mean values of the parameters found +using \link{mmkin}. +} +\examples{ +\dontrun{ +ds <- lapply(experimental_data_for_UBA_2019[6:10], + function(x) subset(x$data[c("name", "time", "value")])) +names(ds) <- paste("Dataset", 6:10) +f_mmkin_parent_p0_fixed <- mmkin("FOMC", ds, +  state.ini = c(parent = 100), fixed_initials = "parent", quiet = TRUE) +f_saem_p0_fixed <- saem(f_mmkin_parent_p0_fixed) + +f_mmkin_parent <- mmkin(c("SFO", "FOMC", "DFOP"), ds, quiet = TRUE) +f_saem_sfo <- saem(f_mmkin_parent["SFO", ]) +f_saem_fomc <- saem(f_mmkin_parent["FOMC", ]) +f_saem_dfop <- saem(f_mmkin_parent["DFOP", ]) + +# The returned saem.mmkin object contains an SaemixObject, therefore we can use +# functions from saemix +library(saemix) +compare.saemix(list(f_saem_sfo$so, f_saem_fomc$so, f_saem_dfop$so)) +plot(f_saem_fomc$so, plot.type = "convergence") +plot(f_saem_fomc$so, plot.type = "individual.fit") +plot(f_saem_fomc$so, plot.type = "npde") +plot(f_saem_fomc$so, plot.type = "vpc") + +f_mmkin_parent_tc <- update(f_mmkin_parent, error_model = "tc") +f_saem_fomc_tc <- saem(f_mmkin_parent_tc["FOMC", ]) +compare.saemix(list(f_saem_fomc$so, f_saem_fomc_tc$so)) + +sfo_sfo <- mkinmod(parent = mkinsub("SFO", "A1"), +  A1 = mkinsub("SFO")) +fomc_sfo <- mkinmod(parent = mkinsub("FOMC", "A1"), +  A1 = mkinsub("SFO")) +dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "A1"), +  A1 = mkinsub("SFO")) +# The following fit uses analytical solutions for SFO-SFO and DFOP-SFO, +# and compiled ODEs for FOMC that are much slower +f_mmkin <- mmkin(list( +    "SFO-SFO" = sfo_sfo, "FOMC-SFO" = fomc_sfo, "DFOP-SFO" = dfop_sfo), +  ds, quiet = TRUE) +# saem fits of SFO-SFO and DFOP-SFO to these data take about five seconds +# each on this system, as we use analytical solutions written for saemix. +# When using the analytical solutions written for mkin this took around +# four minutes +f_saem_sfo_sfo <- saem(f_mmkin["SFO-SFO", ]) +f_saem_dfop_sfo <- saem(f_mmkin["DFOP-SFO", ]) +# We can use print, plot and summary methods to check the results +print(f_saem_dfop_sfo) +plot(f_saem_dfop_sfo) +summary(f_saem_dfop_sfo, data = TRUE) + +# The following takes about 6 minutes +#f_saem_dfop_sfo_deSolve <- saem(f_mmkin["DFOP-SFO", ], solution_type = "deSolve", +#  control = list(nbiter.saemix = c(200, 80), nbdisplay = 10)) + +#saemix::compare.saemix(list( +#  f_saem_dfop_sfo$so, +#  f_saem_dfop_sfo_deSolve$so)) + +# If the model supports it, we can also use eigenvalue based solutions, which +# take a similar amount of time +#f_saem_sfo_sfo_eigen <- saem(f_mmkin["SFO-SFO", ], solution_type = "eigen", +#  control = list(nbiter.saemix = c(200, 80), nbdisplay = 10)) +} +} +\seealso{ +\link{summary.saem.mmkin} \link{plot.mixed.mmkin} +} diff --git a/man/summary.saem.mmkin.Rd b/man/summary.saem.mmkin.Rd new file mode 100644 index 00000000..67cb3cbb --- /dev/null +++ b/man/summary.saem.mmkin.Rd @@ -0,0 +1,100 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/summary.saem.mmkin.R +\name{summary.saem.mmkin} +\alias{summary.saem.mmkin} +\alias{print.summary.saem.mmkin} +\title{Summary method for class "saem.mmkin"} +\usage{ +\method{summary}{saem.mmkin}(object, data = FALSE, verbose = FALSE, distimes = TRUE, ...) + +\method{print}{summary.saem.mmkin}(x, digits = max(3, getOption("digits") - 3), verbose = x$verbose, ...) +} +\arguments{ +\item{object}{an object of class \link{saem.mmkin}} + +\item{data}{logical, indicating whether the full data should be included in +the summary.} + +\item{verbose}{Should the summary be verbose?} + +\item{distimes}{logical, indicating whether DT50 and DT90 values should be +included.} + +\item{\dots}{optional arguments passed to methods like \code{print}.} + +\item{x}{an object of class \link{summary.saem.mmkin}} + +\item{digits}{Number of digits to use for printing} +} +\value{ +The summary function returns a list based on the \link[saemix:SaemixObject-class]{saemix::SaemixObject} +obtained in the fit, with at least the following additional components +\item{saemixversion, mkinversion, Rversion}{The saemix, mkin and R versions used} +\item{date.fit, date.summary}{The dates where the fit and the summary were +produced} +\item{diffs}{The differential equations used in the degradation model} +\item{use_of_ff}{Was maximum or minimum use made of formation fractions} +\item{data}{The data} +\item{confint_trans}{Transformed parameters as used in the optimisation, with confidence intervals} +\item{confint_back}{Backtransformed parameters, with confidence intervals if available} +\item{confint_errmod}{Error model parameters with confidence intervals} +\item{ff}{The estimated formation fractions derived from the fitted +model.} +\item{distimes}{The DT50 and DT90 values for each observed variable.} +\item{SFORB}{If applicable, eigenvalues of SFORB components of the model.} +The print method is called for its side effect, i.e. printing the summary. +} +\description{ +Lists model equations, initial parameter values, optimised parameters +for fixed effects (population), random effects (deviations from the +population mean) and residual error model, as well as the resulting +endpoints such as formation fractions and DT50 values. Optionally +(default is FALSE), the data are listed in full. +} +\examples{ +# Generate five datasets following DFOP-SFO kinetics +sampling_times = c(0, 1, 3, 7, 14, 28, 60, 90, 120) +dfop_sfo <- mkinmod(parent = mkinsub("DFOP", "m1"), + m1 = mkinsub("SFO"), quiet = TRUE) +set.seed(1234) +k1_in <- rlnorm(5, log(0.1), 0.3) +k2_in <- rlnorm(5, log(0.02), 0.3) +g_in <- plogis(rnorm(5, qlogis(0.5), 0.3)) +f_parent_to_m1_in <- plogis(rnorm(5, qlogis(0.3), 0.3)) +k_m1_in <- rlnorm(5, log(0.02), 0.3) + +pred_dfop_sfo <- function(k1, k2, g, f_parent_to_m1, k_m1) { +  mkinpredict(dfop_sfo, +    c(k1 = k1, k2 = k2, g = g, f_parent_to_m1 = f_parent_to_m1, k_m1 = k_m1), +    c(parent = 100, m1 = 0), +    sampling_times) +} + +ds_mean_dfop_sfo <- lapply(1:5, function(i) { +  mkinpredict(dfop_sfo, +    c(k1 = k1_in[i], k2 = k2_in[i], g = g_in[i], +      f_parent_to_m1 = f_parent_to_m1_in[i], k_m1 = k_m1_in[i]), +    c(parent = 100, m1 = 0), +    sampling_times) +}) +names(ds_mean_dfop_sfo) <- paste("ds", 1:5) + +ds_syn_dfop_sfo <- lapply(ds_mean_dfop_sfo, function(ds) { +  add_err(ds, +    sdfunc = function(value) sqrt(1^2 + value^2 * 0.07^2), +    n = 1)[[1]] +}) + +\dontrun{ +# Evaluate using mmkin and saem +f_mmkin_dfop_sfo <- mmkin(list(dfop_sfo), ds_syn_dfop_sfo, +  quiet = TRUE, error_model = "tc", cores = 5) +f_saem_dfop_sfo <- saem(f_mmkin_dfop_sfo) +summary(f_saem_dfop_sfo, data = TRUE) +} + +} +\author{ +Johannes Ranke for the mkin specific parts +saemix authors for the parts inherited from saemix. +} @@ -6,32 +6,39 @@ Testing mkin  ✔ |   2       | Export dataset for reading into CAKE  ✔ |  14       | Results for FOCUS D established in expertise for UBA (Ranke 2014) [1.0 s]  ✔ |   4       | Calculation of FOCUS chi2 error levels [0.5 s] -✔ |   7       | Fitting the SFORB model [3.4 s] -✔ |   5       | Analytical solutions for coupled models [3.3 s] +✔ |   7       | Fitting the SFORB model [3.5 s] +✔ |   5       | Analytical solutions for coupled models [3.2 s]  ✔ |   5       | Calculation of Akaike weights  ✔ |  12       | Confidence intervals and p-values [1.0 s] -✔ |  14       | Error model fitting [4.2 s] +✔ |  14       | Error model fitting [4.4 s]  ✔ |   5       | Time step normalisation  ✔ |   4       | Test fitting the decline of metabolites from their maximum [0.3 s]  ✔ |   1       | Fitting the logistic model [0.2 s] -✔ |   5       | Nonlinear mixed-effects models [0.1 s] +✔ |  34     1 | Nonlinear mixed-effects models [25.9 s] +──────────────────────────────────────────────────────────────────────────────── +Skip (test_mixed.R:150:3): saem results are reproducible for biphasic fits +Reason: Fitting with saemix takes around 10 minutes when using deSolve +────────────────────────────────────────────────────────────────────────────────  ✔ |   2       | Test dataset classes mkinds and mkindsg  ✔ |   1       | mkinfit features [0.3 s]  ✔ |  10       | Special cases of mkinfit calls [0.3 s]  ✔ |   8       | mkinmod model generation and printing [0.2 s]  ✔ |   3       | Model predictions with mkinpredict [0.3 s]  ✔ |  16       | Evaluations according to 2015 NAFTA guidance [1.6 s] -✔ |   9       | Nonlinear mixed-effects models [8.0 s] -✔ |  14       | Plotting [1.7 s] +✔ |   9       | Nonlinear mixed-effects models [8.1 s] +✔ |  16       | Plotting [1.9 s]  ✔ |   4       | Residuals extracted from mkinfit models  ✔ |   2       | Complex test case from Schaefer et al. (2007) Piacenza paper [1.5 s]  ✔ |   4       | Summary [0.1 s]  ✔ |   1       | Summaries of old mkinfit objects  ✔ |   4       | Results for synthetic data established in expertise for UBA (Ranke 2014) [2.2 s] -✔ |   9       | Hypothesis tests [8.1 s] -✔ |   4       | Calculation of maximum time weighted average concentrations (TWAs) [2.6 s] +✔ |   9       | Hypothesis tests [8.3 s] +✔ |   4       | Calculation of maximum time weighted average concentrations (TWAs) [2.5 s]  ══ Results ═════════════════════════════════════════════════════════════════════ -Duration: 41.3 s +Duration: 67.9 s -[ FAIL 0 | WARN 0 | SKIP 0 | PASS 174 ] +── Skipped tests  ────────────────────────────────────────────────────────────── +● Fitting with saemix takes around 10 minutes when using deSolve (1) + +[ FAIL 0 | WARN 0 | SKIP 1 | PASS 205 ] diff --git a/tests/figs/plotting/mixed-model-fit-for-saem-object-with-mkin-transformations.svg b/tests/figs/plotting/mixed-model-fit-for-saem-object-with-mkin-transformations.svg index ce93625d..0c2992d5 100644 --- a/tests/figs/plotting/mixed-model-fit-for-saem-object-with-mkin-transformations.svg +++ b/tests/figs/plotting/mixed-model-fit-for-saem-object-with-mkin-transformations.svg @@ -13,720 +13,720 @@  </defs>  <rect width='100%' height='100%' style='stroke: none; fill: #FFFFFF;'/>  <defs> -  <clipPath id='cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA='> -    <rect x='19.96' y='5.70' width='680.08' height='75.63' /> +  <clipPath id='cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU='> +    <rect x='19.96' y='0.95' width='680.08' height='70.10' />    </clipPath>  </defs> -<line x1='238.69' y1='29.26' x2='252.94' y2='29.26' style='stroke-width: 1.50;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='238.69' y1='38.77' x2='252.94' y2='38.77' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='238.69' y1='48.27' x2='252.94' y2='48.27' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='238.69' y1='57.77' x2='252.94' y2='57.77' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='299.52' y1='29.26' x2='313.78' y2='29.26' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='299.52' y1='38.77' x2='313.78' y2='38.77' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='299.52' y1='48.27' x2='313.78' y2='48.27' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='299.52' y1='57.77' x2='313.78' y2='57.77' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='360.36' y1='29.26' x2='374.61' y2='29.26' style='stroke-width: 0.75; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='360.36' y1='38.77' x2='374.61' y2='38.77' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='360.36' y1='48.27' x2='374.61' y2='48.27' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='360.36' y1='57.77' x2='374.61' y2='57.77' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='421.19' y1='29.26' x2='435.45' y2='29.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='421.19' y1='38.77' x2='435.45' y2='38.77' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='421.19' y1='48.27' x2='435.45' y2='48.27' style='stroke-width: 0.75; stroke: #F5C710; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='421.19' y1='57.77' x2='435.45' y2='57.77' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<circle cx='245.81' cy='38.77' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polyline points='245.81,45.50 248.21,49.66 243.41,49.66 245.81,45.50 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='243.29' y1='57.77' x2='248.33' y2='57.77' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='245.81' y1='60.29' x2='245.81' y2='55.25' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='304.87' y1='31.04' x2='308.43' y2='27.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='304.87' y1='27.48' x2='308.43' y2='31.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polyline points='304.13,38.77 306.65,36.25 309.17,38.77 306.65,41.29 304.13,38.77 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polyline points='306.65,51.04 309.05,46.89 304.25,46.89 306.65,51.04 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<rect x='304.87' y='55.99' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='304.87' y1='59.56' x2='308.43' y2='55.99' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='304.87' y1='55.99' x2='308.43' y2='59.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='365.70' y1='31.04' x2='369.27' y2='27.48' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='365.70' y1='27.48' x2='369.27' y2='31.04' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='364.96' y1='29.26' x2='370.00' y2='29.26' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='367.48' y1='31.78' x2='367.48' y2='26.74' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='364.96' y1='38.77' x2='370.00' y2='38.77' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='367.48' y1='41.29' x2='367.48' y2='36.25' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polyline points='364.96,38.77 367.48,36.25 370.00,38.77 367.48,41.29 364.96,38.77 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<circle cx='367.48' cy='48.27' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='365.70' y1='48.27' x2='369.27' y2='48.27' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='367.48' y1='50.05' x2='367.48' y2='46.49' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polyline points='367.48,60.55 369.88,55.70 365.08,55.70 367.48,60.55 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polyline points='367.48,55.00 369.88,59.85 365.08,59.85 367.48,55.00 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='426.54' y1='29.26' x2='430.10' y2='29.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='428.32' y1='31.04' x2='428.32' y2='27.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<rect x='426.54' y='27.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<circle cx='428.32' cy='38.77' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='426.54' y1='40.55' x2='430.10' y2='36.98' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<line x1='426.54' y1='36.98' x2='430.10' y2='40.55' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polyline points='428.32,46.49 430.10,50.05 426.54,50.05 428.32,46.49 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<rect x='426.54' y='46.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<polygon points='426.54,59.56 430.10,59.56 430.10,55.99 426.54,55.99 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)' /> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='260.07' y='31.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='37.31px' lengthAdjust='spacingAndGlyphs'>Population</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='260.07' y='41.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>1</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='260.07' y='50.99' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='260.07' y='60.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>3</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='320.91' y='31.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='320.91' y='41.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>5</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='320.91' y='50.99' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>6</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='320.91' y='60.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>7</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='381.74' y='31.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>8</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='381.74' y='41.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>9</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='381.74' y='50.99' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='381.74' y='60.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.19px' lengthAdjust='spacingAndGlyphs'>11</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='442.58' y='31.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>12</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='442.58' y='41.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>13</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='442.58' y='50.99' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>14</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDgxLjM0fDUuNzA=)'><text x='442.58' y='60.49' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>15</text></g> +<line x1='238.69' y1='21.74' x2='252.94' y2='21.74' style='stroke-width: 1.50;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='238.69' y1='31.25' x2='252.94' y2='31.25' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='238.69' y1='40.75' x2='252.94' y2='40.75' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='238.69' y1='50.26' x2='252.94' y2='50.26' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='299.52' y1='21.74' x2='313.78' y2='21.74' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='299.52' y1='31.25' x2='313.78' y2='31.25' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='299.52' y1='40.75' x2='313.78' y2='40.75' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='299.52' y1='50.26' x2='313.78' y2='50.26' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='360.36' y1='21.74' x2='374.61' y2='21.74' style='stroke-width: 0.75; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='360.36' y1='31.25' x2='374.61' y2='31.25' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='360.36' y1='40.75' x2='374.61' y2='40.75' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='360.36' y1='50.26' x2='374.61' y2='50.26' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='421.19' y1='21.74' x2='435.45' y2='21.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='421.19' y1='31.25' x2='435.45' y2='31.25' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='421.19' y1='40.75' x2='435.45' y2='40.75' style='stroke-width: 0.75; stroke: #F5C710; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='421.19' y1='50.26' x2='435.45' y2='50.26' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<circle cx='245.81' cy='31.25' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polyline points='245.81,37.98 248.21,42.14 243.41,42.14 245.81,37.98 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='243.29' y1='50.26' x2='248.33' y2='50.26' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='245.81' y1='52.78' x2='245.81' y2='47.74' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='304.87' y1='23.53' x2='308.43' y2='19.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='304.87' y1='19.96' x2='308.43' y2='23.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polyline points='304.13,31.25 306.65,28.73 309.17,31.25 306.65,33.77 304.13,31.25 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polyline points='306.65,43.52 309.05,39.37 304.25,39.37 306.65,43.52 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<rect x='304.87' y='48.47' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='304.87' y1='52.04' x2='308.43' y2='48.47' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='304.87' y1='48.47' x2='308.43' y2='52.04' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='365.70' y1='23.53' x2='369.27' y2='19.96' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='365.70' y1='19.96' x2='369.27' y2='23.53' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='364.96' y1='21.74' x2='370.00' y2='21.74' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='367.48' y1='24.26' x2='367.48' y2='19.22' style='stroke-width: 0.75;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='364.96' y1='31.25' x2='370.00' y2='31.25' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='367.48' y1='33.77' x2='367.48' y2='28.73' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polyline points='364.96,31.25 367.48,28.73 370.00,31.25 367.48,33.77 364.96,31.25 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<circle cx='367.48' cy='40.75' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='365.70' y1='40.75' x2='369.27' y2='40.75' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='367.48' y1='42.53' x2='367.48' y2='38.97' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polyline points='367.48,53.03 369.88,48.18 365.08,48.18 367.48,53.03 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polyline points='367.48,47.48 369.88,52.33 365.08,52.33 367.48,47.48 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='426.54' y1='21.74' x2='430.10' y2='21.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='428.32' y1='23.53' x2='428.32' y2='19.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<rect x='426.54' y='19.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<circle cx='428.32' cy='31.25' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='426.54' y1='33.03' x2='430.10' y2='29.47' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<line x1='426.54' y1='29.47' x2='430.10' y2='33.03' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polyline points='428.32,38.97 430.10,42.53 426.54,42.53 428.32,38.97 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<rect x='426.54' y='38.97' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<polygon points='426.54,52.04 430.10,52.04 430.10,48.47 426.54,48.47 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)' /> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='260.07' y='24.46' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='37.31px' lengthAdjust='spacingAndGlyphs'>Population</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='260.07' y='33.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>1</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='260.07' y='43.47' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='260.07' y='52.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>3</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='320.91' y='24.46' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='320.91' y='33.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>5</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='320.91' y='43.47' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>6</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='320.91' y='52.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>7</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='381.74' y='24.46' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>8</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='381.74' y='33.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>9</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='381.74' y='43.47' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='381.74' y='52.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.19px' lengthAdjust='spacingAndGlyphs'>11</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='442.58' y='24.46' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>12</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='442.58' y='33.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>13</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='442.58' y='43.47' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>14</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDcxLjA1fDAuOTU=)'><text x='442.58' y='52.97' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>15</text></g>  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ='> -    <rect x='38.97' y='102.24' width='301.08' height='186.63' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ=='> +    <rect x='38.97' y='82.45' width='301.08' height='201.03' />    </clipPath>  </defs> -<polyline points='50.12,124.54 52.44,128.53 55.81,134.14 57.09,136.21 61.50,143.12 66.38,150.38 67.19,151.54 72.87,159.42 78.56,166.81 82.64,171.81 84.25,173.73 89.94,180.21 95.63,186.29 101.32,191.99 107.01,197.34 112.70,202.35 115.16,204.43 118.39,207.05 124.08,211.47 129.77,215.61 135.46,219.49 141.15,223.14 146.83,226.57 152.52,229.78 158.21,232.80 163.90,235.64 169.59,238.31 175.28,240.82 180.97,243.17 186.66,245.39 189.50,246.45 192.35,247.47 198.04,249.43 203.73,251.27 209.42,253.01 215.11,254.64 220.79,256.17 226.48,257.62 232.17,258.98 237.86,260.26 243.55,261.47 249.24,262.61 254.93,263.68 259.20,264.44 260.62,264.69 266.31,265.64 272.00,266.53 277.69,267.38 283.38,268.18 289.07,268.93 294.76,269.64 300.44,270.31 306.13,270.94 311.82,271.54 317.51,272.10 323.20,272.63 328.89,273.13 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> +<polyline points='50.12,106.63 52.44,111.09 55.81,117.33 57.09,119.64 61.50,127.29 66.38,135.28 67.19,136.55 72.87,145.17 78.56,153.20 82.64,158.61 84.25,160.68 89.94,167.65 95.63,174.15 101.32,180.21 107.01,185.87 112.70,191.16 115.16,193.34 118.39,196.10 124.08,200.71 129.77,205.03 135.46,209.07 141.15,212.86 146.83,216.40 152.52,219.72 158.21,222.83 163.90,225.75 169.59,228.49 175.28,231.07 180.97,233.49 186.66,235.76 189.50,236.84 192.35,237.89 198.04,239.90 203.73,241.80 209.42,243.58 215.11,245.26 220.79,246.84 226.48,248.33 232.17,249.74 237.86,251.06 243.55,252.32 249.24,253.50 254.93,254.62 259.20,255.42 260.62,255.68 266.31,256.68 272.00,257.63 277.69,258.52 283.38,259.37 289.07,260.18 294.76,260.94 300.44,261.66 306.13,262.34 311.82,262.99 317.51,263.61 323.20,264.19 328.89,264.75 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' />  <defs>    <clipPath id='cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA='>      <rect x='0.00' y='0.00' width='720.00' height='576.00' />    </clipPath>  </defs> -<line x1='50.12' y1='288.88' x2='328.89' y2='288.88' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='50.12' y1='288.88' x2='50.12' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='96.58' y1='288.88' x2='96.58' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='143.04' y1='288.88' x2='143.04' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='189.50' y1='288.88' x2='189.50' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='235.97' y1='288.88' x2='235.97' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='282.43' y1='288.88' x2='282.43' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='328.89' y1='288.88' x2='328.89' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='47.92' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='92.19' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='138.65' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='185.11' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='231.58' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='275.84' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='322.30' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>120</text></g> -<line x1='38.97' y1='281.96' x2='38.97' y2='125.15' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='281.96' x2='34.21' y2='281.96' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='250.60' x2='34.21' y2='250.60' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='219.24' x2='34.21' y2='219.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='187.88' x2='34.21' y2='187.88' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='156.51' x2='34.21' y2='156.51' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='125.15' x2='34.21' y2='125.15' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,284.16) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,254.99) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,223.63) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,192.27) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,160.90) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,131.74) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> -<polyline points='38.97,288.88 340.04,288.88 340.04,102.24 38.97,102.24 38.97,288.88 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='50.12' y1='283.49' x2='328.89' y2='283.49' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='50.12' y1='283.49' x2='50.12' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='96.58' y1='283.49' x2='96.58' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='143.04' y1='283.49' x2='143.04' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='189.50' y1='283.49' x2='189.50' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='235.97' y1='283.49' x2='235.97' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='282.43' y1='283.49' x2='282.43' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='328.89' y1='283.49' x2='328.89' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='47.92' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='92.19' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='138.65' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='185.11' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='231.58' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='275.84' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='322.30' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>120</text></g> +<line x1='38.97' y1='276.04' x2='38.97' y2='107.13' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='276.04' x2='34.21' y2='276.04' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='242.26' x2='34.21' y2='242.26' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='208.48' x2='34.21' y2='208.48' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='174.69' x2='34.21' y2='174.69' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='140.91' x2='34.21' y2='140.91' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='107.13' x2='34.21' y2='107.13' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,278.24) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,246.65) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,212.87) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,179.09) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,145.30) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,113.72) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> +<polyline points='38.97,283.49 340.04,283.49 340.04,82.45 38.97,82.45 38.97,283.49 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMC4wMHwzNjAuMDB8MzE3LjM5fDgyLjI5'> -    <rect x='0.00' y='82.29' width='360.00' height='235.10' /> +  <clipPath id='cpMC4wMHwzNjAuMDB8MzEyLjAwfDcyLjAw'> +    <rect x='0.00' y='72.00' width='360.00' height='240.00' />    </clipPath>  </defs> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8MzE3LjM5fDgyLjI5)'><text x='180.87' y='324.99' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8MzE3LjM5fDgyLjI5)'><text transform='translate(8.55,206.76) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='22.41px' lengthAdjust='spacingAndGlyphs'>parent</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8MzEyLjAwfDcyLjAw)'><text x='180.87' y='319.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8MzEyLjAwfDcyLjAw)'><text transform='translate(8.55,211.74) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='57.53px' lengthAdjust='spacingAndGlyphs'>Residues parent</text></g>  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ='> -    <rect x='38.97' y='102.24' width='301.08' height='186.63' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ=='> +    <rect x='38.97' y='82.45' width='301.08' height='201.03' />    </clipPath>  </defs> -<circle cx='50.12' cy='117.47' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='50.12' cy='130.95' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='52.44' cy='129.86' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='52.44' cy='142.40' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='57.09' cy='156.51' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='57.09' cy='131.42' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='66.38' cy='160.59' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='66.38' cy='166.24' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='82.64' cy='174.55' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='82.64' cy='183.33' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='115.16' cy='203.87' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='115.16' cy='200.58' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='189.50' cy='231.16' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='189.50' cy='231.00' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='259.20' cy='246.99' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='259.20' cy='247.46' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='328.89' cy='253.27' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='328.89' cy='254.68' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,124.68 52.44,131.52 55.81,140.29 57.09,143.32 61.50,152.62 66.38,161.22 67.19,162.50 72.87,170.54 78.56,177.19 82.64,181.30 84.25,182.80 89.94,187.61 95.63,191.81 101.32,195.54 107.01,198.90 112.70,201.97 115.16,203.23 118.39,204.81 124.08,207.46 129.77,209.95 135.46,212.30 141.15,214.55 146.83,216.69 152.52,218.75 158.21,220.72 163.90,222.62 169.59,224.46 175.28,226.23 180.97,227.94 186.66,229.60 189.50,230.41 192.35,231.20 198.04,232.75 203.73,234.26 209.42,235.71 215.11,237.13 220.79,238.49 226.48,239.82 232.17,241.10 237.86,242.35 243.55,243.56 249.24,244.73 254.93,245.86 259.20,246.69 260.62,246.96 266.31,248.03 272.00,249.06 277.69,250.07 283.38,251.04 289.07,251.98 294.76,252.89 300.44,253.78 306.13,254.64 311.82,255.47 317.51,256.28 323.20,257.06 328.89,257.82 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,120.34 52.52,124.50 47.72,124.50 50.12,120.34 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,123.01 52.52,127.16 47.72,127.16 50.12,123.01 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,130.38 54.84,134.53 50.04,134.53 52.44,130.38 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,128.65 54.84,132.81 50.04,132.81 52.44,128.65 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,137.43 59.49,141.59 54.69,141.59 57.09,137.43 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,141.51 59.49,145.67 54.69,145.67 57.09,141.51 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,141.67 68.78,145.82 63.98,145.82 66.38,141.67 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,151.23 68.78,155.39 63.98,155.39 66.38,151.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,169.27 85.04,173.42 80.24,173.42 82.64,169.27 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,161.43 85.04,165.58 80.24,165.58 82.64,161.43 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,202.51 117.56,206.67 112.76,206.67 115.16,202.51 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,205.49 117.56,209.65 112.76,209.65 115.16,205.49 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,232.46 191.90,236.62 187.10,236.62 189.50,232.46 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,228.23 191.90,232.39 187.10,232.39 189.50,228.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,238.42 261.60,242.58 256.80,242.58 259.20,238.42 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,240.46 261.60,244.62 256.80,244.62 259.20,240.46 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,248.46 331.29,252.61 326.49,252.61 328.89,248.46 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,251.44 331.29,255.59 326.49,255.59 328.89,251.44 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,124.52 52.44,128.96 55.81,135.06 57.09,137.28 61.50,144.55 66.38,151.97 67.19,153.13 72.87,160.88 78.56,167.91 82.64,172.53 84.25,174.27 89.94,180.05 95.63,185.31 101.32,190.10 107.01,194.47 112.70,198.47 115.16,200.10 118.39,202.14 124.08,205.50 129.77,208.60 135.46,211.45 141.15,214.09 146.83,216.53 152.52,218.80 158.21,220.92 163.90,222.89 169.59,224.73 175.28,226.46 180.97,228.08 186.66,229.61 189.50,230.35 192.35,231.06 198.04,232.43 203.73,233.72 209.42,234.95 215.11,236.13 220.79,237.25 226.48,238.32 232.17,239.34 237.86,240.32 243.55,241.27 249.24,242.18 254.93,243.05 259.20,243.69 260.62,243.90 266.31,244.72 272.00,245.51 277.69,246.28 283.38,247.02 289.07,247.74 294.76,248.44 300.44,249.12 306.13,249.79 311.82,250.43 317.51,251.06 323.20,251.68 328.89,252.27 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='47.60' y1='141.15' x2='52.64' y2='141.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='143.67' x2='50.12' y2='138.63' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='47.60' y1='127.97' x2='52.64' y2='127.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='130.49' x2='50.12' y2='125.45' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='49.92' y1='126.25' x2='54.96' y2='126.25' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='128.77' x2='52.44' y2='123.73' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='49.92' y1='127.19' x2='54.96' y2='127.19' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='129.71' x2='52.44' y2='124.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='54.57' y1='129.86' x2='59.61' y2='129.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='132.38' x2='57.09' y2='127.34' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='54.57' y1='140.68' x2='59.61' y2='140.68' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='143.20' x2='57.09' y2='138.16' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='63.86' y1='150.55' x2='68.90' y2='150.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='153.07' x2='66.38' y2='148.03' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='63.86' y1='152.12' x2='68.90' y2='152.12' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='154.64' x2='66.38' y2='149.60' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.12' y1='164.04' x2='85.16' y2='164.04' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='166.56' x2='82.64' y2='161.52' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.12' y1='175.49' x2='85.16' y2='175.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='178.01' x2='82.64' y2='172.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='112.64' y1='193.84' x2='117.68' y2='193.84' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='196.36' x2='115.16' y2='191.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='112.64' y1='196.81' x2='117.68' y2='196.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='199.33' x2='115.16' y2='194.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='186.98' y1='234.29' x2='192.02' y2='234.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='236.81' x2='189.50' y2='231.77' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='186.98' y1='237.43' x2='192.02' y2='237.43' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='239.95' x2='189.50' y2='234.91' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='256.68' y1='252.95' x2='261.72' y2='252.95' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='255.47' x2='259.20' y2='250.43' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='256.68' y1='252.95' x2='261.72' y2='252.95' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='255.47' x2='259.20' y2='250.43' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='326.37' y1='267.54' x2='331.41' y2='267.54' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='270.06' x2='328.89' y2='265.02' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='326.37' y1='263.77' x2='331.41' y2='263.77' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='266.29' x2='328.89' y2='261.25' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,126.33 52.44,129.94 55.81,135.00 57.09,136.87 61.50,143.10 66.38,149.62 67.19,150.66 72.87,157.73 78.56,164.33 82.64,168.80 84.25,170.51 89.94,176.29 95.63,181.71 101.32,186.78 107.01,191.54 112.70,196.01 115.16,197.86 118.39,200.20 124.08,204.14 129.77,207.84 135.46,211.33 141.15,214.61 146.83,217.70 152.52,220.62 158.21,223.37 163.90,225.96 169.59,228.42 175.28,230.74 180.97,232.93 186.66,235.01 189.50,236.01 192.35,236.98 198.04,238.84 203.73,240.61 209.42,242.29 215.11,243.89 220.79,245.40 226.48,246.85 232.17,248.22 237.86,249.53 243.55,250.77 249.24,251.96 254.93,253.09 259.20,253.91 260.62,254.17 266.31,255.21 272.00,256.19 277.69,257.14 283.38,258.04 289.07,258.91 294.76,259.73 300.44,260.53 306.13,261.28 311.82,262.01 317.51,262.71 323.20,263.38 328.89,264.03 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='124.58' x2='51.90' y2='121.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='121.02' x2='51.90' y2='124.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='123.17' x2='51.90' y2='119.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='119.61' x2='51.90' y2='123.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='121.92' x2='54.22' y2='118.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='118.35' x2='54.22' y2='121.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='142.14' x2='54.22' y2='138.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='138.58' x2='54.22' y2='142.14' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='143.71' x2='58.87' y2='140.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='140.15' x2='58.87' y2='143.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='143.87' x2='58.87' y2='140.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='140.30' x2='58.87' y2='143.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='148.57' x2='68.16' y2='145.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='145.01' x2='68.16' y2='148.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='164.10' x2='68.16' y2='160.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='160.53' x2='68.16' y2='164.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='176.49' x2='84.42' y2='172.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='172.92' x2='84.42' y2='176.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='167.55' x2='84.42' y2='163.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='163.98' x2='84.42' y2='167.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='202.83' x2='116.95' y2='199.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='199.27' x2='116.95' y2='202.83' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='205.18' x2='116.95' y2='201.62' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='201.62' x2='116.95' y2='205.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='240.31' x2='191.29' y2='236.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='236.74' x2='191.29' y2='240.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='240.15' x2='191.29' y2='236.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='236.59' x2='191.29' y2='240.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='258.50' x2='260.98' y2='254.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='254.93' x2='260.98' y2='258.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='258.97' x2='260.98' y2='255.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='255.41' x2='260.98' y2='258.97' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='269.32' x2='330.67' y2='265.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='265.75' x2='330.67' y2='269.32' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='270.57' x2='330.67' y2='267.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='267.01' x2='330.67' y2='270.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,125.16 52.44,129.28 55.81,135.01 57.09,137.12 61.50,144.11 66.38,151.36 67.19,152.51 72.87,160.28 78.56,167.47 82.64,172.30 84.25,174.13 89.94,180.31 95.63,186.05 101.32,191.37 107.01,196.33 112.70,200.94 115.16,202.84 118.39,205.24 124.08,209.25 129.77,213.00 135.46,216.49 141.15,219.77 146.83,222.84 152.52,225.71 158.21,228.41 163.90,230.94 169.59,233.33 175.28,235.57 180.97,237.69 186.66,239.68 189.50,240.63 192.35,241.56 198.04,243.34 203.73,245.02 209.42,246.61 215.11,248.12 220.79,249.55 226.48,250.90 232.17,252.19 237.86,253.41 243.55,254.58 249.24,255.69 254.93,256.74 259.20,257.50 260.62,257.74 266.31,258.70 272.00,259.62 277.69,260.49 283.38,261.32 289.07,262.12 294.76,262.88 300.44,263.61 306.13,264.31 311.82,264.97 317.51,265.61 323.20,266.23 328.89,266.81 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='47.60,113.86 50.12,111.34 52.64,113.86 50.12,116.38 47.60,113.86 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='47.60,113.39 50.12,110.87 52.64,113.39 50.12,115.91 47.60,113.39 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='49.92,133.31 52.44,130.79 54.96,133.31 52.44,135.83 49.92,133.31 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='49.92,145.85 52.44,143.33 54.96,145.85 52.44,148.37 49.92,145.85 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='54.57,144.91 57.09,142.39 59.61,144.91 57.09,147.43 54.57,144.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='54.57,144.44 57.09,141.92 59.61,144.44 57.09,146.96 54.57,144.44 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='63.86,164.67 66.38,162.15 68.90,164.67 66.38,167.19 63.86,164.67 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='63.86,168.75 66.38,166.22 68.90,168.75 66.38,171.27 63.86,168.75 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='80.12,193.21 82.64,190.69 85.16,193.21 82.64,195.73 80.12,193.21 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='80.12,190.86 82.64,188.34 85.16,190.86 82.64,193.38 80.12,190.86 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='112.64,207.95 115.16,205.43 117.68,207.95 115.16,210.47 112.64,207.95 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='112.64,206.69 115.16,204.17 117.68,206.69 115.16,209.21 112.64,206.69 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='186.98,239.00 189.50,236.48 192.02,239.00 189.50,241.52 186.98,239.00 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='186.98,234.29 189.50,231.77 192.02,234.29 189.50,236.81 186.98,234.29 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='256.68,251.70 259.20,249.18 261.72,251.70 259.20,254.22 256.68,251.70 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='256.68,250.60 259.20,248.08 261.72,250.60 259.20,253.12 256.68,250.60 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='326.37,260.48 328.89,257.96 331.41,260.48 328.89,263.00 326.37,260.48 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='326.37,261.26 328.89,258.74 331.41,261.26 328.89,263.78 326.37,261.26 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,123.15 52.44,131.53 55.81,142.21 57.09,145.87 61.50,157.00 66.38,167.13 67.19,168.61 72.87,177.84 78.56,185.28 82.64,189.77 84.25,191.38 89.94,196.46 95.63,200.78 101.32,204.51 107.01,207.79 112.70,210.72 115.16,211.90 118.39,213.38 124.08,215.81 129.77,218.07 135.46,220.19 141.15,222.19 146.83,224.09 152.52,225.90 158.21,227.63 163.90,229.29 169.59,230.90 175.28,232.44 180.97,233.93 186.66,235.37 189.50,236.08 192.35,236.77 198.04,238.12 203.73,239.43 209.42,240.70 215.11,241.93 220.79,243.12 226.48,244.27 232.17,245.40 237.86,246.48 243.55,247.54 249.24,248.56 254.93,249.55 259.20,250.28 260.62,250.52 266.31,251.45 272.00,252.36 277.69,253.24 283.38,254.09 289.07,254.92 294.76,255.72 300.44,256.50 306.13,257.26 311.82,257.99 317.51,258.71 323.20,259.40 328.89,260.07 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,123.69 52.52,119.53 47.72,119.53 50.12,123.69 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,123.06 52.52,118.90 47.72,118.90 50.12,123.06 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,138.12 54.84,133.96 50.04,133.96 52.44,138.12 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,143.45 54.84,139.29 50.04,139.29 52.44,143.45 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,137.80 59.49,133.64 54.69,133.64 57.09,137.80 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,144.39 59.49,140.23 54.69,140.23 57.09,144.39 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,151.29 68.78,147.13 63.98,147.13 66.38,151.29 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,150.66 68.78,146.50 63.98,146.50 66.38,150.66 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,172.14 85.04,167.99 80.24,167.99 82.64,172.14 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,186.88 85.04,182.73 80.24,182.73 82.64,186.88 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,191.27 117.56,187.12 112.76,187.12 115.16,191.27 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,204.29 117.56,200.13 112.76,200.13 115.16,204.29 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,228.75 191.90,224.60 187.10,224.60 189.50,228.75 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,230.79 191.90,226.63 187.10,226.63 189.50,230.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,240.36 261.60,236.20 256.80,236.20 259.20,240.36 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,241.30 261.60,237.14 256.80,237.14 259.20,241.30 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,250.08 331.29,245.92 326.49,245.92 328.89,250.08 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,253.37 331.29,249.22 326.49,249.22 328.89,253.37 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,125.48 52.44,129.93 55.81,136.01 57.09,138.22 61.50,145.40 66.38,152.67 67.19,153.81 72.87,161.33 78.56,168.08 82.64,172.50 84.25,174.16 89.94,179.63 95.63,184.57 101.32,189.04 107.01,193.10 112.70,196.80 115.16,198.30 118.39,200.17 124.08,203.26 129.77,206.09 135.46,208.70 141.15,211.10 146.83,213.33 152.52,215.41 158.21,217.34 163.90,219.15 169.59,220.84 175.28,222.43 180.97,223.94 186.66,225.36 189.50,226.04 192.35,226.71 198.04,227.99 203.73,229.22 209.42,230.39 215.11,231.51 220.79,232.58 226.48,233.62 232.17,234.61 237.86,235.58 243.55,236.51 249.24,237.41 254.93,238.28 259.20,238.92 260.62,239.13 266.31,239.95 272.00,240.76 277.69,241.54 283.38,242.30 289.07,243.04 294.76,243.76 300.44,244.47 306.13,245.16 311.82,245.84 317.51,246.50 323.20,247.15 328.89,247.78 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='48.34' y='130.27' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='133.83' x2='51.90' y2='130.27' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='130.27' x2='51.90' y2='133.83' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='48.34' y='115.22' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='118.78' x2='51.90' y2='115.22' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='115.22' x2='51.90' y2='118.78' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='50.66' y='127.13' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='130.70' x2='54.22' y2='127.13' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='127.13' x2='54.22' y2='130.70' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='50.66' y='137.33' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='140.89' x2='54.22' y2='137.33' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='137.33' x2='54.22' y2='140.89' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='55.30' y='159.59' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='163.16' x2='58.87' y2='159.59' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='159.59' x2='58.87' y2='163.16' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='55.30' y='142.97' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='146.53' x2='58.87' y2='142.97' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='142.97' x2='58.87' y2='146.53' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='64.60' y='173.86' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='177.43' x2='68.16' y2='173.86' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='173.86' x2='68.16' y2='177.43' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='64.60' y='154.42' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='157.98' x2='68.16' y2='154.42' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='154.42' x2='68.16' y2='157.98' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='80.86' y='186.88' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='190.44' x2='84.42' y2='186.88' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='186.88' x2='84.42' y2='190.44' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='80.86' y='191.58' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='195.15' x2='84.42' y2='191.58' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='191.58' x2='84.42' y2='195.15' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='113.38' y='225.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='229.49' x2='116.95' y2='225.92' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='225.92' x2='116.95' y2='229.49' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='113.38' y='224.20' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='227.76' x2='116.95' y2='224.20' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='224.20' x2='116.95' y2='227.76' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='187.72' y='255.41' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='258.97' x2='191.29' y2='255.41' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='255.41' x2='191.29' y2='258.97' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='187.72' y='255.88' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='259.44' x2='191.29' y2='255.88' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='255.88' x2='191.29' y2='259.44' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='257.42' y='264.03' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='267.59' x2='260.98' y2='264.03' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='264.03' x2='260.98' y2='267.59' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='257.42' y='265.28' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='268.85' x2='260.98' y2='265.28' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='265.28' x2='260.98' y2='268.85' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='327.11' y='270.62' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='274.18' x2='330.67' y2='270.62' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='270.62' x2='330.67' y2='274.18' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='327.11' y='267.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='271.51' x2='330.67' y2='267.95' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='267.95' x2='330.67' y2='271.51' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,124.75 52.44,132.21 55.81,142.16 57.09,145.70 61.50,156.94 66.38,167.87 67.19,169.53 72.87,180.30 78.56,189.56 82.64,195.40 84.25,197.55 89.94,204.48 95.63,210.53 101.32,215.83 107.01,220.50 112.70,224.65 115.16,226.30 118.39,228.35 124.08,231.66 129.77,234.65 135.46,237.36 141.15,239.83 146.83,242.09 152.52,244.17 158.21,246.10 163.90,247.88 169.59,249.54 175.28,251.09 180.97,252.54 186.66,253.91 189.50,254.56 192.35,255.20 198.04,256.41 203.73,257.55 209.42,258.64 215.11,259.67 220.79,260.65 226.48,261.58 232.17,262.47 237.86,263.31 243.55,264.11 249.24,264.88 254.93,265.61 259.20,266.14 260.62,266.31 266.31,266.98 272.00,267.62 277.69,268.23 283.38,268.81 289.07,269.37 294.76,269.90 300.44,270.41 306.13,270.90 311.82,271.37 317.51,271.82 323.20,272.25 328.89,272.66 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='131.48' x2='51.90' y2='127.92' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='127.92' x2='51.90' y2='131.48' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='47.60' y1='129.70' x2='52.64' y2='129.70' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='132.22' x2='50.12' y2='127.18' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='115.17' x2='51.90' y2='111.61' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='111.61' x2='51.90' y2='115.17' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='47.60' y1='113.39' x2='52.64' y2='113.39' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='115.91' x2='50.12' y2='110.87' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='129.76' x2='54.22' y2='126.19' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='126.19' x2='54.22' y2='129.76' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='49.92' y1='127.97' x2='54.96' y2='127.97' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='130.49' x2='52.44' y2='125.45' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='145.59' x2='54.22' y2='142.03' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='142.03' x2='54.22' y2='145.59' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='49.92' y1='143.81' x2='54.96' y2='143.81' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='146.33' x2='52.44' y2='141.29' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='149.36' x2='58.87' y2='145.79' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='145.79' x2='58.87' y2='149.36' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='54.57' y1='147.58' x2='59.61' y2='147.58' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='150.10' x2='57.09' y2='145.06' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='165.51' x2='58.87' y2='161.95' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='161.95' x2='58.87' y2='165.51' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='54.57' y1='163.73' x2='59.61' y2='163.73' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='166.25' x2='57.09' y2='161.21' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='173.98' x2='68.16' y2='170.41' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='170.41' x2='68.16' y2='173.98' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='63.86' y1='172.19' x2='68.90' y2='172.19' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='174.72' x2='66.38' y2='169.67' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='179.15' x2='68.16' y2='175.59' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='175.59' x2='68.16' y2='179.15' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='63.86' y1='177.37' x2='68.90' y2='177.37' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='179.89' x2='66.38' y2='174.85' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='209.73' x2='84.42' y2='206.17' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='206.17' x2='84.42' y2='209.73' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.12' y1='207.95' x2='85.16' y2='207.95' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='210.47' x2='82.64' y2='205.43' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='204.24' x2='84.42' y2='200.68' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='200.68' x2='84.42' y2='204.24' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.12' y1='202.46' x2='85.16' y2='202.46' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='204.98' x2='82.64' y2='199.94' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='228.39' x2='116.95' y2='224.83' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='224.83' x2='116.95' y2='228.39' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='112.64' y1='226.61' x2='117.68' y2='226.61' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='229.13' x2='115.16' y2='224.09' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='225.72' x2='116.95' y2='222.16' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='222.16' x2='116.95' y2='225.72' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='112.64' y1='223.94' x2='117.68' y2='223.94' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='226.46' x2='115.16' y2='221.42' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='247.05' x2='191.29' y2='243.49' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='243.49' x2='191.29' y2='247.05' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='186.98' y1='245.27' x2='192.02' y2='245.27' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='247.79' x2='189.50' y2='242.75' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='246.11' x2='191.29' y2='242.55' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='242.55' x2='191.29' y2='246.11' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='186.98' y1='244.33' x2='192.02' y2='244.33' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='246.85' x2='189.50' y2='241.81' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='255.52' x2='260.98' y2='251.96' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='251.96' x2='260.98' y2='255.52' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='256.68' y1='253.74' x2='261.72' y2='253.74' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='256.26' x2='259.20' y2='251.22' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='255.83' x2='260.98' y2='252.27' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='252.27' x2='260.98' y2='255.83' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='256.68' y1='254.05' x2='261.72' y2='254.05' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='256.57' x2='259.20' y2='251.53' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='263.67' x2='330.67' y2='260.11' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='260.11' x2='330.67' y2='263.67' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='326.37' y1='261.89' x2='331.41' y2='261.89' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='264.41' x2='328.89' y2='259.37' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='262.73' x2='330.67' y2='259.17' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='259.17' x2='330.67' y2='262.73' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='326.37' y1='260.95' x2='331.41' y2='260.95' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='263.47' x2='328.89' y2='258.43' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,124.49 52.44,134.61 55.81,147.49 57.09,151.90 61.50,165.28 66.38,177.36 67.19,179.12 72.87,189.95 78.56,198.51 82.64,203.54 84.25,205.33 89.94,210.83 95.63,215.32 101.32,219.05 107.01,222.18 112.70,224.86 115.16,225.91 118.39,227.19 124.08,229.24 129.77,231.08 135.46,232.75 141.15,234.29 146.83,235.72 152.52,237.05 158.21,238.31 163.90,239.51 169.59,240.66 175.28,241.76 180.97,242.82 186.66,243.84 189.50,244.34 192.35,244.83 198.04,245.79 203.73,246.72 209.42,247.62 215.11,248.50 220.79,249.36 226.48,250.19 232.17,251.00 237.86,251.78 243.55,252.55 249.24,253.30 254.93,254.02 259.20,254.56 260.62,254.73 266.31,255.42 272.00,256.10 277.69,256.75 283.38,257.39 289.07,258.01 294.76,258.62 300.44,259.21 306.13,259.79 311.82,260.35 317.51,260.90 323.20,261.43 328.89,261.95 ' style='stroke-width: 0.75; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='47.60' y1='109.16' x2='52.64' y2='109.16' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='111.68' x2='50.12' y2='106.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='47.60,109.16 50.12,106.64 52.64,109.16 50.12,111.68 47.60,109.16 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='47.60' y1='139.11' x2='52.64' y2='139.11' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='141.63' x2='50.12' y2='136.59' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='47.60,139.11 50.12,136.59 52.64,139.11 50.12,141.63 47.60,139.11 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='49.92' y1='127.19' x2='54.96' y2='127.19' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='129.71' x2='52.44' y2='124.67' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='49.92,127.19 52.44,124.67 54.96,127.19 52.44,129.71 49.92,127.19 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='49.92' y1='118.25' x2='54.96' y2='118.25' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='120.77' x2='52.44' y2='115.73' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='49.92,118.25 52.44,115.73 54.96,118.25 52.44,120.77 49.92,118.25 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='54.57' y1='149.61' x2='59.61' y2='149.61' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='152.13' x2='57.09' y2='147.09' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='54.57,149.61 57.09,147.09 59.61,149.61 57.09,152.13 54.57,149.61 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='54.57' y1='140.52' x2='59.61' y2='140.52' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='143.04' x2='57.09' y2='138.00' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='54.57,140.52 57.09,138.00 59.61,140.52 57.09,143.04 54.57,140.52 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='63.86' y1='158.55' x2='68.90' y2='158.55' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='161.07' x2='66.38' y2='156.03' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='63.86,158.55 66.38,156.03 68.90,158.55 66.38,161.07 63.86,158.55 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='63.86' y1='164.98' x2='68.90' y2='164.98' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='167.50' x2='66.38' y2='162.46' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='63.86,164.98 66.38,162.46 68.90,164.98 66.38,167.50 63.86,164.98 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.12' y1='192.27' x2='85.16' y2='192.27' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='194.79' x2='82.64' y2='189.75' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='80.12,192.27 82.64,189.75 85.16,192.27 82.64,194.79 80.12,192.27 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.12' y1='183.80' x2='85.16' y2='183.80' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='186.32' x2='82.64' y2='181.28' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='80.12,183.80 82.64,181.28 85.16,183.80 82.64,186.32 80.12,183.80 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='112.64' y1='215.32' x2='117.68' y2='215.32' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='217.84' x2='115.16' y2='212.80' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='112.64,215.32 115.16,212.80 117.68,215.32 115.16,217.84 112.64,215.32 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='112.64' y1='211.08' x2='117.68' y2='211.08' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='213.60' x2='115.16' y2='208.56' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='112.64,211.08 115.16,208.56 117.68,211.08 115.16,213.60 112.64,211.08 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='186.98' y1='244.17' x2='192.02' y2='244.17' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='246.69' x2='189.50' y2='241.65' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='186.98,244.17 189.50,241.65 192.02,244.17 189.50,246.69 186.98,244.17 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='186.98' y1='242.76' x2='192.02' y2='242.76' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='245.28' x2='189.50' y2='240.24' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='186.98,242.76 189.50,240.24 192.02,242.76 189.50,245.28 186.98,242.76 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='256.68' y1='253.74' x2='261.72' y2='253.74' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='256.26' x2='259.20' y2='251.22' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='256.68,253.74 259.20,251.22 261.72,253.74 259.20,256.26 256.68,253.74 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='256.68' y1='258.28' x2='261.72' y2='258.28' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='260.80' x2='259.20' y2='255.76' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='256.68,258.28 259.20,255.76 261.72,258.28 259.20,260.80 256.68,258.28 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='326.37' y1='268.16' x2='331.41' y2='268.16' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='270.68' x2='328.89' y2='265.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='326.37,268.16 328.89,265.64 331.41,268.16 328.89,270.68 326.37,268.16 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='326.37' y1='262.36' x2='331.41' y2='262.36' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='264.88' x2='328.89' y2='259.84' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='326.37,262.36 328.89,259.84 331.41,262.36 328.89,264.88 326.37,262.36 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,122.04 52.44,128.59 55.81,137.38 57.09,140.53 61.50,150.60 66.38,160.50 67.19,162.02 72.87,171.92 78.56,180.54 82.64,186.03 84.25,188.06 89.94,194.66 95.63,200.47 101.32,205.61 107.01,210.18 112.70,214.26 115.16,215.90 118.39,217.93 124.08,221.23 129.77,224.23 135.46,226.96 141.15,229.45 146.83,231.75 152.52,233.87 158.21,235.84 163.90,237.68 169.59,239.40 175.28,241.01 180.97,242.53 186.66,243.96 189.50,244.65 192.35,245.32 198.04,246.61 203.73,247.84 209.42,249.01 215.11,250.13 220.79,251.20 226.48,252.22 232.17,253.21 237.86,254.15 243.55,255.06 249.24,255.94 254.93,256.78 259.20,257.40 260.62,257.60 266.31,258.38 272.00,259.14 277.69,259.87 283.38,260.58 289.07,261.26 294.76,261.92 300.44,262.56 306.13,263.17 311.82,263.77 317.51,264.35 323.20,264.91 328.89,265.45 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='50.12' cy='122.80' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='122.80' x2='51.90' y2='122.80' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='124.58' x2='50.12' y2='121.02' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='50.12' cy='123.11' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='123.11' x2='51.90' y2='123.11' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='124.89' x2='50.12' y2='121.33' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='52.44' cy='126.09' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='126.09' x2='54.22' y2='126.09' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='127.87' x2='52.44' y2='124.31' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='52.44' cy='122.80' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='122.80' x2='54.22' y2='122.80' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='124.58' x2='52.44' y2='121.02' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='57.09' cy='136.28' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='136.28' x2='58.87' y2='136.28' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='138.07' x2='57.09' y2='134.50' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='57.09' cy='139.11' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='139.11' x2='58.87' y2='139.11' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='140.89' x2='57.09' y2='137.33' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='66.38' cy='159.81' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='159.81' x2='68.16' y2='159.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='161.59' x2='66.38' y2='158.02' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='66.38' cy='147.58' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='147.58' x2='68.16' y2='147.58' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='149.36' x2='66.38' y2='145.79' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='82.64' cy='165.14' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='165.14' x2='84.42' y2='165.14' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='166.92' x2='82.64' y2='163.36' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='82.64' cy='165.61' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='165.61' x2='84.42' y2='165.61' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='167.39' x2='82.64' y2='163.83' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='115.16' cy='202.62' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='202.62' x2='116.95' y2='202.62' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='204.40' x2='115.16' y2='200.83' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='115.16' cy='191.17' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='191.17' x2='116.95' y2='191.17' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='192.95' x2='115.16' y2='189.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='189.50' cy='235.39' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='235.39' x2='191.29' y2='235.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='237.17' x2='189.50' y2='233.61' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='189.50' cy='235.23' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='235.23' x2='191.29' y2='235.23' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='237.02' x2='189.50' y2='233.45' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='259.20' cy='245.27' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='245.27' x2='260.98' y2='245.27' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='247.05' x2='259.20' y2='243.49' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='259.20' cy='249.66' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='249.66' x2='260.98' y2='249.66' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='251.44' x2='259.20' y2='247.88' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='328.89' cy='261.73' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='261.73' x2='330.67' y2='261.73' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='263.52' x2='328.89' y2='259.95' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='328.89' cy='259.38' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='259.38' x2='330.67' y2='259.38' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='261.16' x2='328.89' y2='257.60' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,123.72 52.44,127.74 55.81,133.32 57.09,135.37 61.50,142.14 66.38,149.14 67.19,150.25 72.87,157.71 78.56,164.59 82.64,169.19 84.25,170.94 89.94,176.80 95.63,182.22 101.32,187.25 107.01,191.90 112.70,196.23 115.16,198.01 118.39,200.26 124.08,204.00 129.77,207.50 135.46,210.76 141.15,213.82 146.83,216.68 152.52,219.36 158.21,221.88 163.90,224.26 169.59,226.49 175.28,228.60 180.97,230.59 186.66,232.48 189.50,233.38 192.35,234.26 198.04,235.95 203.73,237.56 209.42,239.09 215.11,240.55 220.79,241.94 226.48,243.26 232.17,244.53 237.86,245.74 243.55,246.90 249.24,248.01 254.93,249.07 259.20,249.84 260.62,250.09 266.31,251.07 272.00,252.02 277.69,252.92 283.38,253.80 289.07,254.64 294.76,255.45 300.44,256.23 306.13,256.99 311.82,257.72 317.51,258.42 323.20,259.10 328.89,259.76 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,131.06 52.52,126.21 47.72,126.21 50.12,131.06 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,125.52 52.52,130.37 47.72,130.37 50.12,125.52 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,129.65 52.52,124.80 47.72,124.80 50.12,129.65 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,124.10 52.52,128.95 47.72,128.95 50.12,124.10 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,135.45 54.84,130.60 50.04,130.60 52.44,135.45 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,129.91 54.84,134.76 50.04,134.76 52.44,129.91 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,117.57 54.84,112.72 50.04,112.72 52.44,117.57 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,112.03 54.84,116.88 50.04,116.88 52.44,112.03 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,140.47 59.49,135.62 54.69,135.62 57.09,140.47 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,134.92 59.49,139.77 54.69,139.77 57.09,134.92 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,144.54 59.49,139.69 54.69,139.69 57.09,144.54 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,139.00 59.49,143.85 54.69,143.85 57.09,139.00 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,142.66 68.78,137.81 63.98,137.81 66.38,142.66 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,137.12 68.78,141.97 63.98,141.97 66.38,137.12 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,157.87 68.78,153.02 63.98,153.02 66.38,157.87 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,152.33 68.78,157.18 63.98,157.18 66.38,152.33 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,168.54 85.04,163.69 80.24,163.69 82.64,168.54 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,162.99 85.04,167.84 80.24,167.84 82.64,162.99 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,172.77 85.04,167.92 80.24,167.92 82.64,172.77 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,167.23 85.04,172.08 80.24,172.08 82.64,167.23 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,188.30 117.56,183.45 112.76,183.45 115.16,188.30 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,182.75 117.56,187.60 112.76,187.60 115.16,182.75 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,183.59 117.56,178.74 112.76,178.74 115.16,183.59 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,178.05 117.56,182.90 112.76,182.90 115.16,178.05 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,224.21 191.90,219.36 187.10,219.36 189.50,224.21 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,218.66 191.90,223.51 187.10,223.51 189.50,218.66 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,225.77 191.90,220.92 187.10,220.92 189.50,225.77 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,220.23 191.90,225.08 187.10,225.08 189.50,220.23 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,244.12 261.60,239.27 256.80,239.27 259.20,244.12 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,238.58 261.60,243.43 256.80,243.43 259.20,238.58 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,237.69 261.60,232.84 256.80,232.84 259.20,237.69 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,232.15 261.60,237.00 256.80,237.00 259.20,232.15 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,252.12 331.29,247.27 326.49,247.27 328.89,252.12 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,246.58 331.29,251.42 326.49,251.42 328.89,246.58 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,251.96 331.29,247.11 326.49,247.11 328.89,251.96 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,246.42 331.29,251.27 326.49,251.27 328.89,246.42 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,125.59 52.44,128.88 55.81,133.47 57.09,135.16 61.50,140.77 66.38,146.62 67.19,147.55 72.87,153.84 78.56,159.69 82.64,163.63 84.25,165.13 89.94,170.20 95.63,174.93 101.32,179.34 107.01,183.46 112.70,187.32 115.16,188.91 118.39,190.93 124.08,194.31 129.77,197.49 135.46,200.48 141.15,203.29 146.83,205.94 152.52,208.44 158.21,210.81 163.90,213.04 169.59,215.16 175.28,217.16 180.97,219.07 186.66,220.88 189.50,221.76 192.35,222.61 198.04,224.25 203.73,225.82 209.42,227.32 215.11,228.76 220.79,230.13 226.48,231.45 232.17,232.71 237.86,233.93 243.55,235.10 249.24,236.22 254.93,237.30 259.20,238.09 260.62,238.35 266.31,239.36 272.00,240.34 277.69,241.28 283.38,242.19 289.07,243.08 294.76,243.94 300.44,244.77 306.13,245.57 311.82,246.36 317.51,247.12 323.20,247.86 328.89,248.58 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='137.70' x2='51.90' y2='137.70' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='139.48' x2='50.12' y2='135.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='48.34' y='135.91' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='123.11' x2='51.90' y2='123.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.12' y1='124.89' x2='50.12' y2='121.33' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='48.34' y='121.33' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='127.50' x2='54.22' y2='127.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='129.29' x2='52.44' y2='125.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='50.66' y='125.72' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='132.99' x2='54.22' y2='132.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='52.44' y1='134.77' x2='52.44' y2='131.21' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='50.66' y='131.21' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='120.76' x2='58.87' y2='120.76' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='122.54' x2='57.09' y2='118.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='55.30' y='118.98' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='139.89' x2='58.87' y2='139.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='57.09' y1='141.67' x2='57.09' y2='138.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='55.30' y='138.11' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='160.28' x2='68.16' y2='160.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='162.06' x2='66.38' y2='158.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='64.60' y='158.50' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='145.54' x2='68.16' y2='145.54' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='66.38' y1='147.32' x2='66.38' y2='143.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='64.60' y='143.75' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='174.23' x2='84.42' y2='174.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='176.02' x2='82.64' y2='172.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='80.86' y='172.45' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='171.57' x2='84.42' y2='171.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='82.64' y1='173.35' x2='82.64' y2='169.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='80.86' y='169.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='201.52' x2='116.95' y2='201.52' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='203.30' x2='115.16' y2='199.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='113.38' y='199.74' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='199.64' x2='116.95' y2='199.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='115.16' y1='201.42' x2='115.16' y2='197.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='113.38' y='197.86' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='236.17' x2='191.29' y2='236.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='237.96' x2='189.50' y2='234.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='187.72' y='234.39' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='236.49' x2='191.29' y2='236.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='189.50' y1='238.27' x2='189.50' y2='234.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='187.72' y='234.71' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='253.74' x2='260.98' y2='253.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='255.52' x2='259.20' y2='251.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='257.42' y='251.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='249.19' x2='260.98' y2='249.19' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='259.20' y1='250.97' x2='259.20' y2='247.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='257.42' y='247.41' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='260.32' x2='330.67' y2='260.32' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='262.11' x2='328.89' y2='258.54' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='327.11' y='258.54' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='261.26' x2='330.67' y2='261.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='328.89' y1='263.05' x2='328.89' y2='259.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='327.11' y='259.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,125.61 52.44,129.60 55.81,135.15 57.09,137.19 61.50,143.94 66.38,150.93 67.19,152.04 72.87,159.51 78.56,166.41 82.64,171.03 84.25,172.79 89.94,178.69 95.63,184.15 101.32,189.22 107.01,193.93 112.70,198.30 115.16,200.10 118.39,202.37 124.08,206.17 129.77,209.70 135.46,213.01 141.15,216.09 146.83,218.98 152.52,221.69 158.21,224.24 163.90,226.63 169.59,228.87 175.28,230.99 180.97,232.99 186.66,234.88 189.50,235.78 192.35,236.66 198.04,238.35 203.73,239.95 209.42,241.47 215.11,242.91 220.79,244.28 226.48,245.58 232.17,246.83 237.86,248.01 243.55,249.15 249.24,250.23 254.93,251.27 259.20,252.01 260.62,252.26 266.31,253.21 272.00,254.12 277.69,254.99 283.38,255.83 289.07,256.64 294.76,257.42 300.44,258.17 306.13,258.89 311.82,259.58 317.51,260.25 323.20,260.90 328.89,261.52 ' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='50.12' cy='125.31' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='127.09' x2='51.90' y2='123.53' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='123.53' x2='51.90' y2='127.09' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='50.12' cy='128.60' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='130.38' x2='51.90' y2='126.82' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='48.34' y1='126.82' x2='51.90' y2='130.38' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='52.44' cy='126.88' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='128.66' x2='54.22' y2='125.09' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='125.09' x2='54.22' y2='128.66' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='52.44' cy='115.74' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='117.52' x2='54.22' y2='113.96' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='50.66' y1='113.96' x2='54.22' y2='117.52' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='57.09' cy='138.64' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='140.42' x2='58.87' y2='136.86' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='136.86' x2='58.87' y2='140.42' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='57.09' cy='126.41' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='128.19' x2='58.87' y2='124.62' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='55.30' y1='124.62' x2='58.87' y2='128.19' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='66.38' cy='152.91' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='154.69' x2='68.16' y2='151.13' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='151.13' x2='68.16' y2='154.69' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='66.38' cy='150.08' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='151.87' x2='68.16' y2='148.30' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='64.60' y1='148.30' x2='68.16' y2='151.87' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='82.64' cy='173.61' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='175.39' x2='84.42' y2='171.82' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='171.82' x2='84.42' y2='175.39' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='82.64' cy='180.19' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='181.97' x2='84.42' y2='178.41' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='80.86' y1='178.41' x2='84.42' y2='181.97' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='115.16' cy='205.75' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='207.53' x2='116.95' y2='203.97' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='203.97' x2='116.95' y2='207.53' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='115.16' cy='204.03' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='205.81' x2='116.95' y2='202.25' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='113.38' y1='202.25' x2='116.95' y2='205.81' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='189.50' cy='243.86' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='245.64' x2='191.29' y2='242.08' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='242.08' x2='191.29' y2='245.64' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='189.50' cy='239.94' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='241.72' x2='191.29' y2='238.16' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='187.72' y1='238.16' x2='191.29' y2='241.72' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='259.20' cy='258.44' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='260.22' x2='260.98' y2='256.66' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='256.66' x2='260.98' y2='260.22' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='259.20' cy='252.17' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='253.95' x2='260.98' y2='250.39' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='257.42' y1='250.39' x2='260.98' y2='253.95' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='328.89' cy='262.52' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='264.30' x2='330.67' y2='260.74' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='260.74' x2='330.67' y2='264.30' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<circle cx='328.89' cy='261.11' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='262.89' x2='330.67' y2='259.33' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<line x1='327.11' y1='259.33' x2='330.67' y2='262.89' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,122.26 52.44,126.96 55.81,133.45 57.09,135.82 61.50,143.62 66.38,151.61 67.19,152.87 72.87,161.29 78.56,168.97 82.64,174.07 84.25,175.99 89.94,182.41 95.63,188.28 101.32,193.67 107.01,198.62 112.70,203.17 115.16,205.03 118.39,207.36 124.08,211.23 129.77,214.81 135.46,218.12 141.15,221.19 146.83,224.04 152.52,226.70 158.21,229.17 163.90,231.49 169.59,233.65 175.28,235.67 180.97,237.58 186.66,239.36 189.50,240.22 192.35,241.05 198.04,242.64 203.73,244.14 209.42,245.56 215.11,246.90 220.79,248.18 226.48,249.39 232.17,250.54 237.86,251.64 243.55,252.68 249.24,253.68 254.93,254.64 259.20,255.33 260.62,255.55 266.31,256.43 272.00,257.27 277.69,258.07 283.38,258.84 289.07,259.58 294.76,260.30 300.44,260.98 306.13,261.64 311.82,262.28 317.51,262.89 323.20,263.49 328.89,264.06 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,116.00 51.90,119.56 48.34,119.56 50.12,116.00 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='48.34' y='116.00' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,122.43 51.90,125.99 48.34,125.99 50.12,122.43 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='48.34' y='122.43' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,126.35 54.22,129.91 50.66,129.91 52.44,126.35 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='50.66' y='126.35' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='52.44,116.31 54.22,119.88 50.66,119.88 52.44,116.31 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='50.66' y='116.31' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,141.56 58.87,145.12 55.30,145.12 57.09,141.56 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='55.30' y='141.56' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='57.09,145.64 58.87,149.20 55.30,149.20 57.09,145.64 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='55.30' y='145.64' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,156.61 68.16,160.18 64.60,160.18 66.38,156.61 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='64.60' y='156.61' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='66.38,155.67 68.16,159.24 64.60,159.24 66.38,155.67 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='64.60' y='155.67' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,186.72 84.42,190.29 80.86,190.29 82.64,186.72 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='80.86' y='186.72' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='82.64,177.94 84.42,181.50 80.86,181.50 82.64,177.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='80.86' y='177.94' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,207.11 116.95,210.67 113.38,210.67 115.16,207.11 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='113.38' y='207.11' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='115.16,204.28 116.95,207.85 113.38,207.85 115.16,204.28 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='113.38' y='204.28' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,238.94 191.29,242.50 187.72,242.50 189.50,238.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='187.72' y='238.94' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='189.50,239.72 191.29,243.29 187.72,243.29 189.50,239.72 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='187.72' y='239.72' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,253.05 260.98,256.62 257.42,256.62 259.20,253.05 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='257.42' y='253.05' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='259.20,249.76 260.98,253.32 257.42,253.32 259.20,249.76 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='257.42' y='249.76' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,262.15 330.67,265.71 327.11,265.71 328.89,262.15 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='327.11' y='262.15' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='328.89,261.83 330.67,265.40 327.11,265.40 328.89,261.83 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<rect x='327.11' y='261.83' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,123.07 52.44,129.06 55.81,137.14 57.09,140.04 61.50,149.34 66.38,158.54 67.19,159.96 72.87,169.22 78.56,177.33 82.64,182.53 84.25,184.46 89.94,190.76 95.63,196.34 101.32,201.30 107.01,205.74 112.70,209.73 115.16,211.34 118.39,213.33 124.08,216.60 129.77,219.58 135.46,222.30 141.15,224.81 146.83,227.12 152.52,229.27 158.21,231.27 163.90,233.14 169.59,234.90 175.28,236.56 180.97,238.12 186.66,239.60 189.50,240.32 192.35,241.01 198.04,242.35 203.73,243.63 209.42,244.86 215.11,246.03 220.79,247.15 226.48,248.23 232.17,249.27 237.86,250.27 243.55,251.24 249.24,252.17 254.93,253.07 259.20,253.72 260.62,253.94 266.31,254.78 272.00,255.59 277.69,256.37 283.38,257.13 289.07,257.87 294.76,258.59 300.44,259.28 306.13,259.95 311.82,260.60 317.51,261.23 323.20,261.84 328.89,262.43 ' style='stroke-width: 0.75; stroke: #F5C710; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='48.34,118.94 51.90,118.94 51.90,115.37 48.34,115.37 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='48.34,117.21 51.90,117.21 51.90,113.65 48.34,113.65 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='50.66,128.19 54.22,128.19 54.22,124.62 50.66,124.62 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='50.66,130.85 54.22,130.85 54.22,127.29 50.66,127.29 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='55.30,146.38 58.87,146.38 58.87,142.81 55.30,142.81 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='55.30,140.42 58.87,140.42 58.87,136.86 55.30,136.86 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='64.60,162.53 68.16,162.53 68.16,158.97 64.60,158.97 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='64.60,164.57 68.16,164.57 68.16,161.00 64.60,161.00 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='80.86,186.37 84.42,186.37 84.42,182.80 80.86,182.80 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='80.86,193.11 84.42,193.11 84.42,189.54 80.86,189.54 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='113.38,213.81 116.95,213.81 116.95,210.24 113.38,210.24 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='113.38,210.36 116.95,210.36 116.95,206.79 113.38,206.79 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='187.72,237.96 191.29,237.96 191.29,234.39 187.72,234.39 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='187.72,238.27 191.29,238.27 191.29,234.71 187.72,234.71 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='257.42,250.81 260.98,250.81 260.98,247.25 257.42,247.25 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='257.42,249.40 260.98,249.40 260.98,245.84 257.42,245.84 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='327.11,259.91 330.67,259.91 330.67,256.35 327.11,256.35 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polygon points='327.11,255.05 330.67,255.05 330.67,251.48 327.11,251.48 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> -<polyline points='50.12,120.90 52.44,128.98 55.81,139.33 57.09,142.89 61.50,153.78 66.38,163.77 67.19,165.24 72.87,174.44 78.56,181.92 82.64,186.47 84.25,188.11 89.94,193.32 95.63,197.76 101.32,201.62 107.01,205.03 112.70,208.08 115.16,209.32 118.39,210.86 124.08,213.41 129.77,215.78 135.46,217.99 141.15,220.09 146.83,222.07 152.52,223.97 158.21,225.78 163.90,227.52 169.59,229.19 175.28,230.80 180.97,232.36 186.66,233.86 189.50,234.59 192.35,235.31 198.04,236.72 203.73,238.08 209.42,239.40 215.11,240.68 220.79,241.92 226.48,243.12 232.17,244.29 237.86,245.42 243.55,246.52 249.24,247.58 254.93,248.61 259.20,249.36 260.62,249.61 266.31,250.58 272.00,251.52 277.69,252.43 283.38,253.32 289.07,254.17 294.76,255.01 300.44,255.81 306.13,256.60 311.82,257.36 317.51,258.09 323.20,258.81 328.89,259.50 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4OC44OHwxMDIuMjQ=)' /> +<circle cx='50.12' cy='98.85' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='50.12' cy='113.38' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='52.44' cy='112.20' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='52.44' cy='125.71' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='57.09' cy='140.91' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='57.09' cy='113.89' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='66.38' cy='145.30' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='66.38' cy='151.38' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='82.64' cy='160.34' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='82.64' cy='169.80' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='115.16' cy='191.92' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='115.16' cy='188.38' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='189.50' cy='221.31' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='189.50' cy='221.15' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='259.20' cy='238.37' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='259.20' cy='238.88' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='328.89' cy='245.13' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='328.89' cy='246.65' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,108.46 52.44,114.52 55.81,122.63 57.09,125.52 61.50,134.73 66.38,143.73 67.19,145.10 72.87,154.04 78.56,161.77 82.64,166.69 84.25,168.51 89.94,174.41 95.63,179.60 101.32,184.20 107.01,188.31 112.70,192.01 115.16,193.49 118.39,195.34 124.08,198.38 129.77,201.17 135.46,203.74 141.15,206.12 146.83,208.33 152.52,210.41 158.21,212.37 163.90,214.22 169.59,215.98 175.28,217.66 180.97,219.26 186.66,220.79 189.50,221.54 192.35,222.26 198.04,223.68 203.73,225.05 209.42,226.37 215.11,227.65 220.79,228.88 226.48,230.08 232.17,231.25 237.86,232.38 243.55,233.47 249.24,234.54 254.93,235.58 259.20,236.34 260.62,236.59 266.31,237.57 272.00,238.53 277.69,239.46 283.38,240.37 289.07,241.26 294.76,242.12 300.44,242.96 306.13,243.78 311.82,244.58 317.51,245.35 323.20,246.11 328.89,246.85 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,102.16 52.52,106.32 47.72,106.32 50.12,102.16 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,105.03 52.52,109.19 47.72,109.19 50.12,105.03 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,112.97 54.84,117.13 50.04,117.13 52.44,112.97 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,111.11 54.84,115.27 50.04,115.27 52.44,111.11 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,120.57 59.49,124.73 54.69,124.73 57.09,120.57 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,124.97 59.49,129.12 54.69,129.12 57.09,124.97 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,125.13 68.78,129.29 63.98,129.29 66.38,125.13 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,135.44 68.78,139.59 63.98,139.59 66.38,135.44 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,154.86 85.04,159.02 80.24,159.02 82.64,154.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,146.42 85.04,150.57 80.24,150.57 82.64,146.42 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,190.67 117.56,194.83 112.76,194.83 115.16,190.67 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,193.88 117.56,198.04 112.76,198.04 115.16,193.88 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,222.93 191.90,227.09 187.10,227.09 189.50,222.93 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,218.37 191.90,222.53 187.10,222.53 189.50,218.37 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,229.35 261.60,233.51 256.80,233.51 259.20,229.35 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,231.55 261.60,235.71 256.80,235.71 259.20,231.55 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,240.16 331.29,244.32 326.49,244.32 328.89,240.16 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,243.37 331.29,247.53 326.49,247.53 328.89,243.37 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,107.34 52.44,112.12 55.81,118.70 57.09,121.10 61.50,128.96 66.38,136.97 67.19,138.22 72.87,146.60 78.56,154.19 82.64,159.19 84.25,161.07 89.94,167.32 95.63,173.00 101.32,178.18 107.01,182.90 112.70,187.23 115.16,188.98 118.39,191.18 124.08,194.82 129.77,198.16 135.46,201.24 141.15,204.09 146.83,206.72 152.52,209.17 158.21,211.44 163.90,213.56 169.59,215.54 175.28,217.39 180.97,219.13 186.66,220.77 189.50,221.56 192.35,222.32 198.04,223.78 203.73,225.16 209.42,226.48 215.11,227.73 220.79,228.92 226.48,230.06 232.17,231.15 237.86,232.19 243.55,233.19 249.24,234.16 254.93,235.08 259.20,235.76 260.62,235.98 266.31,236.84 272.00,237.68 277.69,238.49 283.38,239.27 289.07,240.04 294.76,240.77 300.44,241.49 306.13,242.19 311.82,242.87 317.51,243.53 323.20,244.18 328.89,244.81 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='47.60' y1='124.36' x2='52.64' y2='124.36' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='126.88' x2='50.12' y2='121.84' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='47.60' y1='110.17' x2='52.64' y2='110.17' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='112.69' x2='50.12' y2='107.65' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='49.92' y1='108.31' x2='54.96' y2='108.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='110.83' x2='52.44' y2='105.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='49.92' y1='109.33' x2='54.96' y2='109.33' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='111.85' x2='52.44' y2='106.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='54.57' y1='112.20' x2='59.61' y2='112.20' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='114.72' x2='57.09' y2='109.68' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='54.57' y1='123.85' x2='59.61' y2='123.85' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='126.37' x2='57.09' y2='121.33' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='63.86' y1='134.49' x2='68.90' y2='134.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='137.01' x2='66.38' y2='131.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='63.86' y1='136.18' x2='68.90' y2='136.18' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='138.70' x2='66.38' y2='133.66' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.12' y1='149.02' x2='85.16' y2='149.02' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='151.54' x2='82.64' y2='146.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.12' y1='161.35' x2='85.16' y2='161.35' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='163.87' x2='82.64' y2='158.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='112.64' y1='181.11' x2='117.68' y2='181.11' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='183.63' x2='115.16' y2='178.59' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='112.64' y1='184.32' x2='117.68' y2='184.32' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='186.84' x2='115.16' y2='181.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='186.98' y1='224.69' x2='192.02' y2='224.69' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='227.21' x2='189.50' y2='222.17' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='186.98' y1='228.07' x2='192.02' y2='228.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='230.59' x2='189.50' y2='225.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='256.68' y1='244.79' x2='261.72' y2='244.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='247.31' x2='259.20' y2='242.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='256.68' y1='244.79' x2='261.72' y2='244.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='247.31' x2='259.20' y2='242.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='326.37' y1='260.50' x2='331.41' y2='260.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='263.02' x2='328.89' y2='257.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='326.37' y1='256.45' x2='331.41' y2='256.45' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='258.97' x2='328.89' y2='253.93' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,108.31 52.44,112.24 55.81,117.72 57.09,119.75 61.50,126.50 66.38,133.56 67.19,134.68 72.87,142.32 78.56,149.45 82.64,154.27 84.25,156.12 89.94,162.35 95.63,168.18 101.32,173.65 107.01,178.76 112.70,183.56 115.16,185.55 118.39,188.07 124.08,192.30 129.77,196.27 135.46,200.01 141.15,203.53 146.83,206.84 152.52,209.96 158.21,212.91 163.90,215.69 169.59,218.32 175.28,220.80 180.97,223.15 186.66,225.37 189.50,226.44 192.35,227.48 198.04,229.48 203.73,231.38 209.42,233.18 215.11,234.89 220.79,236.51 226.48,238.06 232.17,239.53 237.86,240.93 243.55,242.27 249.24,243.55 254.93,244.76 259.20,245.64 260.62,245.93 266.31,247.04 272.00,248.10 277.69,249.11 283.38,250.09 289.07,251.02 294.76,251.91 300.44,252.76 306.13,253.58 311.82,254.37 317.51,255.12 323.20,255.85 328.89,256.54 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='106.38' x2='51.90' y2='102.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='102.81' x2='51.90' y2='106.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='104.86' x2='51.90' y2='101.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='101.29' x2='51.90' y2='104.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='103.51' x2='54.22' y2='99.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='99.94' x2='54.22' y2='103.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='125.30' x2='54.22' y2='121.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='121.73' x2='54.22' y2='125.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='126.98' x2='58.87' y2='123.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='123.42' x2='58.87' y2='126.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='127.15' x2='58.87' y2='123.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='123.59' x2='58.87' y2='127.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='132.22' x2='68.16' y2='128.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='128.66' x2='68.16' y2='132.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='148.94' x2='68.16' y2='145.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='145.38' x2='68.16' y2='148.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='162.29' x2='84.42' y2='158.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='158.72' x2='84.42' y2='162.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='152.66' x2='84.42' y2='149.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='149.10' x2='84.42' y2='152.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='190.67' x2='116.95' y2='187.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='187.10' x2='116.95' y2='190.67' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='193.20' x2='116.95' y2='189.63' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='189.63' x2='116.95' y2='193.20' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='231.04' x2='191.29' y2='227.47' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='227.47' x2='191.29' y2='231.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='230.87' x2='191.29' y2='227.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='227.30' x2='191.29' y2='230.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='250.63' x2='260.98' y2='247.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='247.07' x2='260.98' y2='250.63' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='251.14' x2='260.98' y2='247.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='247.57' x2='260.98' y2='251.14' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='262.28' x2='330.67' y2='258.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='258.72' x2='330.67' y2='262.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='263.64' x2='330.67' y2='260.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='260.07' x2='330.67' y2='263.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,107.41 52.44,111.79 55.81,117.89 57.09,120.13 61.50,127.58 66.38,135.31 67.19,136.54 72.87,144.84 78.56,152.53 82.64,157.70 84.25,159.67 89.94,166.29 95.63,172.44 101.32,178.17 107.01,183.49 112.70,188.46 115.16,190.50 118.39,193.09 124.08,197.41 129.77,201.44 135.46,205.22 141.15,208.75 146.83,212.07 152.52,215.17 158.21,218.09 163.90,220.83 169.59,223.41 175.28,225.83 180.97,228.12 186.66,230.28 189.50,231.31 192.35,232.31 198.04,234.23 203.73,236.05 209.42,237.77 215.11,239.40 220.79,240.95 226.48,242.42 232.17,243.81 237.86,245.13 243.55,246.39 249.24,247.59 254.93,248.73 259.20,249.54 260.62,249.81 266.31,250.85 272.00,251.83 277.69,252.78 283.38,253.68 289.07,254.54 294.76,255.36 300.44,256.14 306.13,256.90 311.82,257.62 317.51,258.31 323.20,258.97 328.89,259.60 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='47.60,94.97 50.12,92.45 52.64,94.97 50.12,97.49 47.60,94.97 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='47.60,94.46 50.12,91.94 52.64,94.46 50.12,96.98 47.60,94.46 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='49.92,115.91 52.44,113.39 54.96,115.91 52.44,118.43 49.92,115.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='49.92,129.43 52.44,126.91 54.96,129.43 52.44,131.95 49.92,129.43 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='54.57,128.41 57.09,125.89 59.61,128.41 57.09,130.93 54.57,128.41 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='54.57,127.91 57.09,125.39 59.61,127.91 57.09,130.43 54.57,127.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='63.86,149.70 66.38,147.18 68.90,149.70 66.38,152.22 63.86,149.70 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='63.86,154.09 66.38,151.57 68.90,154.09 66.38,156.61 63.86,154.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='80.12,180.44 82.64,177.92 85.16,180.44 82.64,182.96 80.12,180.44 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='80.12,177.90 82.64,175.38 85.16,177.90 82.64,180.42 80.12,177.90 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='112.64,196.32 115.16,193.80 117.68,196.32 115.16,198.84 112.64,196.32 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='112.64,194.96 115.16,192.44 117.68,194.96 115.16,197.48 112.64,194.96 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='186.98,229.76 189.50,227.24 192.02,229.76 189.50,232.28 186.98,229.76 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='186.98,224.69 189.50,222.17 192.02,224.69 189.50,227.21 186.98,224.69 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='256.68,243.44 259.20,240.92 261.72,243.44 259.20,245.96 256.68,243.44 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='256.68,242.26 259.20,239.74 261.72,242.26 259.20,244.78 256.68,242.26 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='326.37,252.90 328.89,250.38 331.41,252.90 328.89,255.42 326.37,252.90 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='326.37,253.75 328.89,251.23 331.41,253.75 328.89,256.27 326.37,253.75 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,105.14 52.44,114.12 55.81,125.57 57.09,129.49 61.50,141.45 66.38,152.34 67.19,153.94 72.87,163.88 78.56,171.91 82.64,176.75 84.25,178.49 89.94,183.98 95.63,188.64 101.32,192.67 107.01,196.20 112.70,199.36 115.16,200.63 118.39,202.22 124.08,204.84 129.77,207.27 135.46,209.54 141.15,211.69 146.83,213.72 152.52,215.66 158.21,217.52 163.90,219.30 169.59,221.01 175.28,222.67 180.97,224.27 186.66,225.81 189.50,226.56 192.35,227.30 198.04,228.75 203.73,230.15 209.42,231.51 215.11,232.83 220.79,234.11 226.48,235.34 232.17,236.55 237.86,237.71 243.55,238.84 249.24,239.94 254.93,241.01 259.20,241.78 260.62,242.04 266.31,243.04 272.00,244.02 277.69,244.96 283.38,245.88 289.07,246.77 294.76,247.63 300.44,248.47 306.13,249.28 311.82,250.07 317.51,250.84 323.20,251.58 328.89,252.30 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,105.34 52.52,101.18 47.72,101.18 50.12,105.34 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,104.66 52.52,100.51 47.72,100.51 50.12,104.66 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,120.88 54.84,116.72 50.04,116.72 52.44,120.88 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,126.62 54.84,122.47 50.04,122.47 52.44,126.62 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,120.54 59.49,116.39 54.69,116.39 57.09,120.54 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,127.64 59.49,123.48 54.69,123.48 57.09,127.64 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,135.07 68.78,130.91 63.98,130.91 66.38,135.07 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,134.39 68.78,130.24 63.98,130.24 66.38,134.39 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,157.53 85.04,153.38 80.24,153.38 82.64,157.53 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,173.41 85.04,169.25 80.24,169.25 82.64,173.41 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,178.14 117.56,173.98 112.76,173.98 115.16,178.14 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,192.16 117.56,188.00 112.76,188.00 115.16,192.16 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,218.51 191.90,214.35 187.10,214.35 189.50,218.51 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,220.71 191.90,216.55 187.10,216.55 189.50,220.71 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,231.01 261.60,226.85 256.80,226.85 259.20,231.01 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,232.02 261.60,227.87 256.80,227.87 259.20,232.02 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,241.48 331.29,237.33 326.49,237.33 328.89,241.48 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,245.03 331.29,240.87 326.49,240.87 328.89,245.03 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,107.48 52.44,112.19 55.81,118.66 57.09,121.01 61.50,128.67 66.38,136.43 67.19,137.64 72.87,145.70 78.56,152.95 82.64,157.70 84.25,159.48 89.94,165.39 95.63,170.73 101.32,175.57 107.01,179.97 112.70,183.99 115.16,185.62 118.39,187.66 124.08,191.02 129.77,194.11 135.46,196.95 141.15,199.58 146.83,202.02 152.52,204.29 158.21,206.40 163.90,208.37 169.59,210.22 175.28,211.97 180.97,213.61 186.66,215.16 189.50,215.91 192.35,216.63 198.04,218.03 203.73,219.36 209.42,220.64 215.11,221.86 220.79,223.03 226.48,224.15 232.17,225.23 237.86,226.27 243.55,227.28 249.24,228.26 254.93,229.20 259.20,229.89 260.62,230.12 266.31,231.01 272.00,231.87 277.69,232.71 283.38,233.53 289.07,234.33 294.76,235.11 300.44,235.87 306.13,236.62 311.82,237.34 317.51,238.05 323.20,238.75 328.89,239.43 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='48.34' y='112.78' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='116.34' x2='51.90' y2='112.78' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='112.78' x2='51.90' y2='116.34' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='48.34' y='96.56' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='100.13' x2='51.90' y2='96.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='96.56' x2='51.90' y2='100.13' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='50.66' y='109.40' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='112.97' x2='54.22' y2='109.40' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='109.40' x2='54.22' y2='112.97' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='50.66' y='120.38' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='123.94' x2='54.22' y2='120.38' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='120.38' x2='54.22' y2='123.94' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='55.30' y='144.37' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='147.93' x2='58.87' y2='144.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='144.37' x2='58.87' y2='147.93' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='55.30' y='126.46' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='130.03' x2='58.87' y2='126.46' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='126.46' x2='58.87' y2='130.03' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='64.60' y='159.74' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='163.30' x2='68.16' y2='159.74' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='159.74' x2='68.16' y2='163.30' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='64.60' y='138.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='142.36' x2='68.16' y2='138.79' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='138.79' x2='68.16' y2='142.36' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='80.86' y='173.76' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='177.32' x2='84.42' y2='173.76' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='173.76' x2='84.42' y2='177.32' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='80.86' y='178.82' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='182.39' x2='84.42' y2='178.82' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='178.82' x2='84.42' y2='182.39' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='113.38' y='215.82' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='219.38' x2='116.95' y2='215.82' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='215.82' x2='116.95' y2='219.38' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='113.38' y='213.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='217.52' x2='116.95' y2='213.96' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='213.96' x2='116.95' y2='217.52' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='187.72' y='247.57' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='251.14' x2='191.29' y2='247.57' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='247.57' x2='191.29' y2='251.14' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='187.72' y='248.08' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='251.64' x2='191.29' y2='248.08' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='248.08' x2='191.29' y2='251.64' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='257.42' y='256.86' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='260.43' x2='260.98' y2='256.86' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='256.86' x2='260.98' y2='260.43' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='257.42' y='258.21' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='261.78' x2='260.98' y2='258.21' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='258.21' x2='260.98' y2='261.78' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='327.11' y='263.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='267.52' x2='330.67' y2='263.96' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='263.96' x2='330.67' y2='267.52' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='327.11' y='261.09' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='264.65' x2='330.67' y2='261.09' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='261.09' x2='330.67' y2='264.65' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,107.81 52.44,115.53 55.81,125.87 57.09,129.57 61.50,141.35 66.38,152.88 67.19,154.65 72.87,166.12 78.56,176.04 82.64,182.35 84.25,184.67 89.94,192.20 95.63,198.80 101.32,204.60 107.01,209.74 112.70,214.31 115.16,216.13 118.39,218.38 124.08,222.04 129.77,225.34 135.46,228.33 141.15,231.05 146.83,233.54 152.52,235.82 158.21,237.92 163.90,239.87 169.59,241.67 175.28,243.36 180.97,244.93 186.66,246.40 189.50,247.10 192.35,247.79 198.04,249.09 203.73,250.31 209.42,251.47 215.11,252.57 220.79,253.61 226.48,254.60 232.17,255.54 237.86,256.43 243.55,257.28 249.24,258.09 254.93,258.86 259.20,259.42 260.62,259.60 266.31,260.30 272.00,260.97 277.69,261.61 283.38,262.23 289.07,262.81 294.76,263.37 300.44,263.91 306.13,264.42 311.82,264.91 317.51,265.38 323.20,265.83 328.89,266.26 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='113.81' x2='51.90' y2='110.25' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='110.25' x2='51.90' y2='113.81' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='47.60' y1='112.03' x2='52.64' y2='112.03' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='114.55' x2='50.12' y2='109.51' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='96.24' x2='51.90' y2='92.68' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='92.68' x2='51.90' y2='96.24' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='47.60' y1='94.46' x2='52.64' y2='94.46' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='96.98' x2='50.12' y2='91.94' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='111.95' x2='54.22' y2='108.39' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='108.39' x2='54.22' y2='111.95' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='49.92' y1='110.17' x2='54.96' y2='110.17' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='112.69' x2='52.44' y2='107.65' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='129.01' x2='54.22' y2='125.45' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='125.45' x2='54.22' y2='129.01' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='49.92' y1='127.23' x2='54.96' y2='127.23' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='129.75' x2='52.44' y2='124.71' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='133.07' x2='58.87' y2='129.50' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='129.50' x2='58.87' y2='133.07' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='54.57' y1='131.28' x2='59.61' y2='131.28' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='133.80' x2='57.09' y2='128.76' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='150.46' x2='58.87' y2='146.90' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='146.90' x2='58.87' y2='150.46' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='54.57' y1='148.68' x2='59.61' y2='148.68' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='151.20' x2='57.09' y2='146.16' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='159.59' x2='68.16' y2='156.02' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='156.02' x2='68.16' y2='159.59' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='63.86' y1='157.80' x2='68.90' y2='157.80' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='160.32' x2='66.38' y2='155.28' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='165.16' x2='68.16' y2='161.60' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='161.60' x2='68.16' y2='165.16' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='63.86' y1='163.38' x2='68.90' y2='163.38' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='165.90' x2='66.38' y2='160.86' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='198.10' x2='84.42' y2='194.53' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='194.53' x2='84.42' y2='198.10' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.12' y1='196.32' x2='85.16' y2='196.32' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='198.84' x2='82.64' y2='193.80' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='192.19' x2='84.42' y2='188.62' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='188.62' x2='84.42' y2='192.19' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.12' y1='190.40' x2='85.16' y2='190.40' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='192.92' x2='82.64' y2='187.88' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='218.20' x2='116.95' y2='214.63' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='214.63' x2='116.95' y2='218.20' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='112.64' y1='216.42' x2='117.68' y2='216.42' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='218.94' x2='115.16' y2='213.90' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='215.33' x2='116.95' y2='211.76' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='211.76' x2='116.95' y2='215.33' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='112.64' y1='213.54' x2='117.68' y2='213.54' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='216.06' x2='115.16' y2='211.02' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='238.30' x2='191.29' y2='234.73' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='234.73' x2='191.29' y2='238.30' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='186.98' y1='236.52' x2='192.02' y2='236.52' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='239.04' x2='189.50' y2='234.00' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='237.29' x2='191.29' y2='233.72' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='233.72' x2='191.29' y2='237.29' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='186.98' y1='235.50' x2='192.02' y2='235.50' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='238.02' x2='189.50' y2='232.98' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='247.42' x2='260.98' y2='243.86' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='243.86' x2='260.98' y2='247.42' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='256.68' y1='245.64' x2='261.72' y2='245.64' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='248.16' x2='259.20' y2='243.12' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='247.76' x2='260.98' y2='244.19' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='244.19' x2='260.98' y2='247.76' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='256.68' y1='245.98' x2='261.72' y2='245.98' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='248.50' x2='259.20' y2='243.46' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='256.20' x2='330.67' y2='252.64' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='252.64' x2='330.67' y2='256.20' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='326.37' y1='254.42' x2='331.41' y2='254.42' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='256.94' x2='328.89' y2='251.90' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='255.19' x2='330.67' y2='251.63' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='251.63' x2='330.67' y2='255.19' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='326.37' y1='253.41' x2='331.41' y2='253.41' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='255.93' x2='328.89' y2='250.89' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,105.06 52.44,116.50 55.81,130.90 57.09,135.78 61.50,150.47 66.38,163.52 67.19,165.40 72.87,176.91 78.56,185.89 82.64,191.13 84.25,192.98 89.94,198.68 95.63,203.34 101.32,207.23 107.01,210.52 112.70,213.37 115.16,214.50 118.39,215.88 124.08,218.14 129.77,220.18 135.46,222.07 141.15,223.83 146.83,225.48 152.52,227.04 158.21,228.53 163.90,229.96 169.59,231.32 175.28,232.64 180.97,233.91 186.66,235.13 189.50,235.73 192.35,236.32 198.04,237.47 203.73,238.58 209.42,239.66 215.11,240.71 220.79,241.73 226.48,242.71 232.17,243.67 237.86,244.60 243.55,245.50 249.24,246.38 254.93,247.23 259.20,247.85 260.62,248.06 266.31,248.86 272.00,249.64 277.69,250.40 283.38,251.13 289.07,251.85 294.76,252.54 300.44,253.21 306.13,253.87 311.82,254.50 317.51,255.12 323.20,255.72 328.89,256.31 ' style='stroke-width: 0.75; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='47.60' y1='89.90' x2='52.64' y2='89.90' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='92.42' x2='50.12' y2='87.38' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='47.60,89.90 50.12,87.38 52.64,89.90 50.12,92.42 47.60,89.90 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='47.60' y1='122.16' x2='52.64' y2='122.16' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='124.68' x2='50.12' y2='119.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='47.60,122.16 50.12,119.64 52.64,122.16 50.12,124.68 47.60,122.16 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='49.92' y1='109.33' x2='54.96' y2='109.33' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='111.85' x2='52.44' y2='106.80' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='49.92,109.33 52.44,106.80 54.96,109.33 52.44,111.85 49.92,109.33 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='49.92' y1='99.70' x2='54.96' y2='99.70' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='102.22' x2='52.44' y2='97.18' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='49.92,99.70 52.44,97.18 54.96,99.70 52.44,102.22 49.92,99.70 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='54.57' y1='133.48' x2='59.61' y2='133.48' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='136.00' x2='57.09' y2='130.96' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='54.57,133.48 57.09,130.96 59.61,133.48 57.09,136.00 54.57,133.48 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='54.57' y1='123.68' x2='59.61' y2='123.68' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='126.20' x2='57.09' y2='121.16' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='54.57,123.68 57.09,121.16 59.61,123.68 57.09,126.20 54.57,123.68 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='63.86' y1='143.11' x2='68.90' y2='143.11' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='145.63' x2='66.38' y2='140.59' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='63.86,143.11 66.38,140.59 68.90,143.11 66.38,145.63 63.86,143.11 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='63.86' y1='150.03' x2='68.90' y2='150.03' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='152.55' x2='66.38' y2='147.51' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='63.86,150.03 66.38,147.51 68.90,150.03 66.38,152.55 63.86,150.03 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.12' y1='179.42' x2='85.16' y2='179.42' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='181.94' x2='82.64' y2='176.90' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='80.12,179.42 82.64,176.90 85.16,179.42 82.64,181.94 80.12,179.42 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.12' y1='170.30' x2='85.16' y2='170.30' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='172.82' x2='82.64' y2='167.78' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='80.12,170.30 82.64,167.78 85.16,170.30 82.64,172.82 80.12,170.30 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='112.64' y1='204.25' x2='117.68' y2='204.25' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='206.77' x2='115.16' y2='201.73' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='112.64,204.25 115.16,201.73 117.68,204.25 115.16,206.77 112.64,204.25 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='112.64' y1='199.69' x2='117.68' y2='199.69' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='202.21' x2='115.16' y2='197.17' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='112.64,199.69 115.16,197.17 117.68,199.69 115.16,202.21 112.64,199.69 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='186.98' y1='235.33' x2='192.02' y2='235.33' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='237.85' x2='189.50' y2='232.81' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='186.98,235.33 189.50,232.81 192.02,235.33 189.50,237.85 186.98,235.33 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='186.98' y1='233.81' x2='192.02' y2='233.81' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='236.33' x2='189.50' y2='231.29' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='186.98,233.81 189.50,231.29 192.02,233.81 189.50,236.33 186.98,233.81 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='256.68' y1='245.64' x2='261.72' y2='245.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='248.16' x2='259.20' y2='243.12' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='256.68,245.64 259.20,243.12 261.72,245.64 259.20,248.16 256.68,245.64 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='256.68' y1='250.54' x2='261.72' y2='250.54' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='253.06' x2='259.20' y2='248.02' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='256.68,250.54 259.20,248.02 261.72,250.54 259.20,253.06 256.68,250.54 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='326.37' y1='261.18' x2='331.41' y2='261.18' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='263.70' x2='328.89' y2='258.66' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='326.37,261.18 328.89,258.66 331.41,261.18 328.89,263.70 326.37,261.18 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='326.37' y1='254.93' x2='331.41' y2='254.93' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='257.45' x2='328.89' y2='252.41' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='326.37,254.93 328.89,252.41 331.41,254.93 328.89,257.45 326.37,254.93 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,104.82 52.44,112.12 55.81,121.87 57.09,125.34 61.50,136.36 66.38,147.07 67.19,148.71 72.87,159.28 78.56,168.37 82.64,174.12 84.25,176.24 89.94,183.07 95.63,189.05 101.32,194.30 107.01,198.96 112.70,203.10 115.16,204.76 118.39,206.81 124.08,210.16 129.77,213.20 135.46,215.97 141.15,218.52 146.83,220.88 152.52,223.06 158.21,225.10 163.90,227.01 169.59,228.81 175.28,230.50 180.97,232.11 186.66,233.63 189.50,234.37 192.35,235.08 198.04,236.47 203.73,237.80 209.42,239.07 215.11,240.28 220.79,241.46 226.48,242.58 232.17,243.67 237.86,244.71 243.55,245.72 249.24,246.69 254.93,247.63 259.20,248.31 260.62,248.53 266.31,249.41 272.00,250.26 277.69,251.08 283.38,251.87 289.07,252.63 294.76,253.37 300.44,254.09 306.13,254.78 311.82,255.46 317.51,256.11 323.20,256.73 328.89,257.34 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='50.12' cy='104.60' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='104.60' x2='51.90' y2='104.60' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='106.38' x2='50.12' y2='102.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='50.12' cy='104.93' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='104.93' x2='51.90' y2='104.93' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='106.72' x2='50.12' y2='103.15' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='52.44' cy='108.14' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='108.14' x2='54.22' y2='108.14' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='109.92' x2='52.44' y2='106.36' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='52.44' cy='104.60' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='104.60' x2='54.22' y2='104.60' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='106.38' x2='52.44' y2='102.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='57.09' cy='119.12' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='119.12' x2='58.87' y2='119.12' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='120.90' x2='57.09' y2='117.34' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='57.09' cy='122.16' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='122.16' x2='58.87' y2='122.16' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='123.94' x2='57.09' y2='120.38' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='66.38' cy='144.46' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='144.46' x2='68.16' y2='144.46' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='146.24' x2='66.38' y2='142.68' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='66.38' cy='131.28' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='131.28' x2='68.16' y2='131.28' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='133.07' x2='66.38' y2='129.50' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='82.64' cy='150.20' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='150.20' x2='84.42' y2='150.20' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='151.98' x2='82.64' y2='148.42' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='82.64' cy='150.71' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='150.71' x2='84.42' y2='150.71' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='152.49' x2='82.64' y2='148.93' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='115.16' cy='190.57' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='190.57' x2='116.95' y2='190.57' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='192.35' x2='115.16' y2='188.79' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='115.16' cy='178.24' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='178.24' x2='116.95' y2='178.24' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='180.02' x2='115.16' y2='176.46' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='189.50' cy='225.88' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='225.88' x2='191.29' y2='225.88' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='227.66' x2='189.50' y2='224.09' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='189.50' cy='225.71' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='225.71' x2='191.29' y2='225.71' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='227.49' x2='189.50' y2='223.92' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='259.20' cy='236.52' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='236.52' x2='260.98' y2='236.52' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='238.30' x2='259.20' y2='234.73' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='259.20' cy='241.25' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='241.25' x2='260.98' y2='241.25' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='243.03' x2='259.20' y2='239.46' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='328.89' cy='254.25' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='254.25' x2='330.67' y2='254.25' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='256.03' x2='328.89' y2='252.47' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='328.89' cy='251.72' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='251.72' x2='330.67' y2='251.72' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='253.50' x2='328.89' y2='249.94' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,105.68 52.44,110.00 55.81,115.99 57.09,118.19 61.50,125.46 66.38,132.98 67.19,134.17 72.87,142.20 78.56,149.59 82.64,154.54 84.25,156.42 89.94,162.73 95.63,168.57 101.32,173.98 107.01,179.00 112.70,183.66 115.16,185.58 118.39,188.00 124.08,192.04 129.77,195.81 135.46,199.33 141.15,202.63 146.83,205.72 152.52,208.61 158.21,211.33 163.90,213.90 169.59,216.31 175.28,218.59 180.97,220.74 186.66,222.77 189.50,223.75 192.35,224.70 198.04,226.53 203.73,228.27 209.42,229.92 215.11,231.49 220.79,232.99 226.48,234.42 232.17,235.79 237.86,237.09 243.55,238.34 249.24,239.54 254.93,240.69 259.20,241.52 260.62,241.79 266.31,242.85 272.00,243.87 277.69,244.85 283.38,245.79 289.07,246.70 294.76,247.57 300.44,248.42 306.13,249.23 311.82,250.02 317.51,250.78 323.20,251.51 328.89,252.22 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,113.28 52.52,108.43 47.72,108.43 50.12,113.28 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,107.74 52.52,112.59 47.72,112.59 50.12,107.74 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,111.76 52.52,106.91 47.72,106.91 50.12,111.76 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,106.22 52.52,111.07 47.72,111.07 50.12,106.22 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,118.01 54.84,113.16 50.04,113.16 52.44,118.01 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,112.47 54.84,117.32 50.04,117.32 52.44,112.47 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,98.75 54.84,93.90 50.04,93.90 52.44,98.75 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,93.21 54.84,98.06 50.04,98.06 52.44,93.21 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,123.41 59.49,118.56 54.69,118.56 57.09,123.41 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,117.87 59.49,122.72 54.69,122.72 57.09,117.87 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,127.81 59.49,122.96 54.69,122.96 57.09,127.81 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,122.26 59.49,127.11 54.69,127.11 57.09,122.26 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,125.78 68.78,120.93 63.98,120.93 66.38,125.78 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,120.24 68.78,125.09 63.98,125.09 66.38,120.24 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,142.16 68.78,137.31 63.98,137.31 66.38,142.16 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,136.62 68.78,141.47 63.98,141.47 66.38,136.62 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,153.65 85.04,148.80 80.24,148.80 82.64,153.65 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,148.11 85.04,152.96 80.24,152.96 82.64,148.11 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,158.21 85.04,153.36 80.24,153.36 82.64,158.21 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,152.67 85.04,157.52 80.24,157.52 82.64,152.67 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,174.93 117.56,170.08 112.76,170.08 115.16,174.93 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,169.39 117.56,174.24 112.76,174.24 115.16,169.39 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,169.86 117.56,165.01 112.76,165.01 115.16,169.86 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,164.32 117.56,169.17 112.76,169.17 115.16,164.32 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,213.61 191.90,208.76 187.10,208.76 189.50,213.61 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,208.07 191.90,212.92 187.10,212.92 189.50,208.07 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,215.30 191.90,210.45 187.10,210.45 189.50,215.30 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,209.76 191.90,214.61 187.10,214.61 189.50,209.76 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,235.07 261.60,230.22 256.80,230.22 259.20,235.07 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,229.52 261.60,234.37 256.80,234.37 259.20,229.52 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,228.14 261.60,223.29 256.80,223.29 259.20,228.14 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,222.60 261.60,227.45 256.80,227.45 259.20,222.60 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,243.68 331.29,238.83 326.49,238.83 328.89,243.68 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,238.14 331.29,242.99 326.49,242.99 328.89,238.14 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,243.51 331.29,238.66 326.49,238.66 328.89,243.51 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,237.97 331.29,242.82 326.49,242.82 328.89,237.97 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,107.46 52.44,111.06 55.81,116.07 57.09,117.92 61.50,124.04 66.38,130.41 67.19,131.42 72.87,138.26 78.56,144.60 82.64,148.87 84.25,150.49 89.94,155.97 95.63,161.07 101.32,165.82 107.01,170.25 112.70,174.39 115.16,176.11 118.39,178.27 124.08,181.90 129.77,185.30 135.46,188.50 141.15,191.50 146.83,194.33 152.52,197.00 158.21,199.51 163.90,201.90 169.59,204.15 175.28,206.29 180.97,208.32 186.66,210.24 189.50,211.17 192.35,212.08 198.04,213.83 203.73,215.50 209.42,217.10 215.11,218.62 220.79,220.09 226.48,221.49 232.17,222.84 237.86,224.13 243.55,225.38 249.24,226.58 254.93,227.73 259.20,228.58 260.62,228.85 266.31,229.93 272.00,230.97 277.69,231.98 283.38,232.96 289.07,233.91 294.76,234.83 300.44,235.72 306.13,236.58 311.82,237.42 317.51,238.24 323.20,239.04 328.89,239.81 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='120.64' x2='51.90' y2='120.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='122.42' x2='50.12' y2='118.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='48.34' y='118.86' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='104.93' x2='51.90' y2='104.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.12' y1='106.72' x2='50.12' y2='103.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='48.34' y='103.15' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='109.66' x2='54.22' y2='109.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='111.44' x2='52.44' y2='107.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='50.66' y='107.88' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='115.57' x2='54.22' y2='115.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='52.44' y1='117.36' x2='52.44' y2='113.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='50.66' y='113.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='102.40' x2='58.87' y2='102.40' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='104.18' x2='57.09' y2='100.62' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='55.30' y='100.62' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='123.01' x2='58.87' y2='123.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='57.09' y1='124.79' x2='57.09' y2='121.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='55.30' y='121.23' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='144.97' x2='68.16' y2='144.97' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='146.75' x2='66.38' y2='143.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='64.60' y='143.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='129.09' x2='68.16' y2='129.09' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='66.38' y1='130.87' x2='66.38' y2='127.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='64.60' y='127.31' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='160.00' x2='84.42' y2='160.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='161.78' x2='82.64' y2='158.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='80.86' y='158.22' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='157.13' x2='84.42' y2='157.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='82.64' y1='158.91' x2='82.64' y2='155.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='80.86' y='155.35' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='189.39' x2='116.95' y2='189.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='191.17' x2='115.16' y2='187.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='113.38' y='187.61' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='187.36' x2='116.95' y2='187.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='115.16' y1='189.14' x2='115.16' y2='185.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='113.38' y='185.58' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='226.72' x2='191.29' y2='226.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='228.50' x2='189.50' y2='224.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='187.72' y='224.94' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='227.06' x2='191.29' y2='227.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='189.50' y1='228.84' x2='189.50' y2='225.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='187.72' y='225.28' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='245.64' x2='260.98' y2='245.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='247.42' x2='259.20' y2='243.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='257.42' y='243.86' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='240.74' x2='260.98' y2='240.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='259.20' y1='242.52' x2='259.20' y2='238.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='257.42' y='238.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='252.73' x2='330.67' y2='252.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='254.51' x2='328.89' y2='250.95' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='327.11' y='250.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='253.75' x2='330.67' y2='253.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='328.89' y1='255.53' x2='328.89' y2='251.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='327.11' y='251.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,107.53 52.44,111.89 55.81,117.94 57.09,120.17 61.50,127.51 66.38,135.11 67.19,136.31 72.87,144.42 78.56,151.89 82.64,156.88 84.25,158.77 89.94,165.14 95.63,171.02 101.32,176.47 107.01,181.52 112.70,186.21 115.16,188.14 118.39,190.57 124.08,194.62 129.77,198.40 135.46,201.93 141.15,205.22 146.83,208.30 152.52,211.19 158.21,213.90 163.90,216.44 169.59,218.84 175.28,221.09 180.97,223.22 186.66,225.23 189.50,226.19 192.35,227.13 198.04,228.92 203.73,230.63 209.42,232.25 215.11,233.79 220.79,235.25 226.48,236.64 232.17,237.97 237.86,239.24 243.55,240.45 249.24,241.61 254.93,242.72 259.20,243.53 260.62,243.79 266.31,244.81 272.00,245.79 277.69,246.73 283.38,247.63 289.07,248.50 294.76,249.34 300.44,250.15 306.13,250.92 311.82,251.67 317.51,252.40 323.20,253.09 328.89,253.77 ' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='50.12' cy='107.30' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='109.08' x2='51.90' y2='105.52' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='105.52' x2='51.90' y2='109.08' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='50.12' cy='110.85' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='112.63' x2='51.90' y2='109.06' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='48.34' y1='109.06' x2='51.90' y2='112.63' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='52.44' cy='108.99' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='110.77' x2='54.22' y2='107.21' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='107.21' x2='54.22' y2='110.77' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='52.44' cy='96.99' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='98.78' x2='54.22' y2='95.21' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='50.66' y1='95.21' x2='54.22' y2='98.78' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='57.09' cy='121.66' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='123.44' x2='58.87' y2='119.87' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='119.87' x2='58.87' y2='123.44' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='57.09' cy='108.48' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='110.26' x2='58.87' y2='106.70' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='55.30' y1='106.70' x2='58.87' y2='110.26' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='66.38' cy='137.03' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='138.81' x2='68.16' y2='135.24' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='135.24' x2='68.16' y2='138.81' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='66.38' cy='133.99' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='135.77' x2='68.16' y2='132.20' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='64.60' y1='132.20' x2='68.16' y2='135.77' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='82.64' cy='159.32' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='161.11' x2='84.42' y2='157.54' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='157.54' x2='84.42' y2='161.11' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='82.64' cy='166.42' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='168.20' x2='84.42' y2='164.64' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='80.86' y1='164.64' x2='84.42' y2='168.20' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='115.16' cy='193.95' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='195.73' x2='116.95' y2='192.17' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='192.17' x2='116.95' y2='195.73' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='115.16' cy='192.09' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='193.87' x2='116.95' y2='190.31' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='113.38' y1='190.31' x2='116.95' y2='193.87' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='189.50' cy='235.00' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='236.78' x2='191.29' y2='233.21' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='233.21' x2='191.29' y2='236.78' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='189.50' cy='230.77' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='232.56' x2='191.29' y2='228.99' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='187.72' y1='228.99' x2='191.29' y2='232.56' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='259.20' cy='250.71' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='252.49' x2='260.98' y2='248.92' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='248.92' x2='260.98' y2='252.49' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='259.20' cy='243.95' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='245.73' x2='260.98' y2='242.17' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='257.42' y1='242.17' x2='260.98' y2='245.73' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='328.89' cy='255.10' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='256.88' x2='330.67' y2='253.32' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='253.32' x2='330.67' y2='256.88' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<circle cx='328.89' cy='253.58' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='255.36' x2='330.67' y2='251.79' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<line x1='327.11' y1='251.79' x2='330.67' y2='255.36' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,105.13 52.44,110.03 55.81,116.80 57.09,119.28 61.50,127.43 66.38,135.81 67.19,137.14 72.87,146.00 78.56,154.12 82.64,159.51 84.25,161.55 89.94,168.36 95.63,174.62 101.32,180.38 107.01,185.68 112.70,190.57 115.16,192.57 118.39,195.08 124.08,199.26 129.77,203.13 135.46,206.71 141.15,210.05 146.83,213.15 152.52,216.05 158.21,218.75 163.90,221.28 169.59,223.64 175.28,225.86 180.97,227.95 186.66,229.91 189.50,230.85 192.35,231.76 198.04,233.50 203.73,235.15 209.42,236.71 215.11,238.19 220.79,239.59 226.48,240.92 232.17,242.19 237.86,243.40 243.55,244.55 249.24,245.65 254.93,246.69 259.20,247.45 260.62,247.70 266.31,248.66 272.00,249.58 277.69,250.46 283.38,251.30 289.07,252.11 294.76,252.89 300.44,253.64 306.13,254.36 311.82,255.06 317.51,255.73 323.20,256.37 328.89,256.99 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,97.41 51.90,100.97 48.34,100.97 50.12,97.41 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='48.34' y='97.41' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,104.33 51.90,107.90 48.34,107.90 50.12,104.33 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='48.34' y='104.33' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,108.56 54.22,112.12 50.66,112.12 52.44,108.56 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='50.66' y='108.56' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='52.44,97.75 54.22,101.31 50.66,101.31 52.44,97.75 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='50.66' y='97.75' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,124.94 58.87,128.51 55.30,128.51 57.09,124.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='55.30' y='124.94' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='57.09,129.33 58.87,132.90 55.30,132.90 57.09,129.33 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='55.30' y='129.33' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,141.16 68.16,144.72 64.60,144.72 66.38,141.16 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='64.60' y='141.16' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='66.38,140.14 68.16,143.71 64.60,143.71 66.38,140.14 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='64.60' y='140.14' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,173.59 84.42,177.15 80.86,177.15 82.64,173.59 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='80.86' y='173.59' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='82.64,164.13 84.42,167.69 80.86,167.69 82.64,164.13 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='80.86' y='164.13' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,195.55 116.95,199.11 113.38,199.11 115.16,195.55 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='113.38' y='195.55' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='115.16,192.51 116.95,196.07 113.38,196.07 115.16,192.51 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='113.38' y='192.51' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,229.84 191.29,233.40 187.72,233.40 189.50,229.84 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='187.72' y='229.84' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='189.50,230.68 191.29,234.24 187.72,234.24 189.50,230.68 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='187.72' y='230.68' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,245.04 260.98,248.60 257.42,248.60 259.20,245.04 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='257.42' y='245.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='259.20,241.49 260.98,245.06 257.42,245.06 259.20,241.49 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='257.42' y='241.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,254.84 330.67,258.40 327.11,258.40 328.89,254.84 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='327.11' y='254.84' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='328.89,254.50 330.67,258.06 327.11,258.06 328.89,254.50 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<rect x='327.11' y='254.50' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,104.93 52.44,111.41 55.81,120.14 57.09,123.26 61.50,133.30 66.38,143.21 67.19,144.73 72.87,154.69 78.56,163.40 82.64,168.98 84.25,171.05 89.94,177.80 95.63,183.77 101.32,189.09 107.01,193.84 112.70,198.11 115.16,199.83 118.39,201.97 124.08,205.47 129.77,208.66 135.46,211.59 141.15,214.28 146.83,216.77 152.52,219.08 158.21,221.24 163.90,223.26 169.59,225.16 175.28,226.95 180.97,228.64 186.66,230.25 189.50,231.02 192.35,231.78 198.04,233.23 203.73,234.62 209.42,235.95 215.11,237.23 220.79,238.45 226.48,239.63 232.17,240.76 237.86,241.85 243.55,242.91 249.24,243.92 254.93,244.90 259.20,245.61 260.62,245.85 266.31,246.76 272.00,247.65 277.69,248.51 283.38,249.34 289.07,250.14 294.76,250.92 300.44,251.67 306.13,252.40 311.82,253.11 317.51,253.79 323.20,254.46 328.89,255.10 ' style='stroke-width: 0.75; stroke: #F5C710; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='48.34,100.30 51.90,100.30 51.90,96.73 48.34,96.73 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='48.34,98.44 51.90,98.44 51.90,94.87 48.34,94.87 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='50.66,110.26 54.22,110.26 54.22,106.70 50.66,106.70 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='50.66,113.13 54.22,113.13 54.22,109.57 50.66,109.57 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='55.30,129.86 58.87,129.86 58.87,126.29 55.30,126.29 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='55.30,123.44 58.87,123.44 58.87,119.87 55.30,119.87 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='64.60,147.25 68.16,147.25 68.16,143.69 64.60,143.69 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='64.60,149.45 68.16,149.45 68.16,145.89 64.60,145.89 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='80.86,172.93 84.42,172.93 84.42,169.37 80.86,169.37 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='80.86,180.19 84.42,180.19 84.42,176.63 80.86,176.63 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='113.38,202.49 116.95,202.49 116.95,198.93 113.38,198.93 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='113.38,198.77 116.95,198.77 116.95,195.21 113.38,195.21 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='187.72,228.50 191.29,228.50 191.29,224.94 187.72,224.94 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='187.72,228.84 191.29,228.84 191.29,225.28 187.72,225.28 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='257.42,242.35 260.98,242.35 260.98,238.79 257.42,238.79 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='257.42,240.83 260.98,240.83 260.98,237.27 257.42,237.27 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='327.11,252.15 330.67,252.15 330.67,248.59 327.11,248.59 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polygon points='327.11,246.91 330.67,246.91 330.67,243.35 327.11,243.35 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' /> +<polyline points='50.12,104.32 52.44,111.54 55.81,121.13 57.09,124.53 61.50,135.30 66.38,145.71 67.19,147.29 72.87,157.47 78.56,166.16 82.64,171.61 84.25,173.60 89.94,180.02 95.63,185.59 101.32,190.45 107.01,194.72 112.70,198.50 115.16,200.00 118.39,201.86 124.08,204.88 129.77,207.61 135.46,210.10 141.15,212.37 146.83,214.48 152.52,216.43 158.21,218.25 163.90,219.96 169.59,221.57 175.28,223.10 180.97,224.55 186.66,225.94 189.50,226.61 192.35,227.27 198.04,228.54 203.73,229.77 209.42,230.95 215.11,232.09 220.79,233.20 226.48,234.27 232.17,235.30 237.86,236.31 243.55,237.29 249.24,238.24 254.93,239.17 259.20,239.85 260.62,240.07 266.31,240.95 272.00,241.80 277.69,242.63 283.38,243.44 289.07,244.23 294.76,245.00 300.44,245.76 306.13,246.49 311.82,247.20 317.51,247.90 323.20,248.58 328.89,249.24 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI4My40OXw4Mi40NQ==)' />  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0'> -    <rect x='398.97' y='102.24' width='301.08' height='186.63' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU='> +    <rect x='398.97' y='82.45' width='301.08' height='201.03' />    </clipPath>  </defs>  <defs> @@ -734,626 +734,626 @@      <rect x='0.00' y='0.00' width='720.00' height='576.00' />    </clipPath>  </defs> -<line x1='410.12' y1='288.88' x2='681.54' y2='288.88' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='410.12' y1='288.88' x2='410.12' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='464.40' y1='288.88' x2='464.40' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='518.68' y1='288.88' x2='518.68' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='572.97' y1='288.88' x2='572.97' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='627.25' y1='288.88' x2='627.25' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='681.54' y1='288.88' x2='681.54' y2='293.63' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='407.92' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='460.01' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='514.29' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='568.58' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='622.86' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='674.95' y='305.98' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> -<line x1='398.97' y1='268.04' x2='398.97' y2='123.08' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='268.04' x2='394.21' y2='268.04' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='231.80' x2='394.21' y2='231.80' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='195.56' x2='394.21' y2='195.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='159.32' x2='394.21' y2='159.32' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='123.08' x2='394.21' y2='123.08' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,271.55) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,235.31) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,197.76) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,161.52) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,125.28) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> -<polyline points='398.97,288.88 700.04,288.88 700.04,102.24 398.97,102.24 398.97,288.88 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='410.12' y1='283.49' x2='684.33' y2='283.49' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='410.12' y1='283.49' x2='410.12' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='464.96' y1='283.49' x2='464.96' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='519.80' y1='283.49' x2='519.80' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='574.64' y1='283.49' x2='574.64' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='629.49' y1='283.49' x2='629.49' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='684.33' y1='283.49' x2='684.33' y2='288.24' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='407.92' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='460.57' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='515.41' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='570.25' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='625.10' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='677.74' y='300.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> +<line x1='398.97' y1='263.25' x2='398.97' y2='102.70' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='263.25' x2='394.21' y2='263.25' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='223.11' x2='394.21' y2='223.11' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='182.97' x2='394.21' y2='182.97' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='142.83' x2='394.21' y2='142.83' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='102.70' x2='394.21' y2='102.70' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,266.76) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,226.62) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,185.17) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,145.03) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,104.89) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> +<polyline points='398.97,283.49 700.04,283.49 700.04,82.45 398.97,82.45 398.97,283.49 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMzYwLjAwfDcyMC4wMHwzMTcuMzl8ODIuMjk='> -    <rect x='360.00' y='82.29' width='360.00' height='235.10' /> +  <clipPath id='cpMzYwLjAwfDcyMC4wMHwzMTIuMDB8NzIuMDA='> +    <rect x='360.00' y='72.00' width='360.00' height='240.00' />    </clipPath>  </defs> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwzMTcuMzl8ODIuMjk=)'><text x='532.82' y='324.99' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwzMTcuMzl8ODIuMjk=)'><text transform='translate(368.55,233.76) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwzMTIuMDB8NzIuMDA=)'><text x='532.82' y='319.60' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwzMTIuMDB8NzIuMDA=)'><text transform='translate(368.55,221.17) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g>  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0'> -    <rect x='398.97' y='102.24' width='301.08' height='186.63' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU='> +    <rect x='398.97' y='82.45' width='301.08' height='201.03' />    </clipPath>  </defs> -<line x1='398.97' y1='195.56' x2='700.04' y2='195.56' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='682.34' cy='226.01' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='682.34' cy='169.11' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='670.52' cy='202.56' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='670.52' cy='149.63' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='650.10' cy='139.87' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='650.10' cy='245.73' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='619.10' cy='198.22' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='619.10' cy='174.40' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='584.35' cy='224.06' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='584.35' cy='187.01' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='546.39' cy='192.85' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='546.39' cy='206.75' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='499.35' cy='192.40' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='499.35' cy='193.06' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='471.17' cy='194.28' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='471.17' cy='192.29' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='451.91' cy='214.76' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='451.91' cy='208.81' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='682.62,198.75 685.02,202.90 680.22,202.90 682.62,198.75 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='682.62,187.50 685.02,191.65 680.22,191.65 682.62,187.50 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='674.95,175.10 677.35,179.26 672.55,179.26 674.95,175.10 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='674.95,182.38 677.35,186.54 672.55,186.54 674.95,182.38 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='660.55,180.44 662.95,184.60 658.15,184.60 660.55,180.44 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='660.55,163.24 662.95,167.39 658.15,167.39 660.55,163.24 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='635.12,224.55 637.52,228.71 632.72,228.71 635.12,224.55 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='635.12,184.19 637.52,188.35 632.72,188.35 635.12,184.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='599.53,194.86 601.93,199.02 597.13,199.02 599.53,194.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='599.53,227.94 601.93,232.10 597.13,232.10 599.53,227.94 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='551.81,170.91 554.21,175.07 549.41,175.07 551.81,170.91 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='551.81,158.34 554.21,162.50 549.41,162.50 551.81,158.34 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='499.46,172.17 501.86,176.33 497.06,176.33 499.46,172.17 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='499.46,190.04 501.86,194.19 497.06,194.19 499.46,190.04 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='476.36,203.33 478.76,207.49 473.96,207.49 476.36,203.33 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='476.36,194.73 478.76,198.89 473.96,198.89 476.36,194.73 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='461.50,197.20 463.90,201.36 459.10,201.36 461.50,197.20 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='461.50,184.63 463.90,188.79 459.10,188.79 461.50,184.63 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='676.98' y1='133.03' x2='682.02' y2='133.03' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='679.50' y1='135.55' x2='679.50' y2='130.51' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='676.98' y1='188.61' x2='682.02' y2='188.61' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='679.50' y1='191.13' x2='679.50' y2='186.09' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='670.72' y1='211.14' x2='675.76' y2='211.14' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='673.24' y1='213.67' x2='673.24' y2='208.62' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='670.72' y1='207.18' x2='675.76' y2='207.18' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='673.24' y1='209.70' x2='673.24' y2='204.65' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='658.72' y1='225.18' x2='663.76' y2='225.18' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='661.24' y1='227.70' x2='661.24' y2='222.66' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='658.72' y1='179.52' x2='663.76' y2='179.52' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='661.24' y1='182.04' x2='661.24' y2='177.00' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='636.66' y1='191.63' x2='641.70' y2='191.63' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='639.18' y1='194.15' x2='639.18' y2='189.11' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='636.66' y1='185.01' x2='641.70' y2='185.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='639.18' y1='187.53' x2='639.18' y2='182.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='603.47' y1='215.64' x2='608.51' y2='215.64' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.99' y1='218.16' x2='605.99' y2='213.12' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='603.47' y1='167.34' x2='608.51' y2='167.34' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.99' y1='169.86' x2='605.99' y2='164.82' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='553.18' y1='212.52' x2='558.22' y2='212.52' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='555.70' y1='215.04' x2='555.70' y2='210.00' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='553.18' y1='199.95' x2='558.22' y2='199.95' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='555.70' y1='202.47' x2='555.70' y2='197.43' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='487.14' y1='202.79' x2='492.18' y2='202.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='489.66' y1='205.31' x2='489.66' y2='200.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='487.14' y1='189.56' x2='492.18' y2='189.56' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='489.66' y1='192.08' x2='489.66' y2='187.04' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='456.16' y1='199.59' x2='461.20' y2='199.59' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='458.68' y1='202.11' x2='458.68' y2='197.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='456.16' y1='199.59' x2='461.20' y2='199.59' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='458.68' y1='202.11' x2='458.68' y2='197.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='438.64' y1='180.75' x2='443.68' y2='180.75' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='441.16' y1='183.27' x2='441.16' y2='178.23' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='438.64' y1='196.63' x2='443.68' y2='196.63' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='441.16' y1='199.15' x2='441.16' y2='194.11' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='679.74' y1='207.30' x2='683.30' y2='203.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='679.74' y1='203.74' x2='683.30' y2='207.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='679.74' y1='213.25' x2='683.30' y2='209.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='679.74' y1='209.69' x2='683.30' y2='213.25' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='672.61' y1='235.93' x2='676.18' y2='232.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='672.61' y1='232.36' x2='676.18' y2='235.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='672.61' y1='150.57' x2='676.18' y2='147.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='672.61' y1='147.01' x2='676.18' y2='150.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='659.04' y1='177.05' x2='662.60' y2='173.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='659.04' y1='173.49' x2='662.60' y2='177.05' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='659.04' y1='176.39' x2='662.60' y2='172.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='659.04' y1='172.82' x2='662.60' y2='176.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='634.39' y1='216.61' x2='637.96' y2='213.05' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='634.39' y1='213.05' x2='637.96' y2='216.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='634.39' y1='151.11' x2='637.96' y2='147.54' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='634.39' y1='147.54' x2='637.96' y2='151.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='598.15' y1='187.18' x2='601.72' y2='183.62' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='598.15' y1='183.62' x2='601.72' y2='187.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='598.15' y1='224.90' x2='601.72' y2='221.33' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='598.15' y1='221.33' x2='601.72' y2='224.90' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='545.28' y1='204.91' x2='548.85' y2='201.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='545.28' y1='201.35' x2='548.85' y2='204.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='545.28' y1='194.99' x2='548.85' y2='191.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='545.28' y1='191.42' x2='548.85' y2='194.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='479.87' y1='206.23' x2='483.43' y2='202.67' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='479.87' y1='202.67' x2='483.43' y2='206.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='479.87' y1='206.90' x2='483.43' y2='203.33' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='479.87' y1='203.33' x2='483.43' y2='206.90' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='450.68' y1='200.64' x2='454.25' y2='197.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='450.68' y1='197.07' x2='454.25' y2='200.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='450.68' y1='198.65' x2='454.25' y2='195.09' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='450.68' y1='195.09' x2='454.25' y2='198.65' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='434.56' y1='194.29' x2='438.12' y2='190.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='434.56' y1='190.73' x2='438.12' y2='194.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='434.56' y1='189.00' x2='438.12' y2='185.43' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='434.56' y1='185.43' x2='438.12' y2='189.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='682.48,234.76 685.00,232.24 687.52,234.76 685.00,237.28 682.48,234.76 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='682.48,236.75 685.00,234.23 687.52,236.75 685.00,239.27 682.48,236.75 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='667.97,188.08 670.49,185.56 673.01,188.08 670.49,190.60 667.97,188.08 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='667.97,135.15 670.49,132.63 673.01,135.15 670.49,137.67 667.97,135.15 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='643.16,199.59 645.68,197.07 648.20,199.59 645.68,202.11 643.16,199.59 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='643.16,201.58 645.68,199.06 648.20,201.58 645.68,204.10 643.16,201.58 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='606.36,205.93 608.88,203.41 611.40,205.93 608.88,208.45 606.36,205.93 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='606.36,188.73 608.88,186.21 611.40,188.73 608.88,191.25 606.36,188.73 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='567.18,181.04 569.70,178.52 572.22,181.04 569.70,183.56 567.18,181.04 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='567.18,190.96 569.70,188.44 572.22,190.96 569.70,193.48 567.18,190.96 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='528.87,212.24 531.39,209.72 533.91,212.24 531.39,214.76 528.87,212.24 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='528.87,217.53 531.39,215.01 533.91,217.53 531.39,220.05 528.87,217.53 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='487.02,183.24 489.54,180.72 492.06,183.24 489.54,185.76 487.02,183.24 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='487.02,203.09 489.54,200.57 492.06,203.09 489.54,205.61 487.02,203.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='462.44,189.57 464.96,187.05 467.48,189.57 464.96,192.09 462.44,189.57 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='462.44,194.20 464.96,191.68 467.48,194.20 464.96,196.72 462.44,194.20 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='445.50,193.81 448.02,191.29 450.54,193.81 448.02,196.33 445.50,193.81 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='445.50,190.51 448.02,187.99 450.54,190.51 448.02,193.03 445.50,190.51 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='680.96,217.60 683.36,213.44 678.56,213.44 680.96,217.60 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='680.96,220.24 683.36,216.09 678.56,216.09 680.96,220.24 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='673.27,175.48 675.67,171.32 670.87,171.32 673.27,175.48 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='673.27,152.98 675.67,148.82 670.87,148.82 673.27,152.98 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='658.92,211.77 661.32,207.62 656.52,207.62 658.92,211.77 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='658.92,183.98 661.32,179.83 656.52,179.83 658.92,183.98 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='633.90,215.86 636.30,211.71 631.50,211.71 633.90,215.86 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='633.90,218.51 636.30,214.35 631.50,214.35 633.90,218.51 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='599.58,211.53 601.98,207.37 597.18,207.37 599.58,211.53 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='599.58,149.33 601.98,145.18 597.18,145.18 599.58,149.33 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='554.93,239.66 557.33,235.50 552.53,235.50 554.93,239.66 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='554.93,184.74 557.33,180.58 552.53,180.58 554.93,184.74 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='506.91,198.59 509.31,194.43 504.51,194.43 506.91,198.59 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='506.91,189.98 509.31,185.83 504.51,185.83 506.91,189.98 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='484.62,203.96 487.02,199.81 482.22,199.81 484.62,203.96 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='484.62,199.99 487.02,195.84 482.22,195.84 484.62,199.99 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='469.28,200.32 471.68,196.17 466.88,196.17 469.28,200.32 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='469.28,186.43 471.68,182.27 466.88,182.27 469.28,186.43 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='680.45' y='162.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.45' y1='166.52' x2='684.02' y2='162.96' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.45' y1='162.96' x2='684.02' y2='166.52' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='680.45' y='226.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.45' y1='230.04' x2='684.02' y2='226.48' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.45' y1='226.48' x2='684.02' y2='230.04' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='667.54' y='207.67' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='667.54' y1='211.24' x2='671.10' y2='207.67' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='667.54' y1='207.67' x2='671.10' y2='211.24' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='667.54' y='164.66' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='667.54' y1='168.23' x2='671.10' y2='164.66' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='667.54' y1='164.66' x2='671.10' y2='168.23' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='644.19' y='127.63' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='644.19' y1='131.19' x2='647.76' y2='127.63' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='644.19' y1='127.63' x2='647.76' y2='131.19' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='644.19' y='197.76' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='644.19' y1='201.33' x2='647.76' y2='197.76' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='644.19' y1='197.76' x2='647.76' y2='201.33' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='605.82' y='160.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.82' y1='164.52' x2='609.39' y2='160.95' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.82' y1='160.95' x2='609.39' y2='164.52' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='605.82' y='243.00' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.82' y1='246.56' x2='609.39' y2='243.00' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.82' y1='243.00' x2='609.39' y2='246.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='558.16' y='222.22' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='558.16' y1='225.78' x2='561.73' y2='222.22' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='558.16' y1='222.22' x2='561.73' y2='225.78' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='558.16' y='202.37' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='558.16' y1='205.93' x2='561.73' y2='202.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='558.16' y1='202.37' x2='561.73' y2='205.93' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='504.68' y='187.85' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='504.68' y1='191.41' x2='508.24' y2='187.85' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='504.68' y1='187.85' x2='508.24' y2='191.41' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='504.68' y='195.13' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='504.68' y1='198.69' x2='508.24' y2='195.13' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='504.68' y1='195.13' x2='508.24' y2='198.69' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='455.76' y='182.70' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.76' y1='186.26' x2='459.33' y2='182.70' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.76' y1='182.70' x2='459.33' y2='186.26' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='455.76' y='180.72' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.76' y1='184.28' x2='459.33' y2='180.72' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.76' y1='180.72' x2='459.33' y2='184.28' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='435.72' y='195.16' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='435.72' y1='198.72' x2='439.29' y2='195.16' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='435.72' y1='195.16' x2='439.29' y2='198.72' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='435.72' y='189.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='435.72' y1='193.43' x2='439.29' y2='189.87' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='435.72' y1='189.87' x2='439.29' y2='193.43' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='424.44' y='194.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='424.44' y1='198.43' x2='428.01' y2='194.87' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='424.44' y1='194.87' x2='428.01' y2='198.43' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='424.44' y='206.12' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='424.44' y1='209.68' x2='428.01' y2='206.12' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='424.44' y1='206.12' x2='428.01' y2='209.68' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.90' y1='175.35' x2='684.47' y2='171.79' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.90' y1='171.79' x2='684.47' y2='175.35' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.17' y1='173.57' x2='685.21' y2='173.57' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='682.69' y1='176.09' x2='682.69' y2='171.05' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.90' y1='244.16' x2='684.47' y2='240.60' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.90' y1='240.60' x2='684.47' y2='244.16' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.17' y1='242.38' x2='685.21' y2='242.38' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='682.69' y1='244.90' x2='682.69' y2='239.86' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='663.39' y1='225.33' x2='666.95' y2='221.77' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='663.39' y1='221.77' x2='666.95' y2='225.33' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='662.65' y1='223.55' x2='667.69' y2='223.55' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='665.17' y1='226.07' x2='665.17' y2='221.03' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='663.39' y1='158.51' x2='666.95' y2='154.94' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='663.39' y1='154.94' x2='666.95' y2='158.51' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='662.65' y1='156.73' x2='667.69' y2='156.73' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='665.17' y1='159.25' x2='665.17' y2='154.21' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.45' y1='215.59' x2='637.02' y2='212.03' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.45' y1='212.03' x2='637.02' y2='215.59' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='632.72' y1='213.81' x2='637.76' y2='213.81' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='635.24' y1='216.33' x2='635.24' y2='211.29' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.45' y1='147.44' x2='637.02' y2='143.88' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.45' y1='143.88' x2='637.02' y2='147.44' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='632.72' y1='145.66' x2='637.76' y2='145.66' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='635.24' y1='148.18' x2='635.24' y2='143.14' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='589.39' y1='219.14' x2='592.95' y2='215.57' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='589.39' y1='215.57' x2='592.95' y2='219.14' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='588.65' y1='217.35' x2='593.69' y2='217.35' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='591.17' y1='219.87' x2='591.17' y2='214.83' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='589.39' y1='197.30' x2='592.95' y2='193.74' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='589.39' y1='193.74' x2='592.95' y2='197.30' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='588.65' y1='195.52' x2='593.69' y2='195.52' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='591.17' y1='198.04' x2='591.17' y2='193.00' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='544.07' y1='178.76' x2='547.63' y2='175.20' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='544.07' y1='175.20' x2='547.63' y2='178.76' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='543.33' y1='176.98' x2='548.37' y2='176.98' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='545.85' y1='179.50' x2='545.85' y2='174.46' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='544.07' y1='201.92' x2='547.63' y2='198.35' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='544.07' y1='198.35' x2='547.63' y2='201.92' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='543.33' y1='200.14' x2='548.37' y2='200.14' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='545.85' y1='202.66' x2='545.85' y2='197.62' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='505.36' y1='194.39' x2='508.92' y2='190.82' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='505.36' y1='190.82' x2='508.92' y2='194.39' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='504.62' y1='192.61' x2='509.66' y2='192.61' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='507.14' y1='195.13' x2='507.14' y2='190.09' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='505.36' y1='205.64' x2='508.92' y2='202.07' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='505.36' y1='202.07' x2='508.92' y2='205.64' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='504.62' y1='203.85' x2='509.66' y2='203.85' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='507.14' y1='206.37' x2='507.14' y2='201.33' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='473.45' y1='193.43' x2='477.02' y2='189.87' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='473.45' y1='189.87' x2='477.02' y2='193.43' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='472.71' y1='191.65' x2='477.75' y2='191.65' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='475.23' y1='194.17' x2='475.23' y2='189.13' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='473.45' y1='197.40' x2='477.02' y2='193.84' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='473.45' y1='193.84' x2='477.02' y2='197.40' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='472.71' y1='195.62' x2='477.75' y2='195.62' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='475.23' y1='198.14' x2='475.23' y2='193.10' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.77' y1='200.80' x2='459.34' y2='197.23' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.77' y1='197.23' x2='459.34' y2='200.80' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.03' y1='199.02' x2='460.08' y2='199.02' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='457.56' y1='201.54' x2='457.56' y2='196.50' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.77' y1='199.47' x2='459.34' y2='195.91' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.77' y1='195.91' x2='459.34' y2='199.47' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='455.03' y1='197.69' x2='460.08' y2='197.69' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='457.56' y1='200.21' x2='457.56' y2='195.17' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='442.97' y1='197.60' x2='446.54' y2='194.03' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='442.97' y1='194.03' x2='446.54' y2='197.60' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='442.23' y1='195.81' x2='447.27' y2='195.81' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='444.75' y1='198.33' x2='444.75' y2='193.29' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='442.97' y1='201.57' x2='446.54' y2='198.00' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='442.97' y1='198.00' x2='446.54' y2='201.57' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='442.23' y1='199.78' x2='447.27' y2='199.78' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='444.75' y1='202.30' x2='444.75' y2='197.26' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.40' y1='249.93' x2='689.44' y2='249.93' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='686.92' y1='252.45' x2='686.92' y2='247.41' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='684.40,249.93 686.92,247.41 689.44,249.93 686.92,252.45 684.40,249.93 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.40' y1='123.56' x2='689.44' y2='123.56' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='686.92' y1='126.08' x2='686.92' y2='121.04' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='684.40,123.56 686.92,121.04 689.44,123.56 686.92,126.08 684.40,123.56 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='673.07' y1='201.45' x2='678.11' y2='201.45' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='675.59' y1='203.97' x2='675.59' y2='198.93' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='673.07,201.45 675.59,198.93 678.11,201.45 675.59,203.97 673.07,201.45 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='673.07' y1='239.16' x2='678.11' y2='239.16' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='675.59' y1='241.68' x2='675.59' y2='236.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='673.07,239.16 675.59,236.64 678.11,239.16 675.59,241.68 673.07,239.16 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='652.40' y1='157.22' x2='657.44' y2='157.22' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='654.92' y1='159.74' x2='654.92' y2='154.70' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='652.40,157.22 654.92,154.70 657.44,157.22 654.92,159.74 652.40,157.22 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='652.40' y1='195.60' x2='657.44' y2='195.60' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='654.92' y1='198.12' x2='654.92' y2='193.08' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='652.40,195.60 654.92,193.08 657.44,195.60 654.92,198.12 652.40,195.60 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='617.83' y1='203.78' x2='622.87' y2='203.78' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='620.35' y1='206.30' x2='620.35' y2='201.26' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='617.83,203.78 620.35,201.26 622.87,203.78 620.35,206.30 617.83,203.78 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='617.83' y1='176.65' x2='622.87' y2='176.65' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='620.35' y1='179.17' x2='620.35' y2='174.13' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='617.83,176.65 620.35,174.13 622.87,176.65 620.35,179.17 617.83,176.65 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='573.64' y1='169.25' x2='578.68' y2='169.25' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='576.16' y1='171.77' x2='576.16' y2='166.73' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='573.64,169.25 576.16,166.73 578.68,169.25 576.16,171.77 573.64,169.25 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='573.64' y1='204.98' x2='578.68' y2='204.98' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='576.16' y1='207.50' x2='576.16' y2='202.46' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='573.64,204.98 576.16,202.46 578.68,204.98 576.16,207.50 573.64,204.98 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='521.94' y1='198.01' x2='526.98' y2='198.01' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='524.46' y1='200.53' x2='524.46' y2='195.49' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='521.94,198.01 524.46,195.49 526.98,198.01 524.46,200.53 521.94,198.01 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='521.94' y1='215.88' x2='526.98' y2='215.88' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='524.46' y1='218.40' x2='524.46' y2='213.36' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='521.94,215.88 524.46,213.36 526.98,215.88 524.46,218.40 521.94,215.88 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='472.18' y1='197.57' x2='477.22' y2='197.57' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='474.70' y1='200.09' x2='474.70' y2='195.05' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='472.18,197.57 474.70,195.05 477.22,197.57 474.70,200.09 472.18,197.57 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='472.18' y1='203.53' x2='477.22' y2='203.53' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='474.70' y1='206.05' x2='474.70' y2='201.01' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='472.18,203.53 474.70,201.01 477.22,203.53 474.70,206.05 472.18,203.53 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='450.12' y1='211.01' x2='455.16' y2='211.01' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='452.64' y1='213.53' x2='452.64' y2='208.48' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='450.12,211.01 452.64,208.48 455.16,211.01 452.64,213.53 450.12,211.01 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='450.12' y1='191.82' x2='455.16' y2='191.82' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='452.64' y1='194.34' x2='452.64' y2='189.30' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='450.12,191.82 452.64,189.30 455.16,191.82 452.64,194.34 450.12,191.82 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='436.19' y1='184.09' x2='441.23' y2='184.09' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='438.71' y1='186.61' x2='438.71' y2='181.57' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='436.19,184.09 438.71,181.57 441.23,184.09 438.71,186.61 436.19,184.09 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='436.19' y1='208.57' x2='441.23' y2='208.57' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='438.71' y1='211.09' x2='438.71' y2='206.05' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='436.19,208.57 438.71,206.05 441.23,208.57 438.71,211.09 436.19,208.57 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='684.01' cy='199.45' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='682.23' y1='199.45' x2='685.79' y2='199.45' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.01' y1='201.23' x2='684.01' y2='197.67' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='684.01' cy='198.13' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='682.23' y1='198.13' x2='685.79' y2='198.13' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.01' y1='199.91' x2='684.01' y2='196.34' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='677.05' cy='202.52' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='675.27' y1='202.52' x2='678.83' y2='202.52' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='677.05' y1='204.30' x2='677.05' y2='200.74' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='677.05' cy='216.41' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='675.27' y1='216.41' x2='678.83' y2='216.41' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='677.05' y1='218.20' x2='677.05' y2='214.63' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='663.84' cy='191.71' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='662.06' y1='191.71' x2='665.63' y2='191.71' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='663.84' y1='193.50' x2='663.84' y2='189.93' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='663.84' cy='179.80' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='662.06' y1='179.80' x2='665.63' y2='179.80' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='663.84' y1='181.59' x2='663.84' y2='178.02' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='640.01' cy='150.56' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='638.23' y1='150.56' x2='641.79' y2='150.56' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='640.01' y1='152.35' x2='640.01' y2='148.78' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='640.01' cy='202.17' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='638.23' y1='202.17' x2='641.79' y2='202.17' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='640.01' y1='203.96' x2='640.01' y2='200.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='605.31' cy='212.66' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='603.53' y1='212.66' x2='607.09' y2='212.66' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.31' y1='214.44' x2='605.31' y2='210.88' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='605.31' cy='210.67' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='603.53' y1='210.67' x2='607.09' y2='210.67' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='605.31' y1='212.46' x2='605.31' y2='208.89' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='555.43' cy='176.13' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='553.65' y1='176.13' x2='557.21' y2='176.13' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='555.43' y1='177.91' x2='555.43' y2='174.34' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='555.43' cy='224.43' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='553.65' y1='224.43' x2='557.21' y2='224.43' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='555.43' y1='226.21' x2='555.43' y2='222.64' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='494.21' cy='187.08' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='492.43' y1='187.08' x2='495.99' y2='187.08' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='494.21' y1='188.86' x2='494.21' y2='185.30' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='494.21' cy='187.74' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='492.43' y1='187.74' x2='495.99' y2='187.74' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='494.21' y1='189.52' x2='494.21' y2='185.96' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='465.72' cy='214.85' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='463.94' y1='214.85' x2='467.50' y2='214.85' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='465.72' y1='216.63' x2='465.72' y2='213.06' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='465.72' cy='196.32' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='463.94' y1='196.32' x2='467.50' y2='196.32' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='465.72' y1='198.10' x2='465.72' y2='194.54' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='448.54' cy='187.24' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='446.76' y1='187.24' x2='450.33' y2='187.24' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='448.54' y1='189.02' x2='448.54' y2='185.46' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='448.54' cy='197.16' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='446.76' y1='197.16' x2='450.33' y2='197.16' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='448.54' y1='198.95' x2='448.54' y2='195.38' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='680.78,186.94 683.18,182.09 678.38,182.09 680.78,186.94 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='680.78,181.40 683.18,186.25 678.38,186.25 680.78,181.40 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='680.78,192.90 683.18,188.05 678.38,188.05 680.78,192.90 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='680.78,187.35 683.18,192.20 678.38,192.20 680.78,187.35 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='675.08,182.30 677.48,177.45 672.68,177.45 675.08,182.30 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='675.08,176.76 677.48,181.61 672.68,181.61 675.08,176.76 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='675.08,257.73 677.48,252.88 672.68,252.88 675.08,257.73 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='675.08,252.18 677.48,257.03 672.68,257.03 675.08,252.18 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='664.21,187.63 666.61,182.78 661.81,182.78 664.21,187.63 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='664.21,182.09 666.61,186.94 661.81,186.94 664.21,182.09 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='664.21,170.43 666.61,165.58 661.81,165.58 664.21,170.43 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='664.21,164.88 666.61,169.73 661.81,169.73 664.21,164.88 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='644.38,226.72 646.78,221.87 641.98,221.87 644.38,226.72 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='644.38,221.18 646.78,226.03 641.98,226.03 644.38,221.18 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='644.38,162.54 646.78,157.69 641.98,157.69 644.38,162.54 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='644.38,157.00 646.78,161.85 641.98,161.85 644.38,157.00 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='614.93,189.33 617.33,184.48 612.53,184.48 614.93,189.33 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='614.93,183.78 617.33,188.63 612.53,188.63 614.93,183.78 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='614.93,171.46 617.33,166.61 612.53,166.61 614.93,171.46 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='614.93,165.92 617.33,170.77 612.53,170.77 614.93,165.92 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='571.18,212.62 573.58,207.77 568.78,207.77 571.18,212.62 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='571.18,207.08 573.58,211.93 568.78,211.93 571.18,207.08 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='571.18,232.47 573.58,227.62 568.78,227.62 571.18,232.47 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='571.18,226.93 573.58,231.78 568.78,231.78 571.18,226.93 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='514.33,199.69 516.73,194.84 511.93,194.84 514.33,199.69 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='514.33,194.15 516.73,199.00 511.93,199.00 514.33,194.15 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='514.33,193.07 516.73,188.22 511.93,188.22 514.33,193.07 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='514.33,187.53 516.73,192.38 511.93,192.38 514.33,187.53 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='486.05,184.59 488.45,179.74 483.65,179.74 486.05,184.59 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='486.05,179.05 488.45,183.90 483.65,183.90 486.05,179.05 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='486.05,211.72 488.45,206.87 483.65,206.87 486.05,211.72 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='486.05,206.18 488.45,211.03 483.65,211.03 486.05,206.18 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='467.90,195.10 470.30,190.25 465.50,190.25 467.90,195.10 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='467.90,189.56 470.30,194.41 465.50,194.41 467.90,189.56 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='467.90,195.77 470.30,190.92 465.50,190.92 467.90,195.77 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='467.90,190.22 470.30,195.07 465.50,195.07 467.90,190.22 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='678.96' y1='144.57' x2='682.52' y2='144.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.74' y1='146.35' x2='680.74' y2='142.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='678.96' y='142.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='678.96' y1='206.10' x2='682.52' y2='206.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='680.74' y1='207.89' x2='680.74' y2='204.32' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='678.96' y='204.32' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='672.05' y1='204.42' x2='675.61' y2='204.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='673.83' y1='206.20' x2='673.83' y2='202.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='672.05' y='202.64' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='672.05' y1='181.26' x2='675.61' y2='181.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='673.83' y1='183.04' x2='673.83' y2='179.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='672.05' y='179.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='658.91' y1='264.89' x2='662.48' y2='264.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='660.69' y1='266.68' x2='660.69' y2='263.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='658.91' y='263.11' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='658.91' y1='184.17' x2='662.48' y2='184.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='660.69' y1='185.96' x2='660.69' y2='182.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='658.91' y='182.39' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='635.14' y1='156.12' x2='638.70' y2='156.12' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='636.92' y1='157.90' x2='636.92' y2='154.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='635.14' y='154.34' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='635.14' y1='218.31' x2='638.70' y2='218.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='636.92' y1='220.09' x2='636.92' y2='216.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='635.14' y='216.53' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='600.35' y1='182.04' x2='603.91' y2='182.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='602.13' y1='183.82' x2='602.13' y2='180.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='600.35' y='180.26' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='600.35' y1='193.29' x2='603.91' y2='193.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='602.13' y1='195.07' x2='602.13' y2='191.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='600.35' y='191.51' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='550.02' y1='189.59' x2='553.59' y2='189.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='551.80' y1='191.37' x2='551.80' y2='187.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='550.02' y='187.81' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='550.02' y1='197.53' x2='553.59' y2='197.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='551.80' y1='199.31' x2='551.80' y2='195.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='550.02' y='195.75' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='488.27' y1='193.89' x2='491.84' y2='193.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='490.05' y1='195.68' x2='490.05' y2='192.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='488.27' y='192.11' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='488.27' y1='192.57' x2='491.84' y2='192.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='490.05' y1='194.35' x2='490.05' y2='190.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='488.27' y='190.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='460.17' y1='188.29' x2='463.74' y2='188.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='461.96' y1='190.07' x2='461.96' y2='186.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='460.17' y='186.50' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='460.17' y1='207.47' x2='463.74' y2='207.47' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='461.96' y1='209.26' x2='461.96' y2='205.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='460.17' y='205.69' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='443.72' y1='200.61' x2='447.29' y2='200.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='445.50' y1='202.39' x2='445.50' y2='198.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='443.72' y='198.82' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='443.72' y1='196.64' x2='447.29' y2='196.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='445.50' y1='198.42' x2='445.50' y2='194.85' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='443.72' y='194.85' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='686.54' cy='182.70' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.76' y1='184.48' x2='688.32' y2='180.92' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.76' y1='180.92' x2='688.32' y2='184.48' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='686.54' cy='168.80' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.76' y1='170.59' x2='688.32' y2='167.02' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='684.76' y1='167.02' x2='688.32' y2='170.59' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='678.41' cy='195.91' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='676.62' y1='197.69' x2='680.19' y2='194.13' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='676.62' y1='194.13' x2='680.19' y2='197.69' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='678.41' cy='242.89' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='676.62' y1='244.67' x2='680.19' y2='241.11' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='676.62' y1='241.11' x2='680.19' y2='244.67' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='663.07' cy='183.68' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='661.28' y1='185.46' x2='664.85' y2='181.90' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='661.28' y1='181.90' x2='664.85' y2='185.46' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='663.07' cy='235.29' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='661.28' y1='237.07' x2='664.85' y2='233.51' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='661.28' y1='233.51' x2='664.85' y2='237.07' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='635.74' cy='190.08' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.96' y1='191.86' x2='637.52' y2='188.30' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.96' y1='188.30' x2='637.52' y2='191.86' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='635.74' cy='201.99' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.96' y1='203.77' x2='637.52' y2='200.21' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='633.96' y1='200.21' x2='637.52' y2='203.77' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='596.87' cy='197.50' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='595.09' y1='199.28' x2='598.65' y2='195.72' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='595.09' y1='195.72' x2='598.65' y2='199.28' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='596.87' cy='169.71' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='595.09' y1='171.50' x2='598.65' y2='167.93' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='595.09' y1='167.93' x2='598.65' y2='171.50' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='543.28' cy='192.49' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='541.50' y1='194.28' x2='545.07' y2='190.71' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='541.50' y1='190.71' x2='545.07' y2='194.28' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='543.28' cy='199.77' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='541.50' y1='201.55' x2='545.07' y2='197.99' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='541.50' y1='197.99' x2='545.07' y2='201.55' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='482.37' cy='180.20' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='480.59' y1='181.99' x2='484.15' y2='178.42' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='480.59' y1='178.42' x2='484.15' y2='181.99' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='482.37' cy='196.75' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='480.59' y1='198.53' x2='484.15' y2='194.96' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='480.59' y1='194.96' x2='484.15' y2='198.53' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='456.22' cy='182.42' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='454.44' y1='184.20' x2='458.00' y2='180.64' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='454.44' y1='180.64' x2='458.00' y2='184.20' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='456.22' cy='208.89' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='454.44' y1='210.67' x2='458.00' y2='207.10' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='454.44' y1='207.10' x2='458.00' y2='210.67' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='441.11' cy='202.05' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='439.33' y1='203.83' x2='442.89' y2='200.27' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='439.33' y1='200.27' x2='442.89' y2='203.83' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<circle cx='441.11' cy='208.00' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='439.33' y1='209.79' x2='442.89' y2='206.22' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<line x1='439.33' y1='206.22' x2='442.89' y2='209.79' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='685.14,216.08 686.93,219.65 683.36,219.65 685.14,216.08 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='683.36' y='216.08' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='685.14,188.95 686.93,192.52 683.36,192.52 685.14,188.95 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='683.36' y='188.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='674.77,197.69 676.56,201.25 672.99,201.25 674.77,197.69 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='672.99' y='197.69' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='674.77,240.04 676.56,243.60 672.99,243.60 674.77,240.04 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='672.99' y='240.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='655.77,179.83 657.56,183.39 653.99,183.39 655.77,179.83 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='653.99' y='179.83' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='655.77,162.62 657.56,166.19 653.99,166.19 655.77,162.62 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='653.99' y='162.62' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='623.75,194.38 625.53,197.95 621.97,197.95 623.75,194.38 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='621.97' y='194.38' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='623.75,198.35 625.53,201.92 621.97,201.92 623.75,198.35 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='621.97' y='198.35' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='582.21,168.59 584.00,172.16 580.43,172.16 582.21,168.59 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='580.43' y='168.59' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='582.21,205.64 584.00,209.21 580.43,209.21 582.21,205.64 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='580.43' y='205.64' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='532.36,204.11 534.14,207.67 530.58,207.67 532.36,204.11 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='530.58' y='204.11' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='532.36,216.02 534.14,219.58 530.58,219.58 532.36,216.02 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='530.58' y='216.02' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='482.20,192.07 483.98,195.63 480.42,195.63 482.20,192.07 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='480.42' y='192.07' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='482.20,188.76 483.98,192.32 480.42,192.32 482.20,188.76 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='480.42' y='188.76' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='459.00,189.08 460.78,192.65 457.22,192.65 459.00,189.08 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='457.22' y='189.08' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='459.00,202.98 460.78,206.54 457.22,206.54 459.00,202.98 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='457.22' y='202.98' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='443.93,187.45 445.71,191.01 442.15,191.01 443.93,187.45 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='442.15' y='187.45' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polyline points='443.93,188.77 445.71,192.33 442.15,192.33 443.93,188.77 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<rect x='442.15' y='188.77' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='687.11,213.16 690.67,213.16 690.67,209.59 687.11,209.59 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='687.11,220.44 690.67,220.44 690.67,216.87 687.11,216.87 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='673.12,208.21 676.69,208.21 676.69,204.65 673.12,204.65 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='673.12,196.96 676.69,196.96 676.69,193.40 673.12,193.40 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='649.06,190.13 652.62,190.13 652.62,186.57 649.06,186.57 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='649.06,215.27 652.62,215.27 652.62,211.71 649.06,211.71 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='612.92,210.08 616.48,210.08 616.48,206.52 612.92,206.52 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='612.92,201.48 616.48,201.48 616.48,197.91 612.92,197.91 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='573.62,205.31 577.18,205.31 577.18,201.75 573.62,201.75 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='573.62,176.86 577.18,176.86 577.18,173.30 573.62,173.30 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='534.08,185.92 537.64,185.92 537.64,182.35 534.08,182.35 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='534.08,200.47 537.64,200.47 537.64,196.91 534.08,196.91 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='490.33,190.67 493.89,190.67 493.89,187.10 490.33,187.10 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='490.33,189.34 493.89,189.34 493.89,185.78 490.33,185.78 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='464.76,198.73 468.33,198.73 468.33,195.16 464.76,195.16 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='464.76,204.68 468.33,204.68 468.33,201.12 464.76,201.12 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='447.21,203.15 450.77,203.15 450.77,199.58 447.21,199.58 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> -<polygon points='447.21,223.66 450.77,223.66 450.77,220.09 447.21,220.09 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODguODh8MTAyLjI0)' /> +<line x1='398.97' y1='182.97' x2='700.04' y2='182.97' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='682.17' cy='224.91' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='682.17' cy='161.51' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='672.33' cy='193.12' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='672.33' cy='134.14' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='654.47' cy='115.79' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='654.47' cy='233.76' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='624.92' cy='176.09' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='624.92' cy='149.55' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='587.63' cy='210.71' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='587.63' cy='169.42' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='544.13' cy='189.82' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='544.13' cy='205.30' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='498.60' cy='183.93' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='498.60' cy='184.67' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='474.57' cy='174.09' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='474.57' cy='171.88' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='457.50' cy='190.49' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='457.50' cy='183.85' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.99,190.69 686.39,194.84 681.59,194.84 683.99,190.69 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.99,178.15 686.39,182.31 681.59,182.31 683.99,178.15 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='676.23,164.38 678.63,168.54 673.83,168.54 676.23,164.38 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='676.23,172.49 678.63,176.65 673.83,176.65 676.23,172.49 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='661.64,170.41 664.04,174.57 659.24,174.57 661.64,170.41 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='661.64,151.24 664.04,155.40 659.24,155.40 661.64,151.24 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='635.89,219.75 638.29,223.90 633.49,223.90 635.89,219.75 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='635.89,174.77 638.29,178.93 633.49,178.93 635.89,174.77 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='599.82,186.97 602.22,191.13 597.42,191.13 599.82,186.97 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='599.82,223.84 602.22,227.99 597.42,227.99 599.82,223.84 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='551.45,160.73 553.85,164.89 549.05,164.89 551.45,160.73 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='551.45,146.72 553.85,150.88 549.05,150.88 551.45,146.72 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='498.57,162.09 500.97,166.25 496.17,166.25 498.57,162.09 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='498.57,182.00 500.97,186.15 496.17,186.15 498.57,182.00 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='475.51,196.06 477.91,200.22 473.11,200.22 475.51,196.06 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='475.51,186.48 477.91,190.63 473.11,190.63 475.51,186.48 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='460.82,188.38 463.22,192.54 458.42,192.54 460.82,188.38 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='460.82,174.37 463.22,178.53 458.42,178.53 460.82,174.37 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='679.89' y1='112.92' x2='684.93' y2='112.92' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='682.41' y1='115.44' x2='682.41' y2='110.40' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='679.89' y1='174.86' x2='684.93' y2='174.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='682.41' y1='177.38' x2='682.41' y2='172.34' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='673.52' y1='200.10' x2='678.56' y2='200.10' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='676.04' y1='202.62' x2='676.04' y2='197.58' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='673.52' y1='195.67' x2='678.56' y2='195.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='676.04' y1='198.19' x2='676.04' y2='193.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.32' y1='215.95' x2='666.36' y2='215.95' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='663.84' y1='218.47' x2='663.84' y2='213.43' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.32' y1='165.08' x2='666.36' y2='165.08' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='663.84' y1='167.60' x2='663.84' y2='162.56' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='638.90' y1='178.89' x2='643.95' y2='178.89' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='641.43' y1='181.41' x2='641.43' y2='176.37' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='638.90' y1='171.51' x2='643.95' y2='171.51' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='641.43' y1='174.03' x2='641.43' y2='168.99' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='605.27' y1='205.91' x2='610.31' y2='205.91' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='607.79' y1='208.43' x2='607.79' y2='203.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='605.27' y1='152.09' x2='610.31' y2='152.09' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='607.79' y1='154.61' x2='607.79' y2='149.57' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='554.50' y1='202.33' x2='559.54' y2='202.33' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='557.02' y1='204.85' x2='557.02' y2='199.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='554.50' y1='188.32' x2='559.54' y2='188.32' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='557.02' y1='190.84' x2='557.02' y2='185.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='488.12' y1='190.61' x2='493.16' y2='190.61' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='490.64' y1='193.13' x2='490.64' y2='188.09' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='488.12' y1='175.86' x2='493.16' y2='175.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='490.64' y1='178.38' x2='490.64' y2='173.34' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='456.95' y1='186.67' x2='461.99' y2='186.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='459.47' y1='189.19' x2='459.47' y2='184.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='456.95' y1='186.67' x2='461.99' y2='186.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='459.47' y1='189.19' x2='459.47' y2='184.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.25' y1='165.69' x2='444.29' y2='165.69' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='441.77' y1='168.21' x2='441.77' y2='163.17' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.25' y1='183.39' x2='444.29' y2='183.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='441.77' y1='185.91' x2='441.77' y2='180.87' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='682.10' y1='197.02' x2='685.66' y2='193.46' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='682.10' y1='193.46' x2='685.66' y2='197.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='682.10' y1='203.66' x2='685.66' y2='200.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='682.10' y1='200.10' x2='685.66' y2='203.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='674.99' y1='228.68' x2='678.55' y2='225.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='674.99' y1='225.11' x2='678.55' y2='228.68' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='674.99' y1='133.56' x2='678.55' y2='130.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='674.99' y1='130.00' x2='678.55' y2='133.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.43' y1='162.63' x2='665.00' y2='159.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.43' y1='159.06' x2='665.00' y2='162.63' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.43' y1='161.89' x2='665.00' y2='158.33' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.43' y1='158.33' x2='665.00' y2='161.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.79' y1='206.02' x2='640.36' y2='202.46' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.79' y1='202.46' x2='640.36' y2='206.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.79' y1='133.03' x2='640.36' y2='129.47' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.79' y1='129.47' x2='640.36' y2='133.03' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='600.45' y1='172.50' x2='604.02' y2='168.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='600.45' y1='168.94' x2='604.02' y2='172.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='600.45' y1='214.52' x2='604.02' y2='210.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='600.45' y1='210.96' x2='604.02' y2='214.52' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='547.20' y1='191.82' x2='550.76' y2='188.25' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='547.20' y1='188.25' x2='550.76' y2='191.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='547.20' y1='180.76' x2='550.76' y2='177.19' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='547.20' y1='177.19' x2='550.76' y2='180.76' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='480.96' y1='193.72' x2='484.52' y2='190.16' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='480.96' y1='190.16' x2='484.52' y2='193.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='480.96' y1='194.46' x2='484.52' y2='190.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='480.96' y1='190.89' x2='484.52' y2='194.46' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='451.35' y1='187.80' x2='454.92' y2='184.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='451.35' y1='184.23' x2='454.92' y2='187.80' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='451.35' y1='185.59' x2='454.92' y2='182.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='451.35' y1='182.02' x2='454.92' y2='185.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.02' y1='180.83' x2='438.59' y2='177.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.02' y1='177.27' x2='438.59' y2='180.83' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.02' y1='174.93' x2='438.59' y2='171.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.02' y1='171.37' x2='438.59' y2='174.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='685.03,227.39 687.55,224.87 690.07,227.39 687.55,229.91 685.03,227.39 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='685.03,229.61 687.55,227.09 690.07,229.61 687.55,232.13 685.03,229.61 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='670.46,175.14 672.98,172.62 675.50,175.14 672.98,177.66 670.46,175.14 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='670.46,116.16 672.98,113.64 675.50,116.16 672.98,118.68 670.46,116.16 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='645.51,187.67 648.03,185.15 650.55,187.67 648.03,190.19 645.51,187.67 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='645.51,189.88 648.03,187.36 650.55,189.88 648.03,192.40 645.51,189.88 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='608.41,194.52 610.93,192.00 613.45,194.52 610.93,197.04 608.41,194.52 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='608.41,175.35 610.93,172.83 613.45,175.35 610.93,177.87 608.41,175.35 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='568.79,166.87 571.31,164.35 573.83,166.87 571.31,169.39 568.79,166.87 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='568.79,177.93 571.31,175.41 573.83,177.93 571.31,180.45 568.79,177.93 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='530.02,201.80 532.54,199.28 535.06,201.80 532.54,204.32 530.02,201.80 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='530.02,207.70 532.54,205.18 535.06,207.70 532.54,210.22 530.02,207.70 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='487.92,169.01 490.44,166.49 492.96,169.01 490.44,171.53 487.92,169.01 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='487.92,191.13 490.44,188.61 492.96,191.13 490.44,193.65 487.92,191.13 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='463.21,175.74 465.73,173.22 468.25,175.74 465.73,178.26 463.21,175.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='463.21,180.90 465.73,178.38 468.25,180.90 465.73,183.42 463.21,180.90 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='446.14,180.35 448.66,177.83 451.18,180.35 448.66,182.87 446.14,180.35 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='446.14,176.67 448.66,174.15 451.18,176.67 448.66,179.19 446.14,176.67 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.76,207.17 686.16,203.01 681.36,203.01 683.76,207.17 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.76,210.12 686.16,205.96 681.36,205.96 683.76,210.12 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='676.11,159.93 678.51,155.77 673.71,155.77 676.11,159.93 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='676.11,134.86 678.51,130.70 673.71,130.70 676.11,134.86 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='661.80,199.87 664.20,195.71 659.40,195.71 661.80,199.87 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='661.80,168.91 664.20,164.75 659.40,164.75 661.80,168.91 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='636.76,203.78 639.16,199.62 634.36,199.62 636.76,203.78 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='636.76,206.73 639.16,202.57 634.36,202.57 636.76,206.73 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='602.23,198.57 604.63,194.41 599.83,194.41 602.23,198.57 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='602.23,129.26 604.63,125.10 599.83,125.10 602.23,129.26 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='556.91,230.48 559.31,226.32 554.51,226.32 556.91,230.48 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='556.91,169.28 559.31,165.13 554.51,165.13 556.91,169.28 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='507.74,186.46 510.14,182.31 505.34,182.31 507.74,186.46 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='507.74,176.88 510.14,172.72 505.34,172.72 507.74,176.88 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='485.04,192.95 487.44,188.80 482.64,188.80 485.04,192.95 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='485.04,188.53 487.44,184.37 482.64,184.37 485.04,188.53 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='469.56,188.86 471.96,184.70 467.16,184.70 469.56,188.86 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='469.56,173.38 471.96,169.22 467.16,169.22 469.56,173.38 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='681.44' y='151.73' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='681.44' y1='155.29' x2='685.00' y2='151.73' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='681.44' y1='151.73' x2='685.00' y2='155.29' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='681.44' y='222.51' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='681.44' y1='226.07' x2='685.00' y2='222.51' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='681.44' y1='222.51' x2='685.00' y2='226.07' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='668.91' y='200.16' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='668.91' y1='203.73' x2='672.47' y2='200.16' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='668.91' y1='200.16' x2='672.47' y2='203.73' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='668.91' y='152.24' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='668.91' y1='155.80' x2='672.47' y2='152.24' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='668.91' y1='152.24' x2='672.47' y2='155.80' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='646.12' y='108.81' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='646.12' y1='112.37' x2='649.69' y2='108.81' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='646.12' y1='108.81' x2='649.69' y2='112.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='646.12' y='186.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='646.12' y1='190.53' x2='649.69' y2='186.96' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='646.12' y1='186.96' x2='649.69' y2='190.53' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='608.27' y='143.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='608.27' y1='147.06' x2='611.83' y2='143.49' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='608.27' y1='143.49' x2='611.83' y2='147.06' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='608.27' y='234.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='608.27' y1='238.48' x2='611.83' y2='234.92' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='608.27' y1='234.92' x2='611.83' y2='238.48' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='560.44' y='210.90' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='560.44' y1='214.47' x2='564.00' y2='210.90' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='560.44' y1='210.90' x2='564.00' y2='214.47' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='560.44' y='188.78' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='560.44' y1='192.35' x2='564.00' y2='188.78' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='560.44' y1='188.78' x2='564.00' y2='192.35' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='505.60' y='174.77' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='505.60' y1='178.34' x2='509.16' y2='174.77' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='505.60' y1='174.77' x2='509.16' y2='178.34' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='505.60' y='182.88' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='505.60' y1='186.45' x2='509.16' y2='182.88' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='505.60' y1='182.88' x2='509.16' y2='186.45' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='455.31' y='171.37' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.31' y1='174.93' x2='458.88' y2='171.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.31' y1='171.37' x2='458.88' y2='174.93' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='455.31' y='169.16' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.31' y1='172.72' x2='458.88' y2='169.16' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.31' y1='169.16' x2='458.88' y2='172.72' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='435.32' y='184.57' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.32' y1='188.13' x2='438.89' y2='184.57' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.32' y1='184.57' x2='438.89' y2='188.13' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='435.32' y='178.67' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.32' y1='182.23' x2='438.89' y2='178.67' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='435.32' y1='178.67' x2='438.89' y2='182.23' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='424.22' y='183.47' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='424.22' y1='187.03' x2='427.78' y2='183.47' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='424.22' y1='183.47' x2='427.78' y2='187.03' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='424.22' y='196.00' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='424.22' y1='199.56' x2='427.78' y2='196.00' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='424.22' y1='196.00' x2='427.78' y2='199.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.90' y1='154.34' x2='689.47' y2='150.78' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.90' y1='150.78' x2='689.47' y2='154.34' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.17' y1='152.56' x2='690.21' y2='152.56' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='687.69' y1='155.08' x2='687.69' y2='150.04' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.90' y1='231.02' x2='689.47' y2='227.45' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.90' y1='227.45' x2='689.47' y2='231.02' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.17' y1='229.24' x2='690.21' y2='229.24' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='687.69' y1='231.76' x2='687.69' y2='226.72' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='667.34' y1='212.37' x2='670.90' y2='208.81' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='667.34' y1='208.81' x2='670.90' y2='212.37' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='666.60' y1='210.59' x2='671.64' y2='210.59' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='669.12' y1='213.11' x2='669.12' y2='208.07' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='667.34' y1='137.91' x2='670.90' y2='134.34' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='667.34' y1='134.34' x2='670.90' y2='137.91' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='666.60' y1='136.13' x2='671.64' y2='136.13' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='669.12' y1='138.65' x2='669.12' y2='133.60' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.03' y1='204.40' x2='639.59' y2='200.83' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.03' y1='200.83' x2='639.59' y2='204.40' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='635.29' y1='202.61' x2='640.33' y2='202.61' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='637.81' y1='205.13' x2='637.81' y2='200.09' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.03' y1='128.45' x2='639.59' y2='124.89' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='636.03' y1='124.89' x2='639.59' y2='128.45' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='635.29' y1='126.67' x2='640.33' y2='126.67' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='637.81' y1='129.19' x2='637.81' y2='124.15' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='591.01' y1='209.69' x2='594.57' y2='206.13' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='591.01' y1='206.13' x2='594.57' y2='209.69' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='590.27' y1='207.91' x2='595.31' y2='207.91' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='592.79' y1='210.43' x2='592.79' y2='205.39' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='591.01' y1='185.36' x2='594.57' y2='181.80' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='591.01' y1='181.80' x2='594.57' y2='185.36' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='590.27' y1='183.58' x2='595.31' y2='183.58' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='592.79' y1='186.10' x2='592.79' y2='181.06' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='546.18' y1='162.13' x2='549.74' y2='158.56' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='546.18' y1='158.56' x2='549.74' y2='162.13' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='545.44' y1='160.34' x2='550.48' y2='160.34' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='547.96' y1='162.86' x2='547.96' y2='157.82' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='546.18' y1='187.93' x2='549.74' y2='184.37' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='546.18' y1='184.37' x2='549.74' y2='187.93' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='545.44' y1='186.15' x2='550.48' y2='186.15' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='547.96' y1='188.67' x2='547.96' y2='183.63' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='508.25' y1='176.38' x2='511.81' y2='172.81' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='508.25' y1='172.81' x2='511.81' y2='176.38' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='507.51' y1='174.60' x2='512.55' y2='174.60' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='510.03' y1='177.12' x2='510.03' y2='172.08' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='508.25' y1='188.91' x2='511.81' y2='185.35' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='508.25' y1='185.35' x2='511.81' y2='188.91' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='507.51' y1='187.13' x2='512.55' y2='187.13' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='510.03' y1='189.65' x2='510.03' y2='184.61' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='473.77' y1='181.33' x2='477.34' y2='177.76' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='473.77' y1='177.76' x2='477.34' y2='181.33' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='473.04' y1='179.55' x2='478.08' y2='179.55' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='475.56' y1='182.07' x2='475.56' y2='177.03' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='473.77' y1='185.75' x2='477.34' y2='182.19' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='473.77' y1='182.19' x2='477.34' y2='185.75' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='473.04' y1='183.97' x2='478.08' y2='183.97' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='475.56' y1='186.49' x2='475.56' y2='181.45' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.10' y1='194.41' x2='457.66' y2='190.85' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.10' y1='190.85' x2='457.66' y2='194.41' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='453.36' y1='192.63' x2='458.40' y2='192.63' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.88' y1='195.15' x2='455.88' y2='190.11' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.10' y1='192.94' x2='457.66' y2='189.38' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.10' y1='189.38' x2='457.66' y2='192.94' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='453.36' y1='191.16' x2='458.40' y2='191.16' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.88' y1='193.68' x2='455.88' y2='188.64' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='440.38' y1='192.98' x2='443.94' y2='189.41' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='440.38' y1='189.41' x2='443.94' y2='192.98' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.64' y1='191.19' x2='444.68' y2='191.19' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='442.16' y1='193.71' x2='442.16' y2='188.67' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='440.38' y1='197.40' x2='443.94' y2='193.83' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='440.38' y1='193.83' x2='443.94' y2='197.40' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.64' y1='195.62' x2='444.68' y2='195.62' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='442.16' y1='198.14' x2='442.16' y2='193.10' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.56' y1='248.08' x2='690.60' y2='248.08' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='688.08' y1='250.60' x2='688.08' y2='245.56' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='685.56,248.08 688.08,245.56 690.60,248.08 688.08,250.60 685.56,248.08 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.56' y1='107.26' x2='690.60' y2='107.26' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='688.08' y1='109.78' x2='688.08' y2='104.74' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='685.56,107.26 688.08,104.74 690.60,107.26 688.08,109.78 685.56,107.26 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='673.70' y1='195.19' x2='678.74' y2='195.19' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='676.22' y1='197.71' x2='676.22' y2='192.67' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='673.70,195.19 676.22,192.67 678.74,195.19 676.22,197.71 673.70,195.19 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='673.70' y1='237.21' x2='678.74' y2='237.21' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='676.22' y1='239.73' x2='676.22' y2='234.69' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='673.70,237.21 676.22,234.69 678.74,237.21 676.22,239.73 673.70,237.21 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='652.24' y1='147.44' x2='657.28' y2='147.44' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='654.76' y1='149.96' x2='654.76' y2='144.92' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='652.24,147.44 654.76,144.92 657.28,147.44 654.76,149.96 652.24,147.44 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='652.24' y1='190.21' x2='657.28' y2='190.21' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='654.76' y1='192.73' x2='654.76' y2='187.69' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='652.24,190.21 654.76,187.69 657.28,190.21 654.76,192.73 652.24,190.21 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='616.96' y1='200.28' x2='622.00' y2='200.28' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='619.48' y1='202.80' x2='619.48' y2='197.76' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='616.96,200.28 619.48,197.76 622.00,200.28 619.48,202.80 616.96,200.28 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='616.96' y1='170.05' x2='622.00' y2='170.05' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='619.48' y1='172.57' x2='619.48' y2='167.53' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='616.96,170.05 619.48,167.53 622.00,170.05 619.48,172.57 616.96,170.05 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='573.05' y1='159.83' x2='578.09' y2='159.83' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='575.57' y1='162.35' x2='575.57' y2='157.31' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='573.05,159.83 575.57,157.31 578.09,159.83 575.57,162.35 573.05,159.83 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='573.05' y1='199.64' x2='578.09' y2='199.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='575.57' y1='202.16' x2='575.57' y2='197.12' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='573.05,199.64 575.57,197.12 578.09,199.64 575.57,202.16 573.05,199.64 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='523.32' y1='185.16' x2='528.36' y2='185.16' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='525.84' y1='187.68' x2='525.84' y2='182.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='523.32,185.16 525.84,182.64 528.36,185.16 525.84,187.68 523.32,185.16 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='523.32' y1='205.06' x2='528.36' y2='205.06' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='525.84' y1='207.58' x2='525.84' y2='202.54' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='523.32,205.06 525.84,202.54 528.36,205.06 525.84,207.58 523.32,205.06 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='475.25' y1='178.75' x2='480.29' y2='178.75' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='477.77' y1='181.27' x2='477.77' y2='176.23' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='475.25,178.75 477.77,176.23 480.29,178.75 477.77,181.27 475.25,178.75 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='475.25' y1='185.38' x2='480.29' y2='185.38' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='477.77' y1='187.90' x2='477.77' y2='182.86' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='475.25,185.38 477.77,182.86 480.29,185.38 477.77,187.90 475.25,185.38 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='452.62' y1='194.64' x2='457.66' y2='194.64' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.14' y1='197.16' x2='455.14' y2='192.12' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='452.62,194.64 455.14,192.12 457.66,194.64 455.14,197.16 452.62,194.64 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='452.62' y1='173.26' x2='457.66' y2='173.26' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='455.14' y1='175.78' x2='455.14' y2='170.74' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='452.62,173.26 455.14,170.74 457.66,173.26 455.14,175.78 452.62,173.26 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='437.95' y1='166.23' x2='442.99' y2='166.23' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='440.47' y1='168.75' x2='440.47' y2='163.71' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='437.95,166.23 440.47,163.71 442.99,166.23 440.47,168.75 437.95,166.23 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='437.95' y1='193.51' x2='442.99' y2='193.51' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='440.47' y1='196.03' x2='440.47' y2='190.99' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='437.95,193.51 440.47,190.99 442.99,193.51 440.47,196.03 437.95,193.51 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='686.68' cy='187.72' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='684.89' y1='187.72' x2='688.46' y2='187.72' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='686.68' y1='189.50' x2='686.68' y2='185.93' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='686.68' cy='186.24' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='684.89' y1='186.24' x2='688.46' y2='186.24' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='686.68' y1='188.02' x2='686.68' y2='184.46' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='679.67' cy='191.07' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='677.89' y1='191.07' x2='681.45' y2='191.07' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='679.67' y1='192.85' x2='679.67' y2='189.29' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='679.67' cy='206.55' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='677.89' y1='206.55' x2='681.45' y2='206.55' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='679.67' y1='208.33' x2='679.67' y2='204.77' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='666.37' cy='178.91' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='664.59' y1='178.91' x2='668.15' y2='178.91' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='666.37' y1='180.69' x2='666.37' y2='177.13' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='666.37' cy='165.64' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='664.59' y1='165.64' x2='668.15' y2='165.64' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='666.37' y1='167.42' x2='666.37' y2='163.86' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='642.36' cy='132.88' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='640.58' y1='132.88' x2='644.14' y2='132.88' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='642.36' y1='134.66' x2='642.36' y2='131.10' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='642.36' cy='190.39' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='640.58' y1='190.39' x2='644.14' y2='190.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='642.36' y1='192.17' x2='642.36' y2='188.61' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='607.36' cy='201.91' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='605.58' y1='201.91' x2='609.14' y2='201.91' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='607.36' y1='203.69' x2='607.36' y2='200.13' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='607.36' cy='199.70' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='605.58' y1='199.70' x2='609.14' y2='199.70' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='607.36' y1='201.48' x2='607.36' y2='197.91' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='556.98' cy='161.17' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='555.19' y1='161.17' x2='558.76' y2='161.17' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='556.98' y1='162.95' x2='556.98' y2='159.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='556.98' cy='214.99' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='555.19' y1='214.99' x2='558.76' y2='214.99' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='556.98' y1='216.78' x2='556.98' y2='213.21' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='495.01' cy='173.69' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='493.23' y1='173.69' x2='496.79' y2='173.69' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='495.01' y1='175.48' x2='495.01' y2='171.91' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='495.01' cy='174.43' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='493.23' y1='174.43' x2='496.79' y2='174.43' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='495.01' y1='176.21' x2='495.01' y2='172.65' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='466.16' cy='204.82' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='464.38' y1='204.82' x2='467.94' y2='204.82' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='466.16' y1='206.60' x2='466.16' y2='203.04' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='466.16' cy='184.17' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='464.38' y1='184.17' x2='467.94' y2='184.17' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='466.16' y1='185.96' x2='466.16' y2='182.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='448.79' cy='174.10' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='447.01' y1='174.10' x2='450.57' y2='174.10' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='448.79' y1='175.88' x2='448.79' y2='172.32' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='448.79' cy='185.16' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='447.01' y1='185.16' x2='450.57' y2='185.16' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='448.79' y1='186.94' x2='448.79' y2='183.38' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.79,172.45 686.19,167.60 681.39,167.60 683.79,172.45 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.79,166.91 686.19,171.76 681.39,171.76 683.79,166.91 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.79,179.08 686.19,174.23 681.39,174.23 683.79,179.08 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='683.79,173.54 686.19,178.39 681.39,178.39 683.79,173.54 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='677.95,167.51 680.35,162.66 675.55,162.66 677.95,167.51 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='677.95,161.97 680.35,166.82 675.55,166.82 677.95,161.97 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='677.95,251.56 680.35,246.71 675.55,246.71 677.95,251.56 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='677.95,246.02 680.35,250.87 675.55,250.87 677.95,246.02 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='666.81,173.87 669.21,169.02 664.41,169.02 666.81,173.87 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='666.81,168.32 669.21,173.17 664.41,173.17 666.81,168.32 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='666.81,154.70 669.21,149.85 664.41,149.85 666.81,154.70 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='666.81,149.15 669.21,154.00 664.41,154.00 666.81,149.15 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='646.54,218.05 648.94,213.20 644.14,213.20 646.54,218.05 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='646.54,212.50 648.94,217.35 644.14,217.35 646.54,212.50 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='646.54,146.53 648.94,141.68 644.14,141.68 646.54,146.53 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='646.54,140.99 648.94,145.84 644.14,145.84 646.54,140.99 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='616.57,176.96 618.97,172.11 614.17,172.11 616.57,176.96 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='616.57,171.42 618.97,176.27 614.17,176.27 616.57,171.42 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='616.57,157.05 618.97,152.20 614.17,152.20 616.57,157.05 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='616.57,151.51 618.97,156.36 614.17,156.36 616.57,151.51 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='572.35,202.96 574.75,198.11 569.95,198.11 572.35,202.96 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='572.35,197.42 574.75,202.27 569.95,202.27 572.35,197.42 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='572.35,225.08 574.75,220.23 569.95,220.23 572.35,225.08 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='572.35,219.54 574.75,224.39 569.95,224.39 572.35,219.54 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='515.42,187.19 517.82,182.34 513.02,182.34 515.42,187.19 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='515.42,181.65 517.82,186.50 513.02,186.50 515.42,181.65 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='515.42,179.82 517.82,174.97 513.02,174.97 515.42,179.82 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='515.42,174.28 517.82,179.13 513.02,179.13 515.42,174.28 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='487.17,169.51 489.57,164.66 484.77,164.66 487.17,169.51 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='487.17,163.97 489.57,168.82 484.77,168.82 487.17,163.97 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='487.17,199.74 489.57,194.89 484.77,194.89 487.17,199.74 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='487.17,194.20 489.57,199.05 484.77,199.05 487.17,194.20 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='468.93,180.96 471.33,176.11 466.53,176.11 468.93,180.96 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='468.93,175.41 471.33,180.26 466.53,180.26 468.93,175.41 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='468.93,181.69 471.33,176.84 466.53,176.84 468.93,181.69 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='468.93,176.15 471.33,181.00 466.53,181.00 468.93,176.15 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='681.90' y1='125.73' x2='685.46' y2='125.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='683.68' y1='127.51' x2='683.68' y2='123.95' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='681.90' y='123.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='681.90' y1='194.30' x2='685.46' y2='194.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='683.68' y1='196.08' x2='683.68' y2='192.52' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='681.90' y='192.52' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='674.82' y1='192.69' x2='678.38' y2='192.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='676.60' y1='194.47' x2='676.60' y2='190.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='674.82' y='190.91' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='674.82' y1='166.88' x2='678.38' y2='166.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='676.60' y1='168.67' x2='676.60' y2='165.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='674.82' y='165.10' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.38' y1='260.53' x2='664.94' y2='260.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='663.16' y1='262.31' x2='663.16' y2='258.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='661.38' y='258.75' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='661.38' y1='170.58' x2='664.94' y2='170.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='663.16' y1='172.36' x2='663.16' y2='168.80' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='661.38' y='168.80' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='637.12' y1='139.96' x2='640.68' y2='139.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='638.90' y1='141.74' x2='638.90' y2='138.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='637.12' y='138.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='637.12' y1='209.27' x2='640.68' y2='209.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='638.90' y1='211.05' x2='638.90' y2='207.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='637.12' y='207.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='601.78' y1='169.35' x2='605.35' y2='169.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='603.57' y1='171.13' x2='603.57' y2='167.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='601.78' y='167.57' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='601.78' y1='181.88' x2='605.35' y2='181.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='603.57' y1='183.67' x2='603.57' y2='180.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='601.78' y='180.10' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='551.04' y1='177.51' x2='554.60' y2='177.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='552.82' y1='179.29' x2='552.82' y2='175.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='551.04' y='175.73' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='551.04' y1='186.36' x2='554.60' y2='186.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='552.82' y1='188.14' x2='552.82' y2='184.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='551.04' y='184.58' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='489.27' y1='180.66' x2='492.83' y2='180.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='491.05' y1='182.44' x2='491.05' y2='178.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='489.27' y='178.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='489.27' y1='179.18' x2='492.83' y2='179.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='491.05' y1='180.96' x2='491.05' y2='177.40' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='489.27' y='177.40' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='461.12' y1='173.75' x2='464.69' y2='173.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='462.90' y1='175.54' x2='462.90' y2='171.97' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='461.12' y='171.97' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='461.12' y1='195.13' x2='464.69' y2='195.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='462.90' y1='196.92' x2='462.90' y2='193.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='461.12' y='193.35' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='444.50' y1='187.49' x2='448.06' y2='187.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='446.28' y1='189.27' x2='446.28' y2='185.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='444.50' y='185.71' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='444.50' y1='183.07' x2='448.06' y2='183.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='446.28' y1='184.85' x2='446.28' y2='181.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='444.50' y='181.28' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='687.57' cy='173.52' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.79' y1='175.30' x2='689.35' y2='171.73' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.79' y1='171.73' x2='689.35' y2='175.30' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='687.57' cy='158.03' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.79' y1='159.81' x2='689.35' y2='156.25' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='685.79' y1='156.25' x2='689.35' y2='159.81' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='679.62' cy='187.51' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='677.84' y1='189.29' x2='681.41' y2='185.72' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='677.84' y1='185.72' x2='681.41' y2='189.29' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='679.62' cy='239.85' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='677.84' y1='241.64' x2='681.41' y2='238.07' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='677.84' y1='238.07' x2='681.41' y2='241.64' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='664.61' cy='172.58' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='662.83' y1='174.36' x2='666.39' y2='170.80' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='662.83' y1='170.80' x2='666.39' y2='174.36' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='664.61' cy='230.09' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='662.83' y1='231.87' x2='666.39' y2='228.31' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='662.83' y1='228.31' x2='666.39' y2='231.87' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='637.76' cy='177.68' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='635.98' y1='179.46' x2='639.54' y2='175.90' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='635.98' y1='175.90' x2='639.54' y2='179.46' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='637.76' cy='190.95' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='635.98' y1='192.73' x2='639.54' y2='189.17' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='635.98' y1='189.17' x2='639.54' y2='192.73' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='599.30' cy='183.78' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='597.51' y1='185.56' x2='601.08' y2='182.00' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='597.51' y1='182.00' x2='601.08' y2='185.56' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='599.30' cy='152.81' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='597.51' y1='154.60' x2='601.08' y2='151.03' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='597.51' y1='151.03' x2='601.08' y2='154.60' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='545.63' cy='176.93' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='543.85' y1='178.71' x2='547.41' y2='175.15' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='543.85' y1='175.15' x2='547.41' y2='178.71' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='545.63' cy='185.04' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='543.85' y1='186.82' x2='547.41' y2='183.26' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='543.85' y1='183.26' x2='547.41' y2='186.82' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='483.49' cy='164.86' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='481.70' y1='166.64' x2='485.27' y2='163.08' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='481.70' y1='163.08' x2='485.27' y2='166.64' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='483.49' cy='183.29' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='481.70' y1='185.07' x2='485.27' y2='181.51' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='481.70' y1='181.51' x2='485.27' y2='185.07' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='456.53' cy='168.76' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.75' y1='170.55' x2='458.32' y2='166.98' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.75' y1='166.98' x2='458.32' y2='170.55' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='456.53' cy='198.26' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.75' y1='200.04' x2='458.32' y2='196.47' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='454.75' y1='196.47' x2='458.32' y2='200.04' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='441.04' cy='191.25' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.26' y1='193.03' x2='442.82' y2='189.46' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.26' y1='189.46' x2='442.82' y2='193.03' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<circle cx='441.04' cy='197.88' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.26' y1='199.66' x2='442.82' y2='196.10' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<line x1='439.26' y1='196.10' x2='442.82' y2='199.66' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='687.90,206.23 689.68,209.79 686.12,209.79 687.90,206.23 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='686.12' y='206.23' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='687.90,176.00 689.68,179.56 686.12,179.56 687.90,176.00 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='686.12' y='176.00' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='677.38,185.85 679.17,189.42 675.60,189.42 677.38,185.85 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='675.60' y='185.85' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='677.38,233.04 679.17,236.60 675.60,236.60 677.38,233.04 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='675.60' y='233.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='658.13,166.09 659.92,169.66 656.35,169.66 658.13,166.09 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='656.35' y='166.09' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='658.13,146.92 659.92,150.49 656.35,150.49 658.13,146.92 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='656.35' y='146.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='625.76,182.36 627.54,185.93 623.98,185.93 625.76,182.36 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='623.98' y='182.36' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='625.76,186.79 627.54,190.35 623.98,190.35 625.76,186.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='623.98' y='186.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='583.91,153.32 585.70,156.88 582.13,156.88 583.91,153.32 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='582.13' y='153.32' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='583.91,194.60 585.70,198.17 582.13,198.17 583.91,194.60 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='582.13' y='194.60' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='533.83,192.12 535.62,195.68 532.05,195.68 533.83,192.12 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='532.05' y='192.12' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='533.83,205.39 535.62,208.95 532.05,208.95 533.83,205.39 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='532.05' y='205.39' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='483.20,178.59 484.98,182.15 481.42,182.15 483.20,178.59 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='481.42' y='178.59' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='483.20,174.90 484.98,178.47 481.42,178.47 483.20,174.90 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='481.42' y='174.90' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='459.51,175.93 461.30,179.49 457.73,179.49 459.51,175.93 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='457.73' y='175.93' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='459.51,191.41 461.30,194.97 457.73,194.97 459.51,191.41 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='457.73' y='191.41' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='444.11,174.57 445.90,178.13 442.33,178.13 444.11,174.57 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='442.33' y='174.57' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polyline points='444.11,176.04 445.90,179.61 442.33,179.61 444.11,176.04 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<rect x='442.33' y='176.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='687.11,210.09 690.67,210.09 690.67,206.52 687.11,206.52 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='687.11,218.20 690.67,218.20 690.67,214.63 687.11,214.63 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='675.39,198.09 678.95,198.09 678.95,194.53 675.39,194.53 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='675.39,185.56 678.95,185.56 678.95,182.00 675.39,182.00 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='654.29,169.30 657.86,169.30 657.86,165.74 654.29,165.74 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='654.29,197.32 657.86,197.32 657.86,193.75 654.29,193.75 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='619.91,185.79 623.48,185.79 623.48,182.23 619.91,182.23 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='619.91,176.21 623.48,176.21 623.48,172.64 619.91,172.64 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='577.88,186.75 581.44,186.75 581.44,183.19 577.88,183.19 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='577.88,155.05 581.44,155.05 581.44,151.49 577.88,151.49 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='531.78,181.67 535.34,181.67 535.34,178.11 531.78,178.11 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='531.78,197.89 535.34,197.89 535.34,194.33 531.78,194.33 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='488.59,184.27 492.15,184.27 492.15,180.70 488.59,180.70 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='488.59,182.79 492.15,182.79 492.15,179.23 488.59,179.23 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='467.10,181.59 470.66,181.59 470.66,178.03 467.10,178.03 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='467.10,188.23 470.66,188.23 470.66,184.66 467.10,184.66 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='451.84,179.85 455.40,179.85 455.40,176.28 451.84,176.28 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' /> +<polygon points='451.84,202.70 455.40,202.70 455.40,199.14 451.84,199.14 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyODMuNDl8ODIuNDU=)' />  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU='> -    <rect x='38.97' y='337.35' width='301.08' height='190.18' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU='> +    <rect x='38.97' y='322.45' width='301.08' height='205.08' />    </clipPath>  </defs> -<polyline points='50.12,520.49 52.44,515.99 55.81,509.71 57.09,507.39 61.50,499.67 66.38,491.60 67.19,490.32 72.87,481.61 78.56,473.50 82.64,468.03 84.25,465.94 89.94,458.91 95.63,452.37 101.32,446.29 107.01,440.63 112.70,435.37 115.16,433.21 118.39,430.49 124.08,425.95 129.77,421.74 135.46,417.84 141.15,414.22 146.83,410.86 152.52,407.76 158.21,404.89 163.90,402.24 169.59,399.79 175.28,397.54 180.97,395.46 186.66,393.55 189.50,392.66 192.35,391.80 198.04,390.20 203.73,388.73 209.42,387.40 215.11,386.18 220.79,385.08 226.48,384.09 232.17,383.19 237.86,382.39 243.55,381.67 249.24,381.04 254.93,380.48 259.20,380.11 260.62,380.00 266.31,379.58 272.00,379.23 277.69,378.93 283.38,378.70 289.07,378.51 294.76,378.37 300.44,378.28 306.13,378.23 311.82,378.22 317.51,378.25 323.20,378.31 328.89,378.41 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> +<polyline points='50.12,519.93 52.44,513.91 55.81,505.55 57.09,502.48 61.50,492.35 66.38,481.89 67.19,480.24 72.87,469.13 78.56,458.94 82.64,452.18 84.25,449.62 89.94,441.09 95.63,433.29 101.32,426.17 107.01,419.67 112.70,413.76 115.16,411.36 118.39,408.38 124.08,403.49 129.77,399.07 135.46,395.07 141.15,391.47 146.83,388.23 152.52,385.33 158.21,382.74 163.90,380.44 169.59,378.41 175.28,376.63 180.97,375.07 186.66,373.74 189.50,373.14 192.35,372.60 198.04,371.64 203.73,370.85 209.42,370.22 215.11,369.74 220.79,369.39 226.48,369.17 232.17,369.06 237.86,369.06 243.55,369.17 249.24,369.36 254.93,369.64 259.20,369.90 260.62,369.99 266.31,370.42 272.00,370.92 277.69,371.48 283.38,372.10 289.07,372.77 294.76,373.49 300.44,374.25 306.13,375.05 311.82,375.90 317.51,376.77 323.20,377.68 328.89,378.62 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' />  <defs>    <clipPath id='cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA='>      <rect x='0.00' y='0.00' width='720.00' height='576.00' /> @@ -1374,558 +1374,558 @@  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='231.58' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g>  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='275.84' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g>  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='322.30' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>120</text></g> -<line x1='38.97' y1='520.49' x2='38.97' y2='373.13' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='520.49' x2='34.21' y2='520.49' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='483.65' x2='34.21' y2='483.65' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='446.81' x2='34.21' y2='446.81' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='409.97' x2='34.21' y2='409.97' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='373.13' x2='34.21' y2='373.13' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,522.68) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,488.04) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,451.20) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,414.36) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>30</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,377.52) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> -<polyline points='38.97,527.53 340.04,527.53 340.04,337.35 38.97,337.35 38.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='519.93' x2='38.97' y2='330.52' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='519.93' x2='34.21' y2='519.93' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='472.58' x2='34.21' y2='472.58' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='425.23' x2='34.21' y2='425.23' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='377.88' x2='34.21' y2='377.88' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='330.52' x2='34.21' y2='330.52' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,522.13) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,476.97) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,429.62) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,382.27) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>30</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,334.91) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> +<polyline points='38.97,527.53 340.04,527.53 340.04,322.45 38.97,322.45 38.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMC4wMHwzNjAuMDB8NTc2LjAwfDMxNy4zOQ=='> -    <rect x='0.00' y='317.39' width='360.00' height='258.61' /> +  <clipPath id='cpMC4wMHwzNjAuMDB8NTc2LjAwfDMxMi4wMA=='> +    <rect x='0.00' y='312.00' width='360.00' height='264.00' />    </clipPath>  </defs> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDMxNy4zOQ==)'><text x='180.87' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDMxNy4zOQ==)'><text transform='translate(8.55,437.93) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='10.98px' lengthAdjust='spacingAndGlyphs'>m1</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDMxMi4wMA==)'><text x='180.87' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDMxMi4wMA==)'><text transform='translate(8.55,448.05) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='46.11px' lengthAdjust='spacingAndGlyphs'>Residues m1</text></g>  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU='> -    <rect x='38.97' y='337.35' width='301.08' height='190.18' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU='> +    <rect x='38.97' y='322.45' width='301.08' height='205.08' />    </clipPath>  </defs> -<circle cx='52.44' cy='511.64' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='52.44' cy='513.49' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='57.09' cy='498.75' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='57.09' cy='504.28' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='66.38' cy='486.59' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='66.38' cy='490.65' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='82.64' cy='459.33' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='82.64' cy='470.01' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='115.16' cy='433.91' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='115.16' cy='432.07' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='189.50' cy='404.81' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='189.50' cy='419.91' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='259.20' cy='401.86' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='259.20' cy='408.86' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='328.89' cy='388.60' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='328.89' cy='403.70' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,513.09 55.81,503.61 57.09,500.35 61.50,490.35 66.38,481.16 67.19,479.80 72.87,471.29 78.56,464.32 82.64,460.06 84.25,458.51 89.94,453.59 95.63,449.35 101.32,445.64 107.01,442.35 112.70,439.39 115.16,438.19 118.39,436.69 124.08,434.21 129.77,431.91 135.46,429.77 141.15,427.76 146.83,425.87 152.52,424.08 158.21,422.38 163.90,420.78 169.59,419.25 175.28,417.79 180.97,416.41 186.66,415.10 189.50,414.46 192.35,413.85 198.04,412.66 203.73,411.52 209.42,410.45 215.11,409.42 220.79,408.45 226.48,407.53 232.17,406.66 237.86,405.83 243.55,405.05 249.24,404.32 254.93,403.62 259.20,403.13 260.62,402.97 266.31,402.35 272.00,401.77 277.69,401.23 283.38,400.73 289.07,400.26 294.76,399.82 300.44,399.42 306.13,399.04 311.82,398.70 317.51,398.38 323.20,398.10 328.89,397.84 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,517.35 54.84,521.50 50.04,521.50 52.44,517.35 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,510.71 54.84,514.87 50.04,514.87 52.44,510.71 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,503.72 59.49,507.87 54.69,507.87 57.09,503.72 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,511.45 59.49,515.61 54.69,515.61 57.09,511.45 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,488.24 68.78,492.40 63.98,492.40 66.38,488.24 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,492.66 68.78,496.82 63.98,496.82 66.38,492.66 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,464.30 85.04,468.45 80.24,468.45 82.64,464.30 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,471.66 85.04,475.82 80.24,475.82 82.64,471.66 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,451.03 117.56,455.19 112.76,455.19 115.16,451.03 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,437.03 117.56,441.19 112.76,441.19 115.16,437.03 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,421.19 191.90,425.35 187.10,425.35 189.50,421.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,424.14 191.90,428.30 187.10,428.30 189.50,424.14 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,407.56 261.60,411.72 256.80,411.72 259.20,407.56 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,407.19 261.60,411.35 256.80,411.35 259.20,407.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,417.51 331.29,421.67 326.49,421.67 328.89,417.51 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,407.19 331.29,411.35 326.49,411.35 328.89,407.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,515.68 55.81,509.08 57.09,506.68 61.50,498.84 66.38,490.90 67.19,489.66 72.87,481.41 78.56,474.00 82.64,469.15 84.25,467.33 89.94,461.33 95.63,455.93 101.32,451.06 107.01,446.66 112.70,442.70 115.16,441.10 118.39,439.11 124.08,435.87 129.77,432.93 135.46,430.27 141.15,427.86 146.83,425.66 152.52,423.67 158.21,421.86 163.90,420.21 169.59,418.71 175.28,417.34 180.97,416.09 186.66,414.95 189.50,414.41 192.35,413.90 198.04,412.95 203.73,412.08 209.42,411.28 215.11,410.55 220.79,409.88 226.48,409.26 232.17,408.70 237.86,408.19 243.55,407.72 249.24,407.29 254.93,406.90 259.20,406.63 260.62,406.54 266.31,406.22 272.00,405.93 277.69,405.66 283.38,405.42 289.07,405.21 294.76,405.02 300.44,404.85 306.13,404.70 311.82,404.57 317.51,404.46 323.20,404.37 328.89,404.30 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='49.92' y1='513.49' x2='54.96' y2='513.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='516.01' x2='52.44' y2='510.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='54.57' y1='508.33' x2='59.61' y2='508.33' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='510.85' x2='57.09' y2='505.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='54.57' y1='512.75' x2='59.61' y2='512.75' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='515.27' x2='57.09' y2='510.23' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='63.86' y1='483.65' x2='68.90' y2='483.65' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='486.17' x2='66.38' y2='481.13' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='63.86' y1='486.96' x2='68.90' y2='486.96' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='489.48' x2='66.38' y2='484.44' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.12' y1='469.28' x2='85.16' y2='469.28' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='471.80' x2='82.64' y2='466.76' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.12' y1='462.65' x2='85.16' y2='462.65' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='465.17' x2='82.64' y2='460.13' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='112.64' y1='437.96' x2='117.68' y2='437.96' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='440.48' x2='115.16' y2='435.44' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='112.64' y1='435.39' x2='117.68' y2='435.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='437.91' x2='115.16' y2='432.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='186.98' y1='404.81' x2='192.02' y2='404.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='407.33' x2='189.50' y2='402.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='186.98' y1='387.86' x2='192.02' y2='387.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='390.38' x2='189.50' y2='385.34' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='256.68' y1='386.02' x2='261.72' y2='386.02' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='388.54' x2='259.20' y2='383.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='256.68' y1='394.86' x2='261.72' y2='394.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='397.38' x2='259.20' y2='392.34' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='326.37' y1='387.49' x2='331.41' y2='387.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='390.01' x2='328.89' y2='384.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='326.37' y1='378.28' x2='331.41' y2='378.28' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='380.80' x2='328.89' y2='375.76' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,516.19 55.81,510.20 57.09,507.99 61.50,500.65 66.38,493.00 67.19,491.78 72.87,483.54 78.56,475.89 82.64,470.74 84.25,468.78 89.94,462.18 95.63,456.04 101.32,450.33 107.01,445.03 112.70,440.10 115.16,438.08 118.39,435.52 124.08,431.26 129.77,427.30 135.46,423.62 141.15,420.20 146.83,417.02 152.52,414.06 158.21,411.32 163.90,408.77 169.59,406.40 175.28,404.20 180.97,402.16 186.66,400.27 189.50,399.38 192.35,398.52 198.04,396.90 203.73,395.40 209.42,394.01 215.11,392.73 220.79,391.55 226.48,390.47 232.17,389.47 237.86,388.55 243.55,387.72 249.24,386.95 254.93,386.25 259.20,385.77 260.62,385.62 266.31,385.05 272.00,384.53 277.69,384.07 283.38,383.66 289.07,383.30 294.76,382.98 300.44,382.71 306.13,382.48 311.82,382.28 317.51,382.12 323.20,382.00 328.89,381.90 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='513.79' x2='54.22' y2='510.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='510.23' x2='54.22' y2='513.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='509.37' x2='54.22' y2='505.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='505.81' x2='54.22' y2='509.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='502.37' x2='58.87' y2='498.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='498.81' x2='58.87' y2='502.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='510.11' x2='58.87' y2='506.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='506.55' x2='58.87' y2='510.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='484.32' x2='68.16' y2='480.76' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='480.76' x2='68.16' y2='484.32' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='485.43' x2='68.16' y2='481.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='481.86' x2='68.16' y2='485.43' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='452.64' x2='84.42' y2='449.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='449.08' x2='84.42' y2='452.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='468.11' x2='84.42' y2='464.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='464.55' x2='84.42' y2='468.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='417.27' x2='116.95' y2='413.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='413.71' x2='116.95' y2='417.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='420.22' x2='116.95' y2='416.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='416.66' x2='116.95' y2='420.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='374.91' x2='191.29' y2='371.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='371.34' x2='191.29' y2='374.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='368.64' x2='191.29' y2='365.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='365.08' x2='191.29' y2='368.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='360.91' x2='260.98' y2='357.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='357.34' x2='260.98' y2='360.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='354.65' x2='260.98' y2='351.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='351.08' x2='260.98' y2='354.65' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='357.22' x2='330.67' y2='353.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='353.66' x2='330.67' y2='357.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='347.65' x2='330.67' y2='344.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='344.08' x2='330.67' y2='347.65' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,514.82 55.81,506.95 57.09,504.06 61.50,494.51 66.38,484.64 67.19,483.07 72.87,472.55 78.56,462.87 82.64,456.41 84.25,453.96 89.94,445.75 95.63,438.18 101.32,431.20 107.01,424.76 112.70,418.83 115.16,416.40 118.39,413.34 124.08,408.28 129.77,403.60 135.46,399.28 141.15,395.28 146.83,391.59 152.52,388.18 158.21,385.02 163.90,382.10 169.59,379.40 175.28,376.91 180.97,374.60 186.66,372.47 189.50,371.46 192.35,370.50 198.04,368.68 203.73,367.00 209.42,365.45 215.11,364.03 220.79,362.72 226.48,361.51 232.17,360.40 237.86,359.39 243.55,358.46 249.24,357.61 254.93,356.84 259.20,356.31 260.62,356.14 266.31,355.51 272.00,354.94 277.69,354.43 283.38,353.98 289.07,353.57 294.76,353.22 300.44,352.92 306.13,352.66 311.82,352.44 317.51,352.26 323.20,352.12 328.89,352.01 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='49.92,515.33 52.44,512.81 54.96,515.33 52.44,517.85 49.92,515.33 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='49.92,512.38 52.44,509.86 54.96,512.38 52.44,514.90 49.92,512.38 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='54.57,502.07 57.09,499.55 59.61,502.07 57.09,504.59 54.57,502.07 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='54.57,500.22 57.09,497.70 59.61,500.22 57.09,502.74 54.57,500.22 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='63.86,485.12 66.38,482.60 68.90,485.12 66.38,487.64 63.86,485.12 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='63.86,482.54 66.38,480.02 68.90,482.54 66.38,485.06 63.86,482.54 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='80.12,457.86 82.64,455.34 85.16,457.86 82.64,460.38 80.12,457.86 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='80.12,465.23 82.64,462.71 85.16,465.23 82.64,467.75 80.12,465.23 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='112.64,442.75 115.16,440.23 117.68,442.75 115.16,445.27 112.64,442.75 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='112.64,440.91 115.16,438.39 117.68,440.91 115.16,443.43 112.64,440.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='186.98,422.86 189.50,420.34 192.02,422.86 189.50,425.38 186.98,422.86 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='186.98,421.75 189.50,419.23 192.02,421.75 189.50,424.27 186.98,421.75 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='256.68,421.02 259.20,418.50 261.72,421.02 259.20,423.54 256.68,421.02 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='256.68,416.60 259.20,414.08 261.72,416.60 259.20,419.12 256.68,416.60 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='326.37,412.54 328.89,410.02 331.41,412.54 328.89,415.06 326.37,412.54 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='326.37,430.96 328.89,428.44 331.41,430.96 328.89,433.48 326.37,430.96 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,512.82 55.81,503.09 57.09,499.76 61.50,489.67 66.38,480.56 67.19,479.23 72.87,471.01 78.56,464.46 82.64,460.57 84.25,459.18 89.94,454.84 95.63,451.23 101.32,448.17 107.01,445.53 112.70,443.23 115.16,442.32 118.39,441.19 124.08,439.36 129.77,437.70 135.46,436.18 141.15,434.78 146.83,433.48 152.52,432.26 158.21,431.12 163.90,430.04 169.59,429.03 175.28,428.08 180.97,427.18 186.66,426.33 189.50,425.92 192.35,425.53 198.04,424.77 203.73,424.05 209.42,423.37 215.11,422.74 220.79,422.14 226.48,421.57 232.17,421.04 237.86,420.55 243.55,420.08 249.24,419.65 254.93,419.25 259.20,418.96 260.62,418.87 266.31,418.53 272.00,418.21 277.69,417.92 283.38,417.65 289.07,417.41 294.76,417.19 300.44,416.99 306.13,416.82 311.82,416.66 317.51,416.53 323.20,416.42 328.89,416.33 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,512.94 54.84,508.78 50.04,508.78 52.44,512.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,512.20 54.84,508.05 50.04,508.05 52.44,512.20 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,511.47 59.49,507.31 54.69,507.31 57.09,511.47 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,519.20 59.49,515.05 54.69,515.05 57.09,519.20 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,495.63 68.78,491.47 63.98,491.47 66.38,495.63 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,498.94 68.78,494.79 63.98,494.79 66.38,498.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,473.15 85.04,469.00 80.24,469.00 82.64,473.15 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,479.79 85.04,475.63 80.24,475.63 82.64,479.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,455.10 117.56,450.95 112.76,450.95 115.16,455.10 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,456.94 117.56,452.79 112.76,452.79 115.16,456.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,444.05 191.90,439.89 187.10,439.89 189.50,444.05 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,440.37 191.90,436.21 187.10,436.21 189.50,440.37 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,430.79 261.60,426.63 256.80,426.63 259.20,430.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,427.84 261.60,423.68 256.80,423.68 259.20,427.84 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,434.47 331.29,430.32 326.49,430.32 328.89,434.47 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,435.95 331.29,431.79 326.49,431.79 328.89,435.95 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,516.40 55.81,510.83 57.09,508.81 61.50,502.25 66.38,495.66 67.19,494.63 72.87,487.85 78.56,481.81 82.64,477.89 84.25,476.42 89.94,471.62 95.63,467.32 101.32,463.47 107.01,460.02 112.70,456.92 115.16,455.67 118.39,454.13 124.08,451.62 129.77,449.35 135.46,447.30 141.15,445.45 146.83,443.76 152.52,442.23 158.21,440.83 163.90,439.56 169.59,438.40 175.28,437.33 180.97,436.35 186.66,435.45 189.50,435.03 192.35,434.63 198.04,433.86 203.73,433.16 209.42,432.51 215.11,431.90 220.79,431.34 226.48,430.82 232.17,430.34 237.86,429.89 243.55,429.48 249.24,429.09 254.93,428.73 259.20,428.47 260.62,428.39 266.31,428.08 272.00,427.79 277.69,427.52 283.38,427.27 289.07,427.04 294.76,426.83 300.44,426.63 306.13,426.45 311.82,426.28 317.51,426.13 323.20,425.99 328.89,425.87 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='50.66' y='512.44' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='516.00' x2='54.22' y2='512.44' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='512.44' x2='54.22' y2='516.00' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='50.66' y='505.07' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='508.64' x2='54.22' y2='505.07' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='505.07' x2='54.22' y2='508.64' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='55.30' y='492.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='495.74' x2='58.87' y2='492.18' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='492.18' x2='58.87' y2='495.74' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='55.30' y='499.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='503.48' x2='58.87' y2='499.92' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='499.92' x2='58.87' y2='503.48' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='64.60' y='468.60' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='472.17' x2='68.16' y2='468.60' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='468.60' x2='68.16' y2='472.17' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='64.60' y='467.13' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='470.69' x2='68.16' y2='467.13' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='467.13' x2='68.16' y2='470.69' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='80.86' y='431.39' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='434.96' x2='84.42' y2='431.39' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='431.39' x2='84.42' y2='434.96' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='80.86' y='450.55' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='454.11' x2='84.42' y2='450.55' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='450.55' x2='84.42' y2='454.11' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='113.38' y='400.82' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='404.38' x2='116.95' y2='400.82' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='400.82' x2='116.95' y2='404.38' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='113.38' y='405.97' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='409.54' x2='116.95' y2='405.97' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='405.97' x2='116.95' y2='409.54' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='187.72' y='389.76' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='393.33' x2='191.29' y2='389.76' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='389.76' x2='191.29' y2='393.33' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='187.72' y='387.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='390.75' x2='191.29' y2='387.18' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='387.18' x2='191.29' y2='390.75' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='257.42' y='395.66' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='399.22' x2='260.98' y2='395.66' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='395.66' x2='260.98' y2='399.22' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='257.42' y='377.24' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='380.80' x2='260.98' y2='377.24' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='377.24' x2='260.98' y2='380.80' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='327.11' y='395.66' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='399.22' x2='330.67' y2='395.66' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='395.66' x2='330.67' y2='399.22' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='327.11' y='373.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='377.49' x2='330.67' y2='373.92' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='373.92' x2='330.67' y2='377.49' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,512.16 55.81,501.07 57.09,497.14 61.50,484.69 66.38,472.65 67.19,470.82 72.87,459.05 78.56,449.03 82.64,442.76 84.25,440.47 89.94,433.13 95.63,426.81 101.32,421.35 107.01,416.62 112.70,412.50 115.16,410.88 118.39,408.90 124.08,405.74 129.77,402.96 135.46,400.51 141.15,398.33 146.83,396.40 152.52,394.68 158.21,393.15 163.90,391.77 169.59,390.55 175.28,389.44 180.97,388.46 186.66,387.57 189.50,387.17 192.35,386.78 198.04,386.08 203.73,385.45 209.42,384.89 215.11,384.40 220.79,383.96 226.48,383.59 232.17,383.26 237.86,382.99 243.55,382.75 249.24,382.56 254.93,382.42 259.20,382.33 260.62,382.30 266.31,382.23 272.00,382.18 277.69,382.17 283.38,382.19 289.07,382.24 294.76,382.31 300.44,382.41 306.13,382.53 311.82,382.68 317.51,382.84 323.20,383.03 328.89,383.24 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='513.06' x2='54.22' y2='509.49' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='509.49' x2='54.22' y2='513.06' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='49.92' y1='511.28' x2='54.96' y2='511.28' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='513.80' x2='52.44' y2='508.76' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='509.74' x2='54.22' y2='506.18' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='506.18' x2='54.22' y2='509.74' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='49.92' y1='507.96' x2='54.96' y2='507.96' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='510.48' x2='52.44' y2='505.44' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='493.90' x2='58.87' y2='490.34' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='490.34' x2='58.87' y2='493.90' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='54.57' y1='492.12' x2='59.61' y2='492.12' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='494.64' x2='57.09' y2='489.60' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='488.37' x2='58.87' y2='484.81' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='484.81' x2='58.87' y2='488.37' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='54.57' y1='486.59' x2='59.61' y2='486.59' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='489.11' x2='57.09' y2='484.07' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='459.64' x2='68.16' y2='456.08' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='456.08' x2='68.16' y2='459.64' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='63.86' y1='457.86' x2='68.90' y2='457.86' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='460.38' x2='66.38' y2='455.34' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='460.38' x2='68.16' y2='456.81' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='456.81' x2='68.16' y2='460.38' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='63.86' y1='458.59' x2='68.90' y2='458.59' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='461.11' x2='66.38' y2='456.07' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='430.54' x2='84.42' y2='426.97' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='426.97' x2='84.42' y2='430.54' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.12' y1='428.75' x2='85.16' y2='428.75' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='431.27' x2='82.64' y2='426.23' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='441.22' x2='84.42' y2='437.66' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='437.66' x2='84.42' y2='441.22' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.12' y1='439.44' x2='85.16' y2='439.44' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='441.96' x2='82.64' y2='436.92' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='397.01' x2='116.95' y2='393.45' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='393.45' x2='116.95' y2='397.01' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='112.64' y1='395.23' x2='117.68' y2='395.23' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='397.75' x2='115.16' y2='392.71' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='391.49' x2='116.95' y2='387.92' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='387.92' x2='116.95' y2='391.49' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='112.64' y1='389.70' x2='117.68' y2='389.70' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='392.22' x2='115.16' y2='387.18' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='377.12' x2='191.29' y2='373.55' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='373.55' x2='191.29' y2='377.12' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='186.98' y1='375.34' x2='192.02' y2='375.34' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='377.86' x2='189.50' y2='372.82' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='399.22' x2='191.29' y2='395.66' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='395.66' x2='191.29' y2='399.22' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='186.98' y1='397.44' x2='192.02' y2='397.44' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='399.96' x2='189.50' y2='394.92' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='382.64' x2='260.98' y2='379.08' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='379.08' x2='260.98' y2='382.64' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='256.68' y1='380.86' x2='261.72' y2='380.86' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='383.38' x2='259.20' y2='378.34' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='396.27' x2='260.98' y2='392.71' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='392.71' x2='260.98' y2='396.27' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='256.68' y1='394.49' x2='261.72' y2='394.49' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='397.01' x2='259.20' y2='391.97' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='374.91' x2='330.67' y2='371.34' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='371.34' x2='330.67' y2='374.91' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='326.37' y1='373.13' x2='331.41' y2='373.13' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='375.65' x2='328.89' y2='370.61' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='393.70' x2='330.67' y2='390.13' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='390.13' x2='330.67' y2='393.70' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='326.37' y1='391.91' x2='331.41' y2='391.91' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='394.43' x2='328.89' y2='389.39' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,508.32 55.81,492.86 57.09,487.59 61.50,471.63 66.38,457.32 67.19,455.25 72.87,442.54 78.56,432.63 82.64,426.87 84.25,424.85 89.94,418.69 95.63,413.77 101.32,409.80 107.01,406.55 112.70,403.86 115.16,402.84 118.39,401.61 124.08,399.70 129.77,398.05 135.46,396.62 141.15,395.35 146.83,394.22 152.52,393.21 158.21,392.29 163.90,391.44 169.59,390.67 175.28,389.95 180.97,389.29 186.66,388.67 189.50,388.38 192.35,388.10 198.04,387.56 203.73,387.07 209.42,386.61 215.11,386.18 220.79,385.78 226.48,385.41 232.17,385.07 237.86,384.75 243.55,384.47 249.24,384.20 254.93,383.97 259.20,383.80 260.62,383.75 266.31,383.56 272.00,383.39 277.69,383.24 283.38,383.12 289.07,383.01 294.76,382.92 300.44,382.85 306.13,382.80 311.82,382.77 317.51,382.75 323.20,382.76 328.89,382.77 ' style='stroke-width: 0.75; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='49.92' y1='505.38' x2='54.96' y2='505.38' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='507.90' x2='52.44' y2='502.86' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='49.92,505.38 52.44,502.86 54.96,505.38 52.44,507.90 49.92,505.38 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='49.92' y1='509.07' x2='54.96' y2='509.07' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='511.59' x2='52.44' y2='506.55' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='49.92,509.07 52.44,506.55 54.96,509.07 52.44,511.59 49.92,509.07 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='54.57' y1='487.70' x2='59.61' y2='487.70' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='490.22' x2='57.09' y2='485.18' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='54.57,487.70 57.09,485.18 59.61,487.70 57.09,490.22 54.57,487.70 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='54.57' y1='493.22' x2='59.61' y2='493.22' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='495.74' x2='57.09' y2='490.70' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='54.57,493.22 57.09,490.70 59.61,493.22 57.09,495.74 54.57,493.22 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='63.86' y1='461.17' x2='68.90' y2='461.17' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='463.69' x2='66.38' y2='458.65' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='63.86,461.17 66.38,458.65 68.90,461.17 66.38,463.69 63.86,461.17 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='63.86' y1='469.28' x2='68.90' y2='469.28' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='471.80' x2='66.38' y2='466.76' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='63.86,469.28 66.38,466.76 68.90,469.28 66.38,471.80 63.86,469.28 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.12' y1='429.12' x2='85.16' y2='429.12' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='431.64' x2='82.64' y2='426.60' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='80.12,429.12 82.64,426.60 85.16,429.12 82.64,431.64 80.12,429.12 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.12' y1='429.86' x2='85.16' y2='429.86' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='432.38' x2='82.64' y2='427.34' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='80.12,429.86 82.64,427.34 85.16,429.86 82.64,432.38 80.12,429.86 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='112.64' y1='391.91' x2='117.68' y2='391.91' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='394.43' x2='115.16' y2='389.39' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='112.64,391.91 115.16,389.39 117.68,391.91 115.16,394.43 112.64,391.91 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='112.64' y1='404.81' x2='117.68' y2='404.81' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='407.33' x2='115.16' y2='402.29' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='112.64,404.81 115.16,402.29 117.68,404.81 115.16,407.33 112.64,404.81 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='186.98' y1='361.70' x2='192.02' y2='361.70' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='364.22' x2='189.50' y2='359.18' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='186.98,361.70 189.50,359.18 192.02,361.70 189.50,364.22 186.98,361.70 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='186.98' y1='355.44' x2='192.02' y2='355.44' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='357.96' x2='189.50' y2='352.92' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='186.98,355.44 189.50,352.92 192.02,355.44 189.50,357.96 186.98,355.44 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='256.68' y1='361.70' x2='261.72' y2='361.70' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='364.22' x2='259.20' y2='359.18' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='256.68,361.70 259.20,359.18 261.72,361.70 259.20,364.22 256.68,361.70 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='256.68' y1='358.76' x2='261.72' y2='358.76' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='361.28' x2='259.20' y2='356.24' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='256.68,358.76 259.20,356.24 261.72,358.76 259.20,361.28 256.68,358.76 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='326.37' y1='344.39' x2='331.41' y2='344.39' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='346.91' x2='328.89' y2='341.87' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='326.37,344.39 328.89,341.87 331.41,344.39 328.89,346.91 326.37,344.39 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='326.37' y1='353.23' x2='331.41' y2='353.23' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='355.75' x2='328.89' y2='350.71' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='326.37,353.23 328.89,350.71 331.41,353.23 328.89,355.75 326.37,353.23 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,511.13 55.81,498.59 57.09,494.12 61.50,479.86 66.38,465.93 67.19,463.80 72.87,450.01 78.56,438.13 82.64,430.64 84.25,427.89 89.94,419.03 95.63,411.34 101.32,404.66 107.01,398.84 112.70,393.74 115.16,391.74 118.39,389.28 124.08,385.35 129.77,381.89 135.46,378.83 141.15,376.12 146.83,373.71 152.52,371.56 158.21,369.65 163.90,367.93 169.59,366.40 175.28,365.03 180.97,363.80 186.66,362.70 189.50,362.19 192.35,361.71 198.04,360.82 203.73,360.03 209.42,359.33 215.11,358.70 220.79,358.15 226.48,357.66 232.17,357.24 237.86,356.87 243.55,356.55 249.24,356.29 254.93,356.08 259.20,355.94 260.62,355.91 266.31,355.78 272.00,355.69 277.69,355.64 283.38,355.62 289.07,355.64 294.76,355.69 300.44,355.77 306.13,355.89 311.82,356.03 317.51,356.19 323.20,356.39 328.89,356.60 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='52.44' cy='514.59' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='514.59' x2='54.22' y2='514.59' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='516.37' x2='52.44' y2='512.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='52.44' cy='517.17' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='517.17' x2='54.22' y2='517.17' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='518.95' x2='52.44' y2='515.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='57.09' cy='507.22' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='507.22' x2='58.87' y2='507.22' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='509.01' x2='57.09' y2='505.44' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='57.09' cy='503.91' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='503.91' x2='58.87' y2='503.91' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='505.69' x2='57.09' y2='502.13' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='66.38' cy='483.28' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='483.28' x2='68.16' y2='483.28' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='485.06' x2='66.38' y2='481.50' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='66.38' cy='479.96' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='479.96' x2='68.16' y2='479.96' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='481.74' x2='66.38' y2='478.18' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='82.64' cy='456.02' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='456.02' x2='84.42' y2='456.02' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='457.80' x2='82.64' y2='454.23' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='82.64' cy='457.86' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='457.86' x2='84.42' y2='457.86' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='459.64' x2='82.64' y2='456.08' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='115.16' cy='416.60' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='416.60' x2='116.95' y2='416.60' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='418.38' x2='115.16' y2='414.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='115.16' cy='417.33' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='417.33' x2='116.95' y2='417.33' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='419.12' x2='115.16' y2='415.55' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='189.50' cy='383.81' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='383.81' x2='191.29' y2='383.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='385.59' x2='189.50' y2='382.03' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='189.50' cy='391.18' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='391.18' x2='191.29' y2='391.18' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='392.96' x2='189.50' y2='389.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='259.20' cy='368.34' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='368.34' x2='260.98' y2='368.34' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='370.12' x2='259.20' y2='366.55' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='259.20' cy='361.34' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='361.34' x2='260.98' y2='361.34' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='363.12' x2='259.20' y2='359.55' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='328.89' cy='355.07' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='355.07' x2='330.67' y2='355.07' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='356.86' x2='328.89' y2='353.29' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='328.89' cy='349.55' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='349.55' x2='330.67' y2='349.55' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='351.33' x2='328.89' y2='347.77' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,514.97 55.81,507.32 57.09,504.52 61.50,495.29 66.38,485.79 67.19,484.28 72.87,474.21 78.56,464.98 82.64,458.84 84.25,456.52 89.94,448.75 95.63,441.63 101.32,435.08 107.01,429.06 112.70,423.52 115.16,421.26 118.39,418.42 124.08,413.72 129.77,409.38 135.46,405.38 141.15,401.69 146.83,398.27 152.52,395.12 158.21,392.20 163.90,389.49 169.59,386.99 175.28,384.67 180.97,382.52 186.66,380.52 189.50,379.58 192.35,378.68 198.04,376.96 203.73,375.37 209.42,373.89 215.11,372.52 220.79,371.25 226.48,370.07 232.17,368.98 237.86,367.97 243.55,367.03 249.24,366.17 254.93,365.37 259.20,364.81 260.62,364.63 266.31,363.95 272.00,363.33 277.69,362.75 283.38,362.23 289.07,361.75 294.76,361.32 300.44,360.93 306.13,360.57 311.82,360.26 317.51,359.97 323.20,359.73 328.89,359.51 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,518.10 54.84,513.25 50.04,513.25 52.44,518.10 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,512.56 54.84,517.41 50.04,517.41 52.44,512.56 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,517.36 54.84,512.51 50.04,512.51 52.44,517.36 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,511.82 54.84,516.67 50.04,516.67 52.44,511.82 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,516.99 59.49,512.14 54.69,512.14 57.09,516.99 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,511.45 59.49,516.30 54.69,516.30 57.09,511.45 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,509.99 59.49,505.14 54.69,505.14 57.09,509.99 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,504.45 59.49,509.30 54.69,509.30 57.09,504.45 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,501.52 68.78,496.67 63.98,496.67 66.38,501.52 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,495.98 68.78,500.83 63.98,500.83 66.38,495.98 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,503.36 68.78,498.51 63.98,498.51 66.38,503.36 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,497.82 68.78,502.67 63.98,502.67 66.38,497.82 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,480.89 85.04,476.04 80.24,476.04 82.64,480.89 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,475.35 85.04,480.20 80.24,480.20 82.64,475.35 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,487.52 85.04,482.67 80.24,482.67 82.64,487.52 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,481.98 85.04,486.83 80.24,486.83 82.64,481.98 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,461.73 117.56,456.88 112.76,456.88 115.16,461.73 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,456.19 117.56,461.04 112.76,461.04 115.16,456.19 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,449.21 117.56,444.36 112.76,444.36 115.16,449.21 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,443.67 117.56,448.52 112.76,448.52 115.16,443.67 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,421.95 191.90,417.10 187.10,417.10 189.50,421.95 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,416.40 191.90,421.25 187.10,421.25 189.50,416.40 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,429.68 191.90,424.83 187.10,424.83 189.50,429.68 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,424.14 191.90,428.99 187.10,428.99 189.50,424.14 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,425.63 261.60,420.78 256.80,420.78 259.20,425.63 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,420.09 261.60,424.94 256.80,424.94 259.20,420.09 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,426.37 261.60,421.52 256.80,421.52 259.20,426.37 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,420.83 261.60,425.67 256.80,425.67 259.20,420.83 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,409.42 331.29,404.57 326.49,404.57 328.89,409.42 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,403.88 331.29,408.73 326.49,408.73 328.89,403.88 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,413.47 331.29,408.62 326.49,408.62 328.89,413.47 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,407.93 331.29,412.78 326.49,412.78 328.89,407.93 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,517.03 55.81,512.22 57.09,510.45 61.50,504.60 66.38,498.53 67.19,497.57 72.87,491.08 78.56,485.08 82.64,481.07 84.25,479.54 89.94,474.42 95.63,469.68 101.32,465.30 107.01,461.24 112.70,457.47 115.16,455.93 118.39,453.99 124.08,450.75 129.77,447.75 135.46,444.96 141.15,442.37 146.83,439.96 152.52,437.72 158.21,435.63 163.90,433.69 169.59,431.89 175.28,430.20 180.97,428.63 186.66,427.17 189.50,426.47 192.35,425.80 198.04,424.52 203.73,423.33 209.42,422.22 215.11,421.18 220.79,420.21 226.48,419.31 232.17,418.46 237.86,417.67 243.55,416.93 249.24,416.25 254.93,415.60 259.20,415.15 260.62,415.00 266.31,414.45 272.00,413.93 277.69,413.44 283.38,412.99 289.07,412.57 294.76,412.19 300.44,411.83 306.13,411.50 311.82,411.19 317.51,410.91 323.20,410.66 328.89,410.42 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='519.38' x2='54.22' y2='519.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='521.16' x2='52.44' y2='517.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='50.66' y='517.60' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='511.28' x2='54.22' y2='511.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='52.44' y1='513.06' x2='52.44' y2='509.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='50.66' y='509.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='506.85' x2='58.87' y2='506.85' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='508.64' x2='57.09' y2='505.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='55.30' y='505.07' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='505.75' x2='58.87' y2='505.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='57.09' y1='507.53' x2='57.09' y2='503.97' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='55.30' y='503.97' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='494.70' x2='68.16' y2='494.70' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='496.48' x2='66.38' y2='492.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='64.60' y='492.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='497.28' x2='68.16' y2='497.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='66.38' y1='499.06' x2='66.38' y2='495.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='64.60' y='495.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='475.91' x2='84.42' y2='475.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='477.69' x2='82.64' y2='474.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='80.86' y='474.13' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='478.49' x2='84.42' y2='478.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='82.64' y1='480.27' x2='82.64' y2='476.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='80.86' y='476.71' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='453.44' x2='116.95' y2='453.44' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='455.22' x2='115.16' y2='451.65' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='113.38' y='451.65' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='453.81' x2='116.95' y2='453.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='115.16' y1='455.59' x2='115.16' y2='452.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='113.38' y='452.02' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='415.49' x2='191.29' y2='415.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='417.27' x2='189.50' y2='413.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='187.72' y='413.71' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='421.75' x2='191.29' y2='421.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='189.50' y1='423.54' x2='189.50' y2='419.97' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='187.72' y='419.97' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='401.86' x2='260.98' y2='401.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='403.64' x2='259.20' y2='400.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='257.42' y='400.08' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='414.39' x2='260.98' y2='414.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='259.20' y1='416.17' x2='259.20' y2='412.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='257.42' y='412.60' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='394.12' x2='330.67' y2='394.12' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='395.91' x2='328.89' y2='392.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='327.11' y='392.34' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='409.23' x2='330.67' y2='409.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='328.89' y1='411.01' x2='328.89' y2='407.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='327.11' y='407.45' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,516.50 55.81,510.96 57.09,508.93 61.50,502.24 66.38,495.33 67.19,494.24 72.87,486.90 78.56,480.16 82.64,475.68 84.25,473.98 89.94,468.30 95.63,463.08 101.32,458.28 107.01,453.86 112.70,449.80 115.16,448.14 118.39,446.06 124.08,442.61 129.77,439.43 135.46,436.50 141.15,433.80 146.83,431.31 152.52,429.01 158.21,426.88 163.90,424.92 169.59,423.11 175.28,421.44 180.97,419.89 186.66,418.47 189.50,417.80 192.35,417.15 198.04,415.93 203.73,414.81 209.42,413.77 215.11,412.82 220.79,411.94 226.48,411.12 232.17,410.38 237.86,409.69 243.55,409.06 249.24,408.49 254.93,407.96 259.20,407.60 260.62,407.48 266.31,407.04 272.00,406.65 277.69,406.29 283.38,405.97 289.07,405.68 294.76,405.43 300.44,405.20 306.13,405.00 311.82,404.83 317.51,404.69 323.20,404.57 328.89,404.47 ' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='52.44' cy='517.17' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='518.95' x2='54.22' y2='515.39' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='515.39' x2='54.22' y2='518.95' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='52.44' cy='520.12' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='521.90' x2='54.22' y2='518.34' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='50.66' y1='518.34' x2='54.22' y2='521.90' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='57.09' cy='507.22' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='509.01' x2='58.87' y2='505.44' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='505.44' x2='58.87' y2='509.01' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='57.09' cy='502.07' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='503.85' x2='58.87' y2='500.28' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='55.30' y1='500.28' x2='58.87' y2='503.85' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='66.38' cy='492.49' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='494.27' x2='68.16' y2='490.71' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='490.71' x2='68.16' y2='494.27' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='66.38' cy='496.54' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='498.32' x2='68.16' y2='494.76' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='64.60' y1='494.76' x2='68.16' y2='498.32' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='82.64' cy='477.75' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='479.53' x2='84.42' y2='475.97' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='475.97' x2='84.42' y2='479.53' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='82.64' cy='472.59' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='474.38' x2='84.42' y2='470.81' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='80.86' y1='470.81' x2='84.42' y2='474.38' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='115.16' cy='443.49' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='445.27' x2='116.95' y2='441.71' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='441.71' x2='116.95' y2='445.27' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='115.16' cy='451.59' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='453.38' x2='116.95' y2='449.81' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='113.38' y1='449.81' x2='116.95' y2='453.38' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='189.50' cy='419.54' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='421.33' x2='191.29' y2='417.76' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='417.76' x2='191.29' y2='421.33' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='189.50' cy='406.65' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='408.43' x2='191.29' y2='404.87' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='187.72' y1='404.87' x2='191.29' y2='408.43' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='259.20' cy='419.91' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='421.69' x2='260.98' y2='418.13' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='418.13' x2='260.98' y2='421.69' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='259.20' cy='400.02' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='401.80' x2='260.98' y2='398.24' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='257.42' y1='398.24' x2='260.98' y2='401.80' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='328.89' cy='405.54' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='407.33' x2='330.67' y2='403.76' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='403.76' x2='330.67' y2='407.33' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<circle cx='328.89' cy='403.33' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='405.12' x2='330.67' y2='401.55' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<line x1='327.11' y1='401.55' x2='330.67' y2='405.12' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,516.00 55.81,509.82 57.09,507.57 61.50,500.19 66.38,492.66 67.19,491.47 72.87,483.59 78.56,476.45 82.64,471.74 84.25,469.98 89.94,464.11 95.63,458.79 101.32,453.95 107.01,449.56 112.70,445.57 115.16,443.96 118.39,441.94 124.08,438.64 129.77,435.63 135.46,432.89 141.15,430.39 146.83,428.11 152.52,426.03 158.21,424.13 163.90,422.39 169.59,420.81 175.28,419.36 180.97,418.04 186.66,416.84 189.50,416.28 192.35,415.74 198.04,414.74 203.73,413.82 209.42,412.99 215.11,412.23 220.79,411.54 226.48,410.92 232.17,410.36 237.86,409.85 243.55,409.39 249.24,408.98 254.93,408.61 259.20,408.36 260.62,408.28 266.31,408.00 272.00,407.75 277.69,407.53 283.38,407.34 289.07,407.19 294.76,407.06 300.44,406.96 306.13,406.88 311.82,406.83 317.51,406.80 323.20,406.79 328.89,406.80 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,512.44 54.22,516.00 50.66,516.00 52.44,512.44 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='50.66' y='512.44' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='52.44,509.86 54.22,513.43 50.66,513.43 52.44,509.86 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='50.66' y='509.86' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,497.34 58.87,500.90 55.30,500.90 57.09,497.34 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='55.30' y='497.34' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='57.09,498.81 58.87,502.37 55.30,502.37 57.09,498.81 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='55.30' y='498.81' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,485.18 68.16,488.74 64.60,488.74 66.38,485.18 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='64.60' y='485.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='66.38,471.92 68.16,475.48 64.60,475.48 66.38,471.92 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='64.60' y='471.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,446.87 84.42,450.43 80.86,450.43 82.64,446.87 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='80.86' y='446.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='82.64,451.29 84.42,454.85 80.86,454.85 82.64,451.29 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='80.86' y='451.29' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,431.02 116.95,434.59 113.38,434.59 115.16,431.02 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='113.38' y='431.02' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='115.16,421.08 116.95,424.64 113.38,424.64 115.16,421.08 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='113.38' y='421.08' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,397.50 191.29,401.06 187.72,401.06 189.50,397.50 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='187.72' y='397.50' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='189.50,386.82 191.29,390.38 187.72,390.38 189.50,386.82 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='187.72' y='386.82' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,399.34 260.98,402.91 257.42,402.91 259.20,399.34 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='257.42' y='399.34' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='259.20,383.87 260.98,387.43 257.42,387.43 259.20,383.87 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='257.42' y='383.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,396.03 330.67,399.59 327.11,399.59 328.89,396.03 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='327.11' y='396.03' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='328.89,392.34 330.67,395.91 327.11,395.91 328.89,392.34 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<rect x='327.11' y='392.34' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,513.80 55.81,504.82 57.09,501.60 61.50,491.30 66.38,481.18 67.19,479.62 72.87,469.51 78.56,460.72 82.64,455.13 84.25,453.07 89.94,446.39 95.63,440.53 101.32,435.39 107.01,430.86 112.70,426.85 115.16,425.26 118.39,423.30 124.08,420.14 129.77,417.31 135.46,414.78 141.15,412.50 146.83,410.45 152.52,408.59 158.21,406.90 163.90,405.37 169.59,403.97 175.28,402.70 180.97,401.53 186.66,400.46 189.50,399.96 192.35,399.47 198.04,398.57 203.73,397.74 209.42,396.97 215.11,396.27 220.79,395.62 226.48,395.02 232.17,394.48 237.86,393.97 243.55,393.51 249.24,393.09 254.93,392.71 259.20,392.45 260.62,392.37 266.31,392.06 272.00,391.78 277.69,391.53 283.38,391.31 289.07,391.12 294.76,390.95 300.44,390.81 306.13,390.69 311.82,390.60 317.51,390.53 323.20,390.48 328.89,390.46 ' style='stroke-width: 0.75; stroke: #F5C710; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='50.66,513.06 54.22,513.06 54.22,509.49 50.66,509.49 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='50.66,514.90 54.22,514.90 54.22,511.34 50.66,511.34 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='55.30,501.64 58.87,501.64 58.87,498.07 55.30,498.07 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='55.30,499.43 58.87,499.43 58.87,495.86 55.30,495.86 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='64.60,486.90 68.16,486.90 68.16,483.34 64.60,483.34 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='64.60,472.90 68.16,472.90 68.16,469.34 64.60,469.34 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='80.86,462.22 84.42,462.22 84.42,458.65 80.86,458.65 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='80.86,455.22 84.42,455.22 84.42,451.65 80.86,451.65 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='113.38,427.59 116.95,427.59 116.95,424.02 113.38,424.02 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='113.38,428.33 116.95,428.33 116.95,424.76 113.38,424.76 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='187.72,400.33 191.29,400.33 191.29,396.76 187.72,396.76 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='187.72,399.96 191.29,399.96 191.29,396.39 187.72,396.39 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='257.42,390.38 260.98,390.38 260.98,386.82 257.42,386.82 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='257.42,396.27 260.98,396.27 260.98,392.71 257.42,392.71 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='327.11,383.38 330.67,383.38 330.67,379.82 327.11,379.82 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polygon points='327.11,402.54 330.67,402.54 330.67,398.97 327.11,398.97 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> -<polyline points='50.12,520.49 52.44,511.66 55.81,500.39 57.09,496.52 61.50,484.72 66.38,473.96 67.19,472.38 72.87,462.56 78.56,454.64 82.64,449.89 84.25,448.18 89.94,442.82 95.63,438.32 101.32,434.46 107.01,431.12 112.70,428.18 115.16,427.01 118.39,425.56 124.08,423.20 129.77,421.04 135.46,419.05 141.15,417.22 146.83,415.50 152.52,413.90 158.21,412.39 163.90,410.97 169.59,409.62 175.28,408.35 180.97,407.14 186.66,406.00 189.50,405.45 192.35,404.92 198.04,403.89 203.73,402.91 209.42,401.99 215.11,401.11 220.79,400.28 226.48,399.50 232.17,398.75 237.86,398.06 243.55,397.40 249.24,396.78 254.93,396.19 259.20,395.78 260.62,395.65 266.31,395.14 272.00,394.66 277.69,394.22 283.38,393.80 289.07,393.42 294.76,393.07 300.44,392.75 306.13,392.45 311.82,392.18 317.51,391.94 323.20,391.72 328.89,391.53 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMzcuMzU=)' /> +<circle cx='52.44' cy='508.57' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='52.44' cy='510.94' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='57.09' cy='492.00' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='57.09' cy='499.10' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='66.38' cy='476.84' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='66.38' cy='482.05' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='82.64' cy='442.75' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='82.64' cy='456.48' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='115.16' cy='412.92' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='115.16' cy='411.02' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='189.50' cy='385.45' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='189.50' cy='402.97' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='259.20' cy='389.71' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='259.20' cy='397.29' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='328.89' cy='382.14' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='328.89' cy='399.18' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,511.80 55.81,500.98 57.09,497.14 61.50,485.00 66.38,473.29 67.19,471.52 72.87,460.11 78.56,450.43 82.64,444.40 84.25,442.20 89.94,435.19 95.63,429.19 101.32,424.05 107.01,419.63 112.70,415.82 115.16,414.33 118.39,412.52 124.08,409.67 129.77,407.18 135.46,405.02 141.15,403.12 146.83,401.47 152.52,400.02 158.21,398.75 163.90,397.64 169.59,396.66 175.28,395.81 180.97,395.06 186.66,394.41 189.50,394.12 192.35,393.86 198.04,393.38 203.73,392.97 209.42,392.63 215.11,392.36 220.79,392.14 226.48,391.97 232.17,391.85 237.86,391.78 243.55,391.76 249.24,391.77 254.93,391.82 259.20,391.89 260.62,391.91 266.31,392.04 272.00,392.20 277.69,392.39 283.38,392.61 289.07,392.86 294.76,393.13 300.44,393.44 306.13,393.76 311.82,394.11 317.51,394.49 323.20,394.89 328.89,395.30 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,516.69 54.84,520.85 50.04,520.85 52.44,516.69 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,508.17 54.84,512.32 50.04,512.32 52.44,508.17 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,499.17 59.49,503.33 54.69,503.33 57.09,499.17 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,509.11 59.49,513.27 54.69,513.27 57.09,509.11 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,479.75 68.78,483.91 63.98,483.91 66.38,479.75 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,484.96 68.78,489.12 63.98,489.12 66.38,484.96 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,450.40 85.04,454.55 80.24,454.55 82.64,450.40 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,459.39 85.04,463.55 80.24,463.55 82.64,459.39 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,436.19 117.56,440.35 112.76,440.35 115.16,436.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,418.20 117.56,422.35 112.76,422.35 115.16,418.20 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,407.78 191.90,411.94 187.10,411.94 189.50,407.78 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,411.09 191.90,415.25 187.10,415.25 189.50,411.09 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,401.15 261.60,405.31 256.80,405.31 259.20,401.15 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,400.20 261.60,404.36 256.80,404.36 259.20,400.20 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,420.09 331.29,424.25 326.49,424.25 328.89,420.09 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,409.20 331.29,413.36 326.49,413.36 328.89,409.20 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,514.21 55.81,506.39 57.09,503.55 61.50,494.33 66.38,485.05 67.19,483.61 72.87,474.07 78.56,465.59 82.64,460.10 84.25,458.06 89.94,451.37 95.63,445.44 101.32,440.18 107.01,435.53 112.70,431.42 115.16,429.79 118.39,427.79 124.08,424.59 129.77,421.78 135.46,419.31 141.15,417.16 146.83,415.28 152.52,413.65 158.21,412.25 163.90,411.05 169.59,410.03 175.28,409.17 180.97,408.45 186.66,407.87 189.50,407.62 192.35,407.41 198.04,407.05 203.73,406.79 209.42,406.61 215.11,406.51 220.79,406.49 226.48,406.53 232.17,406.62 237.86,406.77 243.55,406.97 249.24,407.21 254.93,407.49 259.20,407.72 260.62,407.80 266.31,408.15 272.00,408.53 277.69,408.93 283.38,409.36 289.07,409.81 294.76,410.28 300.44,410.78 306.13,411.29 311.82,411.81 317.51,412.35 323.20,412.90 328.89,413.47 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='49.92' y1='510.94' x2='54.96' y2='510.94' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='513.46' x2='52.44' y2='508.42' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='54.57' y1='504.31' x2='59.61' y2='504.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='506.83' x2='57.09' y2='501.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='54.57' y1='509.99' x2='59.61' y2='509.99' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='512.51' x2='57.09' y2='507.47' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='63.86' y1='473.06' x2='68.90' y2='473.06' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='475.58' x2='66.38' y2='470.53' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='63.86' y1='477.32' x2='68.90' y2='477.32' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='479.84' x2='66.38' y2='474.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.12' y1='456.01' x2='85.16' y2='456.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='458.53' x2='82.64' y2='453.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.12' y1='447.01' x2='85.16' y2='447.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='449.53' x2='82.64' y2='444.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='112.64' y1='419.07' x2='117.68' y2='419.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='421.59' x2='115.16' y2='416.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='112.64' y1='415.76' x2='117.68' y2='415.76' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='418.28' x2='115.16' y2='413.24' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='186.98' y1='387.82' x2='192.02' y2='387.82' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='390.34' x2='189.50' y2='385.30' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='186.98' y1='367.93' x2='192.02' y2='367.93' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='370.45' x2='189.50' y2='365.41' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='256.68' y1='375.98' x2='261.72' y2='375.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='378.50' x2='259.20' y2='373.46' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='256.68' y1='386.40' x2='261.72' y2='386.40' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='388.92' x2='259.20' y2='383.88' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='326.37' y1='387.82' x2='331.41' y2='387.82' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='390.34' x2='328.89' y2='385.30' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='326.37' y1='378.35' x2='331.41' y2='378.35' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='380.87' x2='328.89' y2='375.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,514.37 55.81,506.64 57.09,503.79 61.50,494.41 66.38,484.70 67.19,483.17 72.87,472.84 78.56,463.35 82.64,457.03 84.25,454.64 89.94,446.65 95.63,439.33 101.32,432.62 107.01,426.48 112.70,420.87 115.16,418.60 118.39,415.75 124.08,411.08 129.77,406.83 135.46,402.96 141.15,399.45 146.83,396.28 152.52,393.41 158.21,390.83 163.90,388.52 169.59,386.45 175.28,384.61 180.97,382.99 186.66,381.56 189.50,380.91 192.35,380.31 198.04,379.24 203.73,378.32 209.42,377.55 215.11,376.91 220.79,376.40 226.48,376.01 232.17,375.73 237.86,375.56 243.55,375.47 249.24,375.48 254.93,375.57 259.20,375.68 260.62,375.73 266.31,375.96 272.00,376.27 277.69,376.63 283.38,377.05 289.07,377.52 294.76,378.04 300.44,378.61 306.13,379.22 311.82,379.87 317.51,380.56 323.20,381.28 328.89,382.03 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='510.83' x2='54.22' y2='507.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='507.26' x2='54.22' y2='510.83' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='505.14' x2='54.22' y2='501.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='501.58' x2='54.22' y2='505.14' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='496.15' x2='58.87' y2='492.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='492.58' x2='58.87' y2='496.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='506.09' x2='58.87' y2='502.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='502.53' x2='58.87' y2='506.09' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='473.42' x2='68.16' y2='469.85' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='469.85' x2='68.16' y2='473.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='474.84' x2='68.16' y2='471.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='471.27' x2='68.16' y2='474.84' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='433.64' x2='84.42' y2='430.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='430.08' x2='84.42' y2='433.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='453.53' x2='84.42' y2='449.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='449.96' x2='84.42' y2='453.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='391.50' x2='116.95' y2='387.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='387.93' x2='116.95' y2='391.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='395.28' x2='116.95' y2='391.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='391.72' x2='116.95' y2='395.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='347.93' x2='191.29' y2='344.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='344.37' x2='191.29' y2='347.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='340.36' x2='191.29' y2='336.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='336.79' x2='191.29' y2='340.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='341.30' x2='260.98' y2='337.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='337.74' x2='260.98' y2='341.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='334.20' x2='260.98' y2='330.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='330.64' x2='260.98' y2='334.20' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='347.46' x2='330.67' y2='343.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='343.89' x2='330.67' y2='347.46' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='336.57' x2='330.67' y2='333.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='333.00' x2='330.67' y2='336.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,512.65 55.81,502.56 57.09,498.87 61.50,486.69 66.38,474.16 67.19,472.18 72.87,458.93 78.56,446.83 82.64,438.80 84.25,435.77 89.94,425.69 95.63,416.48 101.32,408.09 107.01,400.44 112.70,393.47 115.16,390.65 118.39,387.14 124.08,381.38 129.77,376.15 135.46,371.41 141.15,367.12 146.83,363.24 152.52,359.75 158.21,356.61 163.90,353.79 169.59,351.27 175.28,349.03 180.97,347.05 186.66,345.30 189.50,344.50 192.35,343.77 198.04,342.44 203.73,341.30 209.42,340.33 215.11,339.52 220.79,338.87 226.48,338.35 232.17,337.96 237.86,337.69 243.55,337.53 249.24,337.47 254.93,337.51 259.20,337.59 260.62,337.63 266.31,337.84 272.00,338.13 277.69,338.48 283.38,338.91 289.07,339.39 294.76,339.94 300.44,340.53 306.13,341.18 311.82,341.87 317.51,342.61 323.20,343.39 328.89,344.20 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='49.92,513.30 52.44,510.78 54.96,513.30 52.44,515.82 49.92,513.30 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='49.92,509.52 52.44,507.00 54.96,509.52 52.44,512.04 49.92,509.52 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='54.57,496.26 57.09,493.74 59.61,496.26 57.09,498.78 54.57,496.26 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='54.57,493.89 57.09,491.37 59.61,493.89 57.09,496.41 54.57,493.89 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='63.86,475.42 66.38,472.90 68.90,475.42 66.38,477.94 63.86,475.42 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='63.86,472.11 66.38,469.59 68.90,472.11 66.38,474.63 63.86,472.11 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='80.12,441.80 82.64,439.28 85.16,441.80 82.64,444.32 80.12,441.80 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='80.12,451.27 82.64,448.75 85.16,451.27 82.64,453.79 80.12,451.27 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='112.64,426.18 115.16,423.66 117.68,426.18 115.16,428.70 112.64,426.18 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='112.64,424.28 115.16,421.76 117.68,424.28 115.16,426.80 112.64,424.28 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='186.98,411.97 189.50,409.45 192.02,411.97 189.50,414.49 186.98,411.97 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='186.98,410.55 189.50,408.03 192.02,410.55 189.50,413.07 186.98,410.55 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='256.68,419.07 259.20,416.55 261.72,419.07 259.20,421.59 256.68,419.07 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='256.68,413.86 259.20,411.34 261.72,413.86 259.20,416.38 256.68,413.86 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='326.37,418.13 328.89,415.61 331.41,418.13 328.89,420.65 326.37,418.13 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='326.37,438.01 328.89,435.49 331.41,438.01 328.89,440.53 326.37,438.01 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,510.30 55.81,498.11 57.09,493.96 61.50,481.41 66.38,470.19 67.19,468.56 72.87,458.60 78.56,450.82 82.64,446.27 84.25,444.67 89.94,439.78 95.63,435.83 101.32,432.62 107.01,429.96 112.70,427.75 115.16,426.91 118.39,425.89 124.08,424.30 129.77,422.94 135.46,421.76 141.15,420.74 146.83,419.85 152.52,419.07 158.21,418.39 163.90,417.79 169.59,417.28 175.28,416.84 180.97,416.46 186.66,416.15 189.50,416.01 192.35,415.89 198.04,415.69 203.73,415.54 209.42,415.44 215.11,415.38 220.79,415.36 226.48,415.39 232.17,415.46 237.86,415.56 243.55,415.70 249.24,415.87 254.93,416.08 259.20,416.26 260.62,416.32 266.31,416.58 272.00,416.88 277.69,417.20 283.38,417.55 289.07,417.92 294.76,418.32 300.44,418.73 306.13,419.17 311.82,419.63 317.51,420.11 323.20,420.60 328.89,421.12 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,509.45 54.84,505.29 50.04,505.29 52.44,509.45 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,508.50 54.84,504.34 50.04,504.34 52.44,508.50 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,507.55 59.49,503.40 54.69,503.40 57.09,507.55 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,517.97 59.49,513.81 54.69,513.81 57.09,517.97 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,487.19 68.78,483.03 63.98,483.03 66.38,487.19 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,491.93 68.78,487.77 63.98,487.77 66.38,491.93 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,459.73 85.04,455.57 80.24,455.57 82.64,459.73 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,468.25 85.04,464.09 80.24,464.09 82.64,468.25 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,439.36 117.56,435.21 112.76,435.21 115.16,439.36 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,441.26 117.56,437.10 112.76,437.10 115.16,441.26 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,431.79 191.90,427.63 187.10,427.63 189.50,431.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,427.53 191.90,423.37 187.10,423.37 189.50,427.53 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,422.32 261.60,418.16 256.80,418.16 259.20,422.32 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,419.00 261.60,414.85 256.80,414.85 259.20,419.00 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,433.21 331.29,429.05 326.49,429.05 328.89,433.21 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,434.63 331.29,430.47 326.49,430.47 328.89,434.63 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,514.58 55.81,507.30 57.09,504.66 61.50,496.15 66.38,487.63 67.19,486.31 72.87,477.63 78.56,469.98 82.64,465.06 84.25,463.23 89.94,457.29 95.63,452.06 101.32,447.45 107.01,443.41 112.70,439.85 115.16,438.45 118.39,436.73 124.08,434.00 129.77,431.61 135.46,429.52 141.15,427.71 146.83,426.14 152.52,424.78 158.21,423.61 163.90,422.62 169.59,421.77 175.28,421.06 180.97,420.48 186.66,420.00 189.50,419.79 192.35,419.61 198.04,419.32 203.73,419.10 209.42,418.95 215.11,418.87 220.79,418.85 226.48,418.87 232.17,418.95 237.86,419.06 243.55,419.22 249.24,419.40 254.93,419.63 259.20,419.81 260.62,419.88 266.31,420.15 272.00,420.46 277.69,420.78 283.38,421.13 289.07,421.49 294.76,421.87 300.44,422.27 306.13,422.68 311.82,423.11 317.51,423.55 323.20,424.00 328.89,424.46 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='50.66' y='510.10' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='513.67' x2='54.22' y2='510.10' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='510.10' x2='54.22' y2='513.67' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='50.66' y='500.63' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='504.20' x2='54.22' y2='500.63' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='500.63' x2='54.22' y2='504.20' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='55.30' y='484.53' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='488.10' x2='58.87' y2='484.53' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='484.53' x2='58.87' y2='488.10' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='55.30' y='494.00' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='497.57' x2='58.87' y2='494.00' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='494.00' x2='58.87' y2='497.57' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='64.60' y='454.70' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='458.26' x2='68.16' y2='454.70' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='454.70' x2='68.16' y2='458.26' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='64.60' y='452.33' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='455.90' x2='68.16' y2='452.33' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='452.33' x2='68.16' y2='455.90' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='80.86' y='408.29' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='411.86' x2='84.42' y2='408.29' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='408.29' x2='84.42' y2='411.86' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='80.86' y='432.92' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='436.48' x2='84.42' y2='432.92' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='432.92' x2='84.42' y2='436.48' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='113.38' y='374.20' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='377.76' x2='116.95' y2='374.20' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='374.20' x2='116.95' y2='377.76' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='113.38' y='380.36' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='383.92' x2='116.95' y2='380.36' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='380.36' x2='116.95' y2='383.92' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='187.72' y='371.83' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='375.40' x2='191.29' y2='371.83' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='371.83' x2='191.29' y2='375.40' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='187.72' y='368.52' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='372.08' x2='191.29' y2='368.52' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='368.52' x2='191.29' y2='372.08' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='257.42' y='388.41' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='391.97' x2='260.98' y2='388.41' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='388.41' x2='260.98' y2='391.97' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='257.42' y='367.57' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='371.13' x2='260.98' y2='367.57' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='367.57' x2='260.98' y2='371.13' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='327.11' y='397.40' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='400.97' x2='330.67' y2='397.40' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='397.40' x2='330.67' y2='400.97' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='327.11' y='374.67' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='378.24' x2='330.67' y2='374.67' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='374.67' x2='330.67' y2='378.24' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,509.48 55.81,495.57 57.09,490.63 61.50,475.00 66.38,459.92 67.19,457.63 72.87,442.96 78.56,430.55 82.64,422.85 84.25,420.06 89.94,411.18 95.63,403.67 101.32,397.33 107.01,391.96 112.70,387.44 115.16,385.71 118.39,383.64 124.08,380.45 129.77,377.78 135.46,375.57 141.15,373.75 146.83,372.27 152.52,371.08 158.21,370.15 163.90,369.44 169.59,368.93 175.28,368.59 180.97,368.41 186.66,368.36 189.50,368.39 192.35,368.44 198.04,368.62 203.73,368.90 209.42,369.27 215.11,369.72 220.79,370.24 226.48,370.82 232.17,371.47 237.86,372.16 243.55,372.91 249.24,373.70 254.93,374.53 259.20,375.18 260.62,375.40 266.31,376.30 272.00,377.23 277.69,378.20 283.38,379.18 289.07,380.20 294.76,381.23 300.44,382.28 306.13,383.35 311.82,384.44 317.51,385.54 323.20,386.66 328.89,387.78 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='509.88' x2='54.22' y2='506.31' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='506.31' x2='54.22' y2='509.88' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='49.92' y1='508.10' x2='54.96' y2='508.10' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='510.62' x2='52.44' y2='505.58' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='505.62' x2='54.22' y2='502.05' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='502.05' x2='54.22' y2='505.62' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='49.92' y1='503.83' x2='54.96' y2='503.83' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='506.35' x2='52.44' y2='501.31' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='485.25' x2='58.87' y2='481.69' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='481.69' x2='58.87' y2='485.25' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='54.57' y1='483.47' x2='59.61' y2='483.47' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='485.99' x2='57.09' y2='480.95' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='478.63' x2='58.87' y2='475.06' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='475.06' x2='58.87' y2='478.63' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='54.57' y1='476.84' x2='59.61' y2='476.84' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='479.36' x2='57.09' y2='474.32' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='442.16' x2='68.16' y2='438.60' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='438.60' x2='68.16' y2='442.16' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='63.86' y1='440.38' x2='68.90' y2='440.38' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='442.90' x2='66.38' y2='437.86' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='443.11' x2='68.16' y2='439.55' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='439.55' x2='68.16' y2='443.11' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='63.86' y1='441.33' x2='68.90' y2='441.33' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='443.85' x2='66.38' y2='438.81' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='406.65' x2='84.42' y2='403.09' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='403.09' x2='84.42' y2='406.65' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.12' y1='404.87' x2='85.16' y2='404.87' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='407.39' x2='82.64' y2='402.35' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='420.38' x2='84.42' y2='416.82' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='416.82' x2='84.42' y2='420.38' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.12' y1='418.60' x2='85.16' y2='418.60' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='421.12' x2='82.64' y2='416.08' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='369.71' x2='116.95' y2='366.15' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='366.15' x2='116.95' y2='369.71' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='112.64' y1='367.93' x2='117.68' y2='367.93' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='370.45' x2='115.16' y2='365.41' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='362.61' x2='116.95' y2='359.05' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='359.05' x2='116.95' y2='362.61' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='112.64' y1='360.83' x2='117.68' y2='360.83' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='363.35' x2='115.16' y2='358.31' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='358.35' x2='191.29' y2='354.79' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='354.79' x2='191.29' y2='358.35' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='186.98' y1='356.57' x2='192.02' y2='356.57' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='359.09' x2='189.50' y2='354.05' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='384.39' x2='191.29' y2='380.83' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='380.83' x2='191.29' y2='384.39' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='186.98' y1='382.61' x2='192.02' y2='382.61' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='385.13' x2='189.50' y2='380.09' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='376.34' x2='260.98' y2='372.78' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='372.78' x2='260.98' y2='376.34' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='256.68' y1='374.56' x2='261.72' y2='374.56' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='377.08' x2='259.20' y2='372.04' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='391.50' x2='260.98' y2='387.93' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='387.93' x2='260.98' y2='391.50' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='256.68' y1='389.71' x2='261.72' y2='389.71' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='392.23' x2='259.20' y2='387.19' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='378.71' x2='330.67' y2='375.15' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='375.15' x2='330.67' y2='378.71' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='326.37' y1='376.93' x2='331.41' y2='376.93' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='379.45' x2='328.89' y2='374.41' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='398.13' x2='330.67' y2='394.56' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='394.56' x2='330.67' y2='398.13' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='326.37' y1='396.34' x2='331.41' y2='396.34' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='398.86' x2='328.89' y2='393.82' style='stroke-width: 0.75;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,503.15 55.81,482.17 57.09,475.10 61.50,454.05 66.38,435.68 67.19,433.07 72.87,417.35 78.56,405.53 82.64,398.89 84.25,396.61 89.94,389.85 95.63,384.69 101.32,380.73 107.01,377.68 112.70,375.32 115.16,374.47 118.39,373.48 124.08,372.05 129.77,370.94 135.46,370.07 141.15,369.41 146.83,368.90 152.52,368.53 158.21,368.28 163.90,368.13 169.59,368.05 175.28,368.06 180.97,368.13 186.66,368.27 189.50,368.36 192.35,368.46 198.04,368.70 203.73,369.00 209.42,369.33 215.11,369.72 220.79,370.14 226.48,370.60 232.17,371.09 237.86,371.62 243.55,372.19 249.24,372.78 254.93,373.41 259.20,373.89 260.62,374.06 266.31,374.74 272.00,375.44 277.69,376.17 283.38,376.92 289.07,377.69 294.76,378.48 300.44,379.29 306.13,380.12 311.82,380.97 317.51,381.83 323.20,382.71 328.89,383.60 ' style='stroke-width: 0.75; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='49.92' y1='500.52' x2='54.96' y2='500.52' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='503.04' x2='52.44' y2='498.00' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='49.92,500.52 52.44,498.00 54.96,500.52 52.44,503.04 49.92,500.52 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='49.92' y1='505.25' x2='54.96' y2='505.25' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='507.78' x2='52.44' y2='502.73' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='49.92,505.25 52.44,502.73 54.96,505.25 52.44,507.78 49.92,505.25 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='54.57' y1='477.79' x2='59.61' y2='477.79' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='480.31' x2='57.09' y2='475.27' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='54.57,477.79 57.09,475.27 59.61,477.79 57.09,480.31 54.57,477.79 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='54.57' y1='485.37' x2='59.61' y2='485.37' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='487.89' x2='57.09' y2='482.85' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='54.57,485.37 57.09,482.85 59.61,485.37 57.09,487.89 54.57,485.37 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='63.86' y1='444.17' x2='68.90' y2='444.17' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='446.69' x2='66.38' y2='441.65' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='63.86,444.17 66.38,441.65 68.90,444.17 66.38,446.69 63.86,444.17 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='63.86' y1='455.06' x2='68.90' y2='455.06' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='457.58' x2='66.38' y2='452.54' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='63.86,455.06 66.38,452.54 68.90,455.06 66.38,457.58 63.86,455.06 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.12' y1='404.87' x2='85.16' y2='404.87' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='407.39' x2='82.64' y2='402.35' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='80.12,404.87 82.64,402.35 85.16,404.87 82.64,407.39 80.12,404.87 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.12' y1='405.81' x2='85.16' y2='405.81' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='408.33' x2='82.64' y2='403.29' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='80.12,405.81 82.64,403.29 85.16,405.81 82.64,408.33 80.12,405.81 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='112.64' y1='362.25' x2='117.68' y2='362.25' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='364.77' x2='115.16' y2='359.73' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='112.64,362.25 115.16,359.73 117.68,362.25 115.16,364.77 112.64,362.25 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='112.64' y1='378.35' x2='117.68' y2='378.35' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='380.87' x2='115.16' y2='375.83' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='112.64,378.35 115.16,375.83 117.68,378.35 115.16,380.87 112.64,378.35 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='186.98' y1='337.15' x2='192.02' y2='337.15' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='339.67' x2='189.50' y2='334.63' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='186.98,337.15 189.50,334.63 192.02,337.15 189.50,339.67 186.98,337.15 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='186.98' y1='330.05' x2='192.02' y2='330.05' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='332.57' x2='189.50' y2='327.53' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='186.98,330.05 189.50,327.53 192.02,330.05 189.50,332.57 186.98,330.05 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='256.68' y1='348.99' x2='261.72' y2='348.99' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='351.51' x2='259.20' y2='346.47' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='256.68,348.99 259.20,346.47 261.72,348.99 259.20,351.51 256.68,348.99 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='256.68' y1='345.68' x2='261.72' y2='345.68' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='348.20' x2='259.20' y2='343.16' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='256.68,345.68 259.20,343.16 261.72,345.68 259.20,348.20 256.68,345.68 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='326.37' y1='341.41' x2='331.41' y2='341.41' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='343.93' x2='328.89' y2='338.89' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='326.37,341.41 328.89,338.89 331.41,341.41 328.89,343.93 326.37,341.41 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='326.37' y1='350.41' x2='331.41' y2='350.41' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='352.93' x2='328.89' y2='347.89' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='326.37,350.41 328.89,347.89 331.41,350.41 328.89,352.93 326.37,350.41 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,507.87 55.81,491.86 57.09,486.19 61.50,468.31 66.38,451.13 67.19,448.53 72.87,431.89 78.56,417.85 82.64,409.15 84.25,405.99 89.94,395.95 95.63,387.43 101.32,380.18 107.01,374.01 112.70,368.74 115.16,366.70 118.39,364.23 124.08,360.37 129.77,357.06 135.46,354.22 141.15,351.79 146.83,349.69 152.52,347.90 158.21,346.37 163.90,345.07 169.59,343.97 175.28,343.05 180.97,342.28 186.66,341.66 189.50,341.39 192.35,341.16 198.04,340.77 203.73,340.49 209.42,340.31 215.11,340.21 220.79,340.19 226.48,340.24 232.17,340.36 237.86,340.55 243.55,340.79 249.24,341.09 254.93,341.45 259.20,341.74 260.62,341.85 266.31,342.30 272.00,342.79 277.69,343.32 283.38,343.89 289.07,344.50 294.76,345.14 300.44,345.82 306.13,346.52 311.82,347.26 317.51,348.02 323.20,348.81 328.89,349.62 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='52.44' cy='512.36' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='512.36' x2='54.22' y2='512.36' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='514.14' x2='52.44' y2='510.58' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='52.44' cy='515.67' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='515.67' x2='54.22' y2='515.67' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='517.45' x2='52.44' y2='513.89' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='57.09' cy='502.89' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='502.89' x2='58.87' y2='502.89' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='504.67' x2='57.09' y2='501.11' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='57.09' cy='498.63' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='498.63' x2='58.87' y2='498.63' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='500.41' x2='57.09' y2='496.84' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='66.38' cy='472.58' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='472.58' x2='68.16' y2='472.58' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='474.36' x2='66.38' y2='470.80' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='66.38' cy='468.32' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='468.32' x2='68.16' y2='468.32' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='470.10' x2='66.38' y2='466.54' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='82.64' cy='438.49' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='438.49' x2='84.42' y2='438.49' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='440.27' x2='82.64' y2='436.71' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='82.64' cy='440.86' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='440.86' x2='84.42' y2='440.86' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='442.64' x2='82.64' y2='439.07' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='115.16' cy='391.13' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='391.13' x2='116.95' y2='391.13' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='392.92' x2='115.16' y2='389.35' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='115.16' cy='392.56' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='392.56' x2='116.95' y2='392.56' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='394.34' x2='115.16' y2='390.77' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='189.50' cy='359.41' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='359.41' x2='191.29' y2='359.41' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='361.19' x2='189.50' y2='357.63' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='189.50' cy='368.41' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='368.41' x2='191.29' y2='368.41' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='370.19' x2='189.50' y2='366.62' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='259.20' cy='350.88' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='350.88' x2='260.98' y2='350.88' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='352.67' x2='259.20' y2='349.10' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='259.20' cy='342.36' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='342.36' x2='260.98' y2='342.36' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='344.14' x2='259.20' y2='340.58' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='328.89' cy='345.68' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='345.68' x2='330.67' y2='345.68' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='347.46' x2='328.89' y2='343.89' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='328.89' cy='339.99' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='339.99' x2='330.67' y2='339.99' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='341.78' x2='328.89' y2='338.21' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,512.83 55.81,503.03 57.09,499.44 61.50,487.67 66.38,475.61 67.19,473.72 72.87,461.04 78.56,449.53 82.64,441.93 84.25,439.07 89.94,429.56 95.63,420.93 101.32,413.10 107.01,405.98 112.70,399.52 115.16,396.92 118.39,393.67 124.08,388.36 129.77,383.55 135.46,379.20 141.15,375.27 146.83,371.72 152.52,368.51 158.21,365.63 163.90,363.04 169.59,360.73 175.28,358.66 180.97,356.81 186.66,355.18 189.50,354.44 192.35,353.74 198.04,352.48 203.73,351.38 209.42,350.43 215.11,349.63 220.79,348.95 226.48,348.39 232.17,347.94 237.86,347.60 243.55,347.35 249.24,347.19 254.93,347.11 259.20,347.10 260.62,347.11 266.31,347.18 272.00,347.32 277.69,347.52 283.38,347.77 289.07,348.09 294.76,348.45 300.44,348.86 306.13,349.31 311.82,349.80 317.51,350.34 323.20,350.91 328.89,351.51 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,516.08 54.84,511.23 50.04,511.23 52.44,516.08 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,510.53 54.84,515.38 50.04,515.38 52.44,510.53 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,515.13 54.84,510.28 50.04,510.28 52.44,515.13 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,509.59 54.84,514.44 50.04,514.44 52.44,509.59 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,514.66 59.49,509.81 54.69,509.81 57.09,514.66 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,509.11 59.49,513.96 54.69,513.96 57.09,509.11 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,505.66 59.49,500.81 54.69,500.81 57.09,505.66 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,500.12 59.49,504.97 54.69,504.97 57.09,500.12 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,495.24 68.78,490.39 63.98,490.39 66.38,495.24 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,489.70 68.78,494.55 63.98,494.55 66.38,489.70 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,497.61 68.78,492.76 63.98,492.76 66.38,497.61 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,492.07 68.78,496.92 63.98,496.92 66.38,492.07 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,470.14 85.04,465.29 80.24,465.29 82.64,470.14 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,464.60 85.04,469.45 80.24,469.45 82.64,464.60 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,478.19 85.04,473.34 80.24,473.34 82.64,478.19 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,472.65 85.04,477.50 80.24,477.50 82.64,472.65 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,449.31 117.56,444.46 112.76,444.46 115.16,449.31 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,443.77 117.56,448.62 112.76,448.62 115.16,443.77 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,433.21 117.56,428.36 112.76,428.36 115.16,433.21 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,427.67 117.56,432.52 112.76,432.52 115.16,427.67 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,411.43 191.90,406.58 187.10,406.58 189.50,411.43 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,405.88 191.90,410.73 187.10,410.73 189.50,405.88 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,420.42 191.90,415.57 187.10,415.57 189.50,420.42 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,414.88 191.90,419.73 187.10,419.73 189.50,414.88 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,426.11 261.60,421.26 256.80,421.26 259.20,426.11 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,420.56 261.60,425.41 256.80,425.41 259.20,420.56 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,426.58 261.60,421.73 256.80,421.73 259.20,426.58 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,421.04 261.60,425.89 256.80,425.89 259.20,421.04 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,418.53 331.29,413.68 326.49,413.68 328.89,418.53 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,412.99 331.29,417.84 326.49,417.84 328.89,412.99 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,422.32 331.29,417.47 326.49,417.47 328.89,422.32 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,416.78 331.29,421.62 326.49,421.62 328.89,416.78 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,515.62 55.81,509.66 57.09,507.47 61.50,500.28 66.38,492.89 67.19,491.73 72.87,483.93 78.56,476.82 82.64,472.11 84.25,470.33 89.94,464.43 95.63,459.05 101.32,454.15 107.01,449.69 112.70,445.64 115.16,444.00 118.39,441.96 124.08,438.62 129.77,435.59 135.46,432.85 141.15,430.37 146.83,428.13 152.52,426.11 158.21,424.30 163.90,422.67 169.59,421.21 175.28,419.91 180.97,418.76 186.66,417.74 189.50,417.28 192.35,416.85 198.04,416.07 203.73,415.39 209.42,414.81 215.11,414.32 220.79,413.92 226.48,413.59 232.17,413.33 237.86,413.14 243.55,413.00 249.24,412.93 254.93,412.90 259.20,412.92 260.62,412.93 266.31,413.00 272.00,413.11 277.69,413.26 283.38,413.45 289.07,413.67 294.76,413.92 300.44,414.20 306.13,414.51 311.82,414.84 317.51,415.20 323.20,415.58 328.89,415.98 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='518.51' x2='54.22' y2='518.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='520.30' x2='52.44' y2='516.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='50.66' y='516.73' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='508.10' x2='54.22' y2='508.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='52.44' y1='509.88' x2='52.44' y2='506.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='50.66' y='506.31' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='502.89' x2='58.87' y2='502.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='504.67' x2='57.09' y2='501.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='55.30' y='501.11' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='500.99' x2='58.87' y2='500.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='57.09' y1='502.78' x2='57.09' y2='499.21' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='55.30' y='499.21' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='487.26' x2='68.16' y2='487.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='489.04' x2='66.38' y2='485.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='64.60' y='485.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='490.58' x2='68.16' y2='490.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='66.38' y1='492.36' x2='66.38' y2='488.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='64.60' y='488.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='464.06' x2='84.42' y2='464.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='465.84' x2='82.64' y2='462.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='80.86' y='462.28' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='467.37' x2='84.42' y2='467.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='82.64' y1='469.15' x2='82.64' y2='465.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='80.86' y='465.59' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='438.49' x2='116.95' y2='438.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='440.27' x2='115.16' y2='436.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='113.38' y='436.71' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='438.96' x2='116.95' y2='438.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='115.16' y1='440.74' x2='115.16' y2='437.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='113.38' y='437.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='401.08' x2='191.29' y2='401.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='402.86' x2='189.50' y2='399.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='187.72' y='399.30' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='408.66' x2='191.29' y2='408.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='189.50' y1='410.44' x2='189.50' y2='406.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='187.72' y='406.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='395.40' x2='260.98' y2='395.40' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='397.18' x2='259.20' y2='393.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='257.42' y='393.61' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='409.60' x2='260.98' y2='409.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='259.20' y1='411.38' x2='259.20' y2='407.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='257.42' y='407.82' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='396.82' x2='330.67' y2='396.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='398.60' x2='328.89' y2='395.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='327.11' y='395.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='412.92' x2='330.67' y2='412.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='328.89' y1='414.70' x2='328.89' y2='411.14' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='327.11' y='411.14' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,514.86 55.81,507.85 57.09,505.30 61.50,496.90 66.38,488.31 67.19,486.96 72.87,477.96 78.56,469.79 82.64,464.42 84.25,462.39 89.94,455.69 95.63,449.63 101.32,444.14 107.01,439.17 112.70,434.69 115.16,432.88 118.39,430.64 124.08,426.99 129.77,423.71 135.46,420.76 141.15,418.11 146.83,415.74 152.52,413.62 158.21,411.73 163.90,410.06 169.59,408.58 175.28,407.28 180.97,406.15 186.66,405.16 189.50,404.72 192.35,404.31 198.04,403.59 203.73,402.99 209.42,402.49 215.11,402.10 220.79,401.79 226.48,401.57 232.17,401.43 237.86,401.35 243.55,401.35 249.24,401.40 254.93,401.52 259.20,401.64 260.62,401.68 266.31,401.90 272.00,402.15 277.69,402.45 283.38,402.79 289.07,403.17 294.76,403.58 300.44,404.01 306.13,404.48 311.82,404.98 317.51,405.50 323.20,406.04 328.89,406.60 ' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='52.44' cy='515.67' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='517.45' x2='54.22' y2='513.89' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='513.89' x2='54.22' y2='517.45' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='52.44' cy='519.46' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='521.24' x2='54.22' y2='517.68' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='50.66' y1='517.68' x2='54.22' y2='521.24' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='57.09' cy='502.89' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='504.67' x2='58.87' y2='501.11' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='501.11' x2='58.87' y2='504.67' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='57.09' cy='496.26' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='498.04' x2='58.87' y2='494.48' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='55.30' y1='494.48' x2='58.87' y2='498.04' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='66.38' cy='483.95' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='485.73' x2='68.16' y2='482.16' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='482.16' x2='68.16' y2='485.73' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='66.38' cy='489.63' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='491.41' x2='68.16' y2='487.85' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='64.60' y1='487.85' x2='68.16' y2='491.41' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='82.64' cy='465.95' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='467.73' x2='84.42' y2='464.17' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='464.17' x2='84.42' y2='467.73' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='82.64' cy='458.85' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='460.63' x2='84.42' y2='457.07' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='80.86' y1='457.07' x2='84.42' y2='460.63' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='115.16' cy='423.81' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='425.59' x2='116.95' y2='422.03' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='422.03' x2='116.95' y2='425.59' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='115.16' cy='434.23' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='436.01' x2='116.95' y2='432.44' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='113.38' y1='432.44' x2='116.95' y2='436.01' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='189.50' cy='399.18' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='400.97' x2='191.29' y2='397.40' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='397.40' x2='191.29' y2='400.97' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='189.50' cy='383.08' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='384.87' x2='191.29' y2='381.30' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='187.72' y1='381.30' x2='191.29' y2='384.87' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='259.20' cy='404.39' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='406.18' x2='260.98' y2='402.61' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='402.61' x2='260.98' y2='406.18' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='259.20' cy='380.72' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='382.50' x2='260.98' y2='378.94' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='257.42' y1='378.94' x2='260.98' y2='382.50' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='328.89' cy='393.03' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='394.81' x2='330.67' y2='391.25' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='391.25' x2='330.67' y2='394.81' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<circle cx='328.89' cy='390.66' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='392.44' x2='330.67' y2='388.88' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<line x1='327.11' y1='388.88' x2='330.67' y2='392.44' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,514.06 55.81,505.98 57.09,503.04 61.50,493.42 66.38,483.63 67.19,482.10 72.87,471.92 78.56,462.75 82.64,456.75 84.25,454.50 89.94,447.08 95.63,440.41 101.32,434.41 107.01,429.03 112.70,424.20 115.16,422.27 118.39,419.88 124.08,416.00 129.77,412.54 135.46,409.45 141.15,406.70 146.83,404.25 152.52,402.09 158.21,400.18 163.90,398.49 169.59,397.03 175.28,395.75 180.97,394.64 186.66,393.70 189.50,393.29 192.35,392.90 198.04,392.24 203.73,391.70 209.42,391.27 215.11,390.94 220.79,390.71 226.48,390.57 232.17,390.50 237.86,390.51 243.55,390.58 249.24,390.72 254.93,390.91 259.20,391.09 260.62,391.16 266.31,391.45 272.00,391.79 277.69,392.17 283.38,392.60 289.07,393.05 294.76,393.54 300.44,394.06 306.13,394.61 311.82,395.18 317.51,395.78 323.20,396.40 328.89,397.04 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,510.10 54.22,513.67 50.66,513.67 52.44,510.10 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='50.66' y='510.10' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='52.44,506.79 54.22,510.35 50.66,510.35 52.44,506.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='50.66' y='506.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,490.69 58.87,494.25 55.30,494.25 57.09,490.69 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='55.30' y='490.69' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='57.09,493.06 58.87,496.62 55.30,496.62 57.09,493.06 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='55.30' y='493.06' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,475.53 68.16,479.10 64.60,479.10 66.38,475.53 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='64.60' y='475.53' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='66.38,458.49 68.16,462.05 64.60,462.05 66.38,458.49 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='64.60' y='458.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,428.18 84.42,431.75 80.86,431.75 82.64,428.18 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='80.86' y='428.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='82.64,433.86 84.42,437.43 80.86,437.43 82.64,433.86 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='80.86' y='433.86' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,412.08 116.95,415.65 113.38,415.65 115.16,412.08 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='113.38' y='412.08' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='115.16,399.30 116.95,402.86 113.38,402.86 115.16,399.30 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='113.38' y='399.30' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,382.25 191.29,385.81 187.72,385.81 189.50,382.25 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='187.72' y='382.25' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='189.50,369.94 191.29,373.50 187.72,373.50 189.50,369.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='187.72' y='369.94' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,395.04 260.98,398.60 257.42,398.60 259.20,395.04 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='257.42' y='395.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='259.20,377.99 260.98,381.55 257.42,381.55 259.20,377.99 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='257.42' y='377.99' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,401.19 330.67,404.75 327.11,404.75 328.89,401.19 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='327.11' y='401.19' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='328.89,397.88 330.67,401.44 327.11,401.44 328.89,397.88 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<rect x='327.11' y='397.88' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,511.30 55.81,499.76 57.09,495.64 61.50,482.55 66.38,469.81 67.19,467.87 72.87,455.33 78.56,444.60 82.64,437.88 84.25,435.43 89.94,427.57 95.63,420.84 101.32,415.06 107.01,410.11 112.70,405.86 115.16,404.22 118.39,402.22 124.08,399.10 129.77,396.42 135.46,394.14 141.15,392.19 146.83,390.54 152.52,389.14 158.21,387.97 163.90,386.99 169.59,386.19 175.28,385.54 180.97,385.03 186.66,384.64 189.50,384.49 192.35,384.36 198.04,384.18 203.73,384.09 209.42,384.08 215.11,384.14 220.79,384.27 226.48,384.46 232.17,384.71 237.86,385.01 243.55,385.36 249.24,385.75 254.93,386.18 259.20,386.53 260.62,386.65 266.31,387.16 272.00,387.70 277.69,388.27 283.38,388.87 289.07,389.50 294.76,390.15 300.44,390.83 306.13,391.53 311.82,392.25 317.51,392.99 323.20,393.75 328.89,394.52 ' style='stroke-width: 0.75; stroke: #F5C710; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='50.66,509.88 54.22,509.88 54.22,506.31 50.66,506.31 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='50.66,512.25 54.22,512.25 54.22,508.68 50.66,508.68 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='55.30,495.20 58.87,495.20 58.87,491.63 55.30,491.63 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='55.30,492.36 58.87,492.36 58.87,488.79 55.30,488.79 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='64.60,476.26 68.16,476.26 68.16,472.69 64.60,472.69 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='64.60,458.74 68.16,458.74 68.16,455.17 64.60,455.17 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='80.86,445.95 84.42,445.95 84.42,442.39 80.86,442.39 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='80.86,436.95 84.42,436.95 84.42,433.39 80.86,433.39 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='113.38,404.28 116.95,404.28 116.95,400.72 113.38,400.72 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='113.38,405.23 116.95,405.23 116.95,401.66 113.38,401.66 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='187.72,377.29 191.29,377.29 191.29,373.73 187.72,373.73 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='187.72,376.82 191.29,376.82 191.29,373.25 187.72,373.25 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='257.42,372.08 260.98,372.08 260.98,368.52 257.42,368.52 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='257.42,379.18 260.98,379.18 260.98,375.62 257.42,375.62 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='327.11,371.61 330.67,371.61 330.67,368.04 327.11,368.04 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polygon points='327.11,393.39 330.67,393.39 330.67,389.83 327.11,389.83 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' /> +<polyline points='50.12,519.93 52.44,509.98 55.81,496.81 57.09,492.17 61.50,477.57 66.38,463.63 67.19,461.53 72.87,448.14 78.56,436.95 82.64,430.07 84.25,427.58 89.94,419.72 95.63,413.11 101.32,407.55 107.01,402.86 112.70,398.89 115.16,397.37 118.39,395.54 124.08,392.69 129.77,390.27 135.46,388.21 141.15,386.46 146.83,384.97 152.52,383.71 158.21,382.63 163.90,381.72 169.59,380.96 175.28,380.31 180.97,379.78 186.66,379.34 189.50,379.16 192.35,378.99 198.04,378.72 203.73,378.51 209.42,378.37 215.11,378.29 220.79,378.25 226.48,378.27 232.17,378.33 237.86,378.43 243.55,378.57 249.24,378.74 254.93,378.95 259.20,379.13 260.62,379.19 266.31,379.46 272.00,379.76 277.69,380.09 283.38,380.44 289.07,380.82 294.76,381.22 300.44,381.64 306.13,382.08 311.82,382.55 317.51,383.03 323.20,383.53 328.89,384.05 ' style='stroke-width: 0.75; stroke: #9E9E9E; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMjIuNDU=)' />  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1'> -    <rect x='398.97' y='337.35' width='301.08' height='190.18' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1'> +    <rect x='398.97' y='322.45' width='301.08' height='205.08' />    </clipPath>  </defs>  <defs> @@ -1933,550 +1933,550 @@      <rect x='0.00' y='0.00' width='720.00' height='576.00' />    </clipPath>  </defs> -<line x1='410.12' y1='527.53' x2='653.95' y2='527.53' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='410.12' y1='527.53' x2='699.50' y2='527.53' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <line x1='410.12' y1='527.53' x2='410.12' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='471.08' y1='527.53' x2='471.08' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='532.03' y1='527.53' x2='532.03' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='592.99' y1='527.53' x2='592.99' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='653.95' y1='527.53' x2='653.95' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='482.46' y1='527.53' x2='482.46' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='554.81' y1='527.53' x2='554.81' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='627.15' y1='527.53' x2='627.15' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='699.50' y1='527.53' x2='699.50' y2='532.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='407.92' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='466.68' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='527.64' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='588.60' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>30</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='649.56' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> -<line x1='398.97' y1='506.29' x2='398.97' y2='358.58' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='506.29' x2='394.21' y2='506.29' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='469.37' x2='394.21' y2='469.37' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='432.44' x2='394.21' y2='432.44' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='395.51' x2='394.21' y2='395.51' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='358.58' x2='394.21' y2='358.58' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,509.81) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,472.88) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,434.63) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,397.71) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,360.78) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> -<polyline points='398.97,527.53 700.04,527.53 700.04,337.35 398.97,337.35 398.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='478.07' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='550.42' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='622.76' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>30</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='695.11' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> +<line x1='398.97' y1='506.88' x2='398.97' y2='343.10' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='506.88' x2='394.21' y2='506.88' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='465.94' x2='394.21' y2='465.94' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='424.99' x2='394.21' y2='424.99' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='384.05' x2='394.21' y2='384.05' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='343.10' x2='394.21' y2='343.10' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,510.40) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,469.45) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,427.19) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,386.24) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,345.30) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> +<polyline points='398.97,527.53 700.04,527.53 700.04,322.45 398.97,322.45 398.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8MzE3LjM5'> -    <rect x='360.00' y='317.39' width='360.00' height='258.61' /> +  <clipPath id='cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8MzEyLjAw'> +    <rect x='360.00' y='312.00' width='360.00' height='264.00' />    </clipPath>  </defs> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8MzE3LjM5)'><text x='532.82' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8MzE3LjM5)'><text transform='translate(368.55,470.64) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8MzEyLjAw)'><text x='532.82' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8MzEyLjAw)'><text transform='translate(368.55,463.20) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g>  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1'> -    <rect x='398.97' y='337.35' width='301.08' height='190.18' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1'> +    <rect x='398.97' y='322.45' width='301.08' height='205.08' />    </clipPath>  </defs> -<line x1='398.97' y1='432.44' x2='700.04' y2='432.44' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='422.36' cy='435.08' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='422.36' cy='431.71' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='443.44' cy='435.36' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='443.44' cy='425.24' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='475.19' cy='422.50' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='475.19' cy='415.08' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='510.11' cy='433.77' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='510.11' cy='414.21' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='546.29' cy='440.27' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='546.29' cy='443.64' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='585.55' cy='450.11' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='585.55' cy='422.47' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='604.31' cy='434.76' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='604.31' cy='421.95' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='613.06' cy='449.35' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='613.06' cy='421.70' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='418.07,421.54 420.47,425.70 415.67,425.70 418.07,421.54 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='418.07,433.68 420.47,437.83 415.67,437.83 418.07,433.68 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='432.97,430.02 435.37,434.17 430.57,434.17 432.97,430.02 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='432.97,415.86 435.37,420.01 430.57,420.01 432.97,415.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='459.07,429.46 461.47,433.62 456.67,433.62 459.07,429.46 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='459.07,421.37 461.47,425.53 456.67,425.53 459.07,421.37 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='495.06,433.48 497.46,437.63 492.66,437.63 495.06,433.48 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='495.06,419.99 497.46,424.15 492.66,424.15 495.06,419.99 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='541.48,406.41 543.88,410.57 539.08,410.57 541.48,406.41 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='541.48,432.03 543.88,436.19 539.08,436.19 541.48,432.03 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='585.63,412.19 588.03,416.35 583.23,416.35 585.63,412.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='585.63,406.79 588.03,410.95 583.23,410.95 585.63,406.79 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='598.51,422.89 600.91,427.04 596.11,427.04 598.51,422.89 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='598.51,423.56 600.91,427.72 596.11,427.72 598.51,423.56 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='602.37,400.41 604.77,404.57 599.97,404.57 602.37,400.41 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='602.37,419.29 604.77,423.45 599.97,423.45 602.37,419.29 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='414.70' y1='437.39' x2='419.74' y2='437.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='417.22' y1='439.91' x2='417.22' y2='434.87' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='428.28' y1='431.81' x2='433.32' y2='431.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='430.80' y1='434.33' x2='430.80' y2='429.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='428.28' y1='423.72' x2='433.32' y2='423.72' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='430.80' y1='426.24' x2='430.80' y2='421.20' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='453.09' y1='449.55' x2='458.13' y2='449.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='455.61' y1='452.07' x2='455.61' y2='447.03' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='453.09' y1='443.48' x2='458.13' y2='443.48' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='455.61' y1='446.00' x2='455.61' y2='440.96' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='489.90' y1='435.12' x2='494.94' y2='435.12' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='492.42' y1='437.64' x2='492.42' y2='432.60' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='489.90' y1='447.26' x2='494.94' y2='447.26' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='492.42' y1='449.78' x2='492.42' y2='444.74' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='543.96' y1='432.64' x2='549.00' y2='432.64' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='546.48' y1='435.16' x2='546.48' y2='430.12' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='543.96' y1='437.36' x2='549.00' y2='437.36' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='546.48' y1='439.88' x2='546.48' y2='434.84' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='607.99' y1='422.50' x2='613.03' y2='422.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='610.51' y1='425.02' x2='610.51' y2='419.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='607.99' y1='453.52' x2='613.03' y2='453.52' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='610.51' y1='456.04' x2='610.51' y2='451.00' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='630.50' y1='431.99' x2='635.54' y2='431.99' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='633.02' y1='434.51' x2='633.02' y2='429.47' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='630.50' y1='415.81' x2='635.54' y2='415.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='633.02' y1='418.33' x2='633.02' y2='413.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.90' y1='422.21' x2='641.94' y2='422.21' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='639.42' y1='424.73' x2='639.42' y2='419.69' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.90' y1='439.07' x2='641.94' y2='439.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='639.42' y1='441.59' x2='639.42' y2='436.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='417.71' y1='439.36' x2='421.27' y2='435.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='417.71' y1='435.79' x2='421.27' y2='439.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='417.71' y1='447.45' x2='421.27' y2='443.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='417.71' y1='443.88' x2='421.27' y2='447.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='435.52' y1='440.56' x2='439.08' y2='437.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='435.52' y1='437.00' x2='439.08' y2='440.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='435.52' y1='426.41' x2='439.08' y2='422.84' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='435.52' y1='422.84' x2='439.08' y2='426.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='467.65' y1='438.06' x2='471.22' y2='434.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='467.65' y1='434.49' x2='471.22' y2='438.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='467.65' y1='436.03' x2='471.22' y2='432.47' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='467.65' y1='432.47' x2='471.22' y2='436.03' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='514.36' y1='444.38' x2='517.92' y2='440.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='514.36' y1='440.82' x2='517.92' y2='444.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='514.36' y1='416.06' x2='517.92' y2='412.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='514.36' y1='412.50' x2='517.92' y2='416.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.57' y1='435.87' x2='584.13' y2='432.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.57' y1='432.31' x2='584.13' y2='435.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.57' y1='430.48' x2='584.13' y2='426.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.57' y1='426.92' x2='584.13' y2='430.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='654.92' y1='431.18' x2='658.48' y2='427.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='654.92' y1='427.61' x2='658.48' y2='431.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='654.92' y1='442.64' x2='658.48' y2='439.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='654.92' y1='439.08' x2='658.48' y2='442.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='679.99' y1='429.07' x2='683.56' y2='425.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='679.99' y1='425.50' x2='683.56' y2='429.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='679.99' y1='440.53' x2='683.56' y2='436.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='679.99' y1='436.96' x2='683.56' y2='440.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='687.11' y1='427.94' x2='690.67' y2='424.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='687.11' y1='424.37' x2='690.67' y2='427.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='687.11' y1='445.47' x2='690.67' y2='441.90' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='687.11' y1='441.90' x2='690.67' y2='445.47' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='420.28,427.85 422.80,425.33 425.32,427.85 422.80,430.37 420.28,427.85 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='420.28,433.25 422.80,430.73 425.32,433.25 422.80,435.77 420.28,433.25 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='441.89,428.22 444.41,425.70 446.93,428.22 444.41,430.74 441.89,428.22 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='441.89,431.60 444.41,429.07 446.93,431.60 444.41,434.12 441.89,431.60 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='473.67,424.09 476.19,421.57 478.71,424.09 476.19,426.61 473.67,424.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='473.67,428.81 476.19,426.29 478.71,428.81 476.19,431.33 473.67,428.81 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='506.75,437.39 509.27,434.87 511.79,437.39 509.27,439.91 506.75,437.39 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='506.75,423.91 509.27,421.39 511.79,423.91 509.27,426.43 506.75,423.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='536.93,431.65 539.46,429.13 541.98,431.65 539.46,434.17 536.93,431.65 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='536.93,435.02 539.46,432.50 541.98,435.02 539.46,437.54 536.93,435.02 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='564.07,438.04 566.59,435.52 569.11,438.04 566.59,440.56 564.07,438.04 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='564.07,440.07 566.59,437.55 569.11,440.07 566.59,442.59 564.07,440.07 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='575.58,428.68 578.10,426.16 580.62,428.68 578.10,431.20 575.58,428.68 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='575.58,436.77 578.10,434.25 580.62,436.77 578.10,439.29 575.58,436.77 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='579.94,439.36 582.46,436.84 584.98,439.36 582.46,441.88 579.94,439.36 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='579.94,405.65 582.46,403.13 584.98,405.65 582.46,408.17 579.94,405.65 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='416.87,446.61 419.27,442.46 414.47,442.46 416.87,446.61 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='416.87,447.96 419.27,443.81 414.47,443.81 416.87,447.96 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='429.44,435.41 431.84,431.26 427.04,431.26 429.44,435.41 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='429.44,421.25 431.84,417.10 427.04,417.10 429.44,421.25 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='451.20,440.33 453.60,436.18 448.80,436.18 451.20,440.33 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='451.20,434.27 453.60,430.11 448.80,430.11 451.20,434.27 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='480.60,448.94 483.00,444.79 478.20,444.79 480.60,448.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='480.60,436.81 483.00,432.65 478.20,432.65 480.60,436.81 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='517.36,441.33 519.76,437.17 514.96,437.17 517.36,441.33 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='517.36,437.95 519.76,433.80 514.96,433.80 517.36,437.95 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='551.52,423.77 553.92,419.62 549.12,419.62 551.52,423.77 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='551.52,430.52 553.92,426.36 549.12,426.36 551.52,430.52 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='562.37,436.04 564.77,431.89 559.97,431.89 562.37,436.04 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='562.37,441.44 564.77,437.28 559.97,437.28 562.37,441.44 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='566.68,424.53 569.08,420.37 564.28,420.37 566.68,424.53 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='566.68,421.83 569.08,417.68 564.28,417.68 566.68,421.83 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='422.12' y='426.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='422.12' y1='430.44' x2='425.68' y2='426.87' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='422.12' y1='426.87' x2='425.68' y2='430.44' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='422.12' y='440.36' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='422.12' y1='443.92' x2='425.68' y2='440.36' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='422.12' y1='440.36' x2='425.68' y2='443.92' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='446.96' y='436.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='446.96' y1='440.04' x2='450.53' y2='436.48' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='446.96' y1='436.48' x2='450.53' y2='440.04' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='446.96' y='422.32' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='446.96' y1='425.88' x2='450.53' y2='422.32' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='446.96' y1='422.32' x2='450.53' y2='425.88' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='487.49' y='434.81' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='487.49' y1='438.37' x2='491.05' y2='434.81' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='487.49' y1='434.81' x2='491.05' y2='438.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='487.49' y='437.50' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='487.49' y1='441.07' x2='491.05' y2='437.50' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='487.49' y1='437.50' x2='491.05' y2='441.07' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='536.94' y='448.20' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='536.94' y1='451.77' x2='540.51' y2='448.20' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='536.94' y1='448.20' x2='540.51' y2='451.77' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='536.94' y='413.14' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='536.94' y1='416.70' x2='540.51' y2='413.14' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='536.94' y1='413.14' x2='540.51' y2='416.70' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='589.70' y='445.81' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='589.70' y1='449.38' x2='593.26' y2='445.81' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='589.70' y1='445.81' x2='593.26' y2='449.38' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='589.70' y='436.37' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='589.70' y1='439.94' x2='593.26' y2='436.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='589.70' y1='436.37' x2='593.26' y2='439.94' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='628.93' y='422.65' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='628.93' y1='426.21' x2='632.50' y2='422.65' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='628.93' y1='422.65' x2='632.50' y2='426.21' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='628.93' y='427.37' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='628.93' y1='430.93' x2='632.50' y2='427.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='628.93' y1='427.37' x2='632.50' y2='430.93' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='636.94' y='403.00' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.94' y1='406.56' x2='640.51' y2='403.00' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.94' y1='403.00' x2='640.51' y2='406.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='636.94' y='436.71' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.94' y1='440.27' x2='640.51' y2='436.71' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.94' y1='436.71' x2='640.51' y2='440.27' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='635.44' y='404.66' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='635.44' y1='408.23' x2='639.00' y2='404.66' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='635.44' y1='404.66' x2='639.00' y2='408.23' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='635.44' y='444.44' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='635.44' y1='448.01' x2='639.00' y2='444.44' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='635.44' y1='444.44' x2='639.00' y2='448.01' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='428.47' y1='428.80' x2='432.04' y2='425.24' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='428.47' y1='425.24' x2='432.04' y2='428.80' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='427.73' y1='427.02' x2='432.78' y2='427.02' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='430.25' y1='429.54' x2='430.25' y2='424.50' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='428.47' y1='434.87' x2='432.04' y2='431.31' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='428.47' y1='431.31' x2='432.04' y2='434.87' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='427.73' y1='433.09' x2='432.78' y2='433.09' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='430.25' y1='435.61' x2='430.25' y2='430.57' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='462.77' y1='425.93' x2='466.33' y2='422.36' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='462.77' y1='422.36' x2='466.33' y2='425.93' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='462.03' y1='424.15' x2='467.07' y2='424.15' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='464.55' y1='426.67' x2='464.55' y2='421.63' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='462.77' y1='436.04' x2='466.33' y2='432.48' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='462.77' y1='432.48' x2='466.33' y2='436.04' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='462.03' y1='434.26' x2='467.07' y2='434.26' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='464.55' y1='436.78' x2='464.55' y2='431.74' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.86' y1='433.23' x2='516.42' y2='429.67' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.86' y1='429.67' x2='516.42' y2='433.23' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.12' y1='431.45' x2='517.16' y2='431.45' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='514.64' y1='433.97' x2='514.64' y2='428.93' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.86' y1='431.89' x2='516.42' y2='428.32' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.86' y1='428.32' x2='516.42' y2='431.89' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.12' y1='430.10' x2='517.16' y2='430.10' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='514.64' y1='432.62' x2='514.64' y2='427.58' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='563.23' y1='430.78' x2='566.80' y2='427.21' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='563.23' y1='427.21' x2='566.80' y2='430.78' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='562.49' y1='429.00' x2='567.53' y2='429.00' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='565.01' y1='431.52' x2='565.01' y2='426.48' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='563.23' y1='411.23' x2='566.80' y2='407.66' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='563.23' y1='407.66' x2='566.80' y2='411.23' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='562.49' y1='409.44' x2='567.53' y2='409.44' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='565.01' y1='411.96' x2='565.01' y2='406.92' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='603.00' y1='448.15' x2='606.56' y2='444.58' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='603.00' y1='444.58' x2='606.56' y2='448.15' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='602.26' y1='446.37' x2='607.30' y2='446.37' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='604.78' y1='448.89' x2='604.78' y2='443.85' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='603.00' y1='458.26' x2='606.56' y2='454.70' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='603.00' y1='454.70' x2='606.56' y2='458.26' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='602.26' y1='456.48' x2='607.30' y2='456.48' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='604.78' y1='459.00' x2='604.78' y2='453.96' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='626.93' y1='458.09' x2='630.49' y2='454.53' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='626.93' y1='454.53' x2='630.49' y2='458.09' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='626.19' y1='456.31' x2='631.23' y2='456.31' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='628.71' y1='458.83' x2='628.71' y2='453.79' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='626.93' y1='417.64' x2='630.49' y2='414.07' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='626.93' y1='414.07' x2='630.49' y2='417.64' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='626.19' y1='415.86' x2='631.23' y2='415.86' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='628.71' y1='418.38' x2='628.71' y2='413.34' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='634.50' y1='439.60' x2='638.06' y2='436.04' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='634.50' y1='436.04' x2='638.06' y2='439.60' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='633.76' y1='437.82' x2='638.80' y2='437.82' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.28' y1='440.34' x2='636.28' y2='435.30' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='634.50' y1='414.66' x2='638.06' y2='411.09' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='634.50' y1='411.09' x2='638.06' y2='414.66' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='633.76' y1='412.88' x2='638.80' y2='412.88' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.28' y1='415.40' x2='636.28' y2='410.36' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.20' y1='451.88' x2='639.77' y2='448.31' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.20' y1='448.31' x2='639.77' y2='451.88' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='635.47' y1='450.09' x2='640.51' y2='450.09' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='637.99' y1='452.62' x2='637.99' y2='447.57' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.20' y1='417.49' x2='639.77' y2='413.93' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='636.20' y1='413.93' x2='639.77' y2='417.49' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='635.47' y1='415.71' x2='640.51' y2='415.71' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='637.99' y1='418.23' x2='637.99' y2='413.19' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='423.08' y1='442.96' x2='428.12' y2='442.96' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='425.60' y1='445.48' x2='425.60' y2='440.44' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='423.08,442.96 425.60,440.44 428.12,442.96 425.60,445.48 423.08,442.96 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='423.08' y1='436.21' x2='428.12' y2='436.21' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='425.60' y1='438.73' x2='425.60' y2='433.69' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='423.08,436.21 425.60,433.69 428.12,436.21 425.60,438.73 423.08,436.21 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='451.23' y1='444.19' x2='456.27' y2='444.19' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='453.75' y1='446.71' x2='453.75' y2='441.67' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='451.23,444.19 453.75,441.67 456.27,444.19 453.75,446.71 451.23,444.19 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='451.23' y1='434.08' x2='456.27' y2='434.08' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='453.75' y1='436.60' x2='453.75' y2='431.56' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='451.23,434.08 453.75,431.56 456.27,434.08 453.75,436.60 451.23,434.08 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='497.87' y1='441.14' x2='502.91' y2='441.14' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='500.39' y1='443.66' x2='500.39' y2='438.62' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='497.87,441.14 500.39,438.62 502.91,441.14 500.39,443.66 497.87,441.14 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='497.87' y1='426.31' x2='502.91' y2='426.31' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='500.39' y1='428.83' x2='500.39' y2='423.79' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='497.87,426.31 500.39,423.79 502.91,426.31 500.39,428.83 497.87,426.31 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='556.26' y1='435.22' x2='561.30' y2='435.22' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='558.78' y1='437.74' x2='558.78' y2='432.70' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='556.26,435.22 558.78,432.70 561.30,435.22 558.78,437.74 556.26,435.22 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='556.26' y1='433.87' x2='561.30' y2='433.87' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='558.78' y1='436.39' x2='558.78' y2='431.35' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='556.26,433.87 558.78,431.35 561.30,433.87 558.78,436.39 556.26,433.87 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='620.63' y1='432.11' x2='625.67' y2='432.11' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='623.15' y1='434.63' x2='623.15' y2='429.59' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='620.63,432.11 623.15,429.59 625.67,432.11 623.15,434.63 620.63,432.11 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='620.63' y1='408.52' x2='625.67' y2='408.52' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='623.15' y1='411.04' x2='623.15' y2='406.00' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='620.63,408.52 623.15,406.00 625.67,408.52 623.15,411.04 620.63,408.52 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='669.52' y1='433.33' x2='674.57' y2='433.33' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='672.04' y1='435.85' x2='672.04' y2='430.81' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='669.52,433.33 672.04,430.81 674.57,433.33 672.04,435.85 669.52,433.33 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='669.52' y1='444.79' x2='674.57' y2='444.79' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='672.04' y1='447.31' x2='672.04' y2='442.27' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='669.52,444.79 672.04,442.27 674.57,444.79 672.04,447.31 669.52,444.79 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='679.86' y1='421.89' x2='684.90' y2='421.89' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='682.38' y1='424.41' x2='682.38' y2='419.37' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='679.86,421.89 682.38,419.37 684.90,421.89 682.38,424.41 679.86,421.89 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='679.86' y1='427.29' x2='684.90' y2='427.29' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='682.38' y1='429.81' x2='682.38' y2='424.77' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='679.86,427.29 682.38,424.77 684.90,427.29 682.38,429.81 679.86,427.29 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='678.77' y1='454.79' x2='683.81' y2='454.79' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='681.29' y1='457.31' x2='681.29' y2='452.27' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='678.77,454.79 681.29,452.27 683.81,454.79 681.29,457.31 678.77,454.79 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='678.77' y1='438.61' x2='683.81' y2='438.61' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='681.29' y1='441.13' x2='681.29' y2='436.09' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='678.77,438.61 681.29,436.09 683.81,438.61 681.29,441.13 678.77,438.61 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='419.25' cy='433.13' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='417.47' y1='433.13' x2='421.03' y2='433.13' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='419.25' y1='434.91' x2='419.25' y2='431.34' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='419.25' cy='428.41' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='417.47' y1='428.41' x2='421.03' y2='428.41' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='419.25' y1='430.19' x2='419.25' y2='426.62' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='436.53' cy='427.49' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='434.75' y1='427.49' x2='438.31' y2='427.49' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='436.53' y1='429.28' x2='436.53' y2='425.71' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='436.53' cy='433.56' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='434.75' y1='433.56' x2='438.31' y2='433.56' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='436.53' y1='435.34' x2='436.53' y2='431.78' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='467.54' cy='437.03' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='465.75' y1='437.03' x2='469.32' y2='437.03' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='467.54' y1='438.81' x2='467.54' y2='435.25' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='467.54' cy='443.10' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='465.75' y1='443.10' x2='469.32' y2='443.10' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='467.54' y1='444.88' x2='467.54' y2='441.31' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='512.12' cy='437.61' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='510.34' y1='437.61' x2='513.90' y2='437.61' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.12' y1='439.39' x2='512.12' y2='435.83' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='512.12' cy='434.24' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='510.34' y1='434.24' x2='513.90' y2='434.24' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='512.12' y1='436.02' x2='512.12' y2='432.46' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='574.31' cy='440.97' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='572.53' y1='440.97' x2='576.09' y2='440.97' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='574.31' y1='442.75' x2='574.31' y2='439.19' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='574.31' cy='439.62' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='572.53' y1='439.62' x2='576.09' y2='439.62' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='574.31' y1='441.40' x2='574.31' y2='437.84' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='643.27' cy='424.70' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='641.48' y1='424.70' x2='645.05' y2='424.70' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='643.27' y1='426.48' x2='643.27' y2='422.92' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='643.27' cy='411.22' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='641.48' y1='411.22' x2='645.05' y2='411.22' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='643.27' y1='413.00' x2='643.27' y2='409.44' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='667.71' cy='425.98' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='665.93' y1='425.98' x2='669.49' y2='425.98' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='667.71' y1='427.77' x2='667.71' y2='424.20' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='667.71' cy='438.79' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='665.93' y1='438.79' x2='669.49' y2='438.79' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='667.71' y1='440.58' x2='667.71' y2='437.01' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='676.48' cy='440.56' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='674.69' y1='440.56' x2='678.26' y2='440.56' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='676.48' y1='442.34' x2='676.48' y2='438.78' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='676.48' cy='450.67' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='674.69' y1='450.67' x2='678.26' y2='450.67' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='676.48' y1='452.46' x2='676.48' y2='448.89' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='415.84,438.32 418.24,433.47 413.44,433.47 415.84,438.32 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='415.84,432.78 418.24,437.63 413.44,437.63 415.84,432.78 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='415.84,439.67 418.24,434.82 413.44,434.82 415.84,439.67 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='415.84,434.13 418.24,438.98 413.44,438.98 415.84,434.13 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='426.72,428.31 429.12,423.46 424.32,423.46 426.72,428.31 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='426.72,422.77 429.12,427.62 424.32,427.62 426.72,422.77 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='426.72,441.12 429.12,436.27 424.32,436.27 426.72,441.12 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='426.72,435.58 429.12,440.43 424.32,440.43 426.72,435.58 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='446.45,434.81 448.85,429.96 444.05,429.96 446.45,434.81 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='446.45,429.26 448.85,434.11 444.05,434.11 446.45,429.26 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='446.45,431.43 448.85,426.59 444.05,426.59 446.45,431.43 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='446.45,425.89 448.85,430.74 444.05,430.74 446.45,425.89 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='475.34,440.60 477.74,435.75 472.94,435.75 475.34,440.60 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='475.34,435.06 477.74,439.91 472.94,439.91 475.34,435.06 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='475.34,428.47 477.74,423.62 472.94,423.62 475.34,428.47 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='475.34,422.92 477.74,427.77 472.94,427.77 475.34,422.92 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='516.94,429.66 519.34,424.81 514.54,424.81 516.94,429.66 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='516.94,424.12 519.34,428.97 514.54,428.97 516.94,424.12 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='516.94,452.58 519.34,447.73 514.54,447.73 516.94,452.58 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='516.94,447.04 519.34,451.89 514.54,451.89 516.94,447.04 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='565.68,448.56 568.08,443.71 563.28,443.71 565.68,448.56 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='565.68,443.02 568.08,447.87 563.28,447.87 565.68,443.02 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='565.68,434.40 568.08,429.55 563.28,429.55 565.68,434.40 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='565.68,428.86 568.08,433.71 563.28,433.71 565.68,428.86 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='584.41,421.10 586.81,416.25 582.01,416.25 584.41,421.10 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='584.41,415.56 586.81,420.41 582.01,420.41 584.41,415.56 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='584.41,419.75 586.81,414.90 582.01,414.90 584.41,419.75 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='584.41,414.21 586.81,419.06 582.01,419.06 584.41,414.21 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='592.24,442.11 594.64,437.26 589.84,437.26 592.24,442.11 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='592.24,436.57 594.64,441.42 589.84,441.42 592.24,436.57 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='592.24,434.69 594.64,429.84 589.84,429.84 592.24,434.69 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='592.24,429.15 594.64,434.00 589.84,434.00 592.24,429.15 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='414.94' y1='427.16' x2='418.50' y2='427.16' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='416.72' y1='428.94' x2='416.72' y2='425.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='414.94' y='425.38' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='414.94' y1='441.99' x2='418.50' y2='441.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='416.72' y1='443.77' x2='416.72' y2='440.21' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='414.94' y='440.21' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='427.45' y1='436.24' x2='431.02' y2='436.24' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='429.23' y1='438.02' x2='429.23' y2='434.46' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='427.45' y='434.46' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='427.45' y1='438.26' x2='431.02' y2='438.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='429.23' y1='440.04' x2='429.23' y2='436.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='427.45' y='436.48' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='449.96' y1='433.59' x2='453.53' y2='433.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='451.75' y1='435.37' x2='451.75' y2='431.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='449.96' y='431.81' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='449.96' y1='428.87' x2='453.53' y2='428.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='451.75' y1='430.65' x2='451.75' y2='427.09' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='449.96' y='427.09' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='482.48' y1='432.01' x2='486.04' y2='432.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='484.26' y1='433.80' x2='484.26' y2='430.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='482.48' y='430.23' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='482.48' y1='427.29' x2='486.04' y2='427.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='484.26' y1='429.08' x2='484.26' y2='425.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='482.48' y='425.51' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='528.04' y1='422.74' x2='531.61' y2='422.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='529.83' y1='424.52' x2='529.83' y2='420.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='528.04' y='420.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='528.04' y1='422.07' x2='531.61' y2='422.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='529.83' y1='423.85' x2='529.83' y2='420.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='528.04' y='420.29' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='578.25' y1='436.65' x2='581.82' y2='436.65' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.04' y1='438.44' x2='580.04' y2='434.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='578.25' y='434.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='578.25' y1='425.19' x2='581.82' y2='425.19' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.04' y1='426.97' x2='580.04' y2='423.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='578.25' y='423.41' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='595.13' y1='442.94' x2='598.69' y2='442.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='596.91' y1='444.72' x2='596.91' y2='441.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='595.13' y='441.15' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='595.13' y1='420.01' x2='598.69' y2='420.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='596.91' y1='421.79' x2='596.91' y2='418.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='595.13' y='418.23' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='600.30' y1='451.38' x2='603.86' y2='451.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='602.08' y1='453.16' x2='602.08' y2='449.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='600.30' y='449.60' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='600.30' y1='423.74' x2='603.86' y2='423.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='602.08' y1='425.52' x2='602.08' y2='421.95' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='600.30' y='421.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='417.54' cy='430.30' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='415.76' y1='432.08' x2='419.32' y2='428.52' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='415.76' y1='428.52' x2='419.32' y2='432.08' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='417.54' cy='424.90' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='415.76' y1='426.69' x2='419.32' y2='423.12' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='415.76' y1='423.12' x2='419.32' y2='426.69' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='431.49' cy='433.07' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='429.71' y1='434.86' x2='433.27' y2='431.29' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='429.71' y1='431.29' x2='433.27' y2='434.86' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='431.49' cy='442.51' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='429.71' y1='444.29' x2='433.27' y2='440.73' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='429.71' y1='440.73' x2='433.27' y2='444.29' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='456.17' cy='432.75' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='454.39' y1='434.53' x2='457.95' y2='430.96' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='454.39' y1='430.96' x2='457.95' y2='434.53' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='456.17' cy='425.33' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='454.39' y1='427.11' x2='457.95' y2='423.55' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='454.39' y1='423.55' x2='457.95' y2='427.11' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='490.77' cy='421.45' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='488.99' y1='423.23' x2='492.55' y2='419.66' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='488.99' y1='419.66' x2='492.55' y2='423.23' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='490.77' cy='430.88' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='488.99' y1='432.67' x2='492.55' y2='429.10' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='488.99' y1='429.10' x2='492.55' y2='432.67' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='536.75' cy='433.29' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='534.97' y1='435.07' x2='538.53' y2='431.51' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='534.97' y1='431.51' x2='538.53' y2='435.07' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='536.75' cy='418.46' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='534.97' y1='420.24' x2='538.53' y2='416.68' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='534.97' y1='416.68' x2='538.53' y2='420.24' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='582.55' cy='426.46' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.77' y1='428.24' x2='584.33' y2='424.68' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.77' y1='424.68' x2='584.33' y2='428.24' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='582.55' cy='450.06' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.77' y1='451.84' x2='584.33' y2='448.28' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='580.77' y1='448.28' x2='584.33' y2='451.84' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='595.65' cy='411.30' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='593.86' y1='413.08' x2='597.43' y2='409.52' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='593.86' y1='409.52' x2='597.43' y2='413.08' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='595.65' cy='447.71' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='593.86' y1='449.49' x2='597.43' y2='445.92' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='593.86' y1='445.92' x2='597.43' y2='449.49' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='598.24' cy='434.73' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='596.45' y1='436.51' x2='600.02' y2='432.95' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='596.45' y1='432.95' x2='600.02' y2='436.51' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<circle cx='598.24' cy='438.77' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='596.45' y1='440.56' x2='600.02' y2='436.99' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<line x1='596.45' y1='436.99' x2='600.02' y2='440.56' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='421.17,429.89 422.96,433.45 419.39,433.45 421.17,429.89 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='419.39' y='429.89' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='421.17,434.61 422.96,438.17 419.39,438.17 421.17,434.61 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='419.39' y='434.61' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='441.37,435.20 443.15,438.76 439.58,438.76 441.37,435.20 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='439.58' y='435.20' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='441.37,432.50 443.15,436.07 439.58,436.07 441.37,432.50 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='439.58' y='432.50' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='475.16,420.07 476.94,423.64 473.38,423.64 475.16,420.07 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='473.38' y='420.07' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='475.16,444.34 476.94,447.91 473.38,447.91 475.16,444.34 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='473.38' y='444.34' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='518.26,442.52 520.04,446.08 516.48,446.08 518.26,442.52 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='516.48' y='442.52' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='518.26,434.43 520.04,437.99 516.48,437.99 518.26,434.43 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='516.48' y='434.43' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='567.68,416.85 569.46,420.41 565.90,420.41 567.68,416.85 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='565.90' y='416.85' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='567.68,435.05 569.46,438.62 565.90,438.62 567.68,435.05 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='565.90' y='435.05' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='609.56,431.89 611.34,435.45 607.77,435.45 609.56,431.89 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='607.77' y='431.89' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='609.56,451.44 611.34,455.01 607.77,455.01 609.56,451.44 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='607.77' y='451.44' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='621.97,414.78 623.75,418.35 620.19,418.35 621.97,414.78 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='620.19' y='414.78' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='621.97,443.10 623.75,446.67 620.19,446.67 621.97,443.10 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='620.19' y='443.10' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='625.27,417.20 627.05,420.77 623.49,420.77 625.27,417.20 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='623.49' y='417.20' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polyline points='625.27,423.95 627.05,427.51 623.49,427.51 625.27,423.95 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<rect x='623.49' y='423.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='422.94,434.93 426.50,434.93 426.50,431.36 422.94,431.36 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='422.94,431.56 426.50,431.56 426.50,427.99 422.94,427.99 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='447.99,428.12 451.55,428.12 451.55,424.56 447.99,424.56 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='447.99,432.16 451.55,432.16 451.55,428.60 447.99,428.60 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='485.33,413.79 488.89,413.79 488.89,410.22 485.33,410.22 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='485.33,439.41 488.89,439.41 488.89,435.85 485.33,435.85 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='525.16,414.91 528.72,414.91 528.72,411.35 525.16,411.35 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='525.16,427.72 528.72,427.72 528.72,424.16 525.16,424.16 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='563.00,436.43 566.57,436.43 566.57,432.86 563.00,432.86 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='563.00,435.08 566.57,435.08 566.57,431.51 563.00,431.51 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='598.68,446.86 602.24,446.86 602.24,443.29 598.68,443.29 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='598.68,447.53 602.24,447.53 602.24,443.97 598.68,443.97 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='614.68,447.37 618.24,447.37 618.24,443.80 614.68,443.80 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='614.68,436.58 618.24,436.58 618.24,433.01 614.68,433.01 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='621.71,452.40 625.27,452.40 625.27,448.84 621.71,448.84 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> -<polygon points='621.71,417.34 625.27,417.34 625.27,413.78 621.71,413.78 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzM3LjM1)' /> +<line x1='398.97' y1='424.99' x2='700.04' y2='424.99' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='422.55' cy='430.12' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='422.55' cy='426.36' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='444.94' cy='433.16' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='444.94' cy='421.88' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='481.38' cy='419.35' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='481.38' cy='411.08' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='525.52' cy='427.61' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='525.52' cy='405.80' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='571.45' cy='427.24' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='571.45' cy='430.25' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='602.33' cy='438.77' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='602.33' cy='410.94' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='605.75' cy='428.45' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='605.75' cy='416.41' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='600.53' cy='445.90' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='600.53' cy='418.83' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='418.86,413.88 421.26,418.04 416.46,418.04 418.86,413.88 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='418.86,427.42 421.26,431.58 416.46,431.58 418.86,427.42 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='435.15,424.78 437.55,428.94 432.75,428.94 435.15,424.78 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='435.15,408.99 437.55,413.14 432.75,413.14 435.15,408.99 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='463.41,426.23 465.81,430.39 461.01,430.39 463.41,426.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='463.41,417.96 465.81,422.11 461.01,422.11 463.41,417.96 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='501.53,433.23 503.93,437.39 499.13,437.39 501.53,433.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='501.53,418.94 503.93,423.10 499.13,423.10 501.53,418.94 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='547.85,407.65 550.25,411.81 545.45,411.81 547.85,407.65 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='547.85,436.23 550.25,440.39 545.45,440.39 547.85,436.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='581.71,417.57 584.11,421.73 579.31,421.73 581.71,417.57 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='581.71,412.31 584.11,416.47 579.31,416.47 581.71,412.31 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='581.56,428.25 583.96,432.41 579.16,432.41 581.56,428.25 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='581.56,429.76 583.96,433.92 579.16,433.92 581.56,429.76 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='572.78,407.30 575.18,411.46 570.38,411.46 572.78,407.30 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='572.78,424.60 575.18,428.76 570.38,428.76 572.78,424.60 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='416.10' y1='430.44' x2='421.14' y2='430.44' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='418.62' y1='432.96' x2='418.62' y2='427.92' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='432.26' y1='424.18' x2='437.30' y2='424.18' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='434.78' y1='426.70' x2='434.78' y2='421.66' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='432.26' y1='415.15' x2='437.30' y2='415.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='434.78' y1='417.67' x2='434.78' y2='412.63' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='461.43' y1='443.49' x2='466.47' y2='443.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='463.95' y1='446.01' x2='463.95' y2='440.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='461.43' y1='436.72' x2='466.47' y2='436.72' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='463.95' y1='439.24' x2='463.95' y2='434.20' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='503.70' y1='426.62' x2='508.74' y2='426.62' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='506.22' y1='429.14' x2='506.22' y2='424.10' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='503.70' y1='440.91' x2='508.74' y2='440.91' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='506.22' y1='443.43' x2='506.22' y2='438.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='562.42' y1='424.23' x2='567.46' y2='424.23' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='564.94' y1='426.75' x2='564.94' y2='421.71' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='562.42' y1='429.50' x2='567.46' y2='429.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='564.94' y1='432.02' x2='564.94' y2='426.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='619.99' y1='414.02' x2='625.03' y2='414.02' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='622.51' y1='416.54' x2='622.51' y2='411.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='619.99' y1='445.61' x2='625.03' y2='445.61' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='622.51' y1='448.13' x2='622.51' y2='443.09' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='627.99' y1='424.52' x2='633.03' y2='424.52' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.51' y1='427.04' x2='630.51' y2='422.00' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='627.99' y1='407.97' x2='633.03' y2='407.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.51' y1='410.49' x2='630.51' y2='405.45' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='618.29' y1='415.79' x2='623.33' y2='415.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='620.81' y1='418.31' x2='620.81' y2='413.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='618.29' y1='430.83' x2='623.33' y2='430.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='620.81' y1='433.35' x2='620.81' y2='428.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='419.46' y1='432.51' x2='423.03' y2='428.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='419.46' y1='428.94' x2='423.03' y2='432.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='419.46' y1='441.53' x2='423.03' y2='437.97' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='419.46' y1='437.97' x2='423.03' y2='441.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='440.52' y1='433.93' x2='444.09' y2='430.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='440.52' y1='430.36' x2='444.09' y2='433.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='440.52' y1='418.13' x2='444.09' y2='414.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='440.52' y1='414.57' x2='444.09' y2='418.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='478.27' y1='430.78' x2='481.83' y2='427.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='478.27' y1='427.22' x2='481.83' y2='430.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='478.27' y1='428.53' x2='481.83' y2='424.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='478.27' y1='424.96' x2='481.83' y2='428.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='532.29' y1='437.81' x2='535.85' y2='434.24' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='532.29' y1='434.24' x2='535.85' y2='437.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='532.29' y1='406.22' x2='535.85' y2='402.65' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='532.29' y1='402.65' x2='535.85' y2='406.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.85' y1='428.27' x2='609.41' y2='424.70' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.85' y1='424.70' x2='609.41' y2='428.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.85' y1='422.25' x2='609.41' y2='418.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.85' y1='418.69' x2='609.41' y2='422.25' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.36' y1='424.16' x2='679.92' y2='420.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.36' y1='420.60' x2='679.92' y2='424.16' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.36' y1='436.20' x2='679.92' y2='432.63' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.36' y1='432.63' x2='679.92' y2='436.20' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='686.92' y1='423.71' x2='690.48' y2='420.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='686.92' y1='420.15' x2='690.48' y2='423.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='686.92' y1='434.99' x2='690.48' y2='431.43' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='686.92' y1='431.43' x2='690.48' y2='434.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.83' y1='424.43' x2='680.39' y2='420.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.83' y1='420.86' x2='680.39' y2='424.43' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.83' y1='441.72' x2='680.39' y2='438.16' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='676.83' y1='438.16' x2='680.39' y2='441.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='422.31,420.22 424.83,417.70 427.35,420.22 424.83,422.75 422.31,420.22 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='422.31,426.24 424.83,423.72 427.35,426.24 424.83,428.76 422.31,426.24 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='447.29,421.34 449.81,418.82 452.33,421.34 449.81,423.86 447.29,421.34 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='447.29,425.10 449.81,422.58 452.33,425.10 449.81,427.62 447.29,425.10 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='483.60,416.68 486.12,414.16 488.64,416.68 486.12,419.20 483.60,416.68 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='483.60,421.95 486.12,419.43 488.64,421.95 486.12,424.47 483.60,421.95 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='520.14,432.09 522.66,429.57 525.18,432.09 522.66,434.61 520.14,432.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='520.14,417.05 522.66,414.53 525.18,417.05 522.66,419.57 520.14,417.05 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='549.72,426.15 552.24,423.63 554.76,426.15 552.24,428.67 549.72,426.15 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='549.72,429.16 552.24,426.64 554.76,429.16 552.24,431.68 549.72,429.16 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.37,431.42 568.89,428.90 571.41,431.42 568.89,433.94 566.37,431.42 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.37,433.67 568.89,431.15 571.41,433.67 568.89,436.19 566.37,433.67 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.00,420.52 568.52,418.00 571.04,420.52 568.52,423.04 566.00,420.52 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.00,428.79 568.52,426.27 571.04,428.79 568.52,431.31 566.00,428.79 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='558.57,429.74 561.09,427.22 563.61,429.74 561.09,432.26 558.57,429.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='558.57,398.15 561.09,395.63 563.61,398.15 561.09,400.67 558.57,398.15 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='418.29,440.32 420.69,436.16 415.89,436.16 418.29,440.32 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='418.29,441.83 420.69,437.67 415.89,437.67 418.29,441.83 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='433.45,427.58 435.85,423.42 431.05,423.42 433.45,427.58 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='433.45,411.03 435.85,406.87 431.05,406.87 433.45,411.03 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='459.48,432.86 461.88,428.70 457.08,428.70 459.48,432.86 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='459.48,425.34 461.88,421.18 457.08,421.18 459.48,425.34 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='493.95,440.64 496.35,436.48 491.55,436.48 493.95,440.64 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='493.95,427.10 496.35,422.94 491.55,422.94 493.95,427.10 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='534.61,430.71 537.01,426.55 532.21,426.55 534.61,430.71 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='534.61,427.70 537.01,423.54 532.21,423.54 534.61,427.70 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='563.11,413.11 565.51,408.95 560.71,408.95 563.11,413.11 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='563.11,419.88 565.51,415.72 560.71,415.72 563.11,419.88 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='563.09,428.18 565.49,424.03 560.69,424.03 563.09,428.18 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='563.09,433.45 565.49,429.29 560.69,429.29 563.09,433.45 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='555.99,418.27 558.39,414.11 553.59,414.11 555.99,418.27 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='555.99,416.01 558.39,411.85 553.59,411.85 555.99,416.01 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='424.31' y='419.39' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='424.31' y1='422.96' x2='427.87' y2='419.39' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='424.31' y1='419.39' x2='427.87' y2='422.96' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='424.31' y='434.43' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='424.31' y1='438.00' x2='427.87' y2='434.43' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='424.31' y1='434.43' x2='427.87' y2='438.00' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='453.11' y='430.07' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='453.11' y1='433.63' x2='456.67' y2='430.07' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='453.11' y1='430.07' x2='456.67' y2='433.63' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='453.11' y='415.02' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='453.11' y1='418.59' x2='456.67' y2='415.02' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='453.11' y1='415.02' x2='456.67' y2='418.59' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='500.03' y='428.67' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='500.03' y1='432.24' x2='503.59' y2='428.67' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='500.03' y1='428.67' x2='503.59' y2='432.24' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='500.03' y='432.43' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='500.03' y1='436.00' x2='503.59' y2='432.43' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='500.03' y1='432.43' x2='503.59' y2='436.00' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='556.65' y='443.51' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='556.65' y1='447.07' x2='560.22' y2='443.51' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='556.65' y1='443.51' x2='560.22' y2='447.07' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='556.65' y='404.40' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='556.65' y1='407.96' x2='560.22' y2='404.40' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='556.65' y1='404.40' x2='560.22' y2='407.96' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='613.40' y='438.67' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='613.40' y1='442.23' x2='616.96' y2='438.67' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='613.40' y1='438.67' x2='616.96' y2='442.23' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='613.40' y='428.89' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='613.40' y1='432.45' x2='616.96' y2='428.89' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='613.40' y1='428.89' x2='616.96' y2='432.45' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='639.87' y='414.90' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.87' y1='418.47' x2='643.44' y2='414.90' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.87' y1='414.90' x2='643.44' y2='418.47' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='639.87' y='420.17' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.87' y1='423.73' x2='643.44' y2='420.17' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.87' y1='420.17' x2='643.44' y2='423.73' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='629.50' y='399.37' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='629.50' y1='402.93' x2='633.06' y2='399.37' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='629.50' y1='399.37' x2='633.06' y2='402.93' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='629.50' y='432.46' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='629.50' y1='436.03' x2='633.06' y2='432.46' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='629.50' y1='432.46' x2='633.06' y2='436.03' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='610.24' y='405.10' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='610.24' y1='408.67' x2='613.80' y2='405.10' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='610.24' y1='405.10' x2='613.80' y2='408.67' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='610.24' y='441.20' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='610.24' y1='444.77' x2='613.80' y2='441.20' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='610.24' y1='441.20' x2='613.80' y2='444.77' style='stroke-width: 0.75; stroke: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='433.98' y1='418.92' x2='437.54' y2='415.36' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='433.98' y1='415.36' x2='437.54' y2='418.92' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='433.24' y1='417.14' x2='438.28' y2='417.14' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='435.76' y1='419.66' x2='435.76' y2='414.62' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='433.98' y1='425.69' x2='437.54' y2='422.13' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='433.98' y1='422.13' x2='437.54' y2='425.69' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='433.24' y1='423.91' x2='438.28' y2='423.91' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='435.76' y1='426.43' x2='435.76' y2='421.39' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.83' y1='413.48' x2='480.39' y2='409.92' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.83' y1='409.92' x2='480.39' y2='413.48' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.09' y1='411.70' x2='481.13' y2='411.70' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='478.61' y1='414.22' x2='478.61' y2='409.18' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.83' y1='424.01' x2='480.39' y2='420.45' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.83' y1='420.45' x2='480.39' y2='424.01' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.09' y1='422.23' x2='481.13' y2='422.23' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='478.61' y1='424.75' x2='478.61' y2='419.71' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='537.05' y1='419.31' x2='540.62' y2='415.75' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='537.05' y1='415.75' x2='540.62' y2='419.31' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='536.32' y1='417.53' x2='541.36' y2='417.53' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='538.84' y1='420.05' x2='538.84' y2='415.01' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='537.05' y1='417.81' x2='540.62' y2='414.24' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='537.05' y1='414.24' x2='540.62' y2='417.81' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='536.32' y1='416.03' x2='541.36' y2='416.03' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='538.84' y1='418.55' x2='538.84' y2='413.51' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='593.26' y1='417.29' x2='596.83' y2='413.72' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='593.26' y1='413.72' x2='596.83' y2='417.29' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='592.52' y1='415.51' x2='597.56' y2='415.51' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='595.04' y1='418.03' x2='595.04' y2='412.98' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='593.26' y1='395.48' x2='596.83' y2='391.91' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='593.26' y1='391.91' x2='596.83' y2='395.48' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='592.52' y1='393.69' x2='597.56' y2='393.69' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='595.04' y1='396.21' x2='595.04' y2='391.17' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.58' y1='437.16' x2='634.14' y2='433.59' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.58' y1='433.59' x2='634.14' y2='437.16' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='629.84' y1='435.37' x2='634.88' y2='435.37' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='632.36' y1='437.89' x2='632.36' y2='432.85' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.58' y1='448.44' x2='634.14' y2='444.87' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.58' y1='444.87' x2='634.14' y2='448.44' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='629.84' y1='446.66' x2='634.88' y2='446.66' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='632.36' y1='449.18' x2='632.36' y2='444.14' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.92' y1='445.50' x2='643.48' y2='441.93' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.92' y1='441.93' x2='643.48' y2='445.50' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.18' y1='443.72' x2='644.22' y2='443.72' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='641.70' y1='446.24' x2='641.70' y2='441.20' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.92' y1='404.13' x2='643.48' y2='400.57' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.92' y1='400.57' x2='643.48' y2='404.13' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='639.18' y1='402.35' x2='644.22' y2='402.35' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='641.70' y1='404.87' x2='641.70' y2='399.83' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='631.46' y1='425.71' x2='635.02' y2='422.15' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='631.46' y1='422.15' x2='635.02' y2='425.71' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.72' y1='423.93' x2='635.76' y2='423.93' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='633.24' y1='426.45' x2='633.24' y2='421.41' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='631.46' y1='401.65' x2='635.02' y2='398.08' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='631.46' y1='398.08' x2='635.02' y2='401.65' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='630.72' y1='399.86' x2='635.76' y2='399.86' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='633.24' y1='402.38' x2='633.24' y2='397.34' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='616.63' y1='437.36' x2='620.20' y2='433.80' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='616.63' y1='433.80' x2='620.20' y2='437.36' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='615.90' y1='435.58' x2='620.94' y2='435.58' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='618.42' y1='438.10' x2='618.42' y2='433.06' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='616.63' y1='406.53' x2='620.20' y2='402.96' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='616.63' y1='402.96' x2='620.20' y2='406.53' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='615.90' y1='404.74' x2='620.94' y2='404.74' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='618.42' y1='407.26' x2='618.42' y2='402.22' style='stroke-width: 0.75;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='426.03' y1='436.66' x2='431.07' y2='436.66' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='428.55' y1='439.18' x2='428.55' y2='434.14' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='426.03,436.66 428.55,434.14 431.07,436.66 428.55,439.18 426.03,436.66 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='426.03' y1='429.14' x2='431.07' y2='429.14' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='428.55' y1='431.66' x2='428.55' y2='426.62' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='426.03,429.14 428.55,426.62 431.07,429.14 428.55,431.66 426.03,429.14 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='459.15' y1='438.34' x2='464.19' y2='438.34' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='461.67' y1='440.86' x2='461.67' y2='435.82' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='459.15,438.34 461.67,435.82 464.19,438.34 461.67,440.86 459.15,438.34 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='459.15' y1='426.31' x2='464.19' y2='426.31' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='461.67' y1='428.83' x2='461.67' y2='423.79' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='459.15,426.31 461.67,423.79 464.19,426.31 461.67,428.83 459.15,426.31 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='512.71' y1='436.05' x2='517.75' y2='436.05' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='515.23' y1='438.57' x2='515.23' y2='433.53' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='512.71,436.05 515.23,433.53 517.75,436.05 515.23,438.57 512.71,436.05 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='512.71' y1='418.75' x2='517.75' y2='418.75' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='515.23' y1='421.27' x2='515.23' y2='416.23' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='512.71,418.75 515.23,416.23 517.75,418.75 515.23,421.27 512.71,418.75 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='576.85' y1='431.80' x2='581.89' y2='431.80' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='579.37' y1='434.32' x2='579.37' y2='429.28' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='576.85,431.80 579.37,429.28 581.89,431.80 579.37,434.32 576.85,431.80 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='576.85' y1='430.30' x2='581.89' y2='430.30' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='579.37' y1='432.82' x2='579.37' y2='427.78' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='576.85,430.30 579.37,427.78 581.89,430.30 579.37,432.82 576.85,430.30 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='641.71' y1='432.06' x2='646.75' y2='432.06' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='644.23' y1='434.58' x2='644.23' y2='429.54' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='641.71,432.06 644.23,429.54 646.75,432.06 644.23,434.58 641.71,432.06 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='641.71' y1='406.49' x2='646.75' y2='406.49' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='644.23' y1='409.01' x2='644.23' y2='403.97' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='641.71,406.49 644.23,403.97 646.75,406.49 644.23,409.01 641.71,406.49 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='680.37' y1='431.73' x2='685.41' y2='431.73' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='682.89' y1='434.25' x2='682.89' y2='429.21' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='680.37,431.73 682.89,429.21 685.41,431.73 682.89,434.25 680.37,431.73 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='680.37' y1='443.01' x2='685.41' y2='443.01' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='682.89' y1='445.53' x2='682.89' y2='440.49' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='680.37,443.01 682.89,440.49 685.41,443.01 682.89,445.53 680.37,443.01 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='679.84' y1='413.48' x2='684.88' y2='413.48' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='682.36' y1='416.00' x2='682.36' y2='410.96' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='679.84,413.48 682.36,410.96 684.88,413.48 682.36,416.00 679.84,413.48 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='679.84' y1='418.75' x2='684.88' y2='418.75' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='682.36' y1='421.27' x2='682.36' y2='416.23' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='679.84,418.75 682.36,416.23 684.88,418.75 682.36,421.27 679.84,418.75 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='667.80' y1='438.03' x2='672.84' y2='438.03' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='670.32' y1='440.55' x2='670.32' y2='435.51' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='667.80,438.03 670.32,435.51 672.84,438.03 670.32,440.55 667.80,438.03 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='667.80' y1='423.74' x2='672.84' y2='423.74' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='670.32' y1='426.26' x2='670.32' y2='421.22' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='667.80,423.74 670.32,421.22 672.84,423.74 670.32,426.26 667.80,423.74 ' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='420.97' cy='425.75' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='419.18' y1='425.75' x2='422.75' y2='425.75' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='420.97' y1='427.53' x2='420.97' y2='423.97' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='420.97' cy='420.48' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='419.18' y1='420.48' x2='422.75' y2='420.48' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='420.97' y1='422.27' x2='420.97' y2='418.70' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='441.42' cy='419.52' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='439.64' y1='419.52' x2='443.21' y2='419.52' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='441.42' y1='421.30' x2='441.42' y2='417.74' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='441.42' cy='426.29' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='439.64' y1='426.29' x2='443.21' y2='426.29' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='441.42' y1='428.07' x2='441.42' y2='424.51' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='477.83' cy='429.81' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.05' y1='429.81' x2='479.61' y2='429.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='477.83' y1='431.59' x2='477.83' y2='428.03' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='477.83' cy='436.58' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='476.05' y1='436.58' x2='479.61' y2='436.58' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='477.83' y1='438.36' x2='477.83' y2='434.80' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='529.29' cy='430.46' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='527.51' y1='430.46' x2='531.07' y2='430.46' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='529.29' y1='432.24' x2='529.29' y2='428.68' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='529.29' cy='426.70' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='527.51' y1='426.70' x2='531.07' y2='426.70' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='529.29' y1='428.48' x2='529.29' y2='424.92' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='598.07' cy='434.17' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='596.28' y1='434.17' x2='599.85' y2='434.17' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='598.07' y1='435.96' x2='598.07' y2='432.39' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='598.07' cy='431.92' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='596.28' y1='431.92' x2='599.85' y2='431.92' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='598.07' y1='433.70' x2='598.07' y2='430.14' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='662.96' cy='417.10' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='661.18' y1='417.10' x2='664.75' y2='417.10' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='662.96' y1='418.88' x2='662.96' y2='415.32' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='662.96' cy='402.81' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='661.18' y1='402.81' x2='664.75' y2='402.81' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='662.96' y1='404.59' x2='662.96' y2='401.02' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='674.17' cy='418.99' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='672.39' y1='418.99' x2='675.95' y2='418.99' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='674.17' y1='420.77' x2='674.17' y2='417.20' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='674.17' cy='432.52' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='672.39' y1='432.52' x2='675.95' y2='432.52' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='674.17' y1='434.31' x2='674.17' y2='430.74' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='667.43' cy='434.26' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='665.65' y1='434.26' x2='669.22' y2='434.26' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='667.43' y1='436.04' x2='667.43' y2='432.48' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='667.43' cy='443.29' r='1.78pt' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='665.65' y1='443.29' x2='669.22' y2='443.29' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='667.43' y1='445.07' x2='667.43' y2='441.50' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='416.70,431.45 419.10,426.60 414.30,426.60 416.70,431.45 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='416.70,425.90 419.10,430.75 414.30,430.75 416.70,425.90 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='416.70,432.95 419.10,428.10 414.30,428.10 416.70,432.95 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='416.70,427.41 419.10,432.26 414.30,432.26 416.70,427.41 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='429.16,420.76 431.56,415.91 426.76,415.91 429.16,420.76 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='429.16,415.21 431.56,420.06 426.76,420.06 429.16,415.21 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='429.16,435.05 431.56,430.20 426.76,430.20 429.16,435.05 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='429.16,429.50 431.56,434.35 426.76,434.35 429.16,429.50 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='451.43,428.44 453.83,423.59 449.03,423.59 451.43,428.44 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='451.43,422.89 453.83,427.74 449.03,427.74 451.43,422.89 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='451.43,424.68 453.83,419.83 449.03,419.83 451.43,424.68 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='451.43,419.13 453.83,423.98 449.03,423.98 451.43,419.13 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='483.18,435.29 485.58,430.44 480.78,430.44 483.18,435.29 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='483.18,429.74 485.58,434.59 480.78,434.59 483.18,429.74 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='483.18,422.50 485.58,417.65 480.78,417.65 483.18,422.50 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='483.18,416.96 485.58,421.81 480.78,421.81 483.18,416.96 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='526.13,423.74 528.53,418.89 523.73,418.89 526.13,423.74 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='526.13,418.20 528.53,423.05 523.73,423.05 526.13,418.20 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='526.13,449.31 528.53,444.46 523.73,444.46 526.13,449.31 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='526.13,443.77 528.53,448.62 523.73,448.62 526.13,443.77 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.95,441.46 569.35,436.61 564.55,436.61 566.95,441.46 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.95,435.92 569.35,440.77 564.55,440.77 566.95,435.92 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.95,427.17 569.35,422.32 564.55,422.32 566.95,427.17 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='566.95,421.63 569.35,426.48 564.55,426.48 566.95,421.63 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='573.62,411.22 576.02,406.37 571.22,406.37 573.62,411.22 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='573.62,405.68 576.02,410.53 571.22,410.53 573.62,405.68 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='573.62,410.47 576.02,405.62 571.22,405.62 573.62,410.47 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='573.62,404.93 576.02,409.77 571.22,409.77 573.62,404.93 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='568.94,428.11 571.34,423.26 566.54,423.26 568.94,428.11 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='568.94,422.57 571.34,427.42 566.54,427.42 568.94,422.57 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='568.94,422.09 571.34,417.24 566.54,417.24 568.94,422.09 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='568.94,416.55 571.34,421.40 566.54,421.40 568.94,416.55 ' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='416.09' y1='419.19' x2='419.65' y2='419.19' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='417.87' y1='420.97' x2='417.87' y2='417.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='416.09' y='417.41' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='416.09' y1='435.73' x2='419.65' y2='435.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='417.87' y1='437.52' x2='417.87' y2='433.95' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='416.09' y='433.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='430.70' y1='428.82' x2='434.26' y2='428.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='432.48' y1='430.60' x2='432.48' y2='427.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='430.70' y='427.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='430.70' y1='431.83' x2='434.26' y2='431.83' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='432.48' y1='433.61' x2='432.48' y2='430.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='430.70' y='430.04' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='456.65' y1='426.66' x2='460.21' y2='426.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='458.43' y1='428.45' x2='458.43' y2='424.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='456.65' y='424.88' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='456.65' y1='421.40' x2='460.21' y2='421.40' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='458.43' y1='423.18' x2='458.43' y2='419.62' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='456.65' y='419.62' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='493.16' y1='425.56' x2='496.72' y2='425.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='494.94' y1='427.34' x2='494.94' y2='423.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='493.16' y='423.78' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='493.16' y1='420.30' x2='496.72' y2='420.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='494.94' y1='422.08' x2='494.94' y2='418.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='493.16' y='418.51' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='541.33' y1='416.09' x2='544.89' y2='416.09' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='543.11' y1='417.87' x2='543.11' y2='414.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='541.33' y='414.31' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='541.33' y1='415.34' x2='544.89' y2='415.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='543.11' y1='417.12' x2='543.11' y2='413.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='541.33' y='413.56' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='584.36' y1='430.78' x2='587.92' y2='430.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='586.14' y1='432.56' x2='586.14' y2='429.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='584.36' y='429.00' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='584.36' y1='418.74' x2='587.92' y2='418.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='586.14' y1='420.53' x2='586.14' y2='416.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='584.36' y='416.96' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='589.07' y1='434.90' x2='592.64' y2='434.90' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='590.85' y1='436.68' x2='590.85' y2='433.12' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='589.07' y='433.12' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='589.07' y1='412.34' x2='592.64' y2='412.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='590.85' y1='414.12' x2='590.85' y2='410.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='589.07' y='410.56' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='581.49' y1='440.53' x2='585.05' y2='440.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='583.27' y1='442.31' x2='583.27' y2='438.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='581.49' y='438.75' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='581.49' y1='414.96' x2='585.05' y2='414.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='583.27' y1='416.74' x2='583.27' y2='413.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='581.49' y='413.18' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='419.09' cy='422.43' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='417.31' y1='424.21' x2='420.88' y2='420.65' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='417.31' y1='420.65' x2='420.88' y2='424.21' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='419.09' cy='416.41' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='417.31' y1='418.19' x2='420.88' y2='414.63' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='417.31' y1='414.63' x2='420.88' y2='418.19' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='435.93' cy='425.23' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='434.15' y1='427.01' x2='437.71' y2='423.45' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='434.15' y1='423.45' x2='437.71' y2='427.01' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='435.93' cy='435.76' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='434.15' y1='437.54' x2='437.71' y2='433.98' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='434.15' y1='433.98' x2='437.71' y2='437.54' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='465.58' cy='424.49' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='463.80' y1='426.28' x2='467.36' y2='422.71' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='463.80' y1='422.71' x2='467.36' y2='426.28' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='465.58' cy='415.47' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='463.80' y1='417.25' x2='467.36' y2='413.69' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='463.80' y1='413.69' x2='467.36' y2='417.25' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='506.65' cy='410.37' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='504.87' y1='412.16' x2='508.43' y2='408.59' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='504.87' y1='408.59' x2='508.43' y2='412.16' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='506.65' cy='421.66' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='504.87' y1='423.44' x2='508.43' y2='419.87' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='504.87' y1='419.87' x2='508.43' y2='423.44' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='559.33' cy='422.55' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='557.55' y1='424.33' x2='561.11' y2='420.77' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='557.55' y1='420.77' x2='561.11' y2='424.33' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='559.33' cy='406.00' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='557.55' y1='407.78' x2='561.11' y2='404.22' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='557.55' y1='404.22' x2='561.11' y2='407.78' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='603.61' cy='415.62' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='601.83' y1='417.40' x2='605.39' y2='413.84' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='601.83' y1='413.84' x2='605.39' y2='417.40' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='603.61' cy='441.19' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='601.83' y1='442.98' x2='605.39' y2='439.41' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='601.83' y1='439.41' x2='605.39' y2='442.98' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='606.96' cy='403.86' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.18' y1='405.65' x2='608.75' y2='402.08' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.18' y1='402.08' x2='608.75' y2='405.65' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='606.96' cy='441.47' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.18' y1='443.25' x2='608.75' y2='439.69' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='605.18' y1='439.69' x2='608.75' y2='443.25' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='597.87' cy='431.36' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='596.09' y1='433.15' x2='599.66' y2='429.58' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='596.09' y1='429.58' x2='599.66' y2='433.15' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<circle cx='597.87' cy='435.13' r='1.78pt' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='596.09' y1='436.91' x2='599.66' y2='433.34' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<line x1='596.09' y1='433.34' x2='599.66' y2='436.91' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='423.30,422.29 425.09,425.85 421.52,425.85 423.30,422.29 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='421.52' y='422.29' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='423.30,427.55 425.09,431.12 421.52,431.12 423.30,427.55 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='421.52' y='427.55' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='447.23,428.25 449.01,431.81 445.45,431.81 447.23,428.25 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='445.45' y='428.25' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='447.23,424.49 449.01,428.05 445.45,428.05 447.23,424.49 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='445.45' y='424.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='486.70,411.29 488.48,414.85 484.92,414.85 486.70,411.29 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='484.92' y='411.29' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='486.70,438.36 488.48,441.93 484.92,441.93 486.70,438.36 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='484.92' y='438.36' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='535.47,435.79 537.26,439.35 533.69,439.35 535.47,435.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='533.69' y='435.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='535.47,426.76 537.26,430.33 533.69,430.33 535.47,426.76 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='533.69' y='426.76' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='586.91,407.88 588.70,411.45 585.13,411.45 586.91,407.88 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='585.13' y='407.88' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='586.91,428.19 588.70,431.76 585.13,431.76 586.91,428.19 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='585.13' y='428.19' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='617.05,423.94 618.83,427.50 615.27,427.50 617.05,423.94 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='615.27' y='423.94' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='617.05,443.49 618.83,447.05 615.27,447.05 617.05,443.49 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='615.27' y='443.49' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='613.93,406.87 615.71,410.44 612.15,410.44 613.93,406.87 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='612.15' y='406.87' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='613.93,433.95 615.71,437.51 612.15,437.51 613.93,433.95 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='612.15' y='433.95' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='601.72,409.79 603.51,413.35 599.94,413.35 601.72,409.79 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='599.94' y='409.79' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polyline points='601.72,415.05 603.51,418.62 599.94,418.62 601.72,415.05 ' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<rect x='599.94' y='415.05' width='3.56' height='3.56' style='stroke-width: 0.75; stroke: #F5C710;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='423.55,429.76 427.11,429.76 427.11,426.19 423.55,426.19 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='423.55,426.00 427.11,426.00 427.11,422.43 423.55,422.43 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='450.75,424.79 454.32,424.79 454.32,421.23 450.75,421.23 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='450.75,429.31 454.32,429.31 454.32,425.74 450.75,425.74 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='494.36,409.54 497.93,409.54 497.93,405.98 494.36,405.98 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='494.36,437.37 497.93,437.37 497.93,433.81 494.36,433.81 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='545.63,404.38 549.20,404.38 549.20,400.81 545.63,400.81 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='545.63,418.67 549.20,418.67 549.20,415.10 545.63,415.10 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='595.59,418.63 599.15,418.63 599.15,415.06 595.59,415.06 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='595.59,417.12 599.15,417.12 599.15,413.56 595.59,413.56 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='623.41,432.57 626.98,432.57 626.98,429.01 623.41,429.01 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='623.41,433.32 626.98,433.32 626.98,429.76 623.41,429.76 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='623.46,440.80 627.03,440.80 627.03,437.23 623.46,437.23 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='623.46,429.51 627.03,429.51 627.03,425.95 623.46,425.95 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='615.94,449.37 619.50,449.37 619.50,445.80 615.94,445.80 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' /> +<polygon points='615.94,414.77 619.50,414.77 619.50,411.21 615.94,411.21 ' style='stroke-width: 0.75; stroke: none; fill: #9E9E9E;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzIyLjQ1)' />  </svg> diff --git a/tests/figs/plotting/mixed-model-fit-for-saem-object-with-saemix-transformations.svg b/tests/figs/plotting/mixed-model-fit-for-saem-object-with-saemix-transformations.svg index e6bee1c5..e65bc3bb 100644 --- a/tests/figs/plotting/mixed-model-fit-for-saem-object-with-saemix-transformations.svg +++ b/tests/figs/plotting/mixed-model-fit-for-saem-object-with-saemix-transformations.svg @@ -13,209 +13,209 @@  </defs>  <rect width='100%' height='100%' style='stroke: none; fill: #FFFFFF;'/>  <defs> -  <clipPath id='cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA='> -    <rect x='19.96' y='5.70' width='680.08' height='41.14' /> +  <clipPath id='cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU='> +    <rect x='19.96' y='0.95' width='680.08' height='38.88' />    </clipPath>  </defs> -<line x1='267.74' y1='21.52' x2='282.00' y2='21.52' style='stroke-width: 1.50;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='267.74' y1='31.02' x2='282.00' y2='31.02' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='329.49' y1='21.52' x2='343.74' y2='21.52' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='329.49' y1='31.02' x2='343.74' y2='31.02' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='391.23' y1='21.52' x2='405.48' y2='21.52' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='391.23' y1='31.02' x2='405.48' y2='31.02' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<circle cx='274.87' cy='31.02' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<polyline points='336.61,18.75 339.01,22.90 334.21,22.90 336.61,18.75 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='334.09' y1='31.02' x2='339.13' y2='31.02' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='336.61' y1='33.54' x2='336.61' y2='28.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='396.57' y1='23.30' x2='400.14' y2='19.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<line x1='396.57' y1='19.74' x2='400.14' y2='23.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<polyline points='395.83,31.02 398.35,28.50 400.88,31.02 398.35,33.54 395.83,31.02 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)' /> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)'><text x='289.13' y='24.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='37.31px' lengthAdjust='spacingAndGlyphs'>Population</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)'><text x='289.13' y='33.74' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 6</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)'><text x='350.87' y='24.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 7</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)'><text x='350.87' y='33.74' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 8</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)'><text x='412.61' y='24.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 9</text></g> -<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDQ2Ljg0fDUuNzA=)'><text x='412.61' y='33.74' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='38.22px' lengthAdjust='spacingAndGlyphs'>Dataset 10</text></g> +<line x1='267.74' y1='15.64' x2='282.00' y2='15.64' style='stroke-width: 1.50;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='267.74' y1='25.14' x2='282.00' y2='25.14' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='329.49' y1='15.64' x2='343.74' y2='15.64' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='329.49' y1='25.14' x2='343.74' y2='25.14' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='391.23' y1='15.64' x2='405.48' y2='15.64' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='391.23' y1='25.14' x2='405.48' y2='25.14' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<circle cx='274.87' cy='25.14' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<polyline points='336.61,12.87 339.01,17.02 334.21,17.02 336.61,12.87 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='334.09' y1='25.14' x2='339.13' y2='25.14' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='336.61' y1='27.66' x2='336.61' y2='22.62' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='396.57' y1='17.42' x2='400.14' y2='13.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<line x1='396.57' y1='13.86' x2='400.14' y2='17.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<polyline points='395.83,25.14 398.35,22.62 400.88,25.14 398.35,27.66 395.83,25.14 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)' /> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)'><text x='289.13' y='18.36' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='37.31px' lengthAdjust='spacingAndGlyphs'>Population</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)'><text x='289.13' y='27.86' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 6</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)'><text x='350.87' y='18.36' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 7</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)'><text x='350.87' y='27.86' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 8</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)'><text x='412.61' y='18.36' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.83px' lengthAdjust='spacingAndGlyphs'>Dataset 9</text></g> +<g clip-path='url(#cpMTkuOTZ8NzAwLjA0fDM5LjgzfDAuOTU=)'><text x='412.61' y='27.86' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='38.22px' lengthAdjust='spacingAndGlyphs'>Dataset 10</text></g>  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ=='> -    <rect x='38.97' y='67.75' width='301.08' height='203.06' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw=='> +    <rect x='38.97' y='51.23' width='301.08' height='215.90' />    </clipPath>  </defs> -<polyline points='50.12,86.63 51.67,100.99 54.76,124.33 55.81,130.84 59.41,149.30 60.96,155.65 61.50,157.67 62.51,161.24 65.60,170.53 67.19,174.48 71.80,183.73 72.87,185.49 78.56,193.12 81.09,195.81 82.64,197.30 84.25,198.74 89.94,203.16 91.93,204.51 95.63,206.83 96.58,207.39 101.32,210.01 102.77,210.77 107.01,212.87 112.70,215.48 113.62,215.89 118.39,217.91 124.08,220.19 124.46,220.34 129.77,222.34 135.30,224.31 135.46,224.37 141.15,226.29 143.04,226.91 146.83,228.12 147.69,228.38 152.52,229.85 158.21,231.50 158.53,231.59 163.90,233.07 169.59,234.55 175.28,235.97 180.97,237.31 186.66,238.59 189.50,239.21 191.05,239.54 192.35,239.81 198.04,240.96 203.73,242.06 209.42,243.11 215.11,244.10 220.79,245.05 223.58,245.49 226.48,245.94 232.17,246.80 235.97,247.34 237.86,247.61 243.55,248.38 249.24,249.12 254.55,249.77 254.93,249.81 260.62,250.48 266.31,251.11 272.00,251.71 277.69,252.28 283.38,252.82 289.07,253.33 294.76,253.82 300.44,254.29 306.13,254.73 311.82,255.15 317.51,255.55 323.20,255.93 328.89,256.30 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> +<polyline points='50.12,71.31 51.67,86.58 54.76,111.39 55.81,118.32 59.41,137.94 60.96,144.70 61.50,146.84 62.51,150.64 65.60,160.52 67.19,164.72 71.80,174.55 72.87,176.42 78.56,184.53 81.09,187.39 82.64,188.97 84.25,190.51 89.94,195.21 91.93,196.65 95.63,199.11 96.58,199.70 101.32,202.50 102.77,203.30 107.01,205.53 112.70,208.31 113.62,208.74 118.39,210.90 124.08,213.32 124.46,213.47 129.77,215.60 135.30,217.70 135.46,217.76 141.15,219.80 143.04,220.46 146.83,221.74 147.69,222.03 152.52,223.59 158.21,225.34 158.53,225.44 163.90,227.01 169.59,228.59 175.28,230.09 180.97,231.52 186.66,232.88 189.50,233.54 191.05,233.89 192.35,234.17 198.04,235.40 203.73,236.57 209.42,237.68 215.11,238.74 220.79,239.74 223.58,240.22 226.48,240.70 232.17,241.61 235.97,242.19 237.86,242.47 243.55,243.29 249.24,244.07 254.55,244.76 254.93,244.81 260.62,245.52 266.31,246.19 272.00,246.83 277.69,247.43 283.38,248.01 289.07,248.56 294.76,249.08 300.44,249.57 306.13,250.04 311.82,250.49 317.51,250.92 323.20,251.32 328.89,251.71 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' />  <defs>    <clipPath id='cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA='>      <rect x='0.00' y='0.00' width='720.00' height='576.00' />    </clipPath>  </defs> -<line x1='50.12' y1='270.81' x2='282.43' y2='270.81' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='50.12' y1='270.81' x2='50.12' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='127.55' y1='270.81' x2='127.55' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='204.99' y1='270.81' x2='204.99' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='282.43' y1='270.81' x2='282.43' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='47.92' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='123.16' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>50</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='198.41' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='275.84' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>150</text></g> -<line x1='38.97' y1='263.29' x2='38.97' y2='74.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='263.29' x2='34.21' y2='263.29' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='225.61' x2='34.21' y2='225.61' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='187.93' x2='34.21' y2='187.93' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='150.25' x2='34.21' y2='150.25' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='112.57' x2='34.21' y2='112.57' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='74.89' x2='34.21' y2='74.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,265.48) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,230.00) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,192.32) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,154.64) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,116.96) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,81.48) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> -<polyline points='38.97,270.81 340.04,270.81 340.04,67.75 38.97,67.75 38.97,270.81 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='50.12' y1='267.13' x2='282.43' y2='267.13' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='50.12' y1='267.13' x2='50.12' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='127.55' y1='267.13' x2='127.55' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='204.99' y1='267.13' x2='204.99' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='282.43' y1='267.13' x2='282.43' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='47.92' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='123.16' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>50</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='198.41' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='275.84' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>150</text></g> +<line x1='38.97' y1='259.14' x2='38.97' y2='58.83' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='259.14' x2='34.21' y2='259.14' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='219.08' x2='34.21' y2='219.08' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='179.01' x2='34.21' y2='179.01' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='138.95' x2='34.21' y2='138.95' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='98.89' x2='34.21' y2='98.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='58.83' x2='34.21' y2='58.83' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,261.33) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,223.47) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,183.40) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,143.34) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,103.28) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,65.41) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> +<polyline points='38.97,267.13 340.04,267.13 340.04,51.23 38.97,51.23 38.97,267.13 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMC4wMHwzNjAuMDB8Mjk5LjMyfDQ3Ljc5'> -    <rect x='0.00' y='47.79' width='360.00' height='251.53' /> +  <clipPath id='cpMC4wMHwzNjAuMDB8Mjk1LjY1fDQwLjc4'> +    <rect x='0.00' y='40.78' width='360.00' height='254.87' />    </clipPath>  </defs> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8Mjk5LjMyfDQ3Ljc5)'><text x='180.87' y='306.92' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8Mjk5LjMyfDQ3Ljc5)'><text transform='translate(8.55,180.48) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='22.41px' lengthAdjust='spacingAndGlyphs'>parent</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8Mjk1LjY1fDQwLjc4)'><text x='180.87' y='303.25' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8Mjk1LjY1fDQwLjc4)'><text transform='translate(8.55,187.95) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='57.53px' lengthAdjust='spacingAndGlyphs'>Residues parent</text></g>  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ=='> -    <rect x='38.97' y='67.75' width='301.08' height='203.06' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw=='> +    <rect x='38.97' y='51.23' width='301.08' height='215.90' />    </clipPath>  </defs> -<circle cx='50.12' cy='80.17' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='50.12' cy='81.67' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='54.76' cy='129.34' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='54.76' cy='132.92' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='59.41' cy='153.83' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='59.41' cy='156.66' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='65.60' cy='179.64' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='65.60' cy='181.52' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='81.09' cy='200.55' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='81.09' cy='208.28' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='102.77' cy='230.13' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='102.77' cy='229.38' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='135.30' cy='243.50' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='135.30' cy='245.77' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='189.50' cy='254.81' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='189.50' cy='254.43' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='223.58' cy='257.63' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='223.58' cy='256.88' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='254.55' cy='258.95' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<circle cx='254.55' cy='258.20' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='50.12,82.84 51.67,100.83 54.76,128.71 55.81,136.19 59.41,156.69 60.96,163.53 61.50,165.68 62.51,169.48 65.60,179.28 67.19,183.44 71.80,193.33 72.87,195.26 78.56,203.91 81.09,207.12 82.64,208.95 84.25,210.75 89.94,216.46 91.93,218.26 95.63,221.38 96.58,222.14 101.32,225.71 102.77,226.73 107.01,229.55 112.70,232.98 113.62,233.50 118.39,236.05 124.08,238.81 124.46,238.99 129.77,241.29 135.30,243.45 135.46,243.51 141.15,245.51 143.04,246.13 146.83,247.31 147.69,247.56 152.52,248.92 158.21,250.38 158.53,250.45 163.90,251.68 169.59,252.85 175.28,253.91 180.97,254.86 186.66,255.71 189.50,256.10 191.05,256.31 192.35,256.47 198.04,257.16 203.73,257.78 209.42,258.34 215.11,258.84 220.79,259.29 223.58,259.49 226.48,259.69 232.17,260.06 235.97,260.28 237.86,260.38 243.55,260.68 249.24,260.94 254.55,261.16 254.93,261.18 260.62,261.39 266.31,261.58 272.00,261.75 277.69,261.91 283.38,262.05 289.07,262.17 294.76,262.29 300.44,262.39 306.13,262.48 311.82,262.56 317.51,262.63 323.20,262.70 328.89,262.76 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='50.12,84.18 52.52,88.34 47.72,88.34 50.12,84.18 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='50.12,86.63 52.52,90.78 47.72,90.78 50.12,86.63 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='54.76,96.61 57.16,100.77 52.36,100.77 54.76,96.61 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='54.76,105.66 57.16,109.81 52.36,109.81 54.76,105.66 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='60.96,121.10 63.36,125.26 58.56,125.26 60.96,121.10 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='60.96,121.29 63.36,125.45 58.56,125.45 60.96,121.29 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='71.80,139.57 74.20,143.72 69.40,143.72 71.80,139.57 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='71.80,129.58 74.20,133.74 69.40,133.74 71.80,129.58 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='96.58,158.78 98.98,162.94 94.18,162.94 96.58,158.78 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='96.58,157.65 98.98,161.81 94.18,161.81 96.58,157.65 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='143.04,183.09 145.44,187.24 140.64,187.24 143.04,183.09 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='143.04,188.17 145.44,192.33 140.64,192.33 143.04,188.17 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='189.50,199.29 191.90,203.44 187.10,203.44 189.50,199.29 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='189.50,193.64 191.90,197.79 187.10,197.79 189.50,193.64 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='235.97,207.58 238.37,211.73 233.57,211.73 235.97,207.58 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='235.97,205.88 238.37,210.04 233.57,210.04 235.97,205.88 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='328.89,210.59 331.29,214.75 326.49,214.75 328.89,210.59 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='328.89,208.52 331.29,212.68 326.49,212.68 328.89,208.52 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='50.12,91.74 51.67,95.81 54.76,103.46 55.81,105.90 59.41,113.85 60.96,117.05 61.50,118.13 62.51,120.12 65.60,125.91 67.19,128.70 71.80,136.22 72.87,137.85 78.56,145.78 81.09,148.96 82.64,150.82 84.25,152.67 89.94,158.67 91.93,160.58 95.63,163.90 96.58,164.71 101.32,168.48 102.77,169.55 107.01,172.49 112.70,176.02 113.62,176.55 118.39,179.14 124.08,181.90 124.46,182.07 129.77,184.36 135.30,186.49 135.46,186.55 141.15,188.52 143.04,189.13 146.83,190.30 147.69,190.55 152.52,191.90 158.21,193.37 158.53,193.45 163.90,194.71 169.59,195.95 175.28,197.09 180.97,198.15 186.66,199.15 189.50,199.62 191.05,199.87 192.35,200.08 198.04,200.96 203.73,201.80 209.42,202.59 215.11,203.35 220.79,204.08 223.58,204.43 226.48,204.79 232.17,205.47 235.97,205.91 237.86,206.13 243.55,206.77 249.24,207.39 254.55,207.96 254.93,208.00 260.62,208.59 266.31,209.17 272.00,209.74 277.69,210.30 283.38,210.85 289.07,211.39 294.76,211.92 300.44,212.45 306.13,212.97 311.82,213.48 317.51,213.98 323.20,214.48 328.89,214.97 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='47.60' y1='90.15' x2='52.64' y2='90.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='50.12' y1='92.67' x2='50.12' y2='87.63' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='47.60' y1='92.22' x2='52.64' y2='92.22' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='50.12' y1='94.74' x2='50.12' y2='89.70' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='49.15' y1='141.02' x2='54.19' y2='141.02' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='51.67' y1='143.54' x2='51.67' y2='138.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='49.15' y1='138.57' x2='54.19' y2='138.57' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='51.67' y1='141.09' x2='51.67' y2='136.05' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='52.24' y1='181.33' x2='57.28' y2='181.33' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='54.76' y1='183.86' x2='54.76' y2='178.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='52.24' y1='180.20' x2='57.28' y2='180.20' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='54.76' y1='182.72' x2='54.76' y2='177.68' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='59.99' y1='228.81' x2='65.03' y2='228.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='62.51' y1='231.33' x2='62.51' y2='226.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='59.99' y1='229.19' x2='65.03' y2='229.19' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='62.51' y1='231.71' x2='62.51' y2='226.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='69.28' y1='244.07' x2='74.32' y2='244.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='71.80' y1='246.59' x2='71.80' y2='241.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='69.28' y1='242.94' x2='74.32' y2='242.94' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='71.80' y1='245.46' x2='71.80' y2='240.42' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='89.41' y1='254.05' x2='94.45' y2='254.05' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='91.93' y1='256.57' x2='91.93' y2='251.53' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='89.41' y1='257.07' x2='94.45' y2='257.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='91.93' y1='259.59' x2='91.93' y2='254.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='121.94' y1='260.27' x2='126.98' y2='260.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='124.46' y1='262.79' x2='124.46' y2='257.75' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='121.94' y1='260.46' x2='126.98' y2='260.46' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='124.46' y1='262.98' x2='124.46' y2='257.94' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='156.01' y1='261.21' x2='161.05' y2='261.21' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='158.53' y1='263.73' x2='158.53' y2='258.69' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='156.01' y1='261.59' x2='161.05' y2='261.59' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='158.53' y1='264.11' x2='158.53' y2='259.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='50.12,91.31 51.67,135.56 54.76,184.77 55.81,194.61 59.41,216.10 60.96,221.88 61.50,223.60 62.51,226.52 65.60,233.62 67.19,236.50 71.80,243.11 72.87,244.37 78.56,249.77 81.09,251.63 82.64,252.64 84.25,253.60 89.94,256.34 91.93,257.10 95.63,258.30 96.58,258.57 101.32,259.71 102.77,260.00 107.01,260.72 112.70,261.45 113.62,261.54 118.39,261.97 124.08,262.34 124.46,262.36 129.77,262.61 135.30,262.80 135.46,262.80 141.15,262.94 143.04,262.97 146.83,263.04 147.69,263.05 152.52,263.11 158.21,263.16 158.53,263.16 163.90,263.19 169.59,263.22 175.28,263.24 180.97,263.25 186.66,263.26 189.50,263.27 191.05,263.27 192.35,263.27 198.04,263.27 203.73,263.28 209.42,263.28 215.11,263.28 220.79,263.28 223.58,263.28 226.48,263.28 232.17,263.28 235.97,263.28 237.86,263.28 243.55,263.29 249.24,263.29 254.55,263.29 254.93,263.29 260.62,263.29 266.31,263.29 272.00,263.29 277.69,263.29 283.38,263.29 289.07,263.29 294.76,263.29 300.44,263.29 306.13,263.29 311.82,263.29 317.51,263.29 323.20,263.29 328.89,263.29 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='48.34' y1='77.05' x2='51.90' y2='73.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='48.34' y1='73.49' x2='51.90' y2='77.05' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='48.34' y1='79.88' x2='51.90' y2='76.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='48.34' y1='76.31' x2='51.90' y2='79.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='49.88' y1='119.82' x2='53.45' y2='116.25' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='49.88' y1='116.25' x2='53.45' y2='119.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='49.88' y1='119.63' x2='53.45' y2='116.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='49.88' y1='116.06' x2='53.45' y2='119.63' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='52.98' y1='153.92' x2='56.55' y2='150.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='52.98' y1='150.35' x2='56.55' y2='153.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='52.98' y1='155.61' x2='56.55' y2='152.05' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='52.98' y1='152.05' x2='56.55' y2='155.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='60.73' y1='213.45' x2='64.29' y2='209.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='60.73' y1='209.88' x2='64.29' y2='213.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='60.73' y1='210.06' x2='64.29' y2='206.49' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='60.73' y1='206.49' x2='64.29' y2='210.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='70.02' y1='229.08' x2='73.58' y2='225.52' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='70.02' y1='225.52' x2='73.58' y2='229.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='70.02' y1='209.30' x2='73.58' y2='205.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='70.02' y1='205.74' x2='73.58' y2='209.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='90.15' y1='246.04' x2='93.72' y2='242.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='90.15' y1='242.48' x2='93.72' y2='246.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='90.15' y1='230.78' x2='93.72' y2='227.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='90.15' y1='227.22' x2='93.72' y2='230.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='122.67' y1='256.59' x2='126.24' y2='253.03' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='122.67' y1='253.03' x2='126.24' y2='256.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='122.67' y1='247.92' x2='126.24' y2='244.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='122.67' y1='244.36' x2='126.24' y2='247.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='156.75' y1='260.74' x2='160.31' y2='257.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='156.75' y1='257.17' x2='160.31' y2='260.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='156.75' y1='259.60' x2='160.31' y2='256.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='156.75' y1='256.04' x2='160.31' y2='259.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='189.27' y1='261.30' x2='192.83' y2='257.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='189.27' y1='257.74' x2='192.83' y2='261.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='189.27' y1='261.68' x2='192.83' y2='258.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='189.27' y1='258.11' x2='192.83' y2='261.68' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='234.18' y1='261.30' x2='237.75' y2='257.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='234.18' y1='257.74' x2='237.75' y2='261.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='234.18' y1='260.92' x2='237.75' y2='257.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<line x1='234.18' y1='257.36' x2='237.75' y2='260.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='50.12,79.88 51.67,113.89 54.76,158.28 55.81,168.39 59.41,192.07 60.96,198.67 61.50,200.62 62.51,203.90 65.60,211.58 67.19,214.53 71.80,221.02 72.87,222.23 78.56,227.59 81.09,229.59 82.64,230.73 84.25,231.87 89.94,235.51 91.93,236.67 95.63,238.69 96.58,239.19 101.32,241.50 102.77,242.16 107.01,243.98 112.70,246.18 113.62,246.51 118.39,248.13 124.08,249.85 124.46,249.96 129.77,251.38 135.30,252.70 135.46,252.74 141.15,253.94 143.04,254.31 146.83,255.00 147.69,255.15 152.52,255.95 158.21,256.78 158.53,256.82 163.90,257.52 169.59,258.18 175.28,258.76 180.97,259.27 186.66,259.73 189.50,259.94 191.05,260.05 192.35,260.14 198.04,260.49 203.73,260.81 209.42,261.09 215.11,261.34 220.79,261.56 223.58,261.66 226.48,261.76 232.17,261.93 235.97,262.04 237.86,262.09 243.55,262.22 249.24,262.35 254.55,262.45 254.93,262.45 260.62,262.55 266.31,262.63 272.00,262.71 277.69,262.77 283.38,262.83 289.07,262.88 294.76,262.93 300.44,262.97 306.13,263.01 311.82,263.04 317.51,263.07 323.20,263.09 328.89,263.11 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='47.60,82.24 50.12,79.72 52.64,82.24 50.12,84.76 47.60,82.24 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='47.60,85.63 50.12,83.11 52.64,85.63 50.12,88.15 47.60,85.63 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='59.99,124.06 62.51,121.54 65.03,124.06 62.51,126.58 59.99,124.06 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='59.99,124.06 62.51,121.54 65.03,124.06 62.51,126.58 59.99,124.06 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='69.28,132.54 71.80,130.02 74.32,132.54 71.80,135.06 69.28,132.54 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='69.28,125.57 71.80,123.05 74.32,125.57 71.80,128.09 69.28,125.57 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='80.12,139.70 82.64,137.18 85.16,139.70 82.64,142.22 80.12,139.70 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='80.12,140.27 82.64,137.75 85.16,140.27 82.64,142.79 80.12,140.27 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='111.10,157.97 113.62,155.45 116.14,157.97 113.62,160.49 111.10,157.97 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='111.10,160.80 113.62,158.28 116.14,160.80 113.62,163.32 111.10,160.80 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='145.17,174.74 147.69,172.22 150.21,174.74 147.69,177.26 145.17,174.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='145.17,170.41 147.69,167.89 150.21,170.41 147.69,172.93 145.17,170.41 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='188.53,179.07 191.05,176.55 193.57,179.07 191.05,181.59 188.53,179.07 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='188.53,175.31 191.05,172.79 193.57,175.31 191.05,177.83 188.53,175.31 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='233.45,183.97 235.97,181.45 238.49,183.97 235.97,186.49 233.45,183.97 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='233.45,185.48 235.97,182.96 238.49,185.48 235.97,188.00 233.45,185.48 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> -<polyline points='50.12,86.69 51.67,91.34 54.76,99.78 55.81,102.39 59.41,110.59 60.96,113.76 61.50,114.81 62.51,116.73 65.60,122.16 67.19,124.68 71.80,131.22 72.87,132.58 78.56,138.96 81.09,141.40 82.64,142.79 84.25,144.16 89.94,148.44 91.93,149.76 95.63,152.00 96.58,152.54 101.32,155.02 102.77,155.72 107.01,157.61 112.70,159.86 113.62,160.20 118.39,161.85 124.08,163.64 124.46,163.75 129.77,165.26 135.30,166.72 135.46,166.76 141.15,168.16 143.04,168.60 146.83,169.47 147.69,169.66 152.52,170.72 158.21,171.92 158.53,171.99 163.90,173.07 169.59,174.19 175.28,175.28 180.97,176.34 186.66,177.38 189.50,177.89 191.05,178.16 192.35,178.39 198.04,179.39 203.73,180.37 209.42,181.34 215.11,182.29 220.79,183.23 223.58,183.69 226.48,184.16 232.17,185.08 235.97,185.68 237.86,185.98 243.55,186.87 249.24,187.76 254.55,188.57 254.93,188.63 260.62,189.49 266.31,190.34 272.00,191.18 277.69,192.01 283.38,192.83 289.07,193.64 294.76,194.44 300.44,195.24 306.13,196.02 311.82,196.80 317.51,197.56 323.20,198.32 328.89,199.07 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI3MC44MXw2Ny43NQ==)' /> +<circle cx='50.12' cy='64.44' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='50.12' cy='66.04' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='54.76' cy='116.72' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='54.76' cy='120.52' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='59.41' cy='142.76' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='59.41' cy='145.76' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='65.60' cy='170.20' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='65.60' cy='172.20' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='81.09' cy='192.43' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='81.09' cy='200.65' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='102.77' cy='223.88' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='102.77' cy='223.08' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='135.30' cy='238.11' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='135.30' cy='240.51' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='189.50' cy='250.12' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='189.50' cy='249.72' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='223.58' cy='253.13' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='223.58' cy='252.33' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='254.55' cy='254.53' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<circle cx='254.55' cy='253.73' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='50.12,67.27 51.67,86.41 54.76,116.05 55.81,124.00 59.41,145.80 60.96,153.07 61.50,155.36 62.51,159.39 65.60,169.82 67.19,174.25 71.80,184.75 72.87,186.81 78.56,196.01 81.09,199.42 82.64,201.37 84.25,203.28 89.94,209.35 91.93,211.27 95.63,214.59 96.58,215.39 101.32,219.19 102.77,220.27 107.01,223.27 112.70,226.92 113.62,227.47 118.39,230.18 124.08,233.12 124.46,233.30 129.77,235.75 135.30,238.05 135.46,238.11 141.15,240.24 143.04,240.90 146.83,242.15 147.69,242.42 152.52,243.87 158.21,245.41 158.53,245.49 163.90,246.80 169.59,248.05 175.28,249.17 180.97,250.17 186.66,251.08 189.50,251.50 191.05,251.72 192.35,251.90 198.04,252.63 203.73,253.29 209.42,253.88 215.11,254.41 220.79,254.89 223.58,255.10 226.48,255.32 232.17,255.70 235.97,255.94 237.86,256.05 243.55,256.36 249.24,256.64 254.55,256.88 254.93,256.89 260.62,257.12 266.31,257.33 272.00,257.51 277.69,257.67 283.38,257.82 289.07,257.95 294.76,258.07 300.44,258.18 306.13,258.28 311.82,258.37 317.51,258.44 323.20,258.51 328.89,258.58 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='50.12,68.88 52.52,73.03 47.72,73.03 50.12,68.88 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='50.12,71.48 52.52,75.64 47.72,75.64 50.12,71.48 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='54.76,82.10 57.16,86.25 52.36,86.25 54.76,82.10 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='54.76,91.71 57.16,95.87 52.36,95.87 54.76,91.71 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='60.96,108.14 63.36,112.29 58.56,112.29 60.96,108.14 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='60.96,108.34 63.36,112.50 58.56,112.50 60.96,108.34 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='71.80,127.77 74.20,131.93 69.40,131.93 71.80,127.77 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='71.80,117.15 74.20,121.31 69.40,121.31 71.80,117.15 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='96.58,148.20 98.98,152.36 94.18,152.36 96.58,148.20 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='96.58,147.00 98.98,151.15 94.18,151.15 96.58,147.00 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='143.04,174.04 145.44,178.20 140.64,178.20 143.04,174.04 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='143.04,179.45 145.44,183.60 140.64,183.60 143.04,179.45 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='189.50,191.27 191.90,195.42 187.10,195.42 189.50,191.27 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='189.50,185.26 191.90,189.41 187.10,189.41 189.50,185.26 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='235.97,200.08 238.37,204.24 233.57,204.24 235.97,200.08 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='235.97,198.28 238.37,202.43 233.57,202.43 235.97,198.28 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='328.89,203.28 331.29,207.44 326.49,207.44 328.89,203.28 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='328.89,201.08 331.29,205.24 326.49,205.24 328.89,201.08 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='50.12,76.74 51.67,81.06 54.76,89.20 55.81,91.80 59.41,100.25 60.96,103.65 61.50,104.80 62.51,106.92 65.60,113.08 67.19,116.04 71.80,124.03 72.87,125.77 78.56,134.20 81.09,137.58 82.64,139.55 84.25,141.53 89.94,147.90 91.93,149.94 95.63,153.47 96.58,154.32 101.32,158.33 102.77,159.48 107.01,162.60 112.70,166.35 113.62,166.92 118.39,169.67 124.08,172.60 124.46,172.79 129.77,175.22 135.30,177.49 135.46,177.55 141.15,179.64 143.04,180.29 146.83,181.53 147.69,181.80 152.52,183.24 158.21,184.80 158.53,184.88 163.90,186.23 169.59,187.54 175.28,188.75 180.97,189.88 186.66,190.94 189.50,191.44 191.05,191.71 192.35,191.93 198.04,192.87 203.73,193.76 209.42,194.61 215.11,195.41 220.79,196.19 223.58,196.56 226.48,196.94 232.17,197.66 235.97,198.13 237.86,198.36 243.55,199.04 249.24,199.71 254.55,200.31 254.93,200.35 260.62,200.98 266.31,201.60 272.00,202.21 277.69,202.80 283.38,203.39 289.07,203.96 294.76,204.53 300.44,205.08 306.13,205.63 311.82,206.18 317.51,206.71 323.20,207.24 328.89,207.76 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='47.60' y1='75.05' x2='52.64' y2='75.05' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='50.12' y1='77.57' x2='50.12' y2='72.53' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='47.60' y1='77.26' x2='52.64' y2='77.26' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='50.12' y1='79.78' x2='50.12' y2='74.74' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='49.15' y1='129.14' x2='54.19' y2='129.14' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='51.67' y1='131.66' x2='51.67' y2='126.62' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='49.15' y1='126.53' x2='54.19' y2='126.53' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='51.67' y1='129.05' x2='51.67' y2='124.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='52.24' y1='172.00' x2='57.28' y2='172.00' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='54.76' y1='174.52' x2='54.76' y2='169.48' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='52.24' y1='170.80' x2='57.28' y2='170.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='54.76' y1='173.32' x2='54.76' y2='168.28' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='59.99' y1='222.48' x2='65.03' y2='222.48' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='62.51' y1='225.00' x2='62.51' y2='219.96' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='59.99' y1='222.88' x2='65.03' y2='222.88' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='62.51' y1='225.40' x2='62.51' y2='220.36' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='69.28' y1='238.71' x2='74.32' y2='238.71' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='71.80' y1='241.23' x2='71.80' y2='236.19' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='69.28' y1='237.50' x2='74.32' y2='237.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='71.80' y1='240.02' x2='71.80' y2='234.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='89.41' y1='249.32' x2='94.45' y2='249.32' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='91.93' y1='251.84' x2='91.93' y2='246.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='89.41' y1='252.53' x2='94.45' y2='252.53' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='91.93' y1='255.05' x2='91.93' y2='250.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='121.94' y1='255.93' x2='126.98' y2='255.93' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='124.46' y1='258.45' x2='124.46' y2='253.41' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='121.94' y1='256.13' x2='126.98' y2='256.13' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='124.46' y1='258.65' x2='124.46' y2='253.61' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='156.01' y1='256.93' x2='161.05' y2='256.93' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='158.53' y1='259.45' x2='158.53' y2='254.41' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='156.01' y1='257.33' x2='161.05' y2='257.33' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='158.53' y1='259.86' x2='158.53' y2='254.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='50.12,76.28 51.67,123.33 54.76,175.65 55.81,186.12 59.41,208.96 60.96,215.11 61.50,216.94 62.51,220.05 65.60,227.60 67.19,230.65 71.80,237.68 72.87,239.02 78.56,244.76 81.09,246.74 82.64,247.82 84.25,248.84 89.94,251.75 91.93,252.56 95.63,253.84 96.58,254.13 101.32,255.34 102.77,255.65 107.01,256.41 112.70,257.18 113.62,257.29 118.39,257.74 124.08,258.13 124.46,258.15 129.77,258.42 135.30,258.62 135.46,258.62 141.15,258.77 143.04,258.81 146.83,258.87 147.69,258.88 152.52,258.95 158.21,259.00 158.53,259.00 163.90,259.04 169.59,259.07 175.28,259.09 180.97,259.10 186.66,259.11 189.50,259.12 191.05,259.12 192.35,259.12 198.04,259.12 203.73,259.13 209.42,259.13 215.11,259.13 220.79,259.13 223.58,259.13 226.48,259.14 232.17,259.14 235.97,259.14 237.86,259.14 243.55,259.14 249.24,259.14 254.55,259.14 254.93,259.14 260.62,259.14 266.31,259.14 272.00,259.14 277.69,259.14 283.38,259.14 289.07,259.14 294.76,259.14 300.44,259.14 306.13,259.14 311.82,259.14 317.51,259.14 323.20,259.14 328.89,259.14 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='48.34' y1='61.01' x2='51.90' y2='57.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='48.34' y1='57.45' x2='51.90' y2='61.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='48.34' y1='64.02' x2='51.90' y2='60.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='48.34' y1='60.45' x2='51.90' y2='64.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='49.88' y1='106.48' x2='53.45' y2='102.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='49.88' y1='102.92' x2='53.45' y2='106.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='49.88' y1='106.28' x2='53.45' y2='102.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='49.88' y1='102.72' x2='53.45' y2='106.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='52.98' y1='142.74' x2='56.55' y2='139.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='52.98' y1='139.17' x2='56.55' y2='142.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='52.98' y1='144.54' x2='56.55' y2='140.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='52.98' y1='140.98' x2='56.55' y2='144.54' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='60.73' y1='206.04' x2='64.29' y2='202.47' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='60.73' y1='202.47' x2='64.29' y2='206.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='60.73' y1='202.43' x2='64.29' y2='198.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='60.73' y1='198.87' x2='64.29' y2='202.43' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='70.02' y1='222.66' x2='73.58' y2='219.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='70.02' y1='219.10' x2='73.58' y2='222.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='70.02' y1='201.63' x2='73.58' y2='198.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='70.02' y1='198.06' x2='73.58' y2='201.63' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='90.15' y1='240.69' x2='93.72' y2='237.12' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='90.15' y1='237.12' x2='93.72' y2='240.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='90.15' y1='224.46' x2='93.72' y2='220.90' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='90.15' y1='220.90' x2='93.72' y2='224.46' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='122.67' y1='251.91' x2='126.24' y2='248.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='122.67' y1='248.34' x2='126.24' y2='251.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='122.67' y1='242.69' x2='126.24' y2='239.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='122.67' y1='239.13' x2='126.24' y2='242.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='156.75' y1='256.31' x2='160.31' y2='252.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='156.75' y1='252.75' x2='160.31' y2='256.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='156.75' y1='255.11' x2='160.31' y2='251.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='156.75' y1='251.55' x2='160.31' y2='255.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='189.27' y1='256.91' x2='192.83' y2='253.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='189.27' y1='253.35' x2='192.83' y2='256.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='189.27' y1='257.31' x2='192.83' y2='253.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='189.27' y1='253.75' x2='192.83' y2='257.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='234.18' y1='256.91' x2='237.75' y2='253.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='234.18' y1='253.35' x2='237.75' y2='256.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='234.18' y1='256.51' x2='237.75' y2='252.95' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<line x1='234.18' y1='252.95' x2='237.75' y2='256.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='50.12,64.13 51.67,100.30 54.76,147.50 55.81,158.24 59.41,183.42 60.96,190.43 61.50,192.50 62.51,195.99 65.60,204.16 67.19,207.30 71.80,214.20 72.87,215.49 78.56,221.18 81.09,223.31 82.64,224.52 84.25,225.73 89.94,229.61 91.93,230.84 95.63,232.99 96.58,233.51 101.32,235.97 102.77,236.68 107.01,238.61 112.70,240.95 113.62,241.30 118.39,243.02 124.08,244.86 124.46,244.97 129.77,246.48 135.30,247.88 135.46,247.92 141.15,249.20 143.04,249.59 146.83,250.33 147.69,250.49 152.52,251.33 158.21,252.22 158.53,252.27 163.90,253.01 169.59,253.71 175.28,254.32 180.97,254.87 186.66,255.36 189.50,255.58 191.05,255.69 192.35,255.79 198.04,256.17 203.73,256.51 209.42,256.81 215.11,257.07 220.79,257.31 223.58,257.41 226.48,257.52 232.17,257.70 235.97,257.81 237.86,257.86 243.55,258.01 249.24,258.14 254.55,258.24 254.93,258.25 260.62,258.35 266.31,258.44 272.00,258.52 277.69,258.59 283.38,258.65 289.07,258.71 294.76,258.76 300.44,258.80 306.13,258.84 311.82,258.87 317.51,258.90 323.20,258.93 328.89,258.95 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='47.60,66.64 50.12,64.12 52.64,66.64 50.12,69.16 47.60,66.64 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='47.60,70.25 50.12,67.73 52.64,70.25 50.12,72.77 47.60,70.25 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='59.99,111.11 62.51,108.59 65.03,111.11 62.51,113.63 59.99,111.11 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='59.99,111.11 62.51,108.59 65.03,111.11 62.51,113.63 59.99,111.11 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='69.28,120.12 71.80,117.60 74.32,120.12 71.80,122.64 69.28,120.12 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='69.28,112.71 71.80,110.19 74.32,112.71 71.80,115.23 69.28,112.71 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='80.12,127.74 82.64,125.21 85.16,127.74 82.64,130.26 80.12,127.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='80.12,128.34 82.64,125.82 85.16,128.34 82.64,130.86 80.12,128.34 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='111.10,147.17 113.62,144.64 116.14,147.17 113.62,149.69 111.10,147.17 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='111.10,150.17 113.62,147.65 116.14,150.17 113.62,152.69 111.10,150.17 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='145.17,164.99 147.69,162.47 150.21,164.99 147.69,167.51 145.17,164.99 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='145.17,160.39 147.69,157.87 150.21,160.39 147.69,162.91 145.17,160.39 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='188.53,169.60 191.05,167.08 193.57,169.60 191.05,172.12 188.53,169.60 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='188.53,165.59 191.05,163.07 193.57,165.59 191.05,168.11 188.53,165.59 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='233.45,174.81 235.97,172.29 238.49,174.81 235.97,177.33 233.45,174.81 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='233.45,176.41 235.97,173.89 238.49,176.41 235.97,178.93 233.45,176.41 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' /> +<polyline points='50.12,71.37 51.67,76.31 54.76,85.30 55.81,88.07 59.41,96.78 60.96,100.15 61.50,101.27 62.51,103.31 65.60,109.08 67.19,111.77 71.80,118.72 72.87,120.17 78.56,126.95 81.09,129.54 82.64,131.02 84.25,132.47 89.94,137.02 91.93,138.43 95.63,140.82 96.58,141.39 101.32,144.03 102.77,144.77 107.01,146.78 112.70,149.17 113.62,149.53 118.39,151.29 124.08,153.19 124.46,153.31 129.77,154.92 135.30,156.47 135.46,156.51 141.15,157.99 143.04,158.47 146.83,159.39 147.69,159.60 152.52,160.72 158.21,161.99 158.53,162.06 163.90,163.22 169.59,164.41 175.28,165.56 180.97,166.69 186.66,167.79 189.50,168.34 191.05,168.63 192.35,168.87 198.04,169.94 203.73,170.98 209.42,172.01 215.11,173.02 220.79,174.02 223.58,174.51 226.48,175.01 232.17,175.98 235.97,176.62 237.86,176.94 243.55,177.89 249.24,178.83 254.55,179.70 254.93,179.76 260.62,180.67 266.31,181.58 272.00,182.47 277.69,183.35 283.38,184.23 289.07,185.09 294.76,185.94 300.44,186.78 306.13,187.62 311.82,188.44 317.51,189.26 323.20,190.06 328.89,190.86 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDI2Ny4xM3w1MS4yMw==)' />  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU='> -    <rect x='398.97' y='67.75' width='301.08' height='203.06' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM='> +    <rect x='398.97' y='51.23' width='301.08' height='215.90' />    </clipPath>  </defs>  <defs> @@ -223,176 +223,176 @@      <rect x='0.00' y='0.00' width='720.00' height='576.00' />    </clipPath>  </defs> -<line x1='410.12' y1='270.81' x2='696.47' y2='270.81' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='410.12' y1='270.81' x2='410.12' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='467.39' y1='270.81' x2='467.39' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='524.66' y1='270.81' x2='524.66' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='581.93' y1='270.81' x2='581.93' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='639.20' y1='270.81' x2='639.20' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='696.47' y1='270.81' x2='696.47' y2='275.56' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='407.92' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='463.00' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='520.27' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='577.54' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='634.81' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='689.89' y='287.91' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> -<line x1='398.97' y1='251.65' x2='398.97' y2='86.90' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='251.65' x2='394.21' y2='251.65' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='210.47' x2='394.21' y2='210.47' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='169.28' x2='394.21' y2='169.28' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='128.09' x2='394.21' y2='128.09' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='86.90' x2='394.21' y2='86.90' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,255.17) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,213.98) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,171.47) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,130.29) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,89.10) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> -<polyline points='398.97,270.81 700.04,270.81 700.04,67.75 398.97,67.75 398.97,270.81 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='410.12' y1='267.13' x2='696.47' y2='267.13' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='410.12' y1='267.13' x2='410.12' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='467.39' y1='267.13' x2='467.39' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='524.66' y1='267.13' x2='524.66' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='581.93' y1='267.13' x2='581.93' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='639.20' y1='267.13' x2='639.20' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='696.47' y1='267.13' x2='696.47' y2='271.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='407.92' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='463.00' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='520.27' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>40</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='577.54' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>60</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='634.81' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>80</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='689.89' y='284.24' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g> +<line x1='398.97' y1='246.77' x2='398.97' y2='71.60' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='246.77' x2='394.21' y2='246.77' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='202.98' x2='394.21' y2='202.98' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='159.18' x2='394.21' y2='159.18' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='115.39' x2='394.21' y2='115.39' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='71.60' x2='394.21' y2='71.60' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,250.28) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,206.49) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,161.38) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,117.59) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,73.79) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> +<polyline points='398.97,267.13 700.04,267.13 700.04,51.23 398.97,51.23 398.97,267.13 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMzYwLjAwfDcyMC4wMHwyOTkuMzJ8NDcuNzk='> -    <rect x='360.00' y='47.79' width='360.00' height='251.53' /> +  <clipPath id='cpMzYwLjAwfDcyMC4wMHwyOTUuNjV8NDAuNzg='> +    <rect x='360.00' y='40.78' width='360.00' height='254.87' />    </clipPath>  </defs> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwyOTkuMzJ8NDcuNzk=)'><text x='532.82' y='306.92' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwyOTkuMzJ8NDcuNzk=)'><text transform='translate(368.55,207.48) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwyOTUuNjV8NDAuNzg=)'><text x='532.82' y='303.25' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHwyOTUuNjV8NDAuNzg=)'><text transform='translate(368.55,197.39) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g>  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU='> -    <rect x='398.97' y='67.75' width='301.08' height='203.06' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM='> +    <rect x='398.97' y='51.23' width='301.08' height='215.90' />    </clipPath>  </defs> -<line x1='398.97' y1='169.28' x2='700.04' y2='169.28' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='684.40' cy='184.76' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='684.40' cy='176.02' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='614.67' cy='165.62' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='614.67' cy='144.85' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='572.15' cy='185.86' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='572.15' cy='169.46' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='537.80' cy='167.20' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='537.80' cy='156.27' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='495.48' cy='207.42' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='495.48' cy='162.60' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='465.68' cy='149.58' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='465.68' cy='153.95' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='440.26' cy='168.98' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='440.26' cy='155.86' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='421.04' cy='176.78' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='421.04' cy='178.97' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='415.89' cy='180.05' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='415.89' cy='184.42' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='413.35' cy='182.09' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<circle cx='413.35' cy='186.47' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='670.86,194.30 673.26,198.46 668.46,198.46 670.86,194.30 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='670.86,180.09 673.26,184.25 668.46,184.25 670.86,180.09 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='653.05,190.16 655.45,194.32 650.65,194.32 653.05,190.16 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='653.05,137.69 655.45,141.84 650.65,141.84 653.05,137.69 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='632.39,126.90 634.79,131.06 629.99,131.06 632.39,126.90 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='632.39,125.81 634.79,129.97 629.99,129.97 632.39,125.81 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='603.26,131.00 605.66,135.16 600.86,135.16 603.26,131.00 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='603.26,188.94 605.66,193.10 600.86,193.10 603.26,188.94 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='559.96,184.80 562.36,188.96 557.56,188.96 559.96,184.80 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='559.96,191.36 562.36,195.52 557.56,195.52 559.96,191.36 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='522.83,185.51 525.23,189.67 520.43,189.67 522.83,185.51 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='522.83,156.00 525.23,160.15 520.43,160.15 522.83,156.00 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='506.89,152.35 509.29,156.51 504.49,156.51 506.89,152.35 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='506.89,185.15 509.29,189.31 504.49,189.31 506.89,185.15 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='497.33,140.76 499.73,144.91 494.93,144.91 497.33,140.76 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='497.33,150.59 499.73,154.75 494.93,154.75 497.33,150.59 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='483.56,175.81 485.96,179.97 481.16,179.97 483.56,175.81 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='483.56,187.84 485.96,192.00 481.16,192.00 483.56,187.84 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='669.00' y1='175.98' x2='674.04' y2='175.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='671.52' y1='178.50' x2='671.52' y2='173.46' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='669.00' y1='163.95' x2='674.04' y2='163.95' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='671.52' y1='166.47' x2='671.52' y2='161.43' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='601.74' y1='137.58' x2='606.78' y2='137.58' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='604.26' y1='140.10' x2='604.26' y2='135.06' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='601.74' y1='151.79' x2='606.78' y2='151.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='604.26' y1='154.31' x2='604.26' y2='149.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='526.95' y1='189.18' x2='531.99' y2='189.18' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='529.47' y1='191.70' x2='529.47' y2='186.66' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='526.95' y1='195.74' x2='531.99' y2='195.74' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='529.47' y1='198.26' x2='529.47' y2='193.22' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='463.48' y1='156.01' x2='468.52' y2='156.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='466.00' y1='158.53' x2='466.00' y2='153.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='463.48' y1='153.83' x2='468.52' y2='153.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='466.00' y1='156.35' x2='466.00' y2='151.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='438.27' y1='163.70' x2='443.31' y2='163.70' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='440.79' y1='166.22' x2='440.79' y2='161.18' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='438.27' y1='170.26' x2='443.31' y2='170.26' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='440.79' y1='172.78' x2='440.79' y2='167.74' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='417.00' y1='186.96' x2='422.04' y2='186.96' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='419.52' y1='189.48' x2='419.52' y2='184.44' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='417.00' y1='169.47' x2='422.04' y2='169.47' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='419.52' y1='171.99' x2='419.52' y2='166.95' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='409.00' y1='181.40' x2='414.04' y2='181.40' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='411.52' y1='183.92' x2='411.52' y2='178.88' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='409.00' y1='180.31' x2='414.04' y2='180.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='411.52' y1='182.83' x2='411.52' y2='177.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='407.79' y1='180.57' x2='412.83' y2='180.57' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='410.31' y1='183.09' x2='410.31' y2='178.05' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='407.79' y1='178.38' x2='412.83' y2='178.38' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='410.31' y1='180.90' x2='410.31' y2='175.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='687.11' y1='197.82' x2='690.67' y2='194.25' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='687.11' y1='194.25' x2='690.67' y2='197.82' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='687.11' y1='181.42' x2='690.67' y2='177.86' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='687.11' y1='177.86' x2='690.67' y2='181.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='635.41' y1='147.02' x2='638.98' y2='143.46' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='635.41' y1='143.46' x2='638.98' y2='147.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='635.41' y1='148.12' x2='638.98' y2='144.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='635.41' y1='144.55' x2='638.98' y2='148.12' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='567.94' y1='206.75' x2='571.50' y2='203.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='567.94' y1='203.18' x2='571.50' y2='206.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='567.94' y1='196.91' x2='571.50' y2='193.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='567.94' y1='193.35' x2='571.50' y2='196.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='498.60' y1='125.99' x2='502.17' y2='122.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='498.60' y1='122.42' x2='502.17' y2='125.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='498.60' y1='145.66' x2='502.17' y2='142.10' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='498.60' y1='142.10' x2='502.17' y2='145.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='472.57' y1='134.62' x2='476.14' y2='131.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='472.57' y1='131.06' x2='476.14' y2='134.62' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='472.57' y1='249.40' x2='476.14' y2='245.84' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='472.57' y1='245.84' x2='476.14' y2='249.40' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='448.79' y1='127.04' x2='452.35' y2='123.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='448.79' y1='123.48' x2='452.35' y2='127.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='448.79' y1='215.59' x2='452.35' y2='212.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='448.79' y1='212.02' x2='452.35' y2='215.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='428.59' y1='142.93' x2='432.15' y2='139.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='428.59' y1='139.37' x2='432.15' y2='142.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='428.59' y1='193.22' x2='432.15' y2='189.65' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='428.59' y1='189.65' x2='432.15' y2='193.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='418.16' y1='158.71' x2='421.72' y2='155.14' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='418.16' y1='155.14' x2='421.72' y2='158.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='418.16' y1='165.27' x2='421.72' y2='161.70' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='418.16' y1='161.70' x2='421.72' y2='165.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='413.26' y1='174.13' x2='416.82' y2='170.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='413.26' y1='170.57' x2='416.82' y2='174.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='413.26' y1='171.95' x2='416.82' y2='168.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='413.26' y1='168.38' x2='416.82' y2='171.95' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='410.23' y1='185.69' x2='413.80' y2='182.12' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='410.23' y1='182.12' x2='413.80' y2='185.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='410.23' y1='187.87' x2='413.80' y2='184.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<line x1='410.23' y1='184.31' x2='413.80' y2='187.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='676.03,195.07 678.55,192.55 681.07,195.07 678.55,197.59 676.03,195.07 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='676.03,175.40 678.55,172.88 681.07,175.40 678.55,177.92 676.03,175.40 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='630.36,126.74 632.88,124.22 635.40,126.74 632.88,129.26 630.36,126.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='630.36,126.74 632.88,124.22 635.40,126.74 632.88,129.26 630.36,126.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='608.34,161.61 610.86,159.09 613.38,161.61 610.86,164.13 608.34,161.61 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='608.34,202.06 610.86,199.54 613.38,202.06 610.86,204.58 608.34,202.06 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='590.75,187.19 593.27,184.67 595.79,187.19 593.27,189.71 590.75,187.19 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='590.75,183.91 593.27,181.39 595.79,183.91 593.27,186.43 590.75,183.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='564.29,182.18 566.81,179.66 569.33,182.18 566.81,184.70 564.29,182.18 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='564.29,165.79 566.81,163.27 569.33,165.79 566.81,168.31 564.29,165.79 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='549.90,139.82 552.42,137.30 554.94,139.82 552.42,142.34 549.90,139.82 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='549.90,164.97 552.42,162.45 554.94,164.97 552.42,167.49 549.90,164.97 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='536.98,163.99 539.50,161.47 542.02,163.99 539.50,166.51 536.98,163.99 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='536.98,185.85 539.50,183.33 542.02,185.85 539.50,188.37 536.98,185.85 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='525.56,179.19 528.08,176.67 530.60,179.19 528.08,181.71 525.56,179.19 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> -<polyline points='525.56,170.45 528.08,167.93 530.60,170.45 528.08,172.97 525.56,170.45 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNzAuODF8NjcuNzU=)' /> +<line x1='398.97' y1='159.18' x2='700.04' y2='159.18' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='684.40' cy='175.65' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='684.40' cy='166.35' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='614.67' cy='155.30' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='614.67' cy='133.21' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='572.15' cy='176.82' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='572.15' cy='159.38' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='537.80' cy='156.97' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='537.80' cy='145.35' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='495.48' cy='199.73' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='495.48' cy='152.08' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='465.68' cy='138.24' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='465.68' cy='142.89' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='440.26' cy='158.87' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='440.26' cy='144.92' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='421.04' cy='167.16' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='421.04' cy='169.49' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='415.89' cy='170.64' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='415.89' cy='175.29' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='413.35' cy='172.81' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<circle cx='413.35' cy='177.46' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='670.86,185.97 673.26,190.13 668.46,190.13 670.86,185.97 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='670.86,170.86 673.26,175.02 668.46,175.02 670.86,170.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='653.05,181.56 655.45,185.72 650.65,185.72 653.05,181.56 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='653.05,125.77 655.45,129.93 650.65,129.93 653.05,125.77 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='632.39,114.30 634.79,118.46 629.99,118.46 632.39,114.30 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='632.39,113.14 634.79,117.30 629.99,117.30 632.39,113.14 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='603.26,118.66 605.66,122.82 600.86,122.82 603.26,118.66 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='603.26,180.26 605.66,184.42 600.86,184.42 603.26,180.26 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='559.96,175.86 562.36,180.02 557.56,180.02 559.96,175.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='559.96,182.84 562.36,186.99 557.56,186.99 559.96,182.84 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='522.83,176.62 525.23,180.78 520.43,180.78 522.83,176.62 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='522.83,145.24 525.23,149.39 520.43,149.39 522.83,145.24 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='506.89,141.36 509.29,145.52 504.49,145.52 506.89,141.36 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='506.89,176.23 509.29,180.39 504.49,180.39 506.89,176.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='497.33,129.03 499.73,133.19 494.93,133.19 497.33,129.03 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='497.33,139.49 499.73,143.65 494.93,143.65 497.33,139.49 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='483.56,166.31 485.96,170.47 481.16,170.47 483.56,166.31 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='483.56,179.09 485.96,183.25 481.16,183.25 483.56,179.09 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='669.00' y1='166.31' x2='674.04' y2='166.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='671.52' y1='168.83' x2='671.52' y2='163.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='669.00' y1='153.52' x2='674.04' y2='153.52' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='671.52' y1='156.04' x2='671.52' y2='151.00' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='601.74' y1='125.48' x2='606.78' y2='125.48' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='604.26' y1='128.00' x2='604.26' y2='122.96' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='601.74' y1='140.59' x2='606.78' y2='140.59' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='604.26' y1='143.11' x2='604.26' y2='138.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='526.95' y1='180.35' x2='531.99' y2='180.35' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='529.47' y1='182.87' x2='529.47' y2='177.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='526.95' y1='187.32' x2='531.99' y2='187.32' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='529.47' y1='189.84' x2='529.47' y2='184.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='463.48' y1='145.08' x2='468.52' y2='145.08' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='466.00' y1='147.60' x2='466.00' y2='142.56' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='463.48' y1='142.75' x2='468.52' y2='142.75' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='466.00' y1='145.27' x2='466.00' y2='140.23' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='438.27' y1='153.25' x2='443.31' y2='153.25' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='440.79' y1='155.77' x2='440.79' y2='150.73' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='438.27' y1='160.23' x2='443.31' y2='160.23' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='440.79' y1='162.75' x2='440.79' y2='157.71' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='417.00' y1='177.99' x2='422.04' y2='177.99' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='419.52' y1='180.51' x2='419.52' y2='175.47' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='417.00' y1='159.39' x2='422.04' y2='159.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='419.52' y1='161.91' x2='419.52' y2='156.87' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='409.00' y1='172.07' x2='414.04' y2='172.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='411.52' y1='174.59' x2='411.52' y2='169.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='409.00' y1='170.91' x2='414.04' y2='170.91' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='411.52' y1='173.43' x2='411.52' y2='168.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='407.79' y1='171.19' x2='412.83' y2='171.19' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='410.31' y1='173.71' x2='410.31' y2='168.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='407.79' y1='168.86' x2='412.83' y2='168.86' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='410.31' y1='171.38' x2='410.31' y2='166.34' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='687.11' y1='189.42' x2='690.67' y2='185.85' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='687.11' y1='185.85' x2='690.67' y2='189.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='687.11' y1='171.98' x2='690.67' y2='168.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='687.11' y1='168.42' x2='690.67' y2='171.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='635.41' y1='135.41' x2='638.98' y2='131.84' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='635.41' y1='131.84' x2='638.98' y2='135.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='635.41' y1='136.57' x2='638.98' y2='133.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='635.41' y1='133.01' x2='638.98' y2='136.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='567.94' y1='198.91' x2='571.50' y2='195.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='567.94' y1='195.35' x2='571.50' y2='198.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='567.94' y1='188.45' x2='571.50' y2='184.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='567.94' y1='184.89' x2='571.50' y2='188.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='498.60' y1='113.04' x2='502.17' y2='109.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='498.60' y1='109.48' x2='502.17' y2='113.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='498.60' y1='133.96' x2='502.17' y2='130.40' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='498.60' y1='130.40' x2='502.17' y2='133.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='472.57' y1='122.22' x2='476.14' y2='118.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='472.57' y1='118.66' x2='476.14' y2='122.22' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='472.57' y1='244.26' x2='476.14' y2='240.70' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='472.57' y1='240.70' x2='476.14' y2='244.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='448.79' y1='114.16' x2='452.35' y2='110.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='448.79' y1='110.60' x2='452.35' y2='114.16' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='448.79' y1='208.31' x2='452.35' y2='204.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='448.79' y1='204.74' x2='452.35' y2='208.31' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='428.59' y1='131.06' x2='432.15' y2='127.50' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='428.59' y1='127.50' x2='432.15' y2='131.06' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='428.59' y1='184.53' x2='432.15' y2='180.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='428.59' y1='180.96' x2='432.15' y2='184.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='418.16' y1='147.83' x2='421.72' y2='144.27' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='418.16' y1='144.27' x2='421.72' y2='147.83' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='418.16' y1='154.81' x2='421.72' y2='151.24' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='418.16' y1='151.24' x2='421.72' y2='154.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='413.26' y1='164.23' x2='416.82' y2='160.67' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='413.26' y1='160.67' x2='416.82' y2='164.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='413.26' y1='161.91' x2='416.82' y2='158.34' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='413.26' y1='158.34' x2='416.82' y2='161.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='410.23' y1='176.52' x2='413.80' y2='172.95' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='410.23' y1='172.95' x2='413.80' y2='176.52' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='410.23' y1='178.84' x2='413.80' y2='175.28' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<line x1='410.23' y1='175.28' x2='413.80' y2='178.84' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='676.03,186.61 678.55,184.09 681.07,186.61 678.55,189.13 676.03,186.61 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='676.03,165.69 678.55,163.17 681.07,165.69 678.55,168.21 676.03,165.69 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='630.36,113.96 632.88,111.44 635.40,113.96 632.88,116.48 630.36,113.96 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='630.36,113.96 632.88,111.44 635.40,113.96 632.88,116.48 630.36,113.96 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='608.34,151.03 610.86,148.51 613.38,151.03 610.86,153.55 608.34,151.03 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='608.34,194.04 610.86,191.52 613.38,194.04 610.86,196.56 608.34,194.04 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='590.75,178.23 593.27,175.71 595.79,178.23 593.27,180.75 590.75,178.23 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='590.75,174.74 593.27,172.22 595.79,174.74 593.27,177.26 590.75,174.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='564.29,172.91 566.81,170.39 569.33,172.91 566.81,175.43 564.29,172.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='564.29,155.47 566.81,152.95 569.33,155.47 566.81,157.99 564.29,155.47 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='549.90,127.87 552.42,125.35 554.94,127.87 552.42,130.39 549.90,127.87 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='549.90,154.60 552.42,152.08 554.94,154.60 552.42,157.12 549.90,154.60 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='536.98,153.56 539.50,151.04 542.02,153.56 539.50,156.08 536.98,153.56 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='536.98,176.80 539.50,174.28 542.02,176.80 539.50,179.32 536.98,176.80 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='525.56,169.73 528.08,167.21 530.60,169.73 528.08,172.25 525.56,169.73 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' /> +<polyline points='525.56,160.43 528.08,157.91 530.60,160.43 528.08,162.95 525.56,160.43 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHwyNjcuMTN8NTEuMjM=)' />  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg='> -    <rect x='38.97' y='319.28' width='301.08' height='208.25' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA='> +    <rect x='38.97' y='306.10' width='301.08' height='221.43' />    </clipPath>  </defs> -<polyline points='50.12,519.82 51.67,505.46 54.76,482.22 55.81,475.76 59.41,457.55 60.96,451.34 61.50,449.37 62.51,445.90 65.60,436.93 67.19,433.16 71.80,424.49 72.87,422.86 78.56,416.02 81.09,413.69 82.64,412.43 84.25,411.22 89.94,407.66 91.93,406.62 95.63,404.88 96.58,404.47 101.32,402.60 102.77,402.08 107.01,400.67 112.70,398.99 113.62,398.74 118.39,397.51 124.08,396.19 124.46,396.10 129.77,395.01 135.30,393.99 135.46,393.96 141.15,393.02 143.04,392.73 146.83,392.19 147.69,392.07 152.52,391.45 158.21,390.81 158.53,390.77 163.90,390.25 169.59,389.78 175.28,389.38 180.97,389.05 186.66,388.80 189.50,388.69 191.05,388.64 192.35,388.60 198.04,388.47 203.73,388.40 209.42,388.38 215.11,388.41 220.79,388.50 223.58,388.55 226.48,388.62 232.17,388.79 235.97,388.93 237.86,389.00 243.55,389.25 249.24,389.54 254.55,389.83 254.93,389.86 260.62,390.21 266.31,390.59 272.00,390.99 277.69,391.43 283.38,391.89 289.07,392.37 294.76,392.87 300.44,393.40 306.13,393.94 311.82,394.50 317.51,395.08 323.20,395.67 328.89,396.27 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> +<polyline points='50.12,519.33 51.67,504.06 54.76,479.35 55.81,472.48 59.41,453.12 60.96,446.51 61.50,444.42 62.51,440.73 65.60,431.20 67.19,427.19 71.80,417.97 72.87,416.24 78.56,408.96 81.09,406.49 82.64,405.15 84.25,403.86 89.94,400.08 91.93,398.97 95.63,397.12 96.58,396.68 101.32,394.69 102.77,394.14 107.01,392.64 112.70,390.85 113.62,390.59 118.39,389.28 124.08,387.88 124.46,387.79 129.77,386.63 135.30,385.54 135.46,385.51 141.15,384.51 143.04,384.20 146.83,383.62 147.69,383.50 152.52,382.84 158.21,382.16 158.53,382.12 163.90,381.57 169.59,381.06 175.28,380.64 180.97,380.29 186.66,380.02 189.50,379.91 191.05,379.85 192.35,379.81 198.04,379.67 203.73,379.60 209.42,379.58 215.11,379.61 220.79,379.70 223.58,379.76 226.48,379.83 232.17,380.01 235.97,380.16 237.86,380.24 243.55,380.50 249.24,380.81 254.55,381.12 254.93,381.14 260.62,381.52 266.31,381.92 272.00,382.35 277.69,382.82 283.38,383.30 289.07,383.82 294.76,384.35 300.44,384.91 306.13,385.49 311.82,386.08 317.51,386.69 323.20,387.32 328.89,387.97 ' style='stroke-width: 1.50;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' />  <defs>    <clipPath id='cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA='>      <rect x='0.00' y='0.00' width='720.00' height='576.00' /> @@ -407,152 +407,152 @@  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='123.16' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>50</text></g>  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='198.41' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>100</text></g>  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='275.84' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='13.17px' lengthAdjust='spacingAndGlyphs'>150</text></g> -<line x1='38.97' y1='519.82' x2='38.97' y2='347.65' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='519.82' x2='34.21' y2='519.82' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='485.38' x2='34.21' y2='485.38' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='450.95' x2='34.21' y2='450.95' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='416.52' x2='34.21' y2='416.52' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='382.08' x2='34.21' y2='382.08' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='38.97' y1='347.65' x2='34.21' y2='347.65' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,522.01) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,487.58) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>5</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,455.34) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,420.91) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>15</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,386.47) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,352.04) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>25</text></g> -<polyline points='38.97,527.53 340.04,527.53 340.04,319.28 38.97,319.28 38.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='519.33' x2='38.97' y2='336.27' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='519.33' x2='34.21' y2='519.33' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='482.72' x2='34.21' y2='482.72' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='446.10' x2='34.21' y2='446.10' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='409.49' x2='34.21' y2='409.49' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='372.88' x2='34.21' y2='372.88' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='38.97' y1='336.27' x2='34.21' y2='336.27' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,521.52) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,484.91) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>5</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,450.50) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>10</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,413.88) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>15</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,377.27) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(27.56,340.66) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>25</text></g> +<polyline points='38.97,527.53 340.04,527.53 340.04,306.10 38.97,306.10 38.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMC4wMHwzNjAuMDB8NTc2LjAwfDI5OS4zMg=='> -    <rect x='0.00' y='299.32' width='360.00' height='276.68' /> +  <clipPath id='cpMC4wMHwzNjAuMDB8NTc2LjAwfDI5NS42NQ=='> +    <rect x='0.00' y='295.65' width='360.00' height='280.35' />    </clipPath>  </defs> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDI5OS4zMg==)'><text x='180.87' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> -<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDI5OS4zMg==)'><text transform='translate(8.55,428.23) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='9.66px' lengthAdjust='spacingAndGlyphs'>A1</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDI5NS42NQ==)'><text x='180.87' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='17.27px' lengthAdjust='spacingAndGlyphs'>Time</text></g> +<g clip-path='url(#cpMC4wMHwzNjAuMDB8NTc2LjAwfDI5NS42NQ==)'><text transform='translate(8.55,438.99) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='44.34px' lengthAdjust='spacingAndGlyphs'>Residues A1</text></g>  <defs> -  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg='> -    <rect x='38.97' y='319.28' width='301.08' height='208.25' /> +  <clipPath id='cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA='> +    <rect x='38.97' y='306.10' width='301.08' height='221.43' />    </clipPath>  </defs> -<circle cx='54.76' cy='490.20' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='54.76' cy='488.14' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='59.41' cy='471.61' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='59.41' cy='470.23' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='65.60' cy='463.35' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='65.60' cy='464.72' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='81.09' cy='444.06' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='81.09' cy='425.47' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='102.77' cy='440.62' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='102.77' cy='432.36' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='135.30' cy='417.21' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='135.30' cy='419.96' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='189.50' cy='436.49' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='189.50' cy='435.11' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='223.58' cy='451.64' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='223.58' cy='449.57' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='254.55' cy='459.21' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<circle cx='254.55' cy='466.10' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='50.12,519.82 51.67,506.89 54.76,487.08 55.81,481.84 59.41,467.73 60.96,463.15 61.50,461.72 62.51,459.23 65.60,452.97 67.19,450.41 71.80,444.66 72.87,443.60 78.56,439.20 81.09,437.73 82.64,436.93 84.25,436.18 89.94,434.05 91.93,433.45 95.63,432.52 96.58,432.31 101.32,431.45 102.77,431.24 107.01,430.75 112.70,430.37 113.62,430.33 118.39,430.24 124.08,430.34 124.46,430.36 129.77,430.64 135.30,431.10 135.46,431.12 141.15,431.74 143.04,431.98 146.83,432.49 147.69,432.61 152.52,433.35 158.21,434.32 158.53,434.37 163.90,435.36 169.59,436.47 175.28,437.64 180.97,438.86 186.66,440.12 189.50,440.77 191.05,441.12 192.35,441.42 198.04,442.74 203.73,444.07 209.42,445.43 215.11,446.79 220.79,448.15 223.58,448.82 226.48,449.52 232.17,450.88 235.97,451.79 237.86,452.24 243.55,453.59 249.24,454.93 254.55,456.17 254.93,456.26 260.62,457.57 266.31,458.87 272.00,460.15 277.69,461.42 283.38,462.67 289.07,463.90 294.76,465.11 300.44,466.30 306.13,467.47 311.82,468.62 317.51,469.75 323.20,470.86 328.89,471.94 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='54.76,490.19 57.16,494.34 52.36,494.34 54.76,490.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='54.76,495.70 57.16,499.85 52.36,499.85 54.76,495.70 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='60.96,469.53 63.36,473.68 58.56,473.68 60.96,469.53 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='60.96,471.59 63.36,475.75 58.56,475.75 60.96,471.59 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='71.80,445.42 74.20,449.58 69.40,449.58 71.80,445.42 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='71.80,459.89 74.20,464.04 69.40,464.04 71.80,459.89 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='96.58,417.88 98.98,422.03 94.18,422.03 96.58,417.88 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='96.58,422.70 98.98,426.85 94.18,426.85 96.58,422.70 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='143.04,364.85 145.44,369.01 140.64,369.01 143.04,364.85 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='143.04,363.47 145.44,367.63 140.64,367.63 143.04,363.47 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='189.50,327.66 191.90,331.82 187.10,331.82 189.50,327.66 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='189.50,342.12 191.90,346.28 187.10,346.28 189.50,342.12 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='235.97,324.22 238.37,328.38 233.57,328.38 235.97,324.22 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='235.97,333.86 238.37,338.02 233.57,338.02 235.97,333.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='328.89,339.37 331.29,343.53 326.49,343.53 328.89,339.37 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='328.89,342.81 331.29,346.97 326.49,346.97 328.89,342.81 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='50.12,519.82 51.67,513.32 54.76,501.09 55.81,497.19 59.41,484.51 60.96,479.42 61.50,477.70 62.51,474.53 65.60,465.31 67.19,460.88 71.80,448.95 72.87,446.36 78.56,433.81 81.09,428.78 82.64,425.86 84.25,422.94 89.94,413.51 91.93,410.51 95.63,405.32 96.58,404.06 101.32,398.19 102.77,396.52 107.01,391.97 112.70,386.53 113.62,385.72 118.39,381.76 124.08,377.57 124.46,377.31 129.77,373.87 135.30,370.68 135.46,370.60 141.15,367.69 143.04,366.79 146.83,365.09 147.69,364.72 152.52,362.76 158.21,360.67 158.53,360.56 163.90,358.78 169.59,357.06 175.28,355.49 180.97,354.05 186.66,352.73 189.50,352.10 191.05,351.77 192.35,351.50 198.04,350.36 203.73,349.29 209.42,348.29 215.11,347.34 220.79,346.44 223.58,346.02 226.48,345.59 232.17,344.78 235.97,344.26 237.86,344.01 243.55,343.26 249.24,342.54 254.55,341.90 254.93,341.85 260.62,341.19 266.31,340.54 272.00,339.91 277.69,339.30 283.38,338.71 289.07,338.13 294.76,337.57 300.44,337.02 306.13,336.48 311.82,335.95 317.51,335.44 323.20,334.94 328.89,334.45 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='49.15' y1='453.70' x2='54.19' y2='453.70' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='51.67' y1='456.22' x2='51.67' y2='451.18' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='49.15' y1='466.79' x2='54.19' y2='466.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='51.67' y1='469.31' x2='51.67' y2='464.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='52.24' y1='416.52' x2='57.28' y2='416.52' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='54.76' y1='419.04' x2='54.76' y2='414.00' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='52.24' y1='415.83' x2='57.28' y2='415.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='54.76' y1='418.35' x2='54.76' y2='413.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='59.99' y1='373.82' x2='65.03' y2='373.82' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='62.51' y1='376.34' x2='62.51' y2='371.30' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='59.99' y1='374.51' x2='65.03' y2='374.51' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='62.51' y1='377.03' x2='62.51' y2='371.99' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='69.28' y1='384.15' x2='74.32' y2='384.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='71.80' y1='386.67' x2='71.80' y2='381.63' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='69.28' y1='389.66' x2='74.32' y2='389.66' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='71.80' y1='392.18' x2='71.80' y2='387.14' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='89.41' y1='399.30' x2='94.45' y2='399.30' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='91.93' y1='401.82' x2='91.93' y2='396.78' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='89.41' y1='410.32' x2='94.45' y2='410.32' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='91.93' y1='412.84' x2='91.93' y2='407.80' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='121.94' y1='454.39' x2='126.98' y2='454.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='124.46' y1='456.91' x2='124.46' y2='451.87' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='121.94' y1='452.33' x2='126.98' y2='452.33' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='124.46' y1='454.85' x2='124.46' y2='449.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='156.01' y1='477.12' x2='161.05' y2='477.12' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='158.53' y1='479.64' x2='158.53' y2='474.60' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='156.01' y1='477.81' x2='161.05' y2='477.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='158.53' y1='480.33' x2='158.53' y2='475.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='50.12,519.82 51.67,467.30 54.76,412.46 55.81,402.57 59.41,384.46 60.96,381.06 61.50,380.25 62.51,379.11 65.60,377.92 67.19,378.23 71.80,381.14 72.87,382.12 78.56,388.47 81.09,391.74 82.64,393.82 84.25,396.05 89.94,404.18 91.93,407.08 95.63,412.46 96.58,413.84 101.32,420.63 102.77,422.67 107.01,428.50 112.70,435.99 113.62,437.15 118.39,443.02 124.08,449.59 124.46,450.01 129.77,455.68 135.30,461.15 135.46,461.30 141.15,466.47 143.04,468.10 146.83,471.22 147.69,471.89 152.52,475.56 158.21,479.53 158.53,479.74 163.90,483.16 169.59,486.47 175.28,489.48 180.97,492.23 186.66,494.73 189.50,495.89 191.05,496.51 192.35,497.01 198.04,499.08 203.73,500.96 209.42,502.68 215.11,504.23 220.79,505.65 223.58,506.30 226.48,506.94 232.17,508.11 235.97,508.83 237.86,509.18 243.55,510.15 249.24,511.03 254.55,511.78 254.93,511.83 260.62,512.55 266.31,513.22 272.00,513.82 277.69,514.36 283.38,514.86 289.07,515.31 294.76,515.72 300.44,516.09 306.13,516.43 311.82,516.74 317.51,517.02 323.20,517.28 328.89,517.51 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='49.88' y1='492.67' x2='53.45' y2='489.11' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='49.88' y1='489.11' x2='53.45' y2='492.67' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='49.88' y1='494.74' x2='53.45' y2='491.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='49.88' y1='491.18' x2='53.45' y2='494.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='52.98' y1='470.64' x2='56.55' y2='467.07' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='52.98' y1='467.07' x2='56.55' y2='470.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='52.98' y1='467.19' x2='56.55' y2='463.63' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='52.98' y1='463.63' x2='56.55' y2='467.19' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='60.73' y1='421.74' x2='64.29' y2='418.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='60.73' y1='418.18' x2='64.29' y2='421.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='60.73' y1='427.25' x2='64.29' y2='423.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='60.73' y1='423.69' x2='64.29' y2='427.25' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='70.02' y1='423.81' x2='73.58' y2='420.24' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='70.02' y1='420.24' x2='73.58' y2='423.81' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='70.02' y1='437.58' x2='73.58' y2='434.02' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='70.02' y1='434.02' x2='73.58' y2='437.58' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='90.15' y1='427.25' x2='93.72' y2='423.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='90.15' y1='423.69' x2='93.72' y2='427.25' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='90.15' y1='430.69' x2='93.72' y2='427.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='90.15' y1='427.13' x2='93.72' y2='430.69' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='122.67' y1='427.94' x2='126.24' y2='424.38' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='122.67' y1='424.38' x2='126.24' y2='427.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='122.67' y1='415.54' x2='126.24' y2='411.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='122.67' y1='411.98' x2='126.24' y2='415.54' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='156.75' y1='449.98' x2='160.31' y2='446.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='156.75' y1='446.41' x2='160.31' y2='449.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='156.75' y1='441.71' x2='160.31' y2='438.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='156.75' y1='438.15' x2='160.31' y2='441.71' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='189.27' y1='452.73' x2='192.83' y2='449.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='189.27' y1='449.17' x2='192.83' y2='452.73' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='189.27' y1='456.18' x2='192.83' y2='452.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='189.27' y1='452.61' x2='192.83' y2='456.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='234.18' y1='458.93' x2='237.75' y2='455.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='234.18' y1='455.37' x2='237.75' y2='458.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='234.18' y1='459.62' x2='237.75' y2='456.05' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<line x1='234.18' y1='456.05' x2='237.75' y2='459.62' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='50.12,519.82 51.67,494.64 54.76,462.33 55.81,455.15 59.41,438.92 60.96,434.69 61.50,433.48 62.51,431.50 65.60,427.25 67.19,425.82 71.80,423.28 72.87,422.92 78.56,421.82 81.09,421.62 82.64,421.56 84.25,421.54 89.94,421.73 91.93,421.88 95.63,422.26 96.58,422.37 101.32,423.04 102.77,423.28 107.01,424.04 112.70,425.22 113.62,425.43 118.39,426.55 124.08,428.00 124.46,428.10 129.77,429.55 135.30,431.14 135.46,431.19 141.15,432.89 143.04,433.47 146.83,434.64 147.69,434.91 152.52,436.43 158.21,438.25 158.53,438.35 163.90,440.08 169.59,441.92 175.28,443.76 180.97,445.60 186.66,447.42 189.50,448.33 191.05,448.82 192.35,449.23 198.04,451.03 203.73,452.80 209.42,454.54 215.11,456.26 220.79,457.95 223.58,458.76 226.48,459.61 232.17,461.23 235.97,462.30 237.86,462.82 243.55,464.38 249.24,465.91 254.55,467.30 254.93,467.40 260.62,468.86 266.31,470.28 272.00,471.67 277.69,473.02 283.38,474.34 289.07,475.62 294.76,476.88 300.44,478.10 306.13,479.29 311.82,480.44 317.51,481.57 323.20,482.66 328.89,483.73 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='59.99,497.09 62.51,494.57 65.03,497.09 62.51,499.61 59.99,497.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='59.99,496.40 62.51,493.88 65.03,496.40 62.51,498.92 59.99,496.40 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='69.28,492.96 71.80,490.44 74.32,492.96 71.80,495.48 69.28,492.96 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='69.28,499.85 71.80,497.33 74.32,499.85 71.80,502.37 69.28,499.85 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='80.12,475.74 82.64,473.22 85.16,475.74 82.64,478.26 80.12,475.74 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='80.12,470.23 82.64,467.71 85.16,470.23 82.64,472.75 80.12,470.23 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='111.10,457.15 113.62,454.63 116.14,457.15 113.62,459.67 111.10,457.15 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='111.10,461.28 113.62,458.76 116.14,461.28 113.62,463.80 111.10,461.28 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='145.17,439.24 147.69,436.72 150.21,439.24 147.69,441.76 145.17,439.24 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='145.17,437.18 147.69,434.66 150.21,437.18 147.69,439.70 145.17,437.18 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='188.53,428.22 191.05,425.70 193.57,428.22 191.05,430.74 188.53,428.22 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='188.53,428.91 191.05,426.39 193.57,428.91 191.05,431.43 188.53,428.91 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='233.45,421.34 235.97,418.82 238.49,421.34 235.97,423.86 233.45,421.34 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='233.45,436.49 235.97,433.97 238.49,436.49 235.97,439.01 233.45,436.49 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> -<polyline points='50.12,519.82 51.67,515.52 54.76,507.73 55.81,505.32 59.41,497.77 60.96,494.85 61.50,493.88 62.51,492.11 65.60,487.13 67.19,484.81 71.80,478.82 72.87,477.57 78.56,471.75 81.09,469.53 82.64,468.27 84.25,467.03 89.94,463.16 91.93,461.97 95.63,459.95 96.58,459.46 101.32,457.25 102.77,456.63 107.01,454.96 112.70,452.97 113.62,452.68 118.39,451.24 124.08,449.69 124.46,449.59 129.77,448.29 135.30,447.05 135.46,447.02 141.15,445.84 143.04,445.46 146.83,444.74 147.69,444.58 152.52,443.69 158.21,442.70 158.53,442.65 163.90,441.75 169.59,440.84 175.28,439.95 180.97,439.09 186.66,438.26 189.50,437.85 191.05,437.62 192.35,437.44 198.04,436.64 203.73,435.86 209.42,435.09 215.11,434.34 220.79,433.60 223.58,433.24 226.48,432.87 232.17,432.15 235.97,431.68 237.86,431.45 243.55,430.76 249.24,430.08 254.55,429.45 254.93,429.41 260.62,428.75 266.31,428.10 272.00,427.46 277.69,426.83 283.38,426.21 289.07,425.60 294.76,425.00 300.44,424.41 306.13,423.83 311.82,423.26 317.51,422.70 323.20,422.14 328.89,421.60 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMTkuMjg=)' /> +<circle cx='54.76' cy='487.84' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='54.76' cy='485.65' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='59.41' cy='468.07' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='59.41' cy='466.61' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='65.60' cy='459.28' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='65.60' cy='460.75' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='81.09' cy='438.78' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='81.09' cy='419.01' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='102.77' cy='435.12' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='102.77' cy='426.33' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='135.30' cy='410.22' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='135.30' cy='413.15' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='189.50' cy='430.73' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='189.50' cy='429.26' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='223.58' cy='446.84' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='223.58' cy='444.64' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='254.55' cy='454.89' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<circle cx='254.55' cy='462.21' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='50.12,519.33 51.67,505.58 54.76,484.52 55.81,478.95 59.41,463.95 60.96,459.07 61.50,457.56 62.51,454.91 65.60,448.26 67.19,445.54 71.80,439.42 72.87,438.29 78.56,433.61 81.09,432.04 82.64,431.20 84.25,430.41 89.94,428.13 91.93,427.50 95.63,426.51 96.58,426.29 101.32,425.37 102.77,425.15 107.01,424.63 112.70,424.22 113.62,424.18 118.39,424.08 124.08,424.19 124.46,424.21 129.77,424.51 135.30,425.00 135.46,425.02 141.15,425.68 143.04,425.93 146.83,426.48 147.69,426.61 152.52,427.40 158.21,428.42 158.53,428.48 163.90,429.53 169.59,430.71 175.28,431.96 180.97,433.25 186.66,434.59 189.50,435.28 191.05,435.65 192.35,435.97 198.04,437.37 203.73,438.79 209.42,440.23 215.11,441.68 220.79,443.13 223.58,443.84 226.48,444.58 232.17,446.03 235.97,446.99 237.86,447.47 243.55,448.91 249.24,450.33 254.55,451.65 254.93,451.75 260.62,453.15 266.31,454.53 272.00,455.89 277.69,457.24 283.38,458.57 289.07,459.87 294.76,461.16 300.44,462.43 306.13,463.67 311.82,464.89 317.51,466.09 323.20,467.27 328.89,468.43 ' style='stroke-width: 0.75; stroke: #DF536B; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='54.76,488.00 57.16,492.16 52.36,492.16 54.76,488.00 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='54.76,493.86 57.16,498.01 52.36,498.01 54.76,493.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='60.96,466.03 63.36,470.19 58.56,470.19 60.96,466.03 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='60.96,468.23 63.36,472.39 58.56,472.39 60.96,468.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='71.80,440.40 74.20,444.56 69.40,444.56 71.80,440.40 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='71.80,455.78 74.20,459.94 69.40,459.94 71.80,455.78 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='96.58,411.11 98.98,415.27 94.18,415.27 96.58,411.11 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='96.58,416.24 98.98,420.40 94.18,420.40 96.58,416.24 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='143.04,354.73 145.44,358.89 140.64,358.89 143.04,354.73 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='143.04,353.27 145.44,357.42 140.64,357.42 143.04,353.27 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='189.50,315.19 191.90,319.35 187.10,319.35 189.50,315.19 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='189.50,330.57 191.90,334.73 187.10,334.73 189.50,330.57 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='235.97,311.53 238.37,315.69 233.57,315.69 235.97,311.53 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='235.97,321.78 238.37,325.94 233.57,325.94 235.97,321.78 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='328.89,327.64 331.29,331.80 326.49,331.80 328.89,327.64 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='328.89,331.30 331.29,335.46 326.49,335.46 328.89,331.30 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='50.12,519.33 51.67,512.42 54.76,499.42 55.81,495.28 59.41,481.79 60.96,476.38 61.50,474.55 62.51,471.17 65.60,461.37 67.19,456.67 71.80,443.97 72.87,441.23 78.56,427.88 81.09,422.53 82.64,419.43 84.25,416.32 89.94,406.29 91.93,403.11 95.63,397.59 96.58,396.25 101.32,390.01 102.77,388.23 107.01,383.39 112.70,377.61 113.62,376.75 118.39,372.54 124.08,368.08 124.46,367.80 129.77,364.15 135.30,360.76 135.46,360.67 141.15,357.57 143.04,356.62 146.83,354.81 147.69,354.42 152.52,352.34 158.21,350.11 158.53,350.00 163.90,348.10 169.59,346.27 175.28,344.61 180.97,343.08 186.66,341.67 189.50,341.00 191.05,340.65 192.35,340.36 198.04,339.15 203.73,338.01 209.42,336.94 215.11,335.94 220.79,334.99 223.58,334.54 226.48,334.08 232.17,333.22 235.97,332.67 237.86,332.39 243.55,331.60 249.24,330.84 254.55,330.15 254.93,330.11 260.62,329.40 266.31,328.71 272.00,328.04 277.69,327.39 283.38,326.76 289.07,326.15 294.76,325.55 300.44,324.96 306.13,324.39 311.82,323.83 317.51,323.29 323.20,322.75 328.89,322.23 ' style='stroke-width: 0.75; stroke: #61D04F; stroke-dasharray: 1.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='49.15' y1='449.03' x2='54.19' y2='449.03' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='51.67' y1='451.55' x2='51.67' y2='446.51' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='49.15' y1='462.95' x2='54.19' y2='462.95' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='51.67' y1='465.47' x2='51.67' y2='460.43' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='52.24' y1='409.49' x2='57.28' y2='409.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='54.76' y1='412.01' x2='54.76' y2='406.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='52.24' y1='408.76' x2='57.28' y2='408.76' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='54.76' y1='411.28' x2='54.76' y2='406.24' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='59.99' y1='364.09' x2='65.03' y2='364.09' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='62.51' y1='366.61' x2='62.51' y2='361.57' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='59.99' y1='364.83' x2='65.03' y2='364.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='62.51' y1='367.35' x2='62.51' y2='362.31' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='69.28' y1='375.08' x2='74.32' y2='375.08' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='71.80' y1='377.60' x2='71.80' y2='372.56' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='69.28' y1='380.94' x2='74.32' y2='380.94' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='71.80' y1='383.46' x2='71.80' y2='378.42' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='89.41' y1='391.19' x2='94.45' y2='391.19' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='91.93' y1='393.71' x2='91.93' y2='388.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='89.41' y1='402.90' x2='94.45' y2='402.90' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='91.93' y1='405.42' x2='91.93' y2='400.38' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='121.94' y1='449.77' x2='126.98' y2='449.77' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='124.46' y1='452.29' x2='124.46' y2='447.25' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='121.94' y1='447.57' x2='126.98' y2='447.57' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='124.46' y1='450.09' x2='124.46' y2='445.05' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='156.01' y1='473.93' x2='161.05' y2='473.93' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='158.53' y1='476.45' x2='158.53' y2='471.41' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='156.01' y1='474.66' x2='161.05' y2='474.66' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='158.53' y1='477.18' x2='158.53' y2='472.14' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='50.12,519.33 51.67,463.49 54.76,405.17 55.81,394.67 59.41,375.41 60.96,371.79 61.50,370.93 62.51,369.72 65.60,368.46 67.19,368.78 71.80,371.87 72.87,372.92 78.56,379.68 81.09,383.15 82.64,385.36 84.25,387.73 89.94,396.38 91.93,399.46 95.63,405.18 96.58,406.64 101.32,413.86 102.77,416.04 107.01,422.23 112.70,430.19 113.62,431.43 118.39,437.68 124.08,444.66 124.46,445.11 129.77,451.13 135.30,456.95 135.46,457.11 141.15,462.61 143.04,464.34 146.83,467.65 147.69,468.37 152.52,472.27 158.21,476.49 158.53,476.72 163.90,480.35 169.59,483.87 175.28,487.07 180.97,490.00 186.66,492.65 189.50,493.89 191.05,494.54 192.35,495.07 198.04,497.28 203.73,499.28 209.42,501.10 215.11,502.76 220.79,504.27 223.58,504.95 226.48,505.64 232.17,506.88 235.97,507.65 237.86,508.02 243.55,509.05 249.24,509.98 254.55,510.78 254.93,510.83 260.62,511.61 266.31,512.31 272.00,512.95 277.69,513.53 283.38,514.06 289.07,514.54 294.76,514.97 300.44,515.37 306.13,515.73 311.82,516.06 317.51,516.36 323.20,516.63 328.89,516.87 ' style='stroke-width: 0.75; stroke: #2297E6; stroke-dasharray: 1.00,3.00,4.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='49.88' y1='490.36' x2='53.45' y2='486.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='49.88' y1='486.79' x2='53.45' y2='490.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='49.88' y1='492.55' x2='53.45' y2='488.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='49.88' y1='488.99' x2='53.45' y2='492.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='52.98' y1='466.92' x2='56.55' y2='463.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='52.98' y1='463.36' x2='56.55' y2='466.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='52.98' y1='463.26' x2='56.55' y2='459.70' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='52.98' y1='459.70' x2='56.55' y2='463.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='60.73' y1='414.94' x2='64.29' y2='411.37' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='60.73' y1='411.37' x2='64.29' y2='414.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='60.73' y1='420.79' x2='64.29' y2='417.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='60.73' y1='417.23' x2='64.29' y2='420.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='70.02' y1='417.13' x2='73.58' y2='413.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='70.02' y1='413.57' x2='73.58' y2='417.13' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='70.02' y1='431.78' x2='73.58' y2='428.21' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='70.02' y1='428.21' x2='73.58' y2='431.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='90.15' y1='420.79' x2='93.72' y2='417.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='90.15' y1='417.23' x2='93.72' y2='420.79' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='90.15' y1='424.45' x2='93.72' y2='420.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='90.15' y1='420.89' x2='93.72' y2='424.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='122.67' y1='421.53' x2='126.24' y2='417.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='122.67' y1='417.96' x2='126.24' y2='421.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='122.67' y1='408.35' x2='126.24' y2='404.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='122.67' y1='404.78' x2='126.24' y2='408.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='156.75' y1='444.96' x2='160.31' y2='441.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='156.75' y1='441.39' x2='160.31' y2='444.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='156.75' y1='436.17' x2='160.31' y2='432.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='156.75' y1='432.61' x2='160.31' y2='436.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='189.27' y1='447.89' x2='192.83' y2='444.32' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='189.27' y1='444.32' x2='192.83' y2='447.89' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='189.27' y1='451.55' x2='192.83' y2='447.98' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='189.27' y1='447.98' x2='192.83' y2='451.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='234.18' y1='454.48' x2='237.75' y2='450.91' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='234.18' y1='450.91' x2='237.75' y2='454.48' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='234.18' y1='455.21' x2='237.75' y2='451.64' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<line x1='234.18' y1='451.64' x2='237.75' y2='455.21' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='50.12,519.33 51.67,492.56 54.76,458.20 55.81,450.57 59.41,433.32 60.96,428.81 61.50,427.53 62.51,425.42 65.60,420.90 67.19,419.38 71.80,416.68 72.87,416.30 78.56,415.13 81.09,414.92 82.64,414.86 84.25,414.83 89.94,415.04 91.93,415.20 95.63,415.60 96.58,415.72 101.32,416.43 102.77,416.68 107.01,417.49 112.70,418.75 113.62,418.96 118.39,420.16 124.08,421.70 124.46,421.81 129.77,423.35 135.30,425.04 135.46,425.09 141.15,426.90 143.04,427.52 146.83,428.76 147.69,429.05 152.52,430.67 158.21,432.60 158.53,432.70 163.90,434.54 169.59,436.50 175.28,438.46 180.97,440.41 186.66,442.36 189.50,443.32 191.05,443.84 192.35,444.28 198.04,446.19 203.73,448.07 209.42,449.92 215.11,451.75 220.79,453.54 223.58,454.41 226.48,455.31 232.17,457.04 235.97,458.17 237.86,458.73 243.55,460.39 249.24,462.01 254.55,463.49 254.93,463.59 260.62,465.14 266.31,466.66 272.00,468.13 277.69,469.57 283.38,470.97 289.07,472.34 294.76,473.67 300.44,474.97 306.13,476.23 311.82,477.46 317.51,478.66 323.20,479.82 328.89,480.96 ' style='stroke-width: 0.75; stroke: #28E2E5; stroke-dasharray: 7.00,3.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='59.99,495.16 62.51,492.64 65.03,495.16 62.51,497.68 59.99,495.16 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='59.99,494.43 62.51,491.91 65.03,494.43 62.51,496.95 59.99,494.43 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='69.28,490.77 71.80,488.25 74.32,490.77 71.80,493.29 69.28,490.77 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='69.28,498.09 71.80,495.57 74.32,498.09 71.80,500.61 69.28,498.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='80.12,472.47 82.64,469.95 85.16,472.47 82.64,474.99 80.12,472.47 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='80.12,466.61 82.64,464.09 85.16,466.61 82.64,469.13 80.12,466.61 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='111.10,452.69 113.62,450.17 116.14,452.69 113.62,455.21 111.10,452.69 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='111.10,457.09 113.62,454.57 116.14,457.09 113.62,459.61 111.10,457.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='145.17,433.66 147.69,431.14 150.21,433.66 147.69,436.18 145.17,433.66 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='145.17,431.46 147.69,428.94 150.21,431.46 147.69,433.98 145.17,431.46 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='188.53,421.94 191.05,419.42 193.57,421.94 191.05,424.46 188.53,421.94 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='188.53,422.67 191.05,420.15 193.57,422.67 191.05,425.19 188.53,422.67 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='233.45,414.62 235.97,412.10 238.49,414.62 235.97,417.14 233.45,414.62 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='233.45,430.73 235.97,428.21 238.49,430.73 235.97,433.25 233.45,430.73 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' /> +<polyline points='50.12,519.33 51.67,514.76 54.76,506.47 55.81,503.92 59.41,495.89 60.96,492.78 61.50,491.75 62.51,489.87 65.60,484.57 67.19,482.11 71.80,475.74 72.87,474.41 78.56,468.22 81.09,465.86 82.64,464.52 84.25,463.20 89.94,459.08 91.93,457.82 95.63,455.67 96.58,455.16 101.32,452.80 102.77,452.14 107.01,450.36 112.70,448.26 113.62,447.94 118.39,446.41 124.08,444.76 124.46,444.66 129.77,443.28 135.30,441.96 135.46,441.92 141.15,440.67 143.04,440.27 146.83,439.50 147.69,439.33 152.52,438.39 158.21,437.33 158.53,437.28 163.90,436.32 169.59,435.35 175.28,434.41 180.97,433.50 186.66,432.61 189.50,432.17 191.05,431.94 192.35,431.74 198.04,430.89 203.73,430.06 209.42,429.24 215.11,428.44 220.79,427.65 223.58,427.27 226.48,426.88 232.17,426.12 235.97,425.62 237.86,425.37 243.55,424.64 249.24,423.91 254.55,423.25 254.93,423.20 260.62,422.50 266.31,421.81 272.00,421.13 277.69,420.46 283.38,419.80 289.07,419.15 294.76,418.51 300.44,417.89 306.13,417.27 311.82,416.66 317.51,416.06 323.20,415.47 328.89,414.90 ' style='stroke-width: 0.75; stroke: #CD0BBC; stroke-dasharray: 2.00,2.00,6.00,2.00;' clip-path='url(#cpMzguOTd8MzQwLjA0fDUyNy41M3wzMDYuMTA=)' />  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4'> -    <rect x='398.97' y='319.28' width='301.08' height='208.25' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw'> +    <rect x='398.97' y='306.10' width='301.08' height='221.43' />    </clipPath>  </defs>  <defs> @@ -573,141 +573,141 @@  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='561.08' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>15</text></g>  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='612.86' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>20</text></g>  <g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text x='664.64' y='544.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='8.78px' lengthAdjust='spacingAndGlyphs'>25</text></g> -<line x1='398.97' y1='507.89' x2='398.97' y2='338.92' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='507.89' x2='394.21' y2='507.89' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='465.64' x2='394.21' y2='465.64' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='423.40' x2='394.21' y2='423.40' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='381.16' x2='394.21' y2='381.16' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<line x1='398.97' y1='338.92' x2='394.21' y2='338.92' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,511.40) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,469.16) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,425.60) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,383.36) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> -<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,341.12) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> -<polyline points='398.97,527.53 700.04,527.53 700.04,319.28 398.97,319.28 398.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='506.64' x2='398.97' y2='326.99' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='506.64' x2='394.21' y2='506.64' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='461.73' x2='394.21' y2='461.73' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='416.82' x2='394.21' y2='416.82' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='371.90' x2='394.21' y2='371.90' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<line x1='398.97' y1='326.99' x2='394.21' y2='326.99' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' /> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,510.16) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-4</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,465.24) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='7.03px' lengthAdjust='spacingAndGlyphs'>-2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,419.01) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>0</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,374.10) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>2</text></g> +<g clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)'><text transform='translate(387.56,329.18) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='4.39px' lengthAdjust='spacingAndGlyphs'>4</text></g> +<polyline points='398.97,527.53 700.04,527.53 700.04,306.10 398.97,306.10 398.97,527.53 ' style='stroke-width: 0.75;' clip-path='url(#cpMC4wMHw3MjAuMDB8NTc2LjAwfDAuMDA=)' />  <defs> -  <clipPath id='cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8Mjk5LjMy'> -    <rect x='360.00' y='299.32' width='360.00' height='276.68' /> +  <clipPath id='cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8Mjk1LjY1'> +    <rect x='360.00' y='295.65' width='360.00' height='280.35' />    </clipPath>  </defs> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8Mjk5LjMy)'><text x='532.82' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> -<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8Mjk5LjMy)'><text transform='translate(368.55,461.61) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8Mjk1LjY1)'><text x='532.82' y='563.64' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='33.38px' lengthAdjust='spacingAndGlyphs'>Predicted</text></g> +<g clip-path='url(#cpMzYwLjAwfDcyMC4wMHw1NzYuMDB8Mjk1LjY1)'><text transform='translate(368.55,455.02) rotate(-90)' style='font-size: 7.92px; font-family: Liberation Sans;' textLength='76.41px' lengthAdjust='spacingAndGlyphs'>Standardized residual</text></g>  <defs> -  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4'> -    <rect x='398.97' y='319.28' width='301.08' height='208.25' /> +  <clipPath id='cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw'> +    <rect x='398.97' y='306.10' width='301.08' height='221.43' />    </clipPath>  </defs> -<line x1='398.97' y1='423.40' x2='700.04' y2='423.40' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='459.34' cy='418.32' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='459.34' cy='421.69' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='488.44' cy='417.09' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='488.44' cy='419.34' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='510.64' cy='406.52' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='510.64' cy='404.28' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='533.57' cy='413.09' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='533.57' cy='443.36' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='543.32' cy='408.14' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='543.32' cy='421.59' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='543.53' cy='446.02' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='543.53' cy='441.54' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='529.00' cy='430.37' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='529.00' cy='432.61' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='516.89' cy='418.81' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='516.89' cy='422.18' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='505.84' cy='418.45' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<circle cx='505.84' cy='407.23' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='438.27,433.88 440.67,438.03 435.87,438.03 438.27,433.88 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='438.27,424.91 440.67,429.06 435.87,429.06 438.27,424.91 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='470.87,432.23 473.27,436.38 468.47,436.38 470.87,432.23 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='470.87,428.86 473.27,433.02 468.47,433.02 470.87,428.86 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='516.70,421.85 519.10,426.01 514.30,426.01 516.70,421.85 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='516.70,398.31 519.10,402.47 514.30,402.47 516.70,398.31 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='584.20,393.63 586.60,397.79 581.80,397.79 584.20,393.63 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='584.20,385.78 586.60,389.94 581.80,389.94 584.20,385.78 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='640.25,419.27 642.65,423.43 637.85,423.43 640.25,419.27 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='640.25,421.52 642.65,425.67 637.85,425.67 640.25,421.52 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='662.34,455.91 664.74,460.06 659.94,460.06 662.34,455.91 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='662.34,432.36 664.74,436.52 659.94,436.52 662.34,432.36 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='674.13,448.75 676.53,452.91 671.73,452.91 674.13,448.75 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='674.13,433.05 676.53,437.21 671.73,437.21 674.13,433.05 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='688.89,408.10 691.29,412.26 686.49,412.26 688.89,408.10 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='688.89,402.50 691.29,406.66 686.49,406.66 688.89,402.50 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='486.57' y1='445.54' x2='491.61' y2='445.54' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='489.09' y1='448.06' x2='489.09' y2='443.02' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='486.57' y1='424.24' x2='491.61' y2='424.24' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='489.09' y1='426.76' x2='489.09' y2='421.72' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='569.05' y1='416.79' x2='574.09' y2='416.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='571.57' y1='419.31' x2='571.57' y2='414.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='569.05' y1='417.91' x2='574.09' y2='417.91' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='571.57' y1='420.43' x2='571.57' y2='415.39' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='619.20' y1='432.01' x2='624.24' y2='432.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='621.72' y1='434.54' x2='621.72' y2='429.49' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='619.20' y1='430.89' x2='624.24' y2='430.89' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='621.72' y1='433.41' x2='621.72' y2='428.37' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='616.15' y1='418.50' x2='621.19' y2='418.50' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='618.67' y1='421.02' x2='618.67' y2='415.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='616.15' y1='409.53' x2='621.19' y2='409.53' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='618.67' y1='412.05' x2='618.67' y2='407.01' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='577.14' y1='436.07' x2='582.18' y2='436.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='579.66' y1='438.59' x2='579.66' y2='433.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='577.14' y1='418.13' x2='582.18' y2='418.13' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='579.66' y1='420.65' x2='579.66' y2='415.61' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='512.57' y1='416.27' x2='517.62' y2='416.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='515.09' y1='418.79' x2='515.09' y2='413.75' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='512.57' y1='419.63' x2='517.62' y2='419.63' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='515.09' y1='422.15' x2='515.09' y2='417.11' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='467.86' y1='427.67' x2='472.90' y2='427.67' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='470.38' y1='430.19' x2='470.38' y2='425.15' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='467.86' y1='426.55' x2='472.90' y2='426.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='470.38' y1='429.07' x2='470.38' y2='424.03' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='446.20' y1='431.29' x2='449.76' y2='427.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='446.20' y1='427.72' x2='449.76' y2='431.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='446.20' y1='427.92' x2='449.76' y2='424.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='446.20' y1='424.36' x2='449.76' y2='427.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.79' y1='414.56' x2='498.35' y2='411.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.79' y1='411.00' x2='498.35' y2='414.56' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.79' y1='420.17' x2='498.35' y2='416.60' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.79' y1='416.60' x2='498.35' y2='420.17' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='541.15' y1='443.97' x2='544.72' y2='440.41' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='541.15' y1='440.41' x2='544.72' y2='443.97' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='541.15' y1='435.00' x2='544.72' y2='431.44' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='541.15' y1='431.44' x2='544.72' y2='435.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='553.51' y1='427.23' x2='557.08' y2='423.66' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='553.51' y1='423.66' x2='557.08' y2='427.23' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='553.51' y1='404.80' x2='557.08' y2='401.24' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='553.51' y1='401.24' x2='557.08' y2='404.80' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='555.61' y1='419.35' x2='559.18' y2='415.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='555.61' y1='415.78' x2='559.18' y2='419.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='555.61' y1='413.74' x2='559.18' y2='410.18' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='555.61' y1='410.18' x2='559.18' y2='413.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='546.26' y1='428.35' x2='549.83' y2='424.78' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='546.26' y1='424.78' x2='549.83' y2='428.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='546.26' y1='448.53' x2='549.83' y2='444.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='546.26' y1='444.96' x2='549.83' y2='448.53' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='530.85' y1='409.15' x2='534.42' y2='405.59' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='530.85' y1='405.59' x2='534.42' y2='409.15' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='530.85' y1='422.61' x2='534.42' y2='419.04' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='530.85' y1='419.04' x2='534.42' y2='422.61' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='515.10' y1='421.72' x2='518.66' y2='418.16' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='515.10' y1='418.16' x2='518.66' y2='421.72' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='515.10' y1='416.12' x2='518.66' y2='412.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='515.10' y1='412.55' x2='518.66' y2='416.12' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.84' y1='433.57' x2='498.40' y2='430.00' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.84' y1='430.00' x2='498.40' y2='433.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.84' y1='432.45' x2='498.40' y2='428.88' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<line x1='494.84' y1='428.88' x2='498.40' y2='432.45' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='449.26,415.30 451.78,412.78 454.30,415.30 451.78,417.82 449.26,415.30 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='449.26,416.42 451.78,413.90 454.30,416.42 451.78,418.94 449.26,416.42 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='469.25,400.38 471.77,397.86 474.29,400.38 471.77,402.90 469.25,400.38 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='469.25,389.17 471.77,386.65 474.29,389.17 471.77,391.69 469.25,389.17 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='485.12,411.24 487.64,408.72 490.16,411.24 487.64,413.76 485.12,411.24 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='485.12,420.21 487.64,417.69 490.16,420.21 487.64,422.73 485.12,420.21 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='508.56,416.13 511.08,413.61 513.60,416.13 511.08,418.65 508.56,416.13 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='508.56,409.40 511.08,406.88 513.60,409.40 511.08,411.92 508.56,409.40 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='520.75,432.08 523.27,429.56 525.79,432.08 523.27,434.60 520.75,432.08 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='520.75,435.45 523.27,432.93 525.79,435.45 523.27,437.97 520.75,435.45 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='531.20,438.71 533.72,436.19 536.24,438.71 533.72,441.23 531.20,438.71 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='531.20,437.59 533.72,435.07 536.24,437.59 533.72,440.11 531.20,437.59 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='540.14,440.25 542.66,437.73 545.18,440.25 542.66,442.77 540.14,440.25 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> -<polyline points='540.14,415.58 542.66,413.06 545.18,415.58 542.66,418.10 540.14,415.58 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzE5LjI4)' /> +<line x1='398.97' y1='416.82' x2='700.04' y2='416.82' style='stroke-width: 0.75; stroke-dasharray: 4.00,4.00;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='459.34' cy='411.41' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='459.34' cy='414.99' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='488.44' cy='410.11' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='488.44' cy='412.49' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='510.64' cy='398.86' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='510.64' cy='396.48' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='533.57' cy='405.85' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='533.57' cy='438.03' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='543.32' cy='400.58' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='543.32' cy='414.89' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='543.53' cy='440.87' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='543.53' cy='436.10' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='529.00' cy='424.22' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='529.00' cy='426.61' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='516.89' cy='411.93' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='516.89' cy='415.51' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='505.84' cy='411.54' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<circle cx='505.84' cy='399.62' r='1.78pt' style='stroke-width: 0.75; stroke: #DF536B;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='438.27,428.13 440.67,432.28 435.87,432.28 438.27,428.13 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='438.27,418.59 440.67,422.75 435.87,422.75 438.27,418.59 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='470.87,426.37 473.27,430.53 468.47,430.53 470.87,426.37 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='470.87,422.79 473.27,426.95 468.47,426.95 470.87,422.79 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='516.70,415.34 519.10,419.50 514.30,419.50 516.70,415.34 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='516.70,390.31 519.10,394.47 514.30,394.47 516.70,390.31 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='584.20,385.33 586.60,389.49 581.80,389.49 584.20,385.33 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='584.20,376.99 586.60,381.14 581.80,381.14 584.20,376.99 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='640.25,412.60 642.65,416.76 637.85,416.76 640.25,412.60 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='640.25,414.98 642.65,419.14 637.85,419.14 640.25,414.98 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='662.34,451.55 664.74,455.71 659.94,455.71 662.34,451.55 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='662.34,426.52 664.74,430.67 659.94,430.67 662.34,426.52 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='674.13,443.94 676.53,448.10 671.73,448.10 674.13,443.94 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='674.13,427.25 676.53,431.41 671.73,431.41 674.13,427.25 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='688.89,400.72 691.29,404.88 686.49,404.88 688.89,400.72 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='688.89,394.76 691.29,398.92 686.49,398.92 688.89,394.76 ' style='stroke-width: 0.75; stroke: #61D04F;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='486.57' y1='440.36' x2='491.61' y2='440.36' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='489.09' y1='442.88' x2='489.09' y2='437.84' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='486.57' y1='417.71' x2='491.61' y2='417.71' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='489.09' y1='420.23' x2='489.09' y2='415.19' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='569.05' y1='409.79' x2='574.09' y2='409.79' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='571.57' y1='412.31' x2='571.57' y2='407.27' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='569.05' y1='410.98' x2='574.09' y2='410.98' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='571.57' y1='413.50' x2='571.57' y2='408.46' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='619.20' y1='425.97' x2='624.24' y2='425.97' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='621.72' y1='428.49' x2='621.72' y2='423.45' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='619.20' y1='424.78' x2='624.24' y2='424.78' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='621.72' y1='427.30' x2='621.72' y2='422.26' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='616.15' y1='411.60' x2='621.19' y2='411.60' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='618.67' y1='414.12' x2='618.67' y2='409.08' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='616.15' y1='402.07' x2='621.19' y2='402.07' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='618.67' y1='404.59' x2='618.67' y2='399.55' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='577.14' y1='430.28' x2='582.18' y2='430.28' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='579.66' y1='432.80' x2='579.66' y2='427.76' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='577.14' y1='411.21' x2='582.18' y2='411.21' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='579.66' y1='413.73' x2='579.66' y2='408.69' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='512.57' y1='409.23' x2='517.62' y2='409.23' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='515.09' y1='411.75' x2='515.09' y2='406.71' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='512.57' y1='412.81' x2='517.62' y2='412.81' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='515.09' y1='415.33' x2='515.09' y2='410.29' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='467.86' y1='421.36' x2='472.90' y2='421.36' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='470.38' y1='423.88' x2='470.38' y2='418.83' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='467.86' y1='420.16' x2='472.90' y2='420.16' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='470.38' y1='422.68' x2='470.38' y2='417.64' style='stroke-width: 0.75; stroke: #2297E6;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='446.20' y1='425.08' x2='449.76' y2='421.52' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='446.20' y1='421.52' x2='449.76' y2='425.08' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='446.20' y1='421.51' x2='449.76' y2='417.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='446.20' y1='417.94' x2='449.76' y2='421.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.79' y1='407.30' x2='498.35' y2='403.74' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.79' y1='403.74' x2='498.35' y2='407.30' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.79' y1='413.26' x2='498.35' y2='409.70' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.79' y1='409.70' x2='498.35' y2='413.26' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='541.15' y1='438.57' x2='544.72' y2='435.01' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='541.15' y1='435.01' x2='544.72' y2='438.57' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='541.15' y1='429.03' x2='544.72' y2='425.47' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='541.15' y1='425.47' x2='544.72' y2='429.03' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='553.51' y1='420.77' x2='557.08' y2='417.20' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='553.51' y1='417.20' x2='557.08' y2='420.77' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='553.51' y1='396.93' x2='557.08' y2='393.36' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='553.51' y1='393.36' x2='557.08' y2='396.93' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='555.61' y1='412.39' x2='559.18' y2='408.83' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='555.61' y1='408.83' x2='559.18' y2='412.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='555.61' y1='406.43' x2='559.18' y2='402.87' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='555.61' y1='402.87' x2='559.18' y2='406.43' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='546.26' y1='421.96' x2='549.83' y2='418.40' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='546.26' y1='418.40' x2='549.83' y2='421.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='546.26' y1='443.42' x2='549.83' y2='439.85' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='546.26' y1='439.85' x2='549.83' y2='443.42' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='530.85' y1='401.55' x2='534.42' y2='397.99' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='530.85' y1='397.99' x2='534.42' y2='401.55' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='530.85' y1='415.85' x2='534.42' y2='412.29' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='530.85' y1='412.29' x2='534.42' y2='415.85' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='515.10' y1='414.92' x2='518.66' y2='411.35' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='515.10' y1='411.35' x2='518.66' y2='414.92' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='515.10' y1='408.96' x2='518.66' y2='405.39' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='515.10' y1='405.39' x2='518.66' y2='408.96' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.84' y1='427.51' x2='498.40' y2='423.94' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.84' y1='423.94' x2='498.40' y2='427.51' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.84' y1='426.32' x2='498.40' y2='422.75' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<line x1='494.84' y1='422.75' x2='498.40' y2='426.32' style='stroke-width: 0.75; stroke: #28E2E5;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='449.26,408.20 451.78,405.68 454.30,408.20 451.78,410.72 449.26,408.20 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='449.26,409.39 451.78,406.87 454.30,409.39 451.78,411.91 449.26,409.39 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='469.25,392.34 471.77,389.82 474.29,392.34 471.77,394.86 469.25,392.34 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='469.25,380.42 471.77,377.90 474.29,380.42 471.77,382.94 469.25,380.42 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='485.12,403.88 487.64,401.36 490.16,403.88 487.64,406.40 485.12,403.88 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='485.12,413.41 487.64,410.89 490.16,413.41 487.64,415.93 485.12,413.41 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='508.56,409.08 511.08,406.56 513.60,409.08 511.08,411.60 508.56,409.08 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='508.56,401.93 511.08,399.41 513.60,401.93 511.08,404.45 508.56,401.93 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='520.75,426.05 523.27,423.53 525.79,426.05 523.27,428.57 520.75,426.05 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='520.75,429.62 523.27,427.10 525.79,429.62 523.27,432.14 520.75,429.62 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='531.20,433.09 533.72,430.57 536.24,433.09 533.72,435.61 531.20,433.09 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='531.20,431.89 533.72,429.37 536.24,431.89 533.72,434.41 531.20,431.89 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='540.14,434.72 542.66,432.20 545.18,434.72 542.66,437.24 540.14,434.72 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' /> +<polyline points='540.14,408.50 542.66,405.98 545.18,408.50 542.66,411.02 540.14,408.50 ' style='stroke-width: 0.75; stroke: #CD0BBC;' clip-path='url(#cpMzk4Ljk3fDcwMC4wNHw1MjcuNTN8MzA2LjEw)' />  </svg> diff --git a/tests/testthat/setup_script.R b/tests/testthat/setup_script.R index 547b2d6c..9229c198 100644 --- a/tests/testthat/setup_script.R +++ b/tests/testthat/setup_script.R @@ -178,6 +178,10 @@ ds_biphasic <- lapply(ds_biphasic_mean, function(ds) {  })  # Mixed model fits +saemix_available <- FALSE +if (requireNamespace("saemix", quietly = TRUE)) { +  if(packageVersion("saemix") >= "3.1.9000") saemix_available <- TRUE +}  mmkin_sfo_1 <- mmkin("SFO", ds_sfo, quiet = TRUE, error_model = "tc", cores = n_cores)  mmkin_dfop_1 <- mmkin("DFOP", ds_dfop, quiet = TRUE, cores = n_cores)  mmkin_biphasic <- mmkin(list("DFOP-SFO" = DFOP_SFO), ds_biphasic, quiet = TRUE, cores = n_cores) @@ -186,6 +190,16 @@ mmkin_biphasic_mixed <- mixed(mmkin_biphasic)  dfop_nlme_1 <- nlme(mmkin_dfop_1)  nlme_biphasic <- nlme(mmkin_biphasic) +if (saemix_available) { +  sfo_saem_1 <- saem(mmkin_sfo_1, quiet = TRUE, transformations = "saemix") + +  dfop_saemix_1 <- saem(mmkin_dfop_1, quiet = TRUE, transformations = "mkin") +  dfop_saemix_2 <- saem(mmkin_dfop_1, quiet = TRUE, transformations = "saemix") + +  saem_biphasic_m <- saem(mmkin_biphasic, transformations = "mkin", quiet = TRUE) +  saem_biphasic_s <- saem(mmkin_biphasic, transformations = "saemix", quiet = TRUE) +} +  ds_uba <- lapply(experimental_data_for_UBA_2019[6:10],    function(x) subset(x$data[c("name", "time", "value")]))  names(ds_uba) <- paste("Dataset", 6:10) @@ -197,3 +211,7 @@ f_uba_mmkin <- mmkin(list("SFO-SFO" = sfo_sfo_uba, "DFOP-SFO" = dfop_sfo_uba),    ds_uba, quiet = TRUE, cores = n_cores)  f_uba_dfop_sfo_mixed <- mixed(f_uba_mmkin[2, ]) +if (saemix_available) { +  f_uba_sfo_sfo_saem <- saem(f_uba_mmkin["SFO-SFO", ], quiet = TRUE, transformations = "saemix") +  f_uba_dfop_sfo_saem <- saem(f_uba_mmkin["DFOP-SFO", ], quiet = TRUE, transformations = "saemix") +} diff --git a/tests/testthat/summary_saem_biphasic_s.txt b/tests/testthat/summary_saem_biphasic_s.txt new file mode 100644 index 00000000..1e0f1ccc --- /dev/null +++ b/tests/testthat/summary_saem_biphasic_s.txt @@ -0,0 +1,77 @@ +saemix version used for fitting:      Dummy 0.0 for testing  +mkin version used for pre-fitting:  Dummy 0.0 for testing  +R version used for fitting:         Dummy R version for testing  +Date of fit:     Dummy date for testing  +Date of summary: Dummy date for testing  + +Equations: +d_parent/dt = - ((k1 * g * exp(-k1 * time) + k2 * (1 - g) * exp(-k2 * +           time)) / (g * exp(-k1 * time) + (1 - g) * exp(-k2 * time))) +           * parent +d_m1/dt = + f_parent_to_m1 * ((k1 * g * exp(-k1 * time) + k2 * (1 - g) +           * exp(-k2 * time)) / (g * exp(-k1 * time) + (1 - g) * +           exp(-k2 * time))) * parent - k_m1 * m1 + +Data: +509 observations of 2 variable(s) grouped in 15 datasets + +Model predictions using solution type analytical  + +Fitted in test time 0 s using 300, 100 iterations + +Variance model: Constant variance  + +Mean of starting values for individual parameters: +      parent_0           k_m1 f_parent_to_m1             k1             k2  +       1.0e+02        4.8e-03        4.8e-01        6.8e-02        1.3e-02  +             g  +       4.2e-01  + +Fixed degradation parameter values: +None + +Results: + +Likelihood computed by importance sampling +   AIC  BIC logLik +  2645 2654  -1310 + +Optimised parameters: +                  est.   lower   upper +parent_0       1.0e+02  99.627 1.0e+02 +k_m1           4.8e-03   0.004 5.6e-03 +f_parent_to_m1 4.8e-01   0.437 5.2e-01 +k1             6.5e-02   0.051 8.0e-02 +k2             1.2e-02   0.010 1.4e-02 +g              4.3e-01   0.362 5.0e-01 + +Correlation:  +               prnt_0 k_m1   f_p__1 k1     k2     +k_m1           -0.156                             +f_parent_to_m1 -0.157  0.372                      +k1              0.159  0.000 -0.029               +k2              0.074  0.145  0.032  0.332        +g              -0.072 -0.142 -0.044 -0.422 -0.570 + +Random effects: +                  est.  lower upper +SD.parent_0       1.14  0.251  2.03 +SD.k_m1           0.14 -0.073  0.35 +SD.f_parent_to_m1 0.29  0.176  0.41 +SD.k1             0.36  0.211  0.52 +SD.k2             0.18  0.089  0.27 +SD.g              0.32  0.098  0.53 + +Variance model: +    est. lower upper +a.1  2.7   2.5   2.9 + +Resulting formation fractions: +              ff +parent_m1   0.48 +parent_sink 0.52 + +Estimated disappearance times: +       DT50 DT90 DT50back DT50_k1 DT50_k2 +parent   25  145       44      11      58 +m1      145  481       NA      NA      NA diff --git a/tests/testthat/test_mixed.R b/tests/testthat/test_mixed.R index 6f28d0c3..0eb1f0d5 100644 --- a/tests/testthat/test_mixed.R +++ b/tests/testthat/test_mixed.R @@ -1,9 +1,98 @@  context("Nonlinear mixed-effects models") +test_that("Parent fits using saemix are correctly implemented", { +  skip_if(!saemix_available) + +  expect_error(saem(fits), "Only row objects") +  # Some fits were done in the setup script +  mmkin_sfo_2 <- update(mmkin_sfo_1, fixed_initials = c(parent = 100)) +  expect_error(update(mmkin_sfo_1, models = c("SFOOO")), "Please supply models.*") + +  sfo_saem_2 <- saem(mmkin_sfo_1, quiet = TRUE, transformations = "mkin") +  sfo_saem_3 <- expect_error(saem(mmkin_sfo_2, quiet = TRUE), "at least two parameters") +  s_sfo_s1 <- summary(sfo_saem_1) +  s_sfo_s2 <- summary(sfo_saem_2) + +  sfo_nlme_1 <- expect_warning(nlme(mmkin_sfo_1), "not converge") +  s_sfo_n <- summary(sfo_nlme_1) + +  # Compare with input +  expect_equal(round(s_sfo_s2$confint_ranef["SD.log_k_parent", "est."], 1), 0.3) +  # k_parent is a bit different from input 0.03 here +  expect_equal(round(s_sfo_s1$confint_back["k_parent", "est."], 3), 0.035) +  expect_equal(round(s_sfo_s2$confint_back["k_parent", "est."], 3), 0.035) + +  # But the result is pretty unanimous between methods +  expect_equal(round(s_sfo_s1$confint_back["k_parent", "est."], 3), +    round(s_sfo_s2$confint_back["k_parent", "est."], 3)) +  expect_equal(round(s_sfo_s1$confint_back["k_parent", "est."], 3), +    round(s_sfo_n$confint_back["k_parent", "est."], 3)) + +  mmkin_fomc_1 <- mmkin("FOMC", ds_fomc, quiet = TRUE, error_model = "tc", cores = n_cores) +  fomc_saem_1 <- saem(mmkin_fomc_1, quiet = TRUE) +  ci_fomc_s1 <- summary(fomc_saem_1)$confint_back + +  fomc_pop <- as.numeric(fomc_pop) +  expect_true(all(ci_fomc_s1[, "lower"] < fomc_pop)) +  expect_true(all(ci_fomc_s1[, "upper"] > fomc_pop)) + +  mmkin_fomc_2 <- update(mmkin_fomc_1, state.ini = 100, fixed_initials = "parent") +  fomc_saem_2 <- saem(mmkin_fomc_2, quiet = TRUE, transformations = "mkin") +  ci_fomc_s2 <- summary(fomc_saem_2)$confint_back + +  expect_true(all(ci_fomc_s2[, "lower"] < fomc_pop[2:3])) +  expect_true(all(ci_fomc_s2[, "upper"] > fomc_pop[2:3])) + +  s_dfop_s1 <- summary(dfop_saemix_1) +  s_dfop_s2 <- summary(dfop_saemix_2) +  s_dfop_n <- summary(dfop_nlme_1) + +  dfop_pop <- as.numeric(dfop_pop) +  expect_true(all(s_dfop_s1$confint_back[, "lower"] < dfop_pop)) +  expect_true(all(s_dfop_s1$confint_back[, "upper"] > dfop_pop)) +  expect_true(all(s_dfop_s2$confint_back[, "lower"] < dfop_pop)) +  expect_true(all(s_dfop_s2$confint_back[, "upper"] > dfop_pop)) + +  dfop_mmkin_means_trans <- apply(parms(mmkin_dfop_1, transformed = TRUE), 1, mean) +  dfop_mmkin_means <- backtransform_odeparms(dfop_mmkin_means_trans, mmkin_dfop_1$mkinmod) + +  # We get < 22% deviations by averaging the transformed parameters +  rel_diff_mmkin <- (dfop_mmkin_means - dfop_pop) / dfop_pop +  expect_true(all(rel_diff_mmkin < 0.22)) + +  # We get < 50% deviations with transformations made in mkin +  rel_diff_1 <- (s_dfop_s1$confint_back[, "est."] - dfop_pop) / dfop_pop +  expect_true(all(rel_diff_1 < 0.5)) + +  # We get < 12% deviations with transformations made in saemix +  rel_diff_2 <- (s_dfop_s2$confint_back[, "est."] - dfop_pop) / dfop_pop +  expect_true(all(rel_diff_2 < 0.12)) + +  mmkin_hs_1 <- mmkin("HS", ds_hs, quiet = TRUE, error_model = "const", cores = n_cores) +  hs_saem_1 <- saem(mmkin_hs_1, quiet = TRUE) +  ci_hs_s1 <- summary(hs_saem_1)$confint_back + +  hs_pop <- as.numeric(hs_pop) +  # expect_true(all(ci_hs_s1[, "lower"] < hs_pop)) # k1 is overestimated +  expect_true(all(ci_hs_s1[, "upper"] > hs_pop)) + +  mmkin_hs_2 <- update(mmkin_hs_1, state.ini = 100, fixed_initials = "parent") +  hs_saem_2 <- saem(mmkin_hs_2, quiet = TRUE) +  ci_hs_s2 <- summary(hs_saem_2)$confint_back + +  #expect_true(all(ci_hs_s2[, "lower"] < hs_pop[2:4])) # k1 again overestimated +  expect_true(all(ci_hs_s2[, "upper"] > hs_pop[2:4])) + +  # HS would likely benefit from implemenation of transformations = "saemix" +}) +  test_that("Print methods work", {    expect_known_output(print(fits[, 2:3], digits = 2), "print_mmkin_parent.txt")    expect_known_output(print(mmkin_biphasic_mixed, digits = 2), "print_mmkin_biphasic_mixed.txt")    expect_known_output(print(nlme_biphasic, digits = 1), "print_nlme_biphasic.txt") + +  skip_if(!saemix_available) +  expect_known_output(print(sfo_saem_1, digits = 1), "print_sfo_saem_1.txt")  })  test_that("nlme results are reproducible to some degree", { @@ -20,6 +109,50 @@ test_that("nlme results are reproducible to some degree", {    dfop_sfo_pop <- as.numeric(dfop_sfo_pop)    ci_dfop_sfo_n <- summary(nlme_biphasic)$confint_back -  # expect_true(all(ci_dfop_sfo_n[, "lower"] < dfop_sfo_pop)) # k2 is overestimated +  expect_true(all(ci_dfop_sfo_n[, "lower"] < dfop_sfo_pop))    expect_true(all(ci_dfop_sfo_n[, "upper"] > dfop_sfo_pop))  }) + +test_that("saem results are reproducible for biphasic fits", { + +  skip_if(!saemix_available) +  test_summary <- summary(saem_biphasic_s) +  test_summary$saemixversion <- "Dummy 0.0 for testing" +  test_summary$mkinversion <- "Dummy 0.0 for testing" +  test_summary$Rversion <- "Dummy R version for testing" +  test_summary$date.fit <- "Dummy date for testing" +  test_summary$date.summary <- "Dummy date for testing" +  test_summary$time <- c(elapsed = "test time 0") + +  expect_known_output(print(test_summary, digits = 2), "summary_saem_biphasic_s.txt") + +  dfop_sfo_pop <- as.numeric(dfop_sfo_pop) +  no_k1 <- c(1, 2, 3, 5, 6) +  no_k2 <- c(1, 2, 3, 4, 6) +  no_k1_k2 <- c(1, 2, 3, 6) + +  ci_dfop_sfo_s_s <- summary(saem_biphasic_s)$confint_back +  # k1 and k2 are overestimated +  expect_true(all(ci_dfop_sfo_s_s[no_k1_k2, "lower"] < dfop_sfo_pop[no_k1_k2])) +  expect_true(all(ci_dfop_sfo_s_s[, "upper"] > dfop_sfo_pop)) + +  # k1 and k2 are not fitted well +  ci_dfop_sfo_s_m <- summary(saem_biphasic_m)$confint_back +  expect_true(all(ci_dfop_sfo_s_m[no_k2, "lower"] < dfop_sfo_pop[no_k2])) +  expect_true(all(ci_dfop_sfo_s_m[no_k1, "upper"] > dfop_sfo_pop[no_k1])) + +  # I tried to only do few iterations in routine tests as this is so slow +  # but then deSolve fails at some point (presumably at the switch between +  # the two types of iterations) +  #saem_biphasic_2 <- saem(mmkin_biphasic, solution_type = "deSolve", +  # control = list(nbiter.saemix = c(10, 5), nbiter.burn = 5), quiet = TRUE) + +  skip("Fitting with saemix takes around 10 minutes when using deSolve") +  saem_biphasic_2 <- saem(mmkin_biphasic, solution_type = "deSolve", quiet = TRUE) + +  # As with the analytical solution, k1 and k2 are not fitted well +  ci_dfop_sfo_s_d <- summary(saem_biphasic_2)$confint_back +  expect_true(all(ci_dfop_sfo_s_d[no_k2, "lower"] < dfop_sfo_pop[no_k2])) +  expect_true(all(ci_dfop_sfo_s_d[no_k1, "upper"] > dfop_sfo_pop[no_k1])) +}) + diff --git a/tests/testthat/test_plot.R b/tests/testthat/test_plot.R index 0bf3ee66..1c95d069 100644 --- a/tests/testthat/test_plot.R +++ b/tests/testthat/test_plot.R @@ -35,6 +35,11 @@ test_that("Plotting mkinfit, mmkin and mixed model objects is reproducible", {    plot_biphasic_mmkin <- function() plot(f_uba_dfop_sfo_mixed)    vdiffr::expect_doppelganger("mixed model fit for mmkin object", plot_biphasic_mmkin) +  if (saemix_available) { +    plot_biphasic_saem_s <- function() plot(f_uba_dfop_sfo_saem) +    vdiffr::expect_doppelganger("mixed model fit for saem object with saemix transformations", plot_biphasic_saem_s) +  } +    skip_on_travis()    plot_biphasic_nlme <- function() plot(dfop_nlme_1) @@ -43,6 +48,12 @@ test_that("Plotting mkinfit, mmkin and mixed model objects is reproducible", {    #plot_biphasic_mmkin <- function() plot(mixed(mmkin_biphasic))    # Biphasic fits with lots of data and fits have lots of potential for differences    plot_biphasic_nlme <- function() plot(nlme_biphasic) +  if (saemix_available) { +    #plot_biphasic_saem_s <- function() plot(saem_biphasic_s) +    plot_biphasic_saem_m <- function() plot(saem_biphasic_m) + +    vdiffr::expect_doppelganger("mixed model fit for saem object with mkin transformations", plot_biphasic_saem_m) +  }    # different results when working with eigenvalues    plot_errmod_fit_D_obs_eigen <- function() plot_err(fit_D_obs_eigen, sep_obs = FALSE) | 
