Index: trunk/src/mci/mci.nw =================================================================== --- trunk/src/mci/mci.nw (revision 8759) +++ trunk/src/mci/mci.nw (revision 8760) @@ -1,14238 +1,14238 @@ %% -*- ess-noweb-default-code-mode: f90-mode; noweb-default-code-mode: f90-mode; noweb-code-mode: f90-mode; -*- % WHIZARD code as NOWEB source: integration and event generation %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \chapter{Multi-Channel Integration} \includemodulegraph{mci} The abstract representation of multi-channel Monte Carlo algorithms for integration and event generation. \begin{description} \item[Module [[mci_base]]:] The abstract types and their methods. It provides a test integrator that is referenced in later unit tests. \item[iterations] Container for defining integration call and pass settings. \item[integration\_results] This module handles results from integrating processes. It records passes and iterations, calculates statistical averages, and provides the user output of integration results. \end{description} These are the implementations: \begin{description} \item[Module [[mci_midpoint]]:] A simple integrator that uses the midpoint rule to sample the integrand uniformly over the unit hypercube. There is only one integration channel, so this can be matched only to single-channel phase space. \item[Module [[mci_vamp]]:] Interface for the VAMP package. \end{description} %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \clearpage \section{Generic Integrator} This module provides a multi-channel integrator (MCI) base type, a corresponding configuration type, and methods for integration and event generation. <<[[mci_base.f90]]>>= <> module mci_base use kinds use io_units use format_utils, only: pac_fmt use format_defs, only: FMT_14, FMT_17 use diagnostics use cputime use phs_base use rng_base <> <> <> <> contains <> end module mci_base @ %def mci_base @ \subsection{MCI: integrator} The MCI object contains the methods for integration and event generation. For the actual work and data storage, it spawns an MCI instance object. The base object contains the number of integration dimensions and the number of channels as configuration data. Further configuration data are stored in the concrete extensions. The MCI sum contains all relevant information about the integrand. It can be used for comparing the current configuration against a previous one. If they match, we can skip an actual integration. (Implemented only for the VAMP version.) There is a random-number generator (its state with associated methods) available as [[rng]]. It may or may not be used for integration. It will be used for event generation. <>= public :: mci_t <>= type, abstract :: mci_t integer :: n_dim = 0 integer :: n_channel = 0 integer :: n_chain = 0 integer, dimension(:), allocatable :: chain real(default), dimension(:), allocatable :: chain_weights character(32) :: md5sum = "" logical :: integral_known = .false. logical :: error_known = .false. logical :: efficiency_known = .false. real(default) :: integral = 0 real(default) :: error = 0 real(default) :: efficiency = 0 logical :: use_timer = .false. type(timer_t) :: timer class(rng_t), allocatable :: rng contains <> end type mci_t @ %def mci_t @ Finalizer: the random-number generator may need one. <>= procedure :: base_final => mci_final procedure (mci_final), deferred :: final <>= subroutine mci_final (object) class(mci_t), intent(inout) :: object if (allocated (object%rng)) call object%rng%final () end subroutine mci_final @ %def mci_final @ Output: basic and extended output. <>= procedure :: base_write => mci_write procedure (mci_write), deferred :: write <>= subroutine mci_write (object, unit, pacify, md5sum_version) class(mci_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify logical, intent(in), optional :: md5sum_version logical :: md5sum_ver integer :: u, i, j character(len=7) :: fmt call pac_fmt (fmt, FMT_17, FMT_14, pacify) u = given_output_unit (unit) md5sum_ver = .false. if (present (md5sum_version)) md5sum_ver = md5sum_version if (object%use_timer .and. .not. md5sum_ver) then write (u, "(2x)", advance="no") call object%timer%write (u) end if if (object%integral_known) then write (u, "(3x,A," // fmt // ")") & "Integral = ", object%integral end if if (object%error_known) then write (u, "(3x,A," // fmt // ")") & "Error = ", object%error end if if (object%efficiency_known) then write (u, "(3x,A," // fmt // ")") & "Efficiency = ", object%efficiency end if write (u, "(3x,A,I0)") "Number of channels = ", object%n_channel write (u, "(3x,A,I0)") "Number of dimensions = ", object%n_dim if (object%n_chain > 0) then write (u, "(3x,A,I0)") "Number of chains = ", object%n_chain write (u, "(3x,A)") "Chains:" do i = 1, object%n_chain write (u, "(5x,I0,':')", advance = "no") i do j = 1, object%n_channel if (object%chain(j) == i) & write (u, "(1x,I0)", advance = "no") j end do write (u, "(A)") end do end if end subroutine mci_write @ %def mci_write @ Print an informative message when starting integration. <>= procedure (mci_startup_message), deferred :: startup_message procedure :: base_startup_message => mci_startup_message <>= subroutine mci_startup_message (mci, unit, n_calls) class(mci_t), intent(in) :: mci integer, intent(in), optional :: unit, n_calls if (mci%n_chain > 0) then write (msg_buffer, "(A,3(1x,I0,1x,A))") & "Integrator:", mci%n_chain, "chains,", & mci%n_channel, "channels,", & mci%n_dim, "dimensions" else write (msg_buffer, "(A,3(1x,I0,1x,A))") & "Integrator:", & mci%n_channel, "channels,", & mci%n_dim, "dimensions" end if call msg_message (unit = unit) end subroutine mci_startup_message @ %def mci_startup_message @ Dump type-specific info to a logfile. <>= procedure(mci_write_log_entry), deferred :: write_log_entry <>= abstract interface subroutine mci_write_log_entry (mci, u) import class(mci_t), intent(in) :: mci integer, intent(in) :: u end subroutine mci_write_log_entry end interface @ %def mci_write_log_entry In order to avoid dependencies on definite MCI implementations, we introduce a MD5 sum calculator. <>= procedure(mci_compute_md5sum), deferred :: compute_md5sum <>= abstract interface subroutine mci_compute_md5sum (mci, pacify) import class(mci_t), intent(inout) :: mci logical, intent(in), optional :: pacify end subroutine mci_compute_md5sum end interface @ %def mci_compute_md5sum @ Record the index of the MCI object within a process. For multi-component processes with more than one integrator, the integrator should know about its own index, so file names can be unique, etc. The default implementation does nothing, however. <>= procedure :: record_index => mci_record_index <>= subroutine mci_record_index (mci, i_mci) class(mci_t), intent(inout) :: mci integer, intent(in) :: i_mci end subroutine mci_record_index @ %def mci_record_index @ There is no Initializer for the abstract type, but a generic setter for the number of channels and dimensions. We make two aliases available, to be able to override it. <>= procedure :: set_dimensions => mci_set_dimensions procedure :: base_set_dimensions => mci_set_dimensions <>= subroutine mci_set_dimensions (mci, n_dim, n_channel) class(mci_t), intent(inout) :: mci integer, intent(in) :: n_dim integer, intent(in) :: n_channel mci%n_dim = n_dim mci%n_channel = n_channel end subroutine mci_set_dimensions @ %def mci_set_dimensions @ Declare particular dimensions as flat. This information can be used to simplify integration. When generating events, the flat dimensions should be sampled with uniform and uncorrelated distribution. It depends on the integrator what to do with that information. <>= procedure (mci_declare_flat_dimensions), deferred :: declare_flat_dimensions <>= abstract interface subroutine mci_declare_flat_dimensions (mci, dim_flat) import class(mci_t), intent(inout) :: mci integer, dimension(:), intent(in) :: dim_flat end subroutine mci_declare_flat_dimensions end interface @ %def mci_declare_flat_dimensions @ Declare particular channels as equivalent, possibly allowing for permutations or reflections of dimensions. We use the information stored in the [[phs_channel_t]] object array that the phase-space module provides. (We do not test this here, deferring the unit test to the [[mci_vamp]] implementation where we actually use this feature.) <>= procedure (mci_declare_equivalences), deferred :: declare_equivalences <>= abstract interface subroutine mci_declare_equivalences (mci, channel, dim_offset) import class(mci_t), intent(inout) :: mci type(phs_channel_t), dimension(:), intent(in) :: channel integer, intent(in) :: dim_offset end subroutine mci_declare_equivalences end interface @ %def mci_declare_equivalences @ Declare particular channels as chained together. The implementation may use this array for keeping their weights equal to each other, etc. The chain array is an array sized by the number of channels. For each channel, there is an integer entry that indicates the correponding chains. The total number of chains is the maximum value of this entry. <>= procedure :: declare_chains => mci_declare_chains <>= subroutine mci_declare_chains (mci, chain) class(mci_t), intent(inout) :: mci integer, dimension(:), intent(in) :: chain allocate (mci%chain (size (chain))) mci%n_chain = maxval (chain) allocate (mci%chain_weights (mci%n_chain), source = 0._default) mci%chain = chain end subroutine mci_declare_chains @ %def mci_declare_chains @ Collect channel weights according to chains and store them in the [[chain_weights]] for output. We sum up the weights for all channels that share the same [[chain]] index and store the results in the [[chain_weights]] array. <>= procedure :: collect_chain_weights => mci_collect_chain_weights <>= subroutine mci_collect_chain_weights (mci, weight) class(mci_t), intent(inout) :: mci real(default), dimension(:), intent(in) :: weight integer :: i, c if (allocated (mci%chain)) then mci%chain_weights = 0 do i = 1, size (mci%chain) c = mci%chain(i) mci%chain_weights(c) = mci%chain_weights(c) + weight(i) end do end if end subroutine mci_collect_chain_weights @ %def mci_collect_chain_weights @ Check if there are chains. <>= procedure :: has_chains => mci_has_chains <>= function mci_has_chains (mci) result (flag) class(mci_t), intent(in) :: mci logical :: flag flag = allocated (mci%chain) end function mci_has_chains @ %def mci_has_chains @ Output of the chain weights, kept separate from the main [[write]] method. [The formatting will work as long as the number of chains is less than $10^{10}$\ldots] <>= procedure :: write_chain_weights => mci_write_chain_weights <>= subroutine mci_write_chain_weights (mci, unit) class(mci_t), intent(in) :: mci integer, intent(in), optional :: unit integer :: u, i, n, n_digits character(4) :: ifmt u = given_output_unit (unit) if (allocated (mci%chain_weights)) then write (u, "(1x,A)") "Weights of channel chains (groves):" n_digits = 0 n = size (mci%chain_weights) do while (n > 0) n = n / 10 n_digits = n_digits + 1 end do write (ifmt, "(A1,I1)") "I", n_digits do i = 1, size (mci%chain_weights) write (u, "(3x," // ifmt // ",F13.10)") i, mci%chain_weights(i) end do end if end subroutine mci_write_chain_weights @ %def mci_write_chain_weights @ Set the MD5 sum, independent of initialization. <>= procedure :: set_md5sum => mci_set_md5sum <>= subroutine mci_set_md5sum (mci, md5sum) class(mci_t), intent(inout) :: mci character(32), intent(in) :: md5sum mci%md5sum = md5sum end subroutine mci_set_md5sum @ %def mci_set_md5sum @ Initialize a new integration pass. This is not necessarily meaningful, so we provide an empty base method. The [[mci_vamp]] implementation overrides this. <>= procedure :: add_pass => mci_add_pass <>= subroutine mci_add_pass (mci, adapt_grids, adapt_weights, final_pass) class(mci_t), intent(inout) :: mci logical, intent(in), optional :: adapt_grids logical, intent(in), optional :: adapt_weights logical, intent(in), optional :: final_pass end subroutine mci_add_pass @ %def mci_add_pass @ Allocate an instance with matching type. This must be deferred. <>= procedure (mci_allocate_instance), deferred :: allocate_instance <>= abstract interface subroutine mci_allocate_instance (mci, mci_instance) import class(mci_t), intent(in) :: mci class(mci_instance_t), intent(out), pointer :: mci_instance end subroutine mci_allocate_instance end interface @ %def mci_allocate_instance @ Import a random-number generator. We transfer the allocation of an existing generator state into the object. The generator state may already be initialized, or we can reset it by its [[init]] method. <>= procedure :: import_rng => mci_import_rng <>= subroutine mci_import_rng (mci, rng) class(mci_t), intent(inout) :: mci class(rng_t), intent(inout), allocatable :: rng call move_alloc (rng, mci%rng) end subroutine mci_import_rng @ %def mci_import_rng @ Activate or deactivate the timer. <>= procedure :: set_timer => mci_set_timer <>= subroutine mci_set_timer (mci, active) class(mci_t), intent(inout) :: mci logical, intent(in) :: active mci%use_timer = active end subroutine mci_set_timer @ %def mci_set_timer @ Start and stop signal for the timer, if active. The elapsed time can then be retrieved from the MCI record. <>= procedure :: start_timer => mci_start_timer procedure :: stop_timer => mci_stop_timer <>= subroutine mci_start_timer (mci) class(mci_t), intent(inout) :: mci if (mci%use_timer) call mci%timer%start () end subroutine mci_start_timer subroutine mci_stop_timer (mci) class(mci_t), intent(inout) :: mci if (mci%use_timer) call mci%timer%stop () end subroutine mci_stop_timer @ %def mci_start_timer @ %def mci_stop_timer @ Sampler test. Evaluate the sampler a given number of times. Results are discarded, so we don't need the MCI instance which would record them. The evaluation channel is iterated, and the [[x]] parameters are randomly chosen. <>= procedure :: sampler_test => mci_sampler_test <>= subroutine mci_sampler_test (mci, sampler, n_calls) class(mci_t), intent(inout) :: mci class(mci_sampler_t), intent(inout), target :: sampler integer, intent(in) :: n_calls real(default), dimension(:), allocatable :: x_in, f real(default), dimension(:,:), allocatable :: x_out real(default) :: val integer :: i, c allocate (x_in (mci%n_dim)) allocate (f (mci%n_channel)) allocate (x_out (mci%n_dim, mci%n_channel)) do i = 1, n_calls c = mod (i, mci%n_channel) + 1 call mci%rng%generate_array (x_in) call sampler%evaluate (c, x_in, val, x_out, f) end do end subroutine mci_sampler_test @ %def mci_sampler_test @ Integrate: this depends on the implementation. We foresee a pacify flag to take care of small numerical noise on different platforms. <>= procedure (mci_integrate), deferred :: integrate <>= abstract interface subroutine mci_integrate (mci, instance, sampler, & n_it, n_calls, results, pacify) import class(mci_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: pacify class(mci_results_t), intent(inout), optional :: results end subroutine mci_integrate end interface @ %def mci_integrate @ Event generation. Depending on the implementation, event generation may or may not require a previous integration pass. Instead of a black-box [[simulate]] method, we require an initializer, a finalizer, and procedures for generating a single event. This allows us to interface simulation event by event from the outside, and it facilitates the further processing of an event after successful generation. For integration, this is not necessary. The initializer has [[intent(inout)]] for the [[mci]] passed object. The reason is that the initializer can read integration results and grids from file, where the results can modify the [[mci]] record. <>= procedure (mci_prepare_simulation), deferred :: prepare_simulation @ %def mci_final_simulation <>= abstract interface subroutine mci_prepare_simulation (mci) import class(mci_t), intent(inout) :: mci end subroutine mci_prepare_simulation end interface @ %def mci_prepare_simulation @ The generated event will reside in in the [[instance]] object (overall results and weight) and in the [[sampler]] object (detailed data). In the real application, we can subsequently call methods of the [[sampler]] in order to further process the generated event. The [[target]] attributes are required by the VAMP implementation, which uses pointers to refer to the instance and sampler objects from within the integration function. <>= procedure (mci_generate), deferred :: generate_weighted_event procedure (mci_generate), deferred :: generate_unweighted_event @ %def mci_generate_weighted_event @ %def mci_generate_unweighted_event <>= abstract interface subroutine mci_generate (mci, instance, sampler) import class(mci_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler end subroutine mci_generate end interface @ %def mci_generate @ This is analogous, but we rebuild the event from the information stored in [[state]] instead of generating it. Note: currently unused outside of tests, might be deleted later. <>= procedure (mci_rebuild), deferred :: rebuild_event <>= abstract interface subroutine mci_rebuild (mci, instance, sampler, state) import class(mci_t), intent(inout) :: mci class(mci_instance_t), intent(inout) :: instance class(mci_sampler_t), intent(inout) :: sampler class(mci_state_t), intent(in) :: state end subroutine mci_rebuild end interface @ %def mci_rebuild @ Pacify: reduce numerical noise. The base implementation does nothing. <>= procedure :: pacify => mci_pacify <>= subroutine mci_pacify (object, efficiency_reset, error_reset) class(mci_t), intent(inout) :: object logical, intent(in), optional :: efficiency_reset, error_reset end subroutine mci_pacify @ %def mci_pacify @ Return the value of the integral, error, efficiency, and time per call. <>= procedure :: get_integral => mci_get_integral procedure :: get_error => mci_get_error procedure :: get_efficiency => mci_get_efficiency procedure :: get_time => mci_get_time <>= function mci_get_integral (mci) result (integral) class(mci_t), intent(in) :: mci real(default) :: integral if (mci%integral_known) then integral = mci%integral else call msg_bug ("The integral is unknown. This is presumably a" // & "WHIZARD bug.") end if end function mci_get_integral function mci_get_error (mci) result (error) class(mci_t), intent(in) :: mci real(default) :: error if (mci%error_known) then error = mci%error else error = 0 end if end function mci_get_error function mci_get_efficiency (mci) result (efficiency) class(mci_t), intent(in) :: mci real(default) :: efficiency if (mci%efficiency_known) then efficiency = mci%efficiency else efficiency = 0 end if end function mci_get_efficiency function mci_get_time (mci) result (time) class(mci_t), intent(in) :: mci real(default) :: time if (mci%use_timer) then time = mci%timer else time = 0 end if end function mci_get_time @ %def mci_get_integral @ %def mci_get_error @ %def mci_get_efficiency @ %def mci_get_time @ Return the MD5 sum of the configuration. This may be overridden in an extension, to return a different MD5 sum. <>= procedure :: get_md5sum => mci_get_md5sum <>= pure function mci_get_md5sum (mci) result (md5sum) class(mci_t), intent(in) :: mci character(32) :: md5sum md5sum = mci%md5sum end function mci_get_md5sum @ %def mci_get_md5sum @ \subsection{MCI instance} The base type contains an array of channel weights. The value [[mci_weight]] is the combined MCI weight that corresponds to a particular sampling point. For convenience, we also store the [[x]] and Jacobian values for this sampling point. <>= public :: mci_instance_t <>= type, abstract :: mci_instance_t logical :: valid = .false. real(default), dimension(:), allocatable :: w real(default), dimension(:), allocatable :: f real(default), dimension(:,:), allocatable :: x integer :: selected_channel = 0 real(default) :: mci_weight = 0 real(default) :: integrand = 0 logical :: negative_weights = .false. integer :: n_dropped = 0 contains <> end type mci_instance_t @ %def mci_instance_t @ Output: deferred <>= procedure (mci_instance_write), deferred :: write <>= abstract interface subroutine mci_instance_write (object, unit, pacify) import class(mci_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify end subroutine mci_instance_write end interface @ %def mci_instance_write @ A finalizer, just in case. <>= procedure (mci_instance_final), deferred :: final <>= abstract interface subroutine mci_instance_final (object) import class(mci_instance_t), intent(inout) :: object end subroutine mci_instance_final end interface @ %def mci_instance_final @ Init: basic initializer for the arrays, otherwise deferred. Assigning the [[mci]] object is also deferred, because it depends on the concrete type. The weights are initialized with an uniform normalized value. <>= procedure (mci_instance_base_init), deferred :: init procedure :: base_init => mci_instance_base_init <>= subroutine mci_instance_base_init (mci_instance, mci) class(mci_instance_t), intent(out) :: mci_instance class(mci_t), intent(in), target :: mci allocate (mci_instance%w (mci%n_channel)) allocate (mci_instance%f (mci%n_channel)) allocate (mci_instance%x (mci%n_dim, mci%n_channel)) if (mci%n_channel > 0) then call mci_instance%set_channel_weights & (spread (1._default, dim=1, ncopies=mci%n_channel)) end if mci_instance%f = 0 mci_instance%x = 0 end subroutine mci_instance_base_init @ %def mci_instance_base_init @ Explicitly set the array of channel weights. <>= procedure :: set_channel_weights => mci_instance_set_channel_weights <>= subroutine mci_instance_set_channel_weights (mci_instance, weights, sum_non_zero) class(mci_instance_t), intent(inout) :: mci_instance real(default), dimension(:), intent(in) :: weights logical, intent(out), optional :: sum_non_zero real(default) :: wsum wsum = sum (weights) if (wsum /= 0) then mci_instance%w = weights / wsum if (present (sum_non_zero)) sum_non_zero = .true. else if (present (sum_non_zero)) sum_non_zero = .false. call msg_warning ("MC sampler initialization:& & sum of channel weights is zero") end if end subroutine mci_instance_set_channel_weights @ %def mci_instance_set_channel_weights @ Compute the overall weight factor for a configuration of $x$ values and Jacobians $f$. The $x$ values come in [[n_channel]] rows with [[n_dim]] entries each. The $f$ factors constitute an array with [[n_channel]] entries. We assume that the $x$ and $f$ arrays are already stored inside the MC instance. The result is also stored there. <>= procedure (mci_instance_compute_weight), deferred :: compute_weight <>= abstract interface subroutine mci_instance_compute_weight (mci, c) import class(mci_instance_t), intent(inout) :: mci integer, intent(in) :: c end subroutine mci_instance_compute_weight end interface @ %def mci_instance_compute_weight @ Record the integrand as returned by the sampler. Depending on the implementation, this may merely copy the value, or do more complicated things. We may need the MCI weight for the actual computations, so this should be called after the previous routine. <>= procedure (mci_instance_record_integrand), deferred :: record_integrand <>= abstract interface subroutine mci_instance_record_integrand (mci, integrand) import class(mci_instance_t), intent(inout) :: mci real(default), intent(in) :: integrand end subroutine mci_instance_record_integrand end interface @ %def mci_instance_record_integrand @ Sample a point directly: evaluate the sampler, then compute the weight and the weighted integrand. Finally, record the integrand within the MCI instance. If a signal (interrupt) was raised recently, we abort the calculation before entering the sampler. Thus, a previous calculation will have completed and any data are already recorded, but any new point can be discarded. If the [[abort]] flag is present, we may delay the interrupt, so we can do some cleanup. <>= procedure :: evaluate => mci_instance_evaluate <>= subroutine mci_instance_evaluate (mci, sampler, c, x) class(mci_instance_t), intent(inout) :: mci class(mci_sampler_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x real(default) :: val call sampler%evaluate (c, x, val, mci%x, mci%f) mci%valid = sampler%is_valid () if (mci%valid) then call mci%compute_weight (c) call mci%record_integrand (val) end if end subroutine mci_instance_evaluate @ %def mci_instance_evaluate @ Initiate and terminate simulation. In contrast to integration, we implement these as methods of the process instance, since the [[mci]] configuration object is unchanged. The safety factor reduces the acceptance probability for unweighted events. The implementation of this feature depends on the concrete type. <>= procedure (mci_instance_init_simulation), deferred :: init_simulation procedure (mci_instance_final_simulation), deferred :: final_simulation <>= abstract interface subroutine mci_instance_init_simulation (instance, safety_factor) import class(mci_instance_t), intent(inout) :: instance real(default), intent(in), optional :: safety_factor end subroutine mci_instance_init_simulation end interface abstract interface subroutine mci_instance_final_simulation (instance) import class(mci_instance_t), intent(inout) :: instance end subroutine mci_instance_final_simulation end interface @ %def mci_instance_init_simulation mci_instance_final_simulation @ Assuming that the sampler is in a completely defined state, just extract the data that [[evaluate]] would compute. Also record the integrand. <>= procedure :: fetch => mci_instance_fetch <>= subroutine mci_instance_fetch (mci, sampler, c) class(mci_instance_t), intent(inout) :: mci class(mci_sampler_t), intent(in) :: sampler integer, intent(in) :: c real(default) :: val mci%valid = sampler%is_valid () if (mci%valid) then call sampler%fetch (val, mci%x, mci%f) call mci%compute_weight (c) call mci%record_integrand (val) end if end subroutine mci_instance_fetch @ %def mci_instance_fetch @ The value, i.e., the weighted integrand, is the integrand (which should be taken as-is from the sampler) multiplied by the MCI weight. <>= procedure :: get_value => mci_instance_get_value <>= function mci_instance_get_value (mci) result (value) class(mci_instance_t), intent(in) :: mci real(default) :: value if (mci%valid) then value = mci%integrand * mci%mci_weight else value = 0 end if end function mci_instance_get_value @ %def mci_instance_get_value @ This is an extra routine. By default, the event weight is equal to the value returned by the previous routine. However, if we select a channel for event generation not just based on the channel weights, the event weight has to account for this bias, so the event weight that applies to event generation is different. In that case, we should override the default routine. <>= procedure :: get_event_weight => mci_instance_get_value @ %def mci_instance_get_event_weight @ Excess weight can occur during unweighted event generation, if the assumed maximum value of the integrand is too small. This excess should be normalized in the same way as the event weight above (which for unweighted events becomes unity). <>= procedure (mci_instance_get_event_excess), deferred :: get_event_excess <>= abstract interface function mci_instance_get_event_excess (mci) result (excess) import class(mci_instance_t), intent(in) :: mci real(default) :: excess end function mci_instance_get_event_excess end interface @ %def mci_instance_get_event_excess @ Dropped events (i.e., events with zero weight that are not retained) are counted within the [[mci_instance]] object. <>= procedure :: get_n_event_dropped => mci_instance_get_n_event_dropped procedure :: reset_n_event_dropped => mci_instance_reset_n_event_dropped procedure :: record_event_dropped => mci_instance_record_event_dropped <>= function mci_instance_get_n_event_dropped (mci) result (n_dropped) class(mci_instance_t), intent(in) :: mci integer :: n_dropped n_dropped = mci%n_dropped end function mci_instance_get_n_event_dropped subroutine mci_instance_reset_n_event_dropped (mci) class(mci_instance_t), intent(inout) :: mci mci%n_dropped = 0 end subroutine mci_instance_reset_n_event_dropped subroutine mci_instance_record_event_dropped (mci) class(mci_instance_t), intent(inout) :: mci mci%n_dropped = mci%n_dropped + 1 end subroutine mci_instance_record_event_dropped @ %def mci_instance_get_n_event_dropped @ %def mci_instance_reset_n_event_dropped @ %def mci_instance_record_event_dropped @ \subsection{MCI state} This object can hold the relevant information that allows us to reconstruct the MCI instance without re-evaluating the sampler completely. We store the [[x_in]] MC input parameter set, which coincides with the section of the complete [[x]] array that belongs to a particular channel. We also store the MC function value. When we want to reconstruct the state, we can use the input array to recover the complete [[x]] and [[f]] arrays (i.e., the kinematics), but do not need to recompute the MC function value (the dynamics). The [[mci_state_t]] may be extended, to allow storing/recalling more information. In that case, we would override the type-bound procedures. However, the base type is also a concrete type and self-contained. <>= public :: mci_state_t <>= type :: mci_state_t integer :: selected_channel = 0 real(default), dimension(:), allocatable :: x_in real(default) :: val contains <> end type mci_state_t @ %def mci_state_t @ Output: <>= procedure :: write => mci_state_write <>= subroutine mci_state_write (object, unit) class(mci_state_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "MCI state:" write (u, "(3x,A,I0)") "Channel = ", object%selected_channel write (u, "(3x,A,999(1x,F12.10))") "x (in) =", object%x_in write (u, "(3x,A,ES19.12)") "Integrand = ", object%val end subroutine mci_state_write @ %def mci_state_write @ To store the object, we take the relevant section of the [[x]] array. The channel used for storing data is taken from the [[instance]] object, but it could be arbitrary in principle. <>= procedure :: store => mci_instance_store <>= subroutine mci_instance_store (mci, state) class(mci_instance_t), intent(in) :: mci class(mci_state_t), intent(out) :: state state%selected_channel = mci%selected_channel allocate (state%x_in (size (mci%x, 1))) state%x_in = mci%x(:,mci%selected_channel) state%val = mci%integrand end subroutine mci_instance_store @ %def mci_instance_store @ Recalling the state, we must consult the sampler in order to fully reconstruct the [[x]] and [[f]] arrays. The integrand value is known, and we also give it to the sampler, bypassing evaluation. The final steps are equivalent to the [[evaluate]] method above. <>= procedure :: recall => mci_instance_recall <>= subroutine mci_instance_recall (mci, sampler, state) class(mci_instance_t), intent(inout) :: mci class(mci_sampler_t), intent(inout) :: sampler class(mci_state_t), intent(in) :: state if (size (state%x_in) == size (mci%x, 1) & .and. state%selected_channel <= size (mci%x, 2)) then call sampler%rebuild (state%selected_channel, & state%x_in, state%val, mci%x, mci%f) call mci%compute_weight (state%selected_channel) call mci%record_integrand (state%val) else call msg_fatal ("Recalling event: mismatch in channel or dimension") end if end subroutine mci_instance_recall @ %def mci_instance_recall @ \subsection{MCI sampler} A sampler is an object that implements a multi-channel parameterization of the unit hypercube. Specifically, it is able to compute, given a channel and a set of $x$ MC parameter values, the complete set of $x$ values and associated Jacobian factors $f$ for all channels. Furthermore, the sampler should return a single real value, the integrand, for the given point in the hypercube. It must implement a method [[evaluate]] for performing the above computations. <>= public :: mci_sampler_t <>= type, abstract :: mci_sampler_t contains <> end type mci_sampler_t @ %def mci_sampler_t @ Output, deferred to the implementation. <>= procedure (mci_sampler_write), deferred :: write <>= abstract interface subroutine mci_sampler_write (object, unit, testflag) import class(mci_sampler_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag end subroutine mci_sampler_write end interface @ %def mci_sampler_write @ The evaluation routine. Input is the channel index [[c]] and the one-dimensional parameter array [[x_in]]. Output are the integrand value [[val]], the two-dimensional parameter array [[x]] and the Jacobian array [[f]]. <>= procedure (mci_sampler_evaluate), deferred :: evaluate <>= abstract interface subroutine mci_sampler_evaluate (sampler, c, x_in, val, x, f) import class(mci_sampler_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f end subroutine mci_sampler_evaluate end interface @ %def mci_sampler_evaluate @ Query the validity of the sampling point. Can be called after [[evaluate]]. <>= procedure (mci_sampler_is_valid), deferred :: is_valid <>= abstract interface function mci_sampler_is_valid (sampler) result (valid) import class(mci_sampler_t), intent(in) :: sampler logical :: valid end function mci_sampler_is_valid end interface @ %def mci_sampler_is_valid @ The shortcut. Again, the channel index [[c]] and the parameter array [[x_in]] are input. However, we also provide the integrand value [[val]], and we just require that the complete parameter array [[x]] and Jacobian array [[f]] are recovered. <>= procedure (mci_sampler_rebuild), deferred :: rebuild <>= abstract interface subroutine mci_sampler_rebuild (sampler, c, x_in, val, x, f) import class(mci_sampler_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f end subroutine mci_sampler_rebuild end interface @ %def mci_sampler_rebuild @ This routine should extract the important data from a sampler that has been filled by other means. We fetch the integrand value [[val]], the two-dimensional parameter array [[x]] and the Jacobian array [[f]]. <>= procedure (mci_sampler_fetch), deferred :: fetch <>= abstract interface subroutine mci_sampler_fetch (sampler, val, x, f) import class(mci_sampler_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f end subroutine mci_sampler_fetch end interface @ %def mci_sampler_fetch @ \subsection{Results record} This is an abstract type which allows us to implement callback: each integration results can optionally be recorded to an instance of this object. The actual object may store a new result, average results, etc. It may also display a result on-line or otherwise, whenever the [[record]] method is called. <>= public :: mci_results_t <>= type, abstract :: mci_results_t contains <> end type mci_results_t @ %def mci_results_t @ The output routine is deferred. We provide an extra [[verbose]] flag, which could serve any purpose. <>= procedure (mci_results_write), deferred :: write procedure (mci_results_write_verbose), deferred :: write_verbose <>= abstract interface subroutine mci_results_write (object, unit, suppress) import class(mci_results_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: suppress end subroutine mci_results_write subroutine mci_results_write_verbose (object, unit) import class(mci_results_t), intent(in) :: object integer, intent(in), optional :: unit end subroutine mci_results_write_verbose end interface @ %def mci_results_write @ This is the generic [[record]] method, which can be called directly from the integrator. The [[record_extended]] procedure store additionally the valid calls, positive and negative efficiency. <>= generic :: record => record_simple, record_extended procedure (mci_results_record_simple), deferred :: record_simple procedure (mci_results_record_extended), deferred :: record_extended <>= abstract interface subroutine mci_results_record_simple (object, n_it, & n_calls, integral, error, efficiency, chain_weights, suppress) import class(mci_results_t), intent(inout) :: object integer, intent(in) :: n_it integer, intent(in) :: n_calls real(default), intent(in) :: integral real(default), intent(in) :: error real(default), intent(in) :: efficiency real(default), dimension(:), intent(in), optional :: chain_weights logical, intent(in), optional :: suppress end subroutine mci_results_record_simple subroutine mci_results_record_extended (object, n_it, n_calls,& & n_calls_valid, integral, error, efficiency, efficiency_pos,& & efficiency_neg, chain_weights, suppress) import class(mci_results_t), intent(inout) :: object integer, intent(in) :: n_it integer, intent(in) :: n_calls integer, intent(in) :: n_calls_valid real(default), intent(in) :: integral real(default), intent(in) :: error real(default), intent(in) :: efficiency real(default), intent(in) :: efficiency_pos real(default), intent(in) :: efficiency_neg real(default), dimension(:), intent(in), optional :: chain_weights logical, intent(in), optional :: suppress end subroutine mci_results_record_extended end interface @ %def mci_results_record @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[mci_base_ut.f90]]>>= <> module mci_base_ut use unit_tests use mci_base_uti <> <> <> contains <> end module mci_base_ut @ %def mci_base_ut @ <<[[mci_base_uti.f90]]>>= <> module mci_base_uti <> use io_units use diagnostics use phs_base use rng_base use mci_base use rng_base_ut, only: rng_test_t <> <> <> <> contains <> end module mci_base_uti @ %def mci_base_ut @ API: driver for the unit tests below. <>= public :: mci_base_test <>= subroutine mci_base_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine mci_base_test @ %def mci_base_test @ \subsubsection{Test implementation of the configuration type} The concrete type contains the number of requested calls and the integral result, to be determined. The [[max_factor]] entry is set for the actual test integration, where the integrand is not unity but some other constant value. This value should be set here, such that the actual maximum of the integrand is known when vetoing unweighted events. <>= public :: mci_test_t <>= type, extends (mci_t) :: mci_test_t integer :: divisions = 0 integer :: tries = 0 real(default) :: max_factor = 1 contains procedure :: final => mci_test_final procedure :: write => mci_test_write procedure :: startup_message => mci_test_startup_message procedure :: write_log_entry => mci_test_write_log_entry procedure :: compute_md5sum => mci_test_compute_md5sum procedure :: declare_flat_dimensions => mci_test_ignore_flat_dimensions procedure :: declare_equivalences => mci_test_ignore_equivalences procedure :: set_divisions => mci_test_set_divisions procedure :: set_max_factor => mci_test_set_max_factor procedure :: allocate_instance => mci_test_allocate_instance procedure :: integrate => mci_test_integrate procedure :: prepare_simulation => mci_test_ignore_prepare_simulation procedure :: generate_weighted_event => mci_test_generate_weighted_event procedure :: generate_unweighted_event => & mci_test_generate_unweighted_event procedure :: rebuild_event => mci_test_rebuild_event end type mci_test_t @ %def mci_test_t @ Finalizer: base version is sufficient <>= subroutine mci_test_final (object) class(mci_test_t), intent(inout) :: object call object%base_final () end subroutine mci_test_final @ %def mci_test_final @ Output: trivial <>= subroutine mci_test_write (object, unit, pacify, md5sum_version) class(mci_test_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify logical, intent(in), optional :: md5sum_version integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Test integrator:" call object%base_write (u, pacify, md5sum_version) if (object%divisions /= 0) then write (u, "(3x,A,I0)") "Number of divisions = ", object%divisions end if if (allocated (object%rng)) call object%rng%write (u) end subroutine mci_test_write @ %def mci_test_write @ Short version. <>= subroutine mci_test_startup_message (mci, unit, n_calls) class(mci_test_t), intent(in) :: mci integer, intent(in), optional :: unit, n_calls call mci%base_startup_message (unit = unit, n_calls = n_calls) write (msg_buffer, "(A,1x,I0,1x,A)") & "Integrator: Test:", mci%divisions, "divisions" call msg_message (unit = unit) end subroutine mci_test_startup_message @ %def mci_test_startup_message @ Log entry: nothing. <>= subroutine mci_test_write_log_entry (mci, u) class(mci_test_t), intent(in) :: mci integer, intent(in) :: u end subroutine mci_test_write_log_entry @ %def mci_test_write_log_entry @ Compute MD5 sum: nothing. <>= subroutine mci_test_compute_md5sum (mci, pacify) class(mci_test_t), intent(inout) :: mci logical, intent(in), optional :: pacify end subroutine mci_test_compute_md5sum @ %def mci_test_compute_md5sum @ This is a no-op for the test integrator. <>= subroutine mci_test_ignore_flat_dimensions (mci, dim_flat) class(mci_test_t), intent(inout) :: mci integer, dimension(:), intent(in) :: dim_flat end subroutine mci_test_ignore_flat_dimensions @ %def mci_test_ignore_flat_dimensions @ Ditto. <>= subroutine mci_test_ignore_equivalences (mci, channel, dim_offset) class(mci_test_t), intent(inout) :: mci type(phs_channel_t), dimension(:), intent(in) :: channel integer, intent(in) :: dim_offset end subroutine mci_test_ignore_equivalences @ %def mci_test_ignore_equivalences @ Set the number of divisions to a nonzero value. <>= subroutine mci_test_set_divisions (object, divisions) class(mci_test_t), intent(inout) :: object integer, intent(in) :: divisions object%divisions = divisions end subroutine mci_test_set_divisions @ %def mci_test_set_divisions @ Set the maximum factor (default is 1). <>= subroutine mci_test_set_max_factor (object, max_factor) class(mci_test_t), intent(inout) :: object real(default), intent(in) :: max_factor object%max_factor = max_factor end subroutine mci_test_set_max_factor @ %def mci_test_set_max_factor @ Allocate instance with matching type. <>= subroutine mci_test_allocate_instance (mci, mci_instance) class(mci_test_t), intent(in) :: mci class(mci_instance_t), intent(out), pointer :: mci_instance allocate (mci_test_instance_t :: mci_instance) end subroutine mci_test_allocate_instance @ %def mci_test_allocate_instance @ Integrate: sample at the midpoints of uniform bits and add the results. We implement this for one and for two dimensions. In the latter case, we scan over two channels and multiply with the channel weights. The arguments [[n_it]] and [[n_calls]] are ignored in this implementations. The test integrator does not set error or efficiency, so those will remain undefined. <>= subroutine mci_test_integrate (mci, instance, sampler, & n_it, n_calls, results, pacify) class(mci_test_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: pacify class(mci_results_t), intent(inout), optional :: results real(default), dimension(:), allocatable :: integral real(default), dimension(:), allocatable :: x integer :: i, j, c select type (instance) type is (mci_test_instance_t) allocate (integral (mci%n_channel)) integral = 0 allocate (x (mci%n_dim)) select case (mci%n_dim) case (1) do c = 1, mci%n_channel do i = 1, mci%divisions x(1) = (i - 0.5_default) / mci%divisions call instance%evaluate (sampler, c, x) integral(c) = integral(c) + instance%get_value () end do end do mci%integral = dot_product (instance%w, integral) & / mci%divisions mci%integral_known = .true. case (2) do c = 1, mci%n_channel do i = 1, mci%divisions x(1) = (i - 0.5_default) / mci%divisions do j = 1, mci%divisions x(2) = (j - 0.5_default) / mci%divisions call instance%evaluate (sampler, c, x) integral(c) = integral(c) + instance%get_value () end do end do end do mci%integral = dot_product (instance%w, integral) & / mci%divisions / mci%divisions mci%integral_known = .true. end select if (present (results)) then call results%record (n_it, n_calls, & mci%integral, mci%error, & efficiency = 0._default) end if end select end subroutine mci_test_integrate @ %def mci_test_integrate @ Simulation initializer and finalizer: nothing to do here. <>= subroutine mci_test_ignore_prepare_simulation (mci) class(mci_test_t), intent(inout) :: mci end subroutine mci_test_ignore_prepare_simulation @ %def mci_test_ignore_prepare_simulation @ Event generator. We use mock random numbers for first selecting the channel and then setting the $x$ values. The results reside in the state of [[instance]] and [[sampler]]. <>= subroutine mci_test_generate_weighted_event (mci, instance, sampler) class(mci_test_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler real(default) :: r real(default), dimension(:), allocatable :: x integer :: c select type (instance) type is (mci_test_instance_t) allocate (x (mci%n_dim)) select case (mci%n_channel) case (1) c = 1 call mci%rng%generate (x(1)) case (2) call mci%rng%generate (r) if (r < instance%w(1)) then c = 1 else c = 2 end if call mci%rng%generate (x) end select call instance%evaluate (sampler, c, x) end select end subroutine mci_test_generate_weighted_event @ %def mci_test_generate_weighted_event @ For unweighted events, we generate weighted events and apply a simple rejection step to the relative event weight, until an event passes. (This might result in an endless loop if we happen to be in sync with the mock random generator cycle. Therefore, limit the number of tries.) <>= subroutine mci_test_generate_unweighted_event (mci, instance, sampler) class(mci_test_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler real(default) :: r integer :: i select type (instance) type is (mci_test_instance_t) mci%tries = 0 do i = 1, 10 call mci%generate_weighted_event (instance, sampler) mci%tries = mci%tries + 1 call mci%rng%generate (r) if (r < instance%rel_value) exit end do end select end subroutine mci_test_generate_unweighted_event @ %def mci_test_generate_unweighted_event @ Here, we rebuild the event from the state without consulting the rng. <>= subroutine mci_test_rebuild_event (mci, instance, sampler, state) class(mci_test_t), intent(inout) :: mci class(mci_instance_t), intent(inout) :: instance class(mci_sampler_t), intent(inout) :: sampler class(mci_state_t), intent(in) :: state select type (instance) type is (mci_test_instance_t) call instance%recall (sampler, state) end select end subroutine mci_test_rebuild_event @ %def mci_test_rebuild_event @ \subsubsection{Instance of the test MCI type} This instance type simulates the VAMP approach. We implement the VAMP multi-channel formula, but keep the channel-specific probability functions $g_i$ smooth and fixed. We also keep the weights fixed. The setup is as follows: we have $n$ mappings of the unit hypercube \begin{equation} x = x (x^{(k)}) \qquad \text{where $x=(x_1,\ldots)$}. \end{equation} The Jacobian factors are the determinants \begin{equation} f^{(k)}(x^{(k)}) = \left|\frac{\partial x}{\partial x^{(k)}}\right| \end{equation} We introduce arbitrary probability functions \begin{equation} g^{(k)}(x^{(k)}) \qquad \text{with}\quad \int dx^{(k)} g^{(k)}(x^{(k)}) = 1 \end{equation} and weights \begin{equation} w_k \qquad \text{with}\quad \sum_k w_k = 1 \end{equation} and construct the joint probability function \begin{equation} g(x) = \sum_k w_k\frac{g^{(k)}(x^{(k)}(x))}{f^{(k)}(x^{(k)}(x))} \end{equation} which also satisfies \begin{equation} \int g(x)\,dx = 1. \end{equation} The algorithm implements a resolution of unity as follows \begin{align} 1 &= \int dx = \int\frac{g(x)}{g(x)} dx \nonumber\\ &= \sum w_k \int \frac{g^{(k)}(x^{(k)}(x))}{f^{(k)}(x^{(k)}(x))} \,\frac{dx}{g(x)} \nonumber\\ &= \sum w_k \int g^{(k)}(x^{(k)}) \frac{dx^{(k)}}{g(x(x^{(k)}))} \end{align} where each of the integrals in the sum is evaluated using the channel-specific variables $x^{(k)}$. We provide two examples: (1) trivial with one channel, one dimension, and all functions unity and (2) two channels and two dimensions with \begin{align} x (x^{(1)}) &= (x^{(1)}_1, x^{(1)}_2) \nonumber\\ x (x^{(2)}) &= (x^{(2)}_1{}^2, x^{(2)}_2) \end{align} hence \begin{align} f^{(1)}&\equiv 1, &f^{(2)}(x^{(2)}) &= 2x^{(2)}_1 \end{align} The probability functions are \begin{align} g^{(1)}&\equiv 1, &g^{(2)}(x^{(2)}) = 2 x^{(2)}_2 \end{align} In the concrete implementation of the integrator instance we store values for the channel probabilities $g_i$ and the accumulated probability $g$. We also store the result (product of integrand and MCI weight), the expected maximum for the result in each channel. <>= public :: mci_test_instance_t <>= type, extends (mci_instance_t) :: mci_test_instance_t type(mci_test_t), pointer :: mci => null () real(default) :: g = 0 real(default), dimension(:), allocatable :: gi real(default) :: value = 0 real(default) :: rel_value = 0 real(default), dimension(:), allocatable :: max contains procedure :: write => mci_test_instance_write procedure :: final => mci_test_instance_final procedure :: init => mci_test_instance_init procedure :: compute_weight => mci_test_instance_compute_weight procedure :: record_integrand => mci_test_instance_record_integrand procedure :: init_simulation => mci_test_instance_init_simulation procedure :: final_simulation => mci_test_instance_final_simulation procedure :: get_event_excess => mci_test_instance_get_event_excess end type mci_test_instance_t @ %def mci_test_instance_t @ Output: trivial <>= subroutine mci_test_instance_write (object, unit, pacify) class(mci_test_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify integer :: u, c u = given_output_unit (unit) write (u, "(1x,A,ES13.7)") "Result value = ", object%value write (u, "(1x,A,ES13.7)") "Rel. weight = ", object%rel_value write (u, "(1x,A,ES13.7)") "Integrand = ", object%integrand write (u, "(1x,A,ES13.7)") "MCI weight = ", object%mci_weight write (u, "(3x,A,I0)") "c = ", object%selected_channel write (u, "(3x,A,ES13.7)") "g = ", object%g write (u, "(1x,A)") "Channel parameters:" do c = 1, object%mci%n_channel write (u, "(1x,I0,A,4(1x,ES13.7))") c, ": w/f/g/m =", & object%w(c), object%f(c), object%gi(c), object%max(c) write (u, "(4x,A,9(1x,F9.7))") "x =", object%x(:,c) end do end subroutine mci_test_instance_write @ %def mci_test_instance_write @ The finalizer is empty. <>= subroutine mci_test_instance_final (object) class(mci_test_instance_t), intent(inout) :: object end subroutine mci_test_instance_final @ %def mci_test_instance_final @ Initializer. We make use of the analytical result that the maximum of the weighted integrand, in each channel, is equal to $1$ (one-dimensional case) and $2$ (two-dimensional case), respectively. <>= subroutine mci_test_instance_init (mci_instance, mci) class(mci_test_instance_t), intent(out) :: mci_instance class(mci_t), intent(in), target :: mci call mci_instance%base_init (mci) select type (mci) type is (mci_test_t) mci_instance%mci => mci end select allocate (mci_instance%gi (mci%n_channel)) mci_instance%gi = 0 allocate (mci_instance%max (mci%n_channel)) select case (mci%n_channel) case (1) mci_instance%max = 1._default case (2) mci_instance%max = 2._default end select end subroutine mci_test_instance_init @ %def mci_test_instance_init @ Compute weight: we implement the VAMP multi-channel formula. The channel probabilities [[gi]] are predefined functions. <>= subroutine mci_test_instance_compute_weight (mci, c) class(mci_test_instance_t), intent(inout) :: mci integer, intent(in) :: c integer :: i mci%selected_channel = c select case (mci%mci%n_dim) case (1) mci%gi(1) = 1 case (2) mci%gi(1) = 1 mci%gi(2) = 2 * mci%x(2,2) end select mci%g = 0 do i = 1, mci%mci%n_channel mci%g = mci%g + mci%w(i) * mci%gi(i) / mci%f(i) end do mci%mci_weight = mci%gi(c) / mci%g end subroutine mci_test_instance_compute_weight @ %def mci_test_instance_compute_weight @ Record the integrand. Apply the Jacobian weight to get the absolute value. Divide by the channel maximum and by any overall factor to get the value relative to the maximum. <>= subroutine mci_test_instance_record_integrand (mci, integrand) class(mci_test_instance_t), intent(inout) :: mci real(default), intent(in) :: integrand mci%integrand = integrand mci%value = mci%integrand * mci%mci_weight mci%rel_value = mci%value / mci%max(mci%selected_channel) & / mci%mci%max_factor end subroutine mci_test_instance_record_integrand @ %def mci_test_instance_record_integrand @ Nothing to do here. <>= subroutine mci_test_instance_init_simulation (instance, safety_factor) class(mci_test_instance_t), intent(inout) :: instance real(default), intent(in), optional :: safety_factor end subroutine mci_test_instance_init_simulation subroutine mci_test_instance_final_simulation (instance) class(mci_test_instance_t), intent(inout) :: instance end subroutine mci_test_instance_final_simulation @ %def mci_test_instance_init_simulation @ %def mci_test_instance_final_simulation @ Return always zero. <>= function mci_test_instance_get_event_excess (mci) result (excess) class(mci_test_instance_t), intent(in) :: mci real(default) :: excess excess = 0 end function mci_test_instance_get_event_excess @ %def mci_test_instance_get_event_excess @ \subsubsection{Test sampler} The test sampler implements a fixed configuration, either trivial (one-channel, one-dimension), or slightly nontrivial (two-channel, two-dimension). In the second channel, the first parameter is mapped according to $x_1 = x^{(2)}_1{}^2$, so we have $f^{(2)}(x^{(2)}) = 2x^{(2)}_1$. For display purposes, we store the return values inside the object. This is not strictly necessary. <>= type, extends (mci_sampler_t) :: test_sampler_t real(default) :: integrand = 0 integer :: selected_channel = 0 real(default), dimension(:,:), allocatable :: x real(default), dimension(:), allocatable :: f contains procedure :: init => test_sampler_init procedure :: write => test_sampler_write procedure :: compute => test_sampler_compute procedure :: is_valid => test_sampler_is_valid procedure :: evaluate => test_sampler_evaluate procedure :: rebuild => test_sampler_rebuild procedure :: fetch => test_sampler_fetch end type test_sampler_t @ %def test_sampler_t <>= subroutine test_sampler_init (sampler, n) class(test_sampler_t), intent(out) :: sampler integer, intent(in) :: n allocate (sampler%x (n, n)) allocate (sampler%f (n)) end subroutine test_sampler_init @ %def test_sampler_init @ Output <>= subroutine test_sampler_write (object, unit, testflag) class(test_sampler_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u, c u = given_output_unit (unit) write (u, "(1x,A)") "Test sampler:" write (u, "(3x,A,ES13.7)") "Integrand = ", object%integrand write (u, "(3x,A,I0)") "Channel = ", object%selected_channel do c = 1, size (object%f) write (u, "(1x,I0,':',1x,A,ES13.7)") c, "f = ", object%f(c) write (u, "(4x,A,9(1x,F9.7))") "x =", object%x(:,c) end do end subroutine test_sampler_write @ %def test_sampler_write @ Compute $x$ and Jacobians, given the input parameter array. This is called both by [[evaluate]] and [[rebuild]]. <>= subroutine test_sampler_compute (sampler, c, x_in) class(test_sampler_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in sampler%selected_channel = c select case (size (sampler%f)) case (1) sampler%x(:,1) = x_in sampler%f = 1 case (2) select case (c) case (1) sampler%x(:,1) = x_in sampler%x(1,2) = sqrt (x_in(1)) sampler%x(2,2) = x_in(2) case (2) sampler%x(1,1) = x_in(1) ** 2 sampler%x(2,1) = x_in(2) sampler%x(:,2) = x_in end select sampler%f(1) = 1 sampler%f(2) = 2 * sampler%x(1,2) end select end subroutine test_sampler_compute @ %def test_sampler_kineamtics @ The point is always valid. <>= function test_sampler_is_valid (sampler) result (valid) class(test_sampler_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_is_valid @ %def test_sampler_is_valid @ The integrand is always equal to 1. <>= subroutine test_sampler_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) sampler%integrand = 1 val = sampler%integrand x = sampler%x f = sampler%f end subroutine test_sampler_evaluate @ %def test_sampler_evaluate @ Construct kinematics from the input $x$ array. Set the integrand instead of evaluating it. <>= subroutine test_sampler_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) sampler%integrand = val x = sampler%x f = sampler%f end subroutine test_sampler_rebuild @ %def test_sampler_rebuild @ Recall contents. <>= subroutine test_sampler_fetch (sampler, val, x, f) class(test_sampler_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%integrand x = sampler%x f = sampler%f end subroutine test_sampler_fetch @ %def test_sampler_fetch @ \subsubsection{Test results object} This mock object just stores and displays the current result. <>= type, extends (mci_results_t) :: mci_test_results_t integer :: n_it = 0 integer :: n_calls = 0 real(default) :: integral = 0 real(default) :: error = 0 real(default) :: efficiency = 0 contains <> end type mci_test_results_t @ %def mci_test_results_t @ Output. <>= procedure :: write => mci_test_results_write procedure :: write_verbose => mci_test_results_write_verbose <>= subroutine mci_test_results_write (object, unit, suppress) class(mci_test_results_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: suppress integer :: u u = given_output_unit (unit) write (u, "(3x,A,1x,I0)") "Iterations = ", object%n_it write (u, "(3x,A,1x,I0)") "Calls = ", object%n_calls write (u, "(3x,A,1x,F12.10)") "Integral = ", object%integral write (u, "(3x,A,1x,F12.10)") "Error = ", object%error write (u, "(3x,A,1x,F12.10)") "Efficiency = ", object%efficiency end subroutine mci_test_results_write subroutine mci_test_results_write_verbose (object, unit) class(mci_test_results_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(3x,A,1x,I0)") "Iterations = ", object%n_it write (u, "(3x,A,1x,I0)") "Calls = ", object%n_calls write (u, "(3x,A,1x,F12.10)") "Integral = ", object%integral write (u, "(3x,A,1x,F12.10)") "Error = ", object%error write (u, "(3x,A,1x,F12.10)") "Efficiency = ", object%efficiency end subroutine mci_test_results_write_verbose @ %def mci_test_results_write @ Record result. <>= procedure :: record_simple => mci_test_results_record_simple procedure :: record_extended => mci_test_results_record_extended <>= subroutine mci_test_results_record_simple (object, n_it, n_calls, & integral, error, efficiency, chain_weights, suppress) class(mci_test_results_t), intent(inout) :: object integer, intent(in) :: n_it integer, intent(in) :: n_calls real(default), intent(in) :: integral real(default), intent(in) :: error real(default), intent(in) :: efficiency real(default), dimension(:), intent(in), optional :: chain_weights logical, intent(in), optional :: suppress object%n_it = n_it object%n_calls = n_calls object%integral = integral object%error = error object%efficiency = efficiency end subroutine mci_test_results_record_simple subroutine mci_test_results_record_extended (object, n_it, n_calls, & & n_calls_valid, integral, error, efficiency, efficiency_pos, & & efficiency_neg, chain_weights, suppress) class(mci_test_results_t), intent(inout) :: object integer, intent(in) :: n_it integer, intent(in) :: n_calls integer, intent(in) :: n_calls_valid real(default), intent(in) :: integral real(default), intent(in) :: error real(default), intent(in) :: efficiency real(default), intent(in) :: efficiency_pos real(default), intent(in) :: efficiency_neg real(default), dimension(:), intent(in), optional :: chain_weights logical, intent(in), optional :: suppress object%n_it = n_it object%n_calls = n_calls object%integral = integral object%error = error object%efficiency = efficiency end subroutine mci_test_results_record_extended @ %def mci_test_results_record @ \subsubsection{Integrator configuration data} Construct and display a test integrator configuration object. <>= call test (mci_base_1, "mci_base_1", & "integrator configuration", & u, results) <>= public :: mci_base_1 <>= subroutine mci_base_1 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler real(default) :: integrand write (u, "(A)") "* Test output: mci_base_1" write (u, "(A)") "* Purpose: initialize and display & &test integrator" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (2, 2) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_t :: sampler) select type (sampler) type is (test_sampler_t) call sampler%init (2) end select write (u, "(A)") "* Evaluate sampler for given point and channel" write (u, "(A)") call sampler%evaluate (1, [0.25_default, 0.8_default], & integrand, mci_instance%x, mci_instance%f) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Compute MCI weight" write (u, "(A)") call mci_instance%compute_weight (1) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Get integrand and compute weight for another point" write (u, "(A)") call mci_instance%evaluate (sampler, 2, [0.5_default, 0.6_default]) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Recall results, again" write (u, "(A)") call mci_instance%final () deallocate (mci_instance) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) call mci_instance%fetch (sampler, 2) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Retrieve value" write (u, "(A)") write (u, "(1x,A,ES13.7)") "Weighted integrand = ", & mci_instance%get_value () call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_1" end subroutine mci_base_1 @ %def mci_base_1 @ \subsubsection{Trivial integral} Use the MCI approach to compute a trivial one-dimensional integral. <>= call test (mci_base_2, "mci_base_2", & "integration", & u, results) <>= public :: mci_base_2 <>= subroutine mci_base_2 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler write (u, "(A)") "* Test output: mci_base_2" write (u, "(A)") "* Purpose: perform a test integral" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (1, 1) select type (mci) type is (mci_test_t) call mci%set_divisions (10) end select call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_t :: sampler) select type (sampler) type is (test_sampler_t) call sampler%init (1) end select write (u, "(A)") "* Integrate" write (u, "(A)") call mci%integrate (mci_instance, sampler, 0, 0) call mci%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_2" end subroutine mci_base_2 @ %def mci_base_2 @ \subsubsection{Nontrivial integral} Use the MCI approach to compute a simple two-dimensional integral with two channels. <>= call test (mci_base_3, "mci_base_3", & "integration (two channels)", & u, results) <>= public :: mci_base_3 <>= subroutine mci_base_3 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler write (u, "(A)") "* Test output: mci_base_3" write (u, "(A)") "* Purpose: perform a nontrivial test integral" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_test_t) call mci%set_divisions (10) end select write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_t :: sampler) select type (sampler) type is (test_sampler_t) call sampler%init (2) end select write (u, "(A)") "* Integrate" write (u, "(A)") call mci%integrate (mci_instance, sampler, 0, 0) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with higher resolution" write (u, "(A)") select type (mci) type is (mci_test_t) call mci%set_divisions (100) end select call mci%integrate (mci_instance, sampler, 0, 0) call mci%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_3" end subroutine mci_base_3 @ %def mci_base_3 @ \subsubsection{Event generation} We generate ``random'' events, one weighted and one unweighted. The test implementation does not require an integration pass, we can generate events immediately. <>= call test (mci_base_4, "mci_base_4", & "event generation (two channels)", & u, results) <>= public :: mci_base_4 <>= subroutine mci_base_4 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_base_4" write (u, "(A)") "* Purpose: generate events" write (u, "(A)") write (u, "(A)") "* Initialize integrator, instance, sampler" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_test_t) call mci%set_divisions (10) end select call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_t :: sampler) select type (sampler) type is (test_sampler_t) call sampler%init (2) end select allocate (rng_test_t :: rng) call mci%import_rng (rng) write (u, "(A)") "* Generate weighted event" write (u, "(A)") call mci%generate_weighted_event (mci_instance, sampler) call sampler%write (u) write (u, *) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Generate unweighted event" write (u, "(A)") call mci%generate_unweighted_event (mci_instance, sampler) select type (mci) type is (mci_test_t) write (u, "(A,I0)") " Success in try ", mci%tries write (u, "(A)") end select call sampler%write (u) write (u, *) call mci_instance%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_4" end subroutine mci_base_4 @ %def mci_base_4 @ \subsubsection{Store and recall data} We generate an event and store the relevant data, i.e., the input parameters and the result value for a particular channel. Then we use those data to recover the event, as far as the MCI record is concerned. <>= call test (mci_base_5, "mci_base_5", & "store and recall", & u, results) <>= public :: mci_base_5 <>= subroutine mci_base_5 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng class(mci_state_t), allocatable :: state write (u, "(A)") "* Test output: mci_base_5" write (u, "(A)") "* Purpose: store and recall an event" write (u, "(A)") write (u, "(A)") "* Initialize integrator, instance, sampler" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_test_t) call mci%set_divisions (10) end select call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_t :: sampler) select type (sampler) type is (test_sampler_t) call sampler%init (2) end select allocate (rng_test_t :: rng) call mci%import_rng (rng) write (u, "(A)") "* Generate weighted event" write (u, "(A)") call mci%generate_weighted_event (mci_instance, sampler) call sampler%write (u) write (u, *) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Store data" write (u, "(A)") allocate (state) call mci_instance%store (state) call mci_instance%final () deallocate (mci_instance) call state%write (u) write (u, "(A)") write (u, "(A)") "* Recall data and rebuild event" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) call mci%rebuild_event (mci_instance, sampler, state) call sampler%write (u) write (u, *) call mci_instance%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_5" end subroutine mci_base_5 @ %def mci_base_5 @ \subsubsection{Chained channels} Chain channels together. In the base configuration, this just fills entries in an extra array (each channel may belong to a chain). In type implementations, this will be used for grouping equivalent channels by keeping their weights equal. <>= call test (mci_base_6, "mci_base_6", & "chained channels", & u, results) <>= public :: mci_base_6 <>= subroutine mci_base_6 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci write (u, "(A)") "* Test output: mci_base_6" write (u, "(A)") "* Purpose: initialize and display & &test integrator with chains" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (1, 5) write (u, "(A)") "* Introduce chains" write (u, "(A)") call mci%declare_chains ([1, 2, 2, 1, 2]) call mci%write (u) call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_6" end subroutine mci_base_6 @ %def mci_base_6 @ \subsubsection{Recording results} Compute a simple two-dimensional integral and record the result. <>= call test (mci_base_7, "mci_base_7", & "recording results", & u, results) <>= public :: mci_base_7 <>= subroutine mci_base_7 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(mci_results_t), allocatable :: results write (u, "(A)") "* Test output: mci_base_7" write (u, "(A)") "* Purpose: perform a nontrivial test integral & &and record results" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_test_t) call mci%set_divisions (10) end select write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_t :: sampler) select type (sampler) type is (test_sampler_t) call sampler%init (2) end select allocate (mci_test_results_t :: results) write (u, "(A)") "* Integrate" write (u, "(A)") call mci%integrate (mci_instance, sampler, 1, 1000, results) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Display results" write (u, "(A)") call results%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_7" end subroutine mci_base_7 @ %def mci_base_7 @ \subsubsection{Timer} Simple checks for the embedded timer. <>= call test (mci_base_8, "mci_base_8", & "timer", & u, results) <>= public :: mci_base_8 <>= subroutine mci_base_8 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci real(default) :: dummy write (u, "(A)") "* Test output: mci_base_8" write (u, "(A)") "* Purpose: check timer availability" write (u, "(A)") write (u, "(A)") "* Initialize integrator with timer" write (u, "(A)") allocate (mci_test_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_test_t) call mci%set_divisions (10) end select call mci%set_timer (active = .true.) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Start timer" write (u, "(A)") call mci%start_timer () call mci%write (u) write (u, "(A)") write (u, "(A)") "* Stop timer" write (u, "(A)") call mci%stop_timer () write (u, "(A)") " (ok)" write (u, "(A)") write (u, "(A)") "* Readout" write (u, "(A)") dummy = mci%get_time () write (u, "(A)") " (ok)" write (u, "(A)") write (u, "(A)") "* Deactivate timer" write (u, "(A)") call mci%set_timer (active = .false.) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_base_8" end subroutine mci_base_8 @ %def mci_base_8 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Iterations} This module defines a container for the list of iterations and calls, to be submitted to integration. <<[[iterations.f90]]>>= <> module iterations <> <> use io_units use diagnostics <> <> <> contains <> end module iterations @ %def iterations @ \subsection{The iterations list} Each integration pass has a number of iterations and a number of calls per iteration. The last pass produces the end result; the previous passes are used for adaptation. The flags [[adapt_grid]] and [[adapt_weight]] are used only if [[custom_adaptation]] is set. Otherwise, default settings are used that depend on the integration pass. <>= type :: iterations_spec_t private integer :: n_it = 0 integer :: n_calls = 0 logical :: custom_adaptation = .false. logical :: adapt_grids = .false. logical :: adapt_weights = .false. end type iterations_spec_t @ %def iterations_spec_t @ We build up a list of iterations. <>= public :: iterations_list_t <>= type :: iterations_list_t private integer :: n_pass = 0 type(iterations_spec_t), dimension(:), allocatable :: pass contains <> end type iterations_list_t @ %def iterations_list_t @ Initialize an iterations list. For each pass, we have to specify the number of iterations and calls. We may provide the adaption conventions explicitly, either as character codes or as logicals. For passes where the adaptation conventions are not specified, we use the following default setting: adapt weights and grids for all passes except the last one. <>= procedure :: init => iterations_list_init <>= subroutine iterations_list_init & (it_list, n_it, n_calls, adapt, adapt_code, adapt_grids, adapt_weights) class(iterations_list_t), intent(inout) :: it_list integer, dimension(:), intent(in) :: n_it, n_calls logical, dimension(:), intent(in), optional :: adapt type(string_t), dimension(:), intent(in), optional :: adapt_code logical, dimension(:), intent(in), optional :: adapt_grids, adapt_weights integer :: i it_list%n_pass = size (n_it) if (allocated (it_list%pass)) deallocate (it_list%pass) allocate (it_list%pass (it_list%n_pass)) it_list%pass%n_it = n_it it_list%pass%n_calls = n_calls if (present (adapt)) then it_list%pass%custom_adaptation = adapt do i = 1, it_list%n_pass if (adapt(i)) then if (verify (adapt_code(i), "wg") /= 0) then call msg_error ("iteration specification: " & // "adaptation code letters must be 'w' or 'g'") end if it_list%pass(i)%adapt_grids = scan (adapt_code(i), "g") /= 0 it_list%pass(i)%adapt_weights = scan (adapt_code(i), "w") /= 0 end if end do else if (present (adapt_grids) .and. present (adapt_weights)) then it_list%pass%custom_adaptation = .true. it_list%pass%adapt_grids = adapt_grids it_list%pass%adapt_weights = adapt_weights end if do i = 1, it_list%n_pass - 1 if (.not. it_list%pass(i)%custom_adaptation) then it_list%pass(i)%adapt_grids = .true. it_list%pass(i)%adapt_weights = .true. end if end do end subroutine iterations_list_init @ %def iterations_list_init <>= procedure :: clear => iterations_list_clear <>= subroutine iterations_list_clear (it_list) class(iterations_list_t), intent(inout) :: it_list it_list%n_pass = 0 deallocate (it_list%pass) end subroutine iterations_list_clear @ %def iterations_list_clear @ Write the list of iterations. <>= procedure :: write => iterations_list_write <>= subroutine iterations_list_write (it_list, unit) class(iterations_list_t), intent(in) :: it_list integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(A)") char (it_list%to_string ()) end subroutine iterations_list_write @ %def iterations_list_write @ The output as a single-line string. <>= procedure :: to_string => iterations_list_to_string <>= function iterations_list_to_string (it_list) result (buffer) class(iterations_list_t), intent(in) :: it_list type(string_t) :: buffer character(30) :: ibuf integer :: i buffer = "iterations = " if (it_list%n_pass > 0) then do i = 1, it_list%n_pass if (i > 1) buffer = buffer // ", " write (ibuf, "(I0,':',I0)") & it_list%pass(i)%n_it, it_list%pass(i)%n_calls buffer = buffer // trim (ibuf) if (it_list%pass(i)%custom_adaptation & .or. it_list%pass(i)%adapt_grids & .or. it_list%pass(i)%adapt_weights) then buffer = buffer // ':"' if (it_list%pass(i)%adapt_grids) buffer = buffer // "g" if (it_list%pass(i)%adapt_weights) buffer = buffer // "w" buffer = buffer // '"' end if end do else buffer = buffer // "[undefined]" end if end function iterations_list_to_string @ %def iterations_list_to_string @ \subsection{Tools} Return the total number of passes. <>= procedure :: get_n_pass => iterations_list_get_n_pass <>= function iterations_list_get_n_pass (it_list) result (n_pass) class(iterations_list_t), intent(in) :: it_list integer :: n_pass n_pass = it_list%n_pass end function iterations_list_get_n_pass @ %def iterations_list_get_n_pass @ Return the number of calls for a specific pass. <>= procedure :: get_n_calls => iterations_list_get_n_calls <>= function iterations_list_get_n_calls (it_list, pass) result (n_calls) class(iterations_list_t), intent(in) :: it_list integer :: n_calls integer, intent(in) :: pass if (pass <= it_list%n_pass) then n_calls = it_list%pass(pass)%n_calls else n_calls = 0 end if end function iterations_list_get_n_calls @ %def iterations_list_get_n_calls @ <>= procedure :: set_n_calls => iterations_list_set_n_calls <>= subroutine iterations_list_set_n_calls (it_list, pass, n_calls) class(iterations_list_t), intent(inout) :: it_list integer, intent(in) :: pass, n_calls it_list%pass(pass)%n_calls = n_calls end subroutine iterations_list_set_n_calls @ %def iterations_list_set_n_calls @ Get the adaptation mode (automatic/custom) and, for custom adaptation, the flags for a specific pass. <>= procedure :: adapt_grids => iterations_list_adapt_grids procedure :: adapt_weights => iterations_list_adapt_weights <>= function iterations_list_adapt_grids (it_list, pass) result (flag) logical :: flag class(iterations_list_t), intent(in) :: it_list integer, intent(in) :: pass if (pass <= it_list%n_pass) then flag = it_list%pass(pass)%adapt_grids else flag = .false. end if end function iterations_list_adapt_grids function iterations_list_adapt_weights (it_list, pass) result (flag) logical :: flag class(iterations_list_t), intent(in) :: it_list integer, intent(in) :: pass if (pass <= it_list%n_pass) then flag = it_list%pass(pass)%adapt_weights else flag = .false. end if end function iterations_list_adapt_weights @ %def iterations_list_has_custom_adaptation @ %def iterations_list_adapt_grids @ %def iterations_list_adapt_weights @ Return the total number of iterations / the iterations for a specific pass. <>= procedure :: get_n_it => iterations_list_get_n_it <>= function iterations_list_get_n_it (it_list, pass) result (n_it) class(iterations_list_t), intent(in) :: it_list integer :: n_it integer, intent(in) :: pass if (pass <= it_list%n_pass) then n_it = it_list%pass(pass)%n_it else n_it = 0 end if end function iterations_list_get_n_it @ %def iterations_list_get_n_it @ \subsection{Iteration Multipliers} <>= public :: iteration_multipliers_t <>= type :: iteration_multipliers_t real(default) :: mult_real = 1._default real(default) :: mult_virt = 1._default real(default) :: mult_dglap = 1._default real(default) :: mult_threshold = 1._default integer, dimension(:), allocatable :: n_calls0 end type iteration_multipliers_t @ %def iterations_multipliers @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[iterations_ut.f90]]>>= <> module iterations_ut use unit_tests use iterations_uti <> <> contains <> end module iterations_ut @ %def iterations_ut @ <<[[iterations_uti.f90]]>>= <> module iterations_uti <> use iterations <> <> contains <> end module iterations_uti @ %def iterations_ut @ API: driver for the unit tests below. <>= public :: iterations_test <>= subroutine iterations_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine iterations_test @ %def iterations_test @ \subsubsection{Empty list} <>= call test (iterations_1, "iterations_1", & "empty iterations list", & u, results) <>= public :: iterations_1 <>= subroutine iterations_1 (u) integer, intent(in) :: u type(iterations_list_t) :: it_list write (u, "(A)") "* Test output: iterations_1" write (u, "(A)") "* Purpose: display empty iterations list" write (u, "(A)") call it_list%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: iterations_1" end subroutine iterations_1 @ %def iterations_1 @ \subsubsection{Fill list} <>= call test (iterations_2, "iterations_2", & "create iterations list", & u, results) <>= public :: iterations_2 <>= subroutine iterations_2 (u) integer, intent(in) :: u type(iterations_list_t) :: it_list write (u, "(A)") "* Test output: iterations_2" write (u, "(A)") "* Purpose: fill and display iterations list" write (u, "(A)") write (u, "(A)") "* Minimal setup (2 passes)" write (u, "(A)") call it_list%init ([2, 4], [5000, 20000]) call it_list%write (u) call it_list%clear () write (u, "(A)") write (u, "(A)") "* Setup with flags (3 passes)" write (u, "(A)") call it_list%init ([2, 4, 5], [5000, 20000, 400], & [.false., .true., .true.], & [var_str (""), var_str ("g"), var_str ("wg")]) call it_list%write (u) write (u, "(A)") write (u, "(A)") "* Extract data" write (u, "(A)") write (u, "(A,I0)") "n_pass = ", it_list%get_n_pass () write (u, "(A)") write (u, "(A,I0)") "n_calls(2) = ", it_list%get_n_calls (2) write (u, "(A)") write (u, "(A,I0)") "n_it(3) = ", it_list%get_n_it (3) write (u, "(A)") write (u, "(A)") "* Test output end: iterations_2" end subroutine iterations_2 @ %def iterations_2 @ %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Integration results} We record integration results and errors in a dedicated type. This allows us to do further statistics such as weighted average, chi-squared, grouping by integration passes, etc. Note WHIZARD 2.2.0: This code is taken from the previous [[processes]] module essentially unchanged and converted into a separate module. It lacks an overhaul and, in particular, self-tests. <<[[integration_results.f90]]>>= module integration_results <> <> use io_units use format_utils, only: mp_format, pac_fmt use format_defs, only: FMT_10, FMT_14 use diagnostics use md5 use os_interface use mci_base <> <> <> <> <> contains <> end module integration_results @ %def integration_results @ \subsection{Integration results entry} This object collects the results of an integration pass and makes them available to the outside. The results object has to distinguish the process type: We store the process type, the index of the integration pass and the absolute iteration index, the number of iterations contained in this result (for averages), and the integral (cross section or partial width), error estimate, efficiency. For intermediate results, we set a flag if this result is an improvement w.r.t. previous ones. The process type indicates decay or scattering. Dummy entries (skipped iterations) have a process type of [[PRC_UNKNOWN]]. The additional information [[n_calls_valid]], [[efficiency_pos]] and [[efficiency_neg]] are stored, but only used in verbose mode. <>= public :: integration_entry_t <>= type :: integration_entry_t private integer :: process_type = PRC_UNKNOWN integer :: pass = 0 integer :: it = 0 integer :: n_it = 0 integer :: n_calls = 0 integer :: n_calls_valid = 0 logical :: improved = .false. real(default) :: integral = 0 real(default) :: error = 0 real(default) :: efficiency = 0 real(default) :: efficiency_pos = 0 real(default) :: efficiency_neg = 0 real(default) :: chi2 = 0 real(default), dimension(:), allocatable :: chain_weights contains <> end type integration_entry_t @ %def integration_result_t @ The possible values of the type indicator: <>= integer, parameter, public :: PRC_UNKNOWN = 0 integer, parameter, public :: PRC_DECAY = 1 integer, parameter, public :: PRC_SCATTERING = 2 @ %def PRC_UNKNOWN PRC_DECAY PRC_SCATTERING @ Initialize with all relevant data. <>= interface integration_entry_t module procedure integration_entry_init end interface integration_entry_t <>= type(integration_entry_t) function integration_entry_init (process_type, pass,& & it, n_it, n_calls, n_calls_valid, improved, integral, error,& & efficiency, efficiency_pos, efficiency_neg, chi2, chain_weights)& & result (entry) integer, intent(in) :: process_type, pass, it, n_it, n_calls, n_calls_valid logical, intent(in) :: improved real(default), intent(in) :: integral, error, efficiency, efficiency_pos, efficiency_neg real(default), intent(in), optional :: chi2 real(default), dimension(:), intent(in), optional :: chain_weights entry%process_type = process_type entry%pass = pass entry%it = it entry%n_it = n_it entry%n_calls = n_calls entry%n_calls_valid = n_calls_valid entry%improved = improved entry%integral = integral entry%error = error entry%efficiency = efficiency entry%efficiency_pos = efficiency_pos entry%efficiency_neg = efficiency_neg if (present (chi2)) entry%chi2 = chi2 if (present (chain_weights)) then allocate (entry%chain_weights (size (chain_weights))) entry%chain_weights = chain_weights end if end function integration_entry_init @ %def integration_entry_init @ Access values, some of them computed on demand: <>= procedure :: get_pass => integration_entry_get_pass procedure :: get_n_calls => integration_entry_get_n_calls procedure :: get_n_calls_valid => integration_entry_get_n_calls_valid procedure :: get_integral => integration_entry_get_integral procedure :: get_error => integration_entry_get_error procedure :: get_rel_error => integration_entry_get_relative_error procedure :: get_accuracy => integration_entry_get_accuracy procedure :: get_efficiency => integration_entry_get_efficiency procedure :: get_efficiency_pos => integration_entry_get_efficiency_pos procedure :: get_efficiency_neg => integration_entry_get_efficiency_neg procedure :: get_chi2 => integration_entry_get_chi2 procedure :: has_improved => integration_entry_has_improved procedure :: get_n_groves => integration_entry_get_n_groves <>= elemental function integration_entry_get_pass (entry) result (n) integer :: n class(integration_entry_t), intent(in) :: entry n = entry%pass end function integration_entry_get_pass elemental function integration_entry_get_n_calls (entry) result (n) integer :: n class(integration_entry_t), intent(in) :: entry n = entry%n_calls end function integration_entry_get_n_calls elemental function integration_entry_get_n_calls_valid (entry) result (n) integer :: n class(integration_entry_t), intent(in) :: entry n = entry%n_calls_valid end function integration_entry_get_n_calls_valid elemental function integration_entry_get_integral (entry) result (int) real(default) :: int class(integration_entry_t), intent(in) :: entry int = entry%integral end function integration_entry_get_integral elemental function integration_entry_get_error (entry) result (err) real(default) :: err class(integration_entry_t), intent(in) :: entry err = entry%error end function integration_entry_get_error elemental function integration_entry_get_relative_error (entry) result (err) real(default) :: err class(integration_entry_t), intent(in) :: entry err = 0 if (entry%integral /= 0) then err = entry%error / entry%integral end if end function integration_entry_get_relative_error elemental function integration_entry_get_accuracy (entry) result (acc) real(default) :: acc class(integration_entry_t), intent(in) :: entry acc = accuracy (entry%integral, entry%error, entry%n_calls) end function integration_entry_get_accuracy elemental function accuracy (integral, error, n_calls) result (acc) real(default) :: acc real(default), intent(in) :: integral, error integer, intent(in) :: n_calls acc = 0 if (integral /= 0) then acc = error / integral * sqrt (real (n_calls, default)) end if end function accuracy elemental function integration_entry_get_efficiency (entry) result (eff) real(default) :: eff class(integration_entry_t), intent(in) :: entry eff = entry%efficiency end function integration_entry_get_efficiency elemental function integration_entry_get_efficiency_pos (entry) result (eff) real(default) :: eff class(integration_entry_t), intent(in) :: entry eff = entry%efficiency_pos end function integration_entry_get_efficiency_pos elemental function integration_entry_get_efficiency_neg (entry) result (eff) real(default) :: eff class(integration_entry_t), intent(in) :: entry eff = entry%efficiency_neg end function integration_entry_get_efficiency_neg elemental function integration_entry_get_chi2 (entry) result (chi2) real(default) :: chi2 class(integration_entry_t), intent(in) :: entry chi2 = entry%chi2 end function integration_entry_get_chi2 elemental function integration_entry_has_improved (entry) result (flag) logical :: flag class(integration_entry_t), intent(in) :: entry flag = entry%improved end function integration_entry_has_improved elemental function integration_entry_get_n_groves (entry) result (n_groves) integer :: n_groves class(integration_entry_t), intent(in) :: entry n_groves = 0 if (allocated (entry%chain_weights)) then n_groves = size (entry%chain_weights, 1) end if end function integration_entry_get_n_groves @ %def integration_entry_get_pass @ %def integration_entry_get_integral @ %def integration_entry_get_error @ %def integration_entry_get_relative_error @ %def integration_entry_get_accuracy @ %def accuracy @ %def integration_entry_get_efficiency @ %def integration_entry_get_chi2 @ %def integration_entry_has_improved @ %def integration_entry_get_n_groves @ This writes the standard result account into one screen line. The verbose version uses multiple lines and prints the unabridged values. Dummy entries are not written. <>= procedure :: write => integration_entry_write procedure :: write_verbose => integration_entry_write_verbose <>= subroutine integration_entry_write (entry, unit, verbosity, suppress) class(integration_entry_t), intent(in) :: entry integer, intent(in), optional :: unit integer, intent(in), optional :: verbosity logical, intent(in), optional :: suppress integer :: u character(1) :: star character(12) :: fmt character(7) :: fmt2 character(120) :: buffer integer :: verb logical :: supp u = given_output_unit (unit); if (u < 0) return verb = 0; if (present (verbosity)) verb = verbosity supp = .false.; if (present (suppress)) supp = suppress if (entry%process_type /= PRC_UNKNOWN) then if (entry%improved .and. .not. supp) then star = "*" else star = " " end if call pac_fmt (fmt, FMT_14, "3x," // FMT_10 // ",1x", suppress) call pac_fmt (fmt2, "1x,F6.2", "2x,F5.1", suppress) write (buffer, "(1x,I3,1x,I10)") entry%it, entry%n_calls if (verb > 1) then write (buffer, "(A,1x,I10)") trim (buffer), entry%n_calls_valid end if write (buffer, "(A,1x," // fmt // ",1x,ES9.2,1x,F7.2," // & "1x,F7.2,A1," // fmt2 // ")") & trim (buffer), & entry%integral, & abs(entry%error), & abs(integration_entry_get_relative_error (entry)) * 100, & abs(integration_entry_get_accuracy (entry)), & star, & entry%efficiency * 100 if (verb > 2) then write (buffer, "(A,1X," // fmt2 // ",1X," // fmt2 // ")") & trim (buffer), & entry%efficiency_pos * 100, & entry%efficiency_neg * 100 end if if (entry%n_it /= 1) then write (buffer, "(A,1x,F7.2,1x,I3)") & trim (buffer), & entry%chi2, & entry%n_it end if write (u, "(A)") trim (buffer) end if flush (u) end subroutine integration_entry_write subroutine integration_entry_write_verbose (entry, unit) class(integration_entry_t), intent(in) :: entry integer, intent(in) :: unit integer :: u u = given_output_unit (unit); if (u < 0) return write (u, *) " process_type = ", entry%process_type write (u, *) " pass = ", entry%pass write (u, *) " it = ", entry%it write (u, *) " n_it = ", entry%n_it write (u, *) " n_calls = ", entry%n_calls write (u, *) " n_calls_valid = ", entry%n_calls_valid write (u, *) " improved = ", entry%improved write (u, *) " integral = ", entry%integral write (u, *) " error = ", entry%error write (u, *) " efficiency = ", entry%efficiency write (u, *) "efficiency_pos = ", entry%efficiency_pos write (u, *) "efficiency_neg = ", entry%efficiency_neg write (u, *) " chi2 = ", entry%chi2 if (allocated (entry%chain_weights)) then write (u, *) " n_groves = ", size (entry%chain_weights) write (u, *) "chain_weights = ", entry%chain_weights else write (u, *) " n_groves = 0" end if flush (u) end subroutine integration_entry_write_verbose @ %def integration_entry_write @ Read the entry, assuming it has been written in verbose format. <>= procedure :: read => integration_entry_read <>= subroutine integration_entry_read (entry, unit) class(integration_entry_t), intent(out) :: entry integer, intent(in) :: unit character(30) :: dummy character :: equals integer :: n_groves read (unit, *) dummy, equals, entry%process_type read (unit, *) dummy, equals, entry%pass read (unit, *) dummy, equals, entry%it read (unit, *) dummy, equals, entry%n_it read (unit, *) dummy, equals, entry%n_calls read (unit, *) dummy, equals, entry%n_calls_valid read (unit, *) dummy, equals, entry%improved read (unit, *) dummy, equals, entry%integral read (unit, *) dummy, equals, entry%error read (unit, *) dummy, equals, entry%efficiency read (unit, *) dummy, equals, entry%efficiency_pos read (unit, *) dummy, equals, entry%efficiency_neg read (unit, *) dummy, equals, entry%chi2 read (unit, *) dummy, equals, n_groves if (n_groves /= 0) then allocate (entry%chain_weights (n_groves)) read (unit, *) dummy, equals, entry%chain_weights end if end subroutine integration_entry_read @ %def integration_entry_read @ Write an account of the channel weights, accumulated by groves. <>= procedure :: write_chain_weights => integration_entry_write_chain_weights <>= subroutine integration_entry_write_chain_weights (entry, unit) class(integration_entry_t), intent(in) :: entry integer, intent(in), optional :: unit integer :: u, i u = given_output_unit (unit); if (u < 0) return if (allocated (entry%chain_weights)) then do i = 1, size (entry%chain_weights) write (u, "(1x,I3)", advance="no") nint (entry%chain_weights(i) * 100) end do write (u, *) end if end subroutine integration_entry_write_chain_weights @ %def integration_entry_write_chain_weights @ \subsection{Combined integration results} We collect a list of results which grows during the execution of the program. This is implemented as an array which grows if necessary; so we can easily compute averages. We implement this as an extension of the [[mci_results_t]] which is defined in [[mci_base]] as an abstract type. We thus decouple the implementation of the integrator from the implementation of the results display, but nevertheless can record intermediate results during integration. This implies that the present extension implements a [[record]] method. <>= public :: integration_results_t <>= type, extends (mci_results_t) :: integration_results_t private integer :: process_type = PRC_UNKNOWN integer :: current_pass = 0 integer :: n_pass = 0 integer :: n_it = 0 logical :: screen = .false. integer :: unit = 0 integer :: verbosity = 0 real(default) :: error_threshold = 0 type(integration_entry_t), dimension(:), allocatable :: entry type(integration_entry_t), dimension(:), allocatable :: average contains <> end type integration_results_t @ %def integration_results_t @ The array is extended in chunks of 10 entries. <>= integer, parameter :: RESULTS_CHUNK_SIZE = 10 @ %def RESULTS_CHUNK_SIZE @ <>= procedure :: init => integration_results_init <>= subroutine integration_results_init (results, process_type) class(integration_results_t), intent(out) :: results integer, intent(in) :: process_type results%process_type = process_type results%n_pass = 0 results%n_it = 0 allocate (results%entry (RESULTS_CHUNK_SIZE)) allocate (results%average (RESULTS_CHUNK_SIZE)) end subroutine integration_results_init @ %def integration_results_init @ Set verbose output of the integration results. In verbose mode, valid calls, negative as positive efficiency will be printed. <>= procedure :: set_verbosity => integration_results_set_verbosity <>= subroutine integration_results_set_verbosity (results, verbosity) class(integration_results_t), intent(inout) :: results integer, intent(in) :: verbosity results%verbosity = verbosity end subroutine integration_results_set_verbosity @ %def integration_results_set_verbose @ Set additional parameters: the [[error_threshold]] declares that any error value (in absolute numbers) smaller than this is to be considered zero. <>= procedure :: set_error_threshold => integration_results_set_error_threshold <>= subroutine integration_results_set_error_threshold (results, error_threshold) class(integration_results_t), intent(inout) :: results real(default), intent(in) :: error_threshold results%error_threshold = error_threshold end subroutine integration_results_set_error_threshold @ %def integration_results_set_error_threshold @ Output (ASCII format). The [[verbose]] format is used for writing the header in grid files. <>= procedure :: write => integration_results_write procedure :: write_verbose => integration_results_write_verbose <>= subroutine integration_results_write (object, unit, suppress) class(integration_results_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: suppress logical :: verb integer :: u, n u = given_output_unit (unit); if (u < 0) return call object%write_dline (unit) if (object%n_it /= 0) then call object%write_header (unit, logfile = .false.) call object%write_dline (unit) do n = 1, object%n_it if (n > 1) then if (object%entry(n)%pass /= object%entry(n-1)%pass) then call object%write_hline (unit) call object%average(object%entry(n-1)%pass)%write ( & & unit, suppress = suppress) call object%write_hline (unit) end if end if call object%entry(n)%write (unit, & suppress = suppress) end do call object%write_hline(unit) call object%average(object%n_pass)%write (unit, suppress = suppress) else call msg_message ("[WHIZARD integration results: empty]", unit) end if call object%write_dline (unit) flush (u) end subroutine integration_results_write subroutine integration_results_write_verbose (object, unit) class(integration_results_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u, n u = given_output_unit (unit); if (u < 0) return write (u, *) "begin(integration_results)" write (u, *) " n_pass = ", object%n_pass write (u, *) " n_it = ", object%n_it if (object%n_it > 0) then write (u, *) "begin(integration_pass)" do n = 1, object%n_it if (n > 1) then if (object%entry(n)%pass /= object%entry(n-1)%pass) then write (u, *) "end(integration_pass)" write (u, *) "begin(integration_pass)" end if end if write (u, *) "begin(iteration)" call object%entry(n)%write_verbose (unit) write (u, *) "end(iteration)" end do write (u, *) "end(integration_pass)" end if write (u, *) "end(integration_results)" flush (u) end subroutine integration_results_write_verbose @ %def integration_results_write integration_results_verbose @ Write a concise table of chain weights, i.e., the channel history where channels are collected by chains. <>= procedure :: write_chain_weights => & integration_results_write_chain_weights <>= subroutine integration_results_write_chain_weights (results, unit) class(integration_results_t), intent(in) :: results integer, intent(in), optional :: unit integer :: u, i, n u = given_output_unit (unit); if (u < 0) return if (allocated (results%entry(1)%chain_weights) .and. results%n_it /= 0) then call msg_message ("Phase-space chain (grove) weight history: " & // "(numbers in %)", unit) write (u, "(A9)", advance="no") "| chain |" do i = 1, integration_entry_get_n_groves (results%entry(1)) write (u, "(1x,I3)", advance="no") i end do write (u, *) call results%write_dline (unit) do n = 1, results%n_it if (n > 1) then if (results%entry(n)%pass /= results%entry(n-1)%pass) then call results%write_hline (unit) end if end if write (u, "(1x,I6,1x,A1)", advance="no") n, "|" call results%entry(n)%write_chain_weights (unit) end do flush (u) call results%write_dline(unit) end if end subroutine integration_results_write_chain_weights @ %def integration_results_write_chain_weights @ Read the list from file. The file must be written using the [[verbose]] option of the writing routine. <>= procedure :: read => integration_results_read <>= subroutine integration_results_read (results, unit) class(integration_results_t), intent(out) :: results integer, intent(in) :: unit character(80) :: buffer character :: equals integer :: pass, it read (unit, *) buffer if (trim (adjustl (buffer)) /= "begin(integration_results)") then call read_err (); return end if read (unit, *) buffer, equals, results%n_pass read (unit, *) buffer, equals, results%n_it allocate (results%entry (results%n_it + RESULTS_CHUNK_SIZE)) allocate (results%average (results%n_it + RESULTS_CHUNK_SIZE)) it = 0 do pass = 1, results%n_pass read (unit, *) buffer if (trim (adjustl (buffer)) /= "begin(integration_pass)") then call read_err (); return end if READ_ENTRIES: do read (unit, *) buffer if (trim (adjustl (buffer)) /= "begin(iteration)") then exit READ_ENTRIES end if it = it + 1 call results%entry(it)%read (unit) read (unit, *) buffer if (trim (adjustl (buffer)) /= "end(iteration)") then call read_err (); return end if end do READ_ENTRIES if (trim (adjustl (buffer)) /= "end(integration_pass)") then call read_err (); return end if results%average(pass) = compute_average (results%entry, pass) end do read (unit, *) buffer if (trim (adjustl (buffer)) /= "end(integration_results)") then call read_err (); return end if contains subroutine read_err () call msg_fatal ("Reading integration results from file: syntax error") end subroutine read_err end subroutine integration_results_read @ %def integration_results_read @ Auxiliary output. <>= procedure, private :: write_header procedure, private :: write_hline procedure, private :: write_dline <>= subroutine write_header (results, unit, logfile) class(integration_results_t), intent(in) :: results integer, intent(in), optional :: unit logical, intent(in), optional :: logfile character(5) :: phys_unit integer :: u u = given_output_unit (unit); if (u < 0) return select case (results%process_type) case (PRC_DECAY); phys_unit = "[GeV]" case (PRC_SCATTERING); phys_unit = "[fb] " case default phys_unit = " " end select write (msg_buffer, "(A, A)") & "It Calls" if (results%verbosity > 1) then write (msg_buffer, "(A, A)") trim (msg_buffer), & " Valid" end if write (msg_buffer, "(A, A)") trim (msg_buffer), & " Integral" // phys_unit // & " Error" // phys_unit // & " Err[%] Acc Eff[%]" if (results%verbosity > 2) then write (msg_buffer, "(A, A)") trim (msg_buffer), & " (+)[%] (-)[%]" end if write (msg_buffer, "(A, A)") trim (msg_buffer), & " Chi2 N[It] |" call msg_message (unit=u, logfile=logfile) end subroutine write_header subroutine write_hline (results, unit) class(integration_results_t), intent(in) :: results integer, intent(in), optional :: unit integer :: u, len u = given_output_unit (unit); if (u < 0) return len = 77 if (results%verbosity > 1) len = len + 11 if (results%verbosity > 2) len = len + 16 write (u, "(A)") "|" // (repeat ("-", len)) // "|" flush (u) end subroutine write_hline subroutine write_dline (results, unit) class(integration_results_t), intent(in) :: results integer, intent(in), optional :: unit integer :: u, len u = given_output_unit (unit); if (u < 0) return len = 77 if (results%verbosity > 1) len = len + 11 if (results%verbosity > 2) len = len + 16 write (u, "(A)") "|" // (repeat ("=", len)) // "|" flush (u) end subroutine write_dline @ %def write_header write_hline write_dline @ During integration, we do not want to print all results at once, but each intermediate result as soon as we get it. Thus, the previous procedure is chopped in pieces. First piece: store the output unit and a flag whether we want to print to standard output as well. Then write the header if the results are still empty, i.e., before integration has started. The second piece writes a single result to the saved output channels. We call this from the [[record]] method, which can be called from the integrator directly. The third piece writes the average result, once a pass has been completed. The fourth piece writes a footer (if any), assuming that this is the final result. <>= procedure :: display_init => integration_results_display_init procedure :: display_current => integration_results_display_current procedure :: display_pass => integration_results_display_pass procedure :: display_final => integration_results_display_final <>= subroutine integration_results_display_init & (results, screen, unit) class(integration_results_t), intent(inout) :: results logical, intent(in) :: screen integer, intent(in), optional :: unit integer :: u if (present (unit)) results%unit = unit u = given_output_unit () results%screen = screen if (results%n_it == 0) then if (results%screen) then call results%write_dline (u) call results%write_header (u, & logfile=.false.) call results%write_dline (u) end if if (results%unit /= 0) then call results%write_dline (results%unit) call results%write_header (results%unit, & logfile=.false.) call results%write_dline (results%unit) end if else if (results%screen) then call results%write_hline (u) end if if (results%unit /= 0) then call results%write_hline (results%unit) end if end if end subroutine integration_results_display_init subroutine integration_results_display_current (results, pacify) class(integration_results_t), intent(in) :: results integer :: u logical, intent(in), optional :: pacify u = given_output_unit () if (results%screen) then call results%entry(results%n_it)%write (u, & verbosity = results%verbosity, suppress = pacify) end if if (results%unit /= 0) then call results%entry(results%n_it)%write ( & results%unit, verbosity = results%verbosity, suppress = pacify) end if end subroutine integration_results_display_current subroutine integration_results_display_pass (results, pacify) class(integration_results_t), intent(in) :: results logical, intent(in), optional :: pacify integer :: u u = given_output_unit () if (results%screen) then call results%write_hline (u) call results%average(results%entry(results%n_it)%pass)%write ( & u, verbosity = results%verbosity, suppress = pacify) end if if (results%unit /= 0) then call results%write_hline (results%unit) call results%average(results%entry(results%n_it)%pass)%write ( & results%unit, verbosity = results%verbosity, suppress = pacify) end if end subroutine integration_results_display_pass subroutine integration_results_display_final (results) class(integration_results_t), intent(inout) :: results integer :: u u = given_output_unit () if (results%screen) then call results%write_dline (u) end if if (results%unit /= 0) then call results%write_dline (results%unit) end if results%screen = .false. results%unit = 0 end subroutine integration_results_display_final @ %def integration_results_display_init @ %def integration_results_display_current @ %def integration_results_display_pass @ Expand the list of entries if the limit has been reached: <>= procedure :: expand => integration_results_expand <>= subroutine integration_results_expand (results) class(integration_results_t), intent(inout) :: results type(integration_entry_t), dimension(:), allocatable :: entry_tmp if (results%n_it == size (results%entry)) then allocate (entry_tmp (results%n_it)) entry_tmp = results%entry deallocate (results%entry) allocate (results%entry (results%n_it + RESULTS_CHUNK_SIZE)) results%entry(:results%n_it) = entry_tmp deallocate (entry_tmp) end if if (results%n_pass == size (results%average)) then allocate (entry_tmp (results%n_pass)) entry_tmp = results%average deallocate (results%average) allocate (results%average (results%n_it + RESULTS_CHUNK_SIZE)) results%average(:results%n_pass) = entry_tmp deallocate (entry_tmp) end if end subroutine integration_results_expand @ %def integration_results_expand @ Increment the [[current_pass]] counter. Must be done before each new integration pass; after integration, the recording method may use the value of this counter to define the entry. <>= procedure :: new_pass => integration_results_new_pass <>= subroutine integration_results_new_pass (results) class(integration_results_t), intent(inout) :: results results%current_pass = results%current_pass + 1 end subroutine integration_results_new_pass @ %def integration_results_new_pass @ Enter results into the results list. For the error value, we may compare them with a given threshold. This guards against numerical noise, if the exact error would be zero. <>= procedure :: append => integration_results_append <>= subroutine integration_results_append (results, & n_it, n_calls, n_calls_valid, & integral, error, efficiency, efficiency_pos, efficiency_neg, & chain_weights) class(integration_results_t), intent(inout) :: results integer, intent(in) :: n_it, n_calls, n_calls_valid real(default), intent(in) :: integral, error, efficiency, efficiency_pos, & & efficiency_neg real(default), dimension(:), intent(in), optional :: chain_weights logical :: improved type(integration_entry_t) :: entry real(default) :: err_checked improved = .true. if (results%n_it /= 0) improved = abs(accuracy (integral, error, n_calls)) & < abs(results%entry(results%n_it)%get_accuracy ()) err_checked = 0 if (abs (error) >= results%error_threshold) err_checked = error entry = integration_entry_t ( & results%process_type, results%current_pass, & results%n_it+1, n_it, n_calls, n_calls_valid, improved, & integral, err_checked, efficiency, efficiency_pos, efficiency_neg, & chain_weights=chain_weights) if (results%n_it == 0) then results%n_it = 1 results%n_pass = 1 else call results%expand () if (entry%pass /= results%entry(results%n_it)%pass) & results%n_pass = results%n_pass + 1 results%n_it = results%n_it + 1 end if results%entry(results%n_it) = entry results%average(results%n_pass) = & compute_average (results%entry, entry%pass) end subroutine integration_results_append @ %def integration_results_append @ Record an integration pass executed by an [[mci]] integrator object. There is a tolerance below we treat an error (relative to the integral) as zero. <>= real(default), parameter, public :: INTEGRATION_ERROR_TOLERANCE = 1e-10 @ %def INTEGRATION_ERROR_TOLERANCE @ <>= procedure :: record_simple => integration_results_record_simple <>= subroutine integration_results_record_simple & (object, n_it, n_calls, integral, error, efficiency, & chain_weights, suppress) class(integration_results_t), intent(inout) :: object integer, intent(in) :: n_it, n_calls real(default), intent(in) :: integral, error, efficiency real(default), dimension(:), intent(in), optional :: chain_weights real(default) :: err logical, intent(in), optional :: suppress err = 0._default if (abs (error) >= abs (integral) * INTEGRATION_ERROR_TOLERANCE) then err = error end if call object%append (n_it, n_calls, 0, integral, err, efficiency, 0._default,& & 0._default, chain_weights) call object%display_current (suppress) end subroutine integration_results_record_simple @ %def integration_results_record_simple @ Record extended results from integration pass. <>= procedure :: record_extended => integration_results_record_extended <>= subroutine integration_results_record_extended (object, n_it, n_calls,& & n_calls_valid, integral, error, efficiency, efficiency_pos,& & efficiency_neg, chain_weights, suppress) class(integration_results_t), intent(inout) :: object integer, intent(in) :: n_it, n_calls, n_calls_valid real(default), intent(in) :: integral, error, efficiency, efficiency_pos,& & efficiency_neg real(default), dimension(:), intent(in), optional :: chain_weights real(default) :: err logical, intent(in), optional :: suppress err = 0._default if (abs (error) >= abs (integral) * INTEGRATION_ERROR_TOLERANCE) then err = error end if call object%append (n_it, n_calls, n_calls_valid, integral, err, efficiency,& & efficiency_pos, efficiency_neg, chain_weights) call object%display_current (suppress) end subroutine integration_results_record_extended @ %def integration_results_record_extended @ Compute the average for all entries in the specified integration pass. The integrals are weighted w.r.t.\ their individual errors. The quoted error of the result is the expected error, computed from the weighted average of the given individual errors. This should be compared to the actual distribution of the results, from which we also can compute an error estimate if there is more than one iteration. The ratio of the distribution error and the averaged error, is the $\chi^2$ value. All error distributions are assumed Gaussian, of course. The $\chi^2$ value is a partial check for this assumption. If it is significantly greater than unity, there is something wrong with the individual errors. The efficiency returned is the one of the last entry in the integration pass. If any error vanishes, averaging by this algorithm would fail. In this case, we simply average the entries and use the deviations from this average (if any) to estimate the error. <>= type(integration_entry_t) function compute_average (entry, pass) & & result (result) type(integration_entry_t), dimension(:), intent(in) :: entry integer, intent(in) :: pass integer :: i logical, dimension(size(entry)) :: mask real(default), dimension(size(entry)) :: ivar real(default) :: sum_ivar, variance result%process_type = entry(1)%process_type result%pass = pass mask = entry%pass == pass .and. entry%process_type /= PRC_UNKNOWN result%it = maxval (entry%it, mask) result%n_it = count (mask) result%n_calls = sum (entry%n_calls, mask) result%n_calls_valid = sum (entry%n_calls_valid, mask) if (.not. any (mask .and. entry%error == 0)) then where (mask) ivar = 1 / entry%error ** 2 elsewhere ivar = 0 end where sum_ivar = sum (ivar, mask) variance = 0 if (sum_ivar /= 0) then variance = 1 / sum_ivar end if result%integral = sum (entry%integral * ivar, mask) * variance if (result%n_it > 1) then result%chi2 = & sum ((entry%integral - result%integral)**2 * ivar, mask) & / (result%n_it - 1) end if else if (result%n_it /= 0) then result%integral = sum (entry%integral, mask) / result%n_it variance = 0 if (result%n_it > 1) then variance = & sum ((entry%integral - result%integral)**2, mask) & / (result%n_it - 1) if (result%integral /= 0) then if (abs (variance / result%integral) & < 100 * epsilon (1._default)) then variance = 0 end if end if end if result%chi2 = variance / result%n_it end if result%error = sqrt (variance) result%efficiency = entry(last_index (mask))%efficiency result%efficiency_pos = entry(last_index (mask))%efficiency_pos result%efficiency_neg = entry(last_index (mask))%efficiency_neg contains integer function last_index (mask) result (index) logical, dimension(:), intent(in) :: mask integer :: i do i = size (mask), 1, -1 if (mask(i)) exit end do index = i end function last_index end function compute_average @ %def compute_average @ \subsection{Access results} Return true if the results object has entries. <>= procedure :: exist => integration_results_exist <>= function integration_results_exist (results) result (flag) logical :: flag class(integration_results_t), intent(in) :: results flag = results%n_pass > 0 end function integration_results_exist @ %def integration_results_exist @ Retrieve information from the results record. If [[last]] is set and true, take the last iteration. If [[it]] is set instead, take this iteration. If [[pass]] is set, take this average. If none is set, take the final average. If the result would be invalid, the entry is not assigned. Due to default initialization, this returns a null entry. <>= procedure :: get_entry => results_get_entry <>= function results_get_entry (results, last, it, pass) result (entry) class(integration_results_t), intent(in) :: results type(integration_entry_t) :: entry logical, intent(in), optional :: last integer, intent(in), optional :: it, pass if (present (last)) then if (allocated (results%entry) .and. results%n_it > 0) then entry = results%entry(results%n_it) else call error () end if else if (present (it)) then if (allocated (results%entry) .and. it > 0 .and. it <= results%n_it) then entry = results%entry(it) else call error () end if else if (present (pass)) then if (allocated (results%average) & .and. pass > 0 .and. pass <= results%n_pass) then entry = results%average (pass) else call error () end if else if (allocated (results%average) .and. results%n_pass > 0) then entry = results%average (results%n_pass) else call error () end if end if contains subroutine error () call msg_fatal ("Requested integration result is not available") end subroutine error end function results_get_entry @ %def results_get_entry @ The individual procedures. The [[results]] record should have the [[target]] attribute, but only locally within the function. <>= procedure :: get_n_calls => integration_results_get_n_calls procedure :: get_integral => integration_results_get_integral procedure :: get_error => integration_results_get_error procedure :: get_accuracy => integration_results_get_accuracy procedure :: get_chi2 => integration_results_get_chi2 procedure :: get_efficiency => integration_results_get_efficiency <>= function integration_results_get_n_calls (results, last, it, pass) & result (n_calls) class(integration_results_t), intent(in), target :: results integer :: n_calls logical, intent(in), optional :: last integer, intent(in), optional :: it, pass type(integration_entry_t) :: entry entry = results%get_entry (last, it, pass) n_calls = entry%get_n_calls () end function integration_results_get_n_calls function integration_results_get_integral (results, last, it, pass) & result (integral) class(integration_results_t), intent(in), target :: results real(default) :: integral logical, intent(in), optional :: last integer, intent(in), optional :: it, pass type(integration_entry_t) :: entry entry = results%get_entry (last, it, pass) integral = entry%get_integral () end function integration_results_get_integral function integration_results_get_error (results, last, it, pass) & result (error) class(integration_results_t), intent(in), target :: results real(default) :: error logical, intent(in), optional :: last integer, intent(in), optional :: it, pass type(integration_entry_t) :: entry entry = results%get_entry (last, it, pass) error = entry%get_error () end function integration_results_get_error function integration_results_get_accuracy (results, last, it, pass) & result (accuracy) class(integration_results_t), intent(in), target :: results real(default) :: accuracy logical, intent(in), optional :: last integer, intent(in), optional :: it, pass type(integration_entry_t) :: entry entry = results%get_entry (last, it, pass) accuracy = entry%get_accuracy () end function integration_results_get_accuracy function integration_results_get_chi2 (results, last, it, pass) & result (chi2) class(integration_results_t), intent(in), target :: results real(default) :: chi2 logical, intent(in), optional :: last integer, intent(in), optional :: it, pass type(integration_entry_t) :: entry entry = results%get_entry (last, it, pass) chi2 = entry%get_chi2 () end function integration_results_get_chi2 function integration_results_get_efficiency (results, last, it, pass) & result (efficiency) class(integration_results_t), intent(in), target :: results real(default) :: efficiency logical, intent(in), optional :: last integer, intent(in), optional :: it, pass type(integration_entry_t) :: entry entry = results%get_entry (last, it, pass) efficiency = entry%get_efficiency () end function integration_results_get_efficiency @ %def integration_results_get_n_calls @ %def integration_results_get_integral @ %def integration_results_get_error @ %def integration_results_get_accuracy @ %def integration_results_get_chi2 @ %def integration_results_get_efficiency @ Return the last pass index and the index of the last iteration \emph{within} the last pass. The third routine returns the absolute index of the last iteration. <>= function integration_results_get_current_pass (results) result (pass) integer :: pass type(integration_results_t), intent(in) :: results pass = results%n_pass end function integration_results_get_current_pass function integration_results_get_current_it (results) result (it) integer :: it type(integration_results_t), intent(in) :: results it = 0 if (allocated (results%entry)) then it = count (results%entry(1:results%n_it)%pass == results%n_pass) end if end function integration_results_get_current_it function integration_results_get_last_it (results) result (it) integer :: it type(integration_results_t), intent(in) :: results it = results%n_it end function integration_results_get_last_it @ %def integration_results_get_current_pass @ %def integration_results_get_current_it @ %def integration_results_get_last_it @ Return the index of the best iteration (lowest accuracy value) within the current pass. If none qualifies, return zero. <>= function integration_results_get_best_it (results) result (it) integer :: it type(integration_results_t), intent(in) :: results integer :: i real(default) :: acc, acc_best acc_best = -1 it = 0 do i = 1, results%n_it if (results%entry(i)%pass == results%n_pass) then acc = integration_entry_get_accuracy (results%entry(i)) if (acc_best < 0 .or. acc <= acc_best) then acc_best = acc it = i end if end if end do end function integration_results_get_best_it @ %def integration_results_get_best_it @ Compute the MD5 sum by printing everything and checksumming the resulting file. <>= function integration_results_get_md5sum (results) result (md5sum_results) character(32) :: md5sum_results type(integration_results_t), intent(in) :: results integer :: u u = free_unit () open (unit = u, status = "scratch", action = "readwrite") call results%write_verbose (u) rewind (u) md5sum_results = md5sum (u) close (u) end function integration_results_get_md5sum @ %def integration_results_get_md5sum @ This is (ab)used to suppress numerical noise when integrating constant matrix elements. <>= procedure :: pacify => integration_results_pacify <>= subroutine integration_results_pacify (results, efficiency_reset) class(integration_results_t), intent(inout) :: results logical, intent(in), optional :: efficiency_reset integer :: i logical :: reset reset = .false. if (present (efficiency_reset)) reset = efficiency_reset if (allocated (results%entry)) then do i = 1, size (results%entry) call pacify (results%entry(i)%error, & results%entry(i)%integral * 1.E-9_default) if (reset) results%entry(i)%efficiency = 1 end do end if if (allocated (results%average)) then do i = 1, size (results%average) call pacify (results%average(i)%error, & results%average(i)%integral * 1.E-9_default) if (reset) results%average(i)%efficiency = 1 end do end if end subroutine integration_results_pacify @ %def integration_results_pacify @ <>= procedure :: record_correction => integration_results_record_correction <>= subroutine integration_results_record_correction (object, corr, err) class(integration_results_t), intent(inout) :: object real(default), intent(in) :: corr, err integer :: u u = given_output_unit () if (object%screen) then call object%write_hline (u) call msg_message ("NLO Correction: [O(alpha_s+1)/O(alpha_s)]") - write(msg_buffer,'(1X,A1,F8.4,A4,F9.5,1X,A3)') '(', corr, ' +- ', err, ') %' + write(msg_buffer,'(1X,A1,F7.2,A4,F6.2,1X,A3)') '(', corr, ' +- ', err, ') %' call msg_message () end if end subroutine integration_results_record_correction @ %def integration_results_record_correction @ \subsection{Results display} Write a driver file for history visualization. The ratio of $y$ range over $y$ value must not become too small, otherwise we run into an arithmetic overflow in GAMELAN. 2\% appears to be safe. <>= real, parameter, public :: GML_MIN_RANGE_RATIO = 0.02 <>= public :: integration_results_write_driver <>= subroutine integration_results_write_driver (results, filename, eff_reset) type(integration_results_t), intent(inout) :: results type(string_t), intent(in) :: filename logical, intent(in), optional :: eff_reset type(string_t) :: file_tex integer :: unit integer :: n, i, n_pass, pass integer, dimension(:), allocatable :: ipass real(default) :: ymin, ymax, yavg, ydif, y0, y1 real(default), dimension(results%n_it) :: ymin_arr, ymax_arr logical :: reset file_tex = filename // ".tex" unit = free_unit () open (unit=unit, file=char(file_tex), action="write", status="replace") reset = .false.; if (present (eff_reset)) reset = eff_reset n = results%n_it n_pass = results%n_pass allocate (ipass (results%n_pass)) ipass(1) = 0 pass = 2 do i = 1, n-1 if (integration_entry_get_pass (results%entry(i)) & /= integration_entry_get_pass (results%entry(i+1))) then ipass(pass) = i pass = pass + 1 end if end do ymin_arr = integration_entry_get_integral (results%entry(:n)) & - integration_entry_get_error (results%entry(:n)) ymin = minval (ymin_arr) ymax_arr = integration_entry_get_integral (results%entry(:n)) & + integration_entry_get_error (results%entry(:n)) ymax = maxval (ymax_arr) yavg = (ymax + ymin) / 2 ydif = (ymax - ymin) if (ydif * 1.5 > GML_MIN_RANGE_RATIO * yavg) then y0 = yavg - ydif * 0.75 y1 = yavg + ydif * 0.75 else y0 = yavg * (1 - GML_MIN_RANGE_RATIO / 2) y1 = yavg * (1 + GML_MIN_RANGE_RATIO / 2) end if write (unit, "(A)") "\documentclass{article}" write (unit, "(A)") "\usepackage{a4wide}" write (unit, "(A)") "\usepackage{gamelan}" write (unit, "(A)") "\usepackage{amsmath}" write (unit, "(A)") "" write (unit, "(A)") "\begin{document}" write (unit, "(A)") "\begin{gmlfile}" write (unit, "(A)") "\section*{Integration Results Display}" write (unit, "(A)") "" write (unit, "(A)") "Process: \verb|" // char (filename) // "|" write (unit, "(A)") "" write (unit, "(A)") "\vspace*{2\baselineskip}" write (unit, "(A)") "\unitlength 1mm" write (unit, "(A)") "\begin{gmlcode}" write (unit, "(A)") " picture sym; sym = fshape (circle scaled 1mm)();" write (unit, "(A)") " color col.band; col.band = 0.9white;" write (unit, "(A)") " color col.eband; col.eband = 0.98white;" write (unit, "(A)") "\end{gmlcode}" write (unit, "(A)") "\begin{gmlgraph*}(130,180)[history]" write (unit, "(A)") " setup (linear, linear);" write (unit, "(A,I0,A)") " history.n_pass = ", n_pass, ";" write (unit, "(A,I0,A)") " history.n_it = ", n, ";" write (unit, "(A,A,A)") " history.y0 = #""", char (mp_format (y0)), """;" write (unit, "(A,A,A)") " history.y1 = #""", char (mp_format (y1)), """;" write (unit, "(A)") & " graphrange (#0.5, history.y0), (#(n+0.5), history.y1);" do pass = 1, n_pass write (unit, "(A,I0,A,I0,A)") & " history.pass[", pass, "] = ", ipass(pass), ";" write (unit, "(A,I0,A,A,A)") & " history.avg[", pass, "] = #""", & char (mp_format & (integration_entry_get_integral (results%average(pass)))), & """;" write (unit, "(A,I0,A,A,A)") & " history.err[", pass, "] = #""", & char (mp_format & (integration_entry_get_error (results%average(pass)))), & """;" write (unit, "(A,I0,A,A,A)") & " history.chi[", pass, "] = #""", & char (mp_format & (integration_entry_get_chi2 (results%average(pass)))), & """;" end do write (unit, "(A,I0,A,I0,A)") & " history.pass[", n_pass + 1, "] = ", n, ";" write (unit, "(A)") " for i = 1 upto history.n_pass:" write (unit, "(A)") " if history.chi[i] greater one:" write (unit, "(A)") " fill plot (" write (unit, "(A)") & " (#(history.pass[i] +.5), " & // "history.avg[i] minus history.err[i] times history.chi[i])," write (unit, "(A)") & " (#(history.pass[i+1]+.5), " & // "history.avg[i] minus history.err[i] times history.chi[i])," write (unit, "(A)") & " (#(history.pass[i+1]+.5), " & // "history.avg[i] plus history.err[i] times history.chi[i])," write (unit, "(A)") & " (#(history.pass[i] +.5), " & // "history.avg[i] plus history.err[i] times history.chi[i])" write (unit, "(A)") " ) withcolor col.eband fi;" write (unit, "(A)") " fill plot (" write (unit, "(A)") & " (#(history.pass[i] +.5), history.avg[i] minus history.err[i])," write (unit, "(A)") & " (#(history.pass[i+1]+.5), history.avg[i] minus history.err[i])," write (unit, "(A)") & " (#(history.pass[i+1]+.5), history.avg[i] plus history.err[i])," write (unit, "(A)") & " (#(history.pass[i] +.5), history.avg[i] plus history.err[i])" write (unit, "(A)") " ) withcolor col.band;" write (unit, "(A)") " draw plot (" write (unit, "(A)") & " (#(history.pass[i] +.5), history.avg[i])," write (unit, "(A)") & " (#(history.pass[i+1]+.5), history.avg[i])" write (unit, "(A)") " ) dashed evenly;" write (unit, "(A)") " endfor" write (unit, "(A)") " for i = 1 upto history.n_pass + 1:" write (unit, "(A)") " draw plot (" write (unit, "(A)") & " (#(history.pass[i]+.5), history.y0)," write (unit, "(A)") & " (#(history.pass[i]+.5), history.y1)" write (unit, "(A)") " ) dashed withdots;" write (unit, "(A)") " endfor" do i = 1, n write (unit, "(A,I0,A,A,A,A,A)") " plot (history) (#", & i, ", #""", & char (mp_format (integration_entry_get_integral (results%entry(i)))),& """) vbar #""", & char (mp_format (integration_entry_get_error (results%entry(i)))), & """;" end do write (unit, "(A)") " draw piecewise from (history) " & // "withsymbol sym;" write (unit, "(A)") " fullgrid.lr (5,20);" write (unit, "(A)") " standardgrid.bt (n);" write (unit, "(A)") " begingmleps ""Whizard-Logo.eps"";" write (unit, "(A)") " base := (120*unitlength,170*unitlength);" write (unit, "(A)") " height := 9.6*unitlength;" write (unit, "(A)") " width := 11.2*unitlength;" write (unit, "(A)") " endgmleps;" write (unit, "(A)") "\end{gmlgraph*}" write (unit, "(A)") "\end{gmlfile}" write (unit, "(A)") "\clearpage" write (unit, "(A)") "\begin{verbatim}" if (reset) then call results%pacify (reset) end if call integration_results_write (results, unit) write (unit, "(A)") "\end{verbatim}" write (unit, "(A)") "\end{document}" close (unit) end subroutine integration_results_write_driver @ %def integration_results_write_driver @ Call \LaTeX\ and Metapost for the history driver file, and convert to PS and PDF. <>= public :: integration_results_compile_driver <>= subroutine integration_results_compile_driver (results, filename, os_data) type(integration_results_t), intent(in) :: results type(string_t), intent(in) :: filename type(os_data_t), intent(in) :: os_data integer :: unit_dev, status type(string_t) :: file_tex, file_dvi, file_ps, file_pdf, file_mp type(string_t) :: setenv_tex, setenv_mp, pipe, pipe_dvi if (.not. os_data%event_analysis) then call msg_warning ("Skipping integration history display " & // "because latex or mpost is not available") return end if file_tex = filename // ".tex" file_dvi = filename // ".dvi" file_ps = filename // ".ps" file_pdf = filename // ".pdf" file_mp = filename // ".mp" call msg_message ("Creating integration history display "& // char (file_ps) // " and " // char (file_pdf)) BLOCK: do unit_dev = free_unit () open (file = "/dev/null", unit = unit_dev, & action = "write", iostat = status) if (status /= 0) then pipe = "" pipe_dvi = "" else pipe = " > /dev/null" pipe_dvi = " 2>/dev/null 1>/dev/null" end if close (unit_dev) if (os_data%whizard_texpath /= "") then setenv_tex = & "TEXINPUTS=" // os_data%whizard_texpath // ":$TEXINPUTS " setenv_mp = & "MPINPUTS=" // os_data%whizard_texpath // ":$MPINPUTS " else setenv_tex = "" setenv_mp = "" end if call os_system_call (setenv_tex // os_data%latex // " " // & file_tex // pipe, status) if (status /= 0) exit BLOCK if (os_data%gml /= "") then call os_system_call (setenv_mp // os_data%gml // " " // & file_mp // pipe, status) else call msg_error ("Could not use GAMELAN/MetaPOST.") exit BLOCK end if if (status /= 0) exit BLOCK call os_system_call (setenv_tex // os_data%latex // " " // & file_tex // pipe, status) if (status /= 0) exit BLOCK if (os_data%event_analysis_ps) then call os_system_call (os_data%dvips // " " // & file_dvi // pipe_dvi, status) if (status /= 0) exit BLOCK else call msg_warning ("Skipping PostScript generation because dvips " & // "is not available") exit BLOCK end if if (os_data%event_analysis_pdf) then call os_system_call (os_data%ps2pdf // " " // & file_ps, status) if (status /= 0) exit BLOCK else call msg_warning ("Skipping PDF generation because ps2pdf " & // "is not available") exit BLOCK end if exit BLOCK end do BLOCK if (status /= 0) then call msg_error ("Unable to compile integration history display") end if end subroutine integration_results_compile_driver @ %def integration_results_compile_driver @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[integration_results_ut.f90]]>>= <> module integration_results_ut use unit_tests use integration_results_uti <> <> contains <> end module integration_results_ut @ %def integration_results_ut @ <<[[integration_results_uti.f90]]>>= <> module integration_results_uti <> use integration_results <> <> contains <> end module integration_results_uti @ %def integration_results_ut @ API: driver for the unit tests below. <>= public :: integration_results_test <>= subroutine integration_results_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine integration_results_test @ %def integration_results_test @ \subsubsection{Integration entry} <>= call test (integration_results_1, "integration_results_1", & "record single line and write to log", & u, results) <>= public :: integration_results_1 <>= subroutine integration_results_1 (u) integer, intent(in) :: u type(integration_entry_t) :: entry write (u, "(A)") "* Test output: integration_results_1" write (u, "(A)") "* Purpose: record single entry and write to log" write (u, "(A)") write (u, "(A)") "* Write single line output" write (u, "(A)") entry = integration_entry_t ( & & process_type = 1, & & pass = 1, & & it = 1, & & n_it = 10, & & n_calls = 1000, & & n_calls_valid = 500, & & improved = .true., & & integral = 1.0_default, & & error = 0.5_default, & & efficiency = 0.25_default, & & efficiency_pos = 0.22_default, & & efficiency_neg = 0.03_default) call entry%write (u, 3) write (u, "(A)") write (u, "(A)") "* Test output end: integration_results_1" end subroutine integration_results_1 @ %def integration_results_1 @ <>= call test (integration_results_2, "integration_results_2", & "record single result and write to log", & u, results) <>= public :: integration_results_2 <>= subroutine integration_results_2 (u) integer, intent(in) :: u type(integration_results_t) :: results write (u, "(A)") "* Test output: integration_results_2" write (u, "(A)") "* Purpose: record single result and write to log" write (u, "(A)") write (u, "(A)") "* Write single line output" write (u, "(A)") call results%init (PRC_DECAY) call results%append (1, 250, 0, 1.0_default, 0.5_default, 0.25_default,& & 0._default, 0._default) call results%write (u) write (u, "(A)") write (u, "(A)") "* Test output end: integration_results_2" end subroutine integration_results_2 @ %def integration_results_2 @ <>= call test (integration_results_3, "integration_results_3", & "initialize display and add/display each entry", & u, results) <>= public :: integration_results_3 <>= subroutine integration_results_3 (u) integer, intent(in) :: u type(integration_results_t) :: results write (u, "(A)") "* Test output: integration_results_2" write (u, "(A)") "* Purpose: intialize display, record three entries,& & display pass average and finalize display" write (u, "(A)") write (u, "(A)") "* Initialize display and add entry" write (u, "(A)") call results%init (PRC_DECAY) call results%set_verbosity (1) call results%display_init (screen = .false., unit = u) call results%new_pass () call results%record (1, 250, 1.0_default, 0.5_default, 0.25_default) call results%record (1, 250, 1.1_default, 0.5_default, 0.25_default) call results%record (1, 250, 0.9_default, 0.5_default, 0.25_default) write (u, "(A)") write (u, "(A)") "* Display pass" write (u, "(A)") call results%display_pass () write (u, "(A)") write (u, "(A)") "* Finalize displays" write (u, "(A)") call results%display_final () write (u, "(A)") write (u, "(A)") "* Test output end: integration_results_3" end subroutine integration_results_3 @ %def integration_results_3 @ <>= call test (integration_results_4, "integration_results_4", & "record extended results and display", & u, results) <>= public :: integration_results_4 <>= subroutine integration_results_4 (u) integer, intent(in) :: u type(integration_results_t) :: results write (u, "(A)") "* Test output: integration_results_4" write (u, "(A)") "* Purpose: record extended results and display with verbosity = 2" write (u, "(A)") write (u, "(A)") "* Initialize display and record extended result" write (u, "(A)") call results%init (PRC_DECAY) call results%set_verbosity (2) call results%display_init (screen = .false., unit = u) call results%new_pass () call results%record (1, 250, 150, 1.0_default, 0.5_default, 0.25_default,& & 0.22_default, 0.03_default) call results%record (1, 250, 180, 1.1_default, 0.5_default, 0.25_default,& & 0.23_default, 0.02_default) call results%record (1, 250, 130, 0.9_default, 0.5_default, 0.25_default,& & 0.25_default, 0.00_default) write (u, "(A)") write (u, "(A)") "* Display pass" write (u, "(A)") call results%display_pass () write (u, "(A)") write (u, "(A)") "* Finalize displays" write (u, "(A)") call results%display_final () write (u, "(A)") write (u, "(A)") "* Test output end: integration_results_4" end subroutine integration_results_4 @ %def integration_results_4 @ <>= call test (integration_results_5, "integration_results_5", & "record extended results and display", & u, results) <>= public :: integration_results_5 <>= subroutine integration_results_5 (u) integer, intent(in) :: u type(integration_results_t) :: results write (u, "(A)") "* Test output: integration_results_5" write (u, "(A)") "* Purpose: record extended results and display with verbosity = 3" write (u, "(A)") write (u, "(A)") "* Initialize display and record extended result" write (u, "(A)") call results%init (PRC_DECAY) call results%set_verbosity (3) call results%display_init (screen = .false., unit = u) call results%new_pass () call results%record (1, 250, 150, 1.0_default, 0.5_default, 0.25_default,& & 0.22_default, 0.03_default) call results%record (1, 250, 180, 1.1_default, 0.5_default, 0.25_default,& & 0.23_default, 0.02_default) call results%record (1, 250, 130, 0.9_default, 0.5_default, 0.25_default,& & 0.25_default, 0.00_default) call results%display_pass () call results%display_final () write (u, "(A)") write (u, "(A)") "* Test output end: integration_results_5" end subroutine integration_results_5 @ %def integration_results_5 @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Dummy integrator} This implementation acts as a placeholder for cases where no integration or event generation is required at all. <<[[mci_none.f90]]>>= <> module mci_none <> use io_units, only: given_output_unit use diagnostics, only: msg_message, msg_fatal use phs_base, only: phs_channel_t use mci_base <> <> <> contains <> end module mci_none @ %def mci_none @ \subsection{Integrator} The object contains the methods for integration and event generation. For the actual work and data storage, it spawns an instance object. After an integration pass, we update the [[max]] parameter to indicate the maximum absolute value of the integrand that the integrator encountered. This is required for event generation. <>= public :: mci_none_t <>= type, extends (mci_t) :: mci_none_t contains <> end type mci_none_t @ %def mci_t @ Finalizer: no-op. <>= procedure :: final => mci_none_final <>= subroutine mci_none_final (object) class(mci_none_t), intent(inout) :: object end subroutine mci_none_final @ %def mci_none_final @ Output. <>= procedure :: write => mci_none_write <>= subroutine mci_none_write (object, unit, pacify, md5sum_version) class(mci_none_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify logical, intent(in), optional :: md5sum_version integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Integrator: non-functional dummy" end subroutine mci_none_write @ %def mci_none_write @ Startup message: short version. <>= procedure :: startup_message => mci_none_startup_message <>= subroutine mci_none_startup_message (mci, unit, n_calls) class(mci_none_t), intent(in) :: mci integer, intent(in), optional :: unit, n_calls call msg_message ("Integrator: none") end subroutine mci_none_startup_message @ %def mci_none_startup_message @ Log entry: just headline. <>= procedure :: write_log_entry => mci_none_write_log_entry <>= subroutine mci_none_write_log_entry (mci, u) class(mci_none_t), intent(in) :: mci integer, intent(in) :: u write (u, "(1x,A)") "MC Integrator is none (no-op)" end subroutine mci_none_write_log_entry @ %def mci_none_write_log_entry @ MD5 sum: nothing. <>= procedure :: compute_md5sum => mci_none_compute_md5sum <>= subroutine mci_none_compute_md5sum (mci, pacify) class(mci_none_t), intent(inout) :: mci logical, intent(in), optional :: pacify end subroutine mci_none_compute_md5sum @ %def mci_none_compute_md5sum @ The number of channels must be one. <>= procedure :: set_dimensions => mci_none_set_dimensions <>= subroutine mci_none_set_dimensions (mci, n_dim, n_channel) class(mci_none_t), intent(inout) :: mci integer, intent(in) :: n_dim integer, intent(in) :: n_channel if (n_channel == 1) then mci%n_channel = n_channel mci%n_dim = n_dim allocate (mci%dim_is_binned (mci%n_dim)) mci%dim_is_binned = .true. mci%n_dim_binned = count (mci%dim_is_binned) allocate (mci%n_bin (mci%n_dim)) mci%n_bin = 0 else call msg_fatal ("Attempt to initialize single-channel integrator & &for multiple channels") end if end subroutine mci_none_set_dimensions @ %def mci_none_set_dimensions @ Required by API. <>= procedure :: declare_flat_dimensions => mci_none_ignore_flat_dimensions <>= subroutine mci_none_ignore_flat_dimensions (mci, dim_flat) class(mci_none_t), intent(inout) :: mci integer, dimension(:), intent(in) :: dim_flat end subroutine mci_none_ignore_flat_dimensions @ %def mci_none_ignore_flat_dimensions @ Required by API. <>= procedure :: declare_equivalences => mci_none_ignore_equivalences <>= subroutine mci_none_ignore_equivalences (mci, channel, dim_offset) class(mci_none_t), intent(inout) :: mci type(phs_channel_t), dimension(:), intent(in) :: channel integer, intent(in) :: dim_offset end subroutine mci_none_ignore_equivalences @ %def mci_none_ignore_equivalences @ Allocate instance with matching type. <>= procedure :: allocate_instance => mci_none_allocate_instance <>= subroutine mci_none_allocate_instance (mci, mci_instance) class(mci_none_t), intent(in) :: mci class(mci_instance_t), intent(out), pointer :: mci_instance allocate (mci_none_instance_t :: mci_instance) end subroutine mci_none_allocate_instance @ %def mci_none_allocate_instance @ Integrate. This must not be called at all. <>= procedure :: integrate => mci_none_integrate <>= subroutine mci_none_integrate (mci, instance, sampler, n_it, n_calls, & results, pacify) class(mci_none_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: pacify class(mci_results_t), intent(inout), optional :: results call msg_fatal ("Integration: attempt to integrate with the 'mci_none' method") end subroutine mci_none_integrate @ %def mci_none_integrate @ Simulation initializer and finalizer: nothing to do here. <>= procedure :: prepare_simulation => mci_none_ignore_prepare_simulation <>= subroutine mci_none_ignore_prepare_simulation (mci) class(mci_none_t), intent(inout) :: mci end subroutine mci_none_ignore_prepare_simulation @ %def mci_none_ignore_prepare_simulation @ Generate events, must not be called. <>= procedure :: generate_weighted_event => mci_none_generate_no_event procedure :: generate_unweighted_event => mci_none_generate_no_event <>= subroutine mci_none_generate_no_event (mci, instance, sampler) class(mci_none_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler call msg_fatal ("Integration: attempt to generate event with the 'mci_none' method") end subroutine mci_none_generate_no_event @ %def mci_none_generate_no_event @ Rebuild an event, no-op. <>= procedure :: rebuild_event => mci_none_rebuild_event <>= subroutine mci_none_rebuild_event (mci, instance, sampler, state) class(mci_none_t), intent(inout) :: mci class(mci_instance_t), intent(inout) :: instance class(mci_sampler_t), intent(inout) :: sampler class(mci_state_t), intent(in) :: state end subroutine mci_none_rebuild_event @ %def mci_none_rebuild_event @ \subsection{Integrator instance} Covering the case of flat dimensions, we store a complete [[x]] array. This is filled when generating events. <>= public :: mci_none_instance_t <>= type, extends (mci_instance_t) :: mci_none_instance_t contains <> end type mci_none_instance_t @ %def mci_none_instance_t @ Output. <>= procedure :: write => mci_none_instance_write <>= subroutine mci_none_instance_write (object, unit, pacify) class(mci_none_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Integrator instance: non-functional dummy" end subroutine mci_none_instance_write @ %def mci_none_instance_write @ The finalizer is empty. <>= procedure :: final => mci_none_instance_final <>= subroutine mci_none_instance_final (object) class(mci_none_instance_t), intent(inout) :: object end subroutine mci_none_instance_final @ %def mci_none_instance_final @ Initializer, empty. <>= procedure :: init => mci_none_instance_init <>= subroutine mci_none_instance_init (mci_instance, mci) class(mci_none_instance_t), intent(out) :: mci_instance class(mci_t), intent(in), target :: mci end subroutine mci_none_instance_init @ %def mci_none_instance_init @ Copy the stored extrema of the integrand in the instance record. <>= procedure :: get_max => mci_none_instance_get_max <>= subroutine mci_none_instance_get_max (instance) class(mci_none_instance_t), intent(inout) :: instance associate (mci => instance%mci) if (mci%max_known) then instance%max_known = .true. instance%max = mci%max instance%min = mci%min instance%max_abs = mci%max_abs instance%min_abs = mci%min_abs end if end associate end subroutine mci_none_instance_get_max @ %def mci_none_instance_get_max @ Reverse operations: recall the extrema, but only if they are wider than the extrema already stored in the configuration. Also recalculate the efficiency value. <>= procedure :: set_max => mci_none_instance_set_max <>= subroutine mci_none_instance_set_max (instance) class(mci_none_instance_t), intent(inout) :: instance associate (mci => instance%mci) if (instance%max_known) then if (mci%max_known) then mci%max = max (mci%max, instance%max) mci%min = min (mci%min, instance%min) mci%max_abs = max (mci%max_abs, instance%max_abs) mci%min_abs = min (mci%min_abs, instance%min_abs) else mci%max = instance%max mci%min = instance%min mci%max_abs = instance%max_abs mci%min_abs = instance%min_abs mci%max_known = .true. end if if (mci%max_abs /= 0) then if (mci%integral_neg == 0) then mci%efficiency = mci%integral / mci%max_abs mci%efficiency_known = .true. else if (mci%n_calls /= 0) then mci%efficiency = & (mci%integral_pos - mci%integral_neg) / mci%max_abs mci%efficiency_known = .true. end if end if end if end associate end subroutine mci_none_instance_set_max @ %def mci_none_instance_set_max @ The weight cannot be computed. <>= procedure :: compute_weight => mci_none_instance_compute_weight <>= subroutine mci_none_instance_compute_weight (mci, c) class(mci_none_instance_t), intent(inout) :: mci integer, intent(in) :: c call msg_fatal ("Integration: attempt to compute weight with the 'mci_none' method") end subroutine mci_none_instance_compute_weight @ %def mci_none_instance_compute_weight @ Record the integrand, no-op. <>= procedure :: record_integrand => mci_none_instance_record_integrand <>= subroutine mci_none_instance_record_integrand (mci, integrand) class(mci_none_instance_t), intent(inout) :: mci real(default), intent(in) :: integrand end subroutine mci_none_instance_record_integrand @ %def mci_none_instance_record_integrand @ No-op. <>= procedure :: init_simulation => mci_none_instance_init_simulation procedure :: final_simulation => mci_none_instance_final_simulation <>= subroutine mci_none_instance_init_simulation (instance, safety_factor) class(mci_none_instance_t), intent(inout) :: instance real(default), intent(in), optional :: safety_factor end subroutine mci_none_instance_init_simulation subroutine mci_none_instance_final_simulation (instance) class(mci_none_instance_t), intent(inout) :: instance end subroutine mci_none_instance_final_simulation @ %def mci_none_instance_init_simulation @ %def mci_none_instance_final_simulation @ Return excess weight for the current event: return zero, just in case. <>= procedure :: get_event_excess => mci_none_instance_get_event_excess <>= function mci_none_instance_get_event_excess (mci) result (excess) class(mci_none_instance_t), intent(in) :: mci real(default) :: excess excess = 0 end function mci_none_instance_get_event_excess @ %def mci_none_instance_get_event_excess @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[mci_none_ut.f90]]>>= <> module mci_none_ut use unit_tests use mci_none_uti <> <> contains <> end module mci_none_ut @ %def mci_none_ut @ <<[[mci_none_uti.f90]]>>= <> module mci_none_uti use mci_base use mci_none <> <> <> contains <> end module mci_none_uti @ %def mci_none_ut @ API: driver for the unit tests below. <>= public :: mci_none_test <>= subroutine mci_none_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine mci_none_test @ %def mci_none_test @ \subsubsection{Trivial sanity check} Construct an integrator and display it. <>= call test (mci_none_1, "mci_none_1", & "dummy integrator", & u, results) <>= public :: mci_none_1 <>= subroutine mci_none_1 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler write (u, "(A)") "* Test output: mci_none_1" write (u, "(A)") "* Purpose: display mci configuration" write (u, "(A)") write (u, "(A)") "* Allocate integrator" write (u, "(A)") allocate (mci_none_t :: mci) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) call mci_instance%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_none_1" end subroutine mci_none_1 @ %def mci_none_1 @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Simple midpoint integration} This is a most simple implementation of an integrator. The algorithm is the straightforward multi-dimensional midpoint rule, i.e., the integration hypercube is binned uniformly, the integrand is evaluated at the midpoints of each bin, and the result is the average. The binning is equivalent for all integration dimensions. This rule is accurate to the order $h^2$, where $h$ is the bin width. Given that $h=N^{-1/d}$, where $d$ is the integration dimension and $N$ is the total number of sampling points, we get a relative error of order $N^{-2/d}$. This is superior to MC integration if $d<4$, and equivalent if $d=4$. It is not worse than higher-order formulas (such as Gauss integration) if the integrand is not smooth, e.g., if it contains cuts. The integrator is specifically single-channel. However, we do not limit the dimension. <<[[mci_midpoint.f90]]>>= <> module mci_midpoint <> use io_units use diagnostics use phs_base use mci_base <> <> <> contains <> end module mci_midpoint @ %def mci_midpoint @ \subsection{Integrator} The object contains the methods for integration and event generation. For the actual work and data storage, it spawns an instance object. After an integration pass, we update the [[max]] parameter to indicate the maximum absolute value of the integrand that the integrator encountered. This is required for event generation. <>= public :: mci_midpoint_t <>= type, extends (mci_t) :: mci_midpoint_t integer :: n_dim_binned = 0 logical, dimension(:), allocatable :: dim_is_binned logical :: calls_known = .false. integer :: n_calls = 0 integer :: n_calls_pos = 0 integer :: n_calls_nul = 0 integer :: n_calls_neg = 0 real(default) :: integral_pos = 0 real(default) :: integral_neg = 0 integer, dimension(:), allocatable :: n_bin logical :: max_known = .false. real(default) :: max = 0 real(default) :: min = 0 real(default) :: max_abs = 0 real(default) :: min_abs = 0 contains <> end type mci_midpoint_t @ %def mci_t @ Finalizer: base version is sufficient <>= procedure :: final => mci_midpoint_final <>= subroutine mci_midpoint_final (object) class(mci_midpoint_t), intent(inout) :: object call object%base_final () end subroutine mci_midpoint_final @ %def mci_midpoint_final @ Output. <>= procedure :: write => mci_midpoint_write <>= subroutine mci_midpoint_write (object, unit, pacify, md5sum_version) class(mci_midpoint_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify logical, intent(in), optional :: md5sum_version integer :: u, i u = given_output_unit (unit) write (u, "(1x,A)") "Single-channel midpoint rule integrator:" call object%base_write (u, pacify, md5sum_version) if (object%n_dim_binned < object%n_dim) then write (u, "(3x,A,99(1x,I0))") "Flat dimensions =", & pack ([(i, i = 1, object%n_dim)], mask = .not. object%dim_is_binned) write (u, "(3x,A,I0)") "Number of binned dim = ", object%n_dim_binned end if if (object%calls_known) then write (u, "(3x,A,99(1x,I0))") "Number of bins =", object%n_bin write (u, "(3x,A,I0)") "Number of calls = ", object%n_calls if (object%n_calls_pos /= object%n_calls) then write (u, "(3x,A,I0)") " positive value = ", object%n_calls_pos write (u, "(3x,A,I0)") " zero value = ", object%n_calls_nul write (u, "(3x,A,I0)") " negative value = ", object%n_calls_neg write (u, "(3x,A,ES17.10)") & "Integral (pos. part) = ", object%integral_pos write (u, "(3x,A,ES17.10)") & "Integral (neg. part) = ", object%integral_neg end if end if if (object%max_known) then write (u, "(3x,A,ES17.10)") "Maximum of integrand = ", object%max write (u, "(3x,A,ES17.10)") "Minimum of integrand = ", object%min if (object%min /= object%min_abs) then write (u, "(3x,A,ES17.10)") "Maximum (abs. value) = ", object%max_abs write (u, "(3x,A,ES17.10)") "Minimum (abs. value) = ", object%min_abs end if end if if (allocated (object%rng)) call object%rng%write (u) end subroutine mci_midpoint_write @ %def mci_midpoint_write @ Startup message: short version. <>= procedure :: startup_message => mci_midpoint_startup_message <>= subroutine mci_midpoint_startup_message (mci, unit, n_calls) class(mci_midpoint_t), intent(in) :: mci integer, intent(in), optional :: unit, n_calls call mci%base_startup_message (unit = unit, n_calls = n_calls) if (mci%n_dim_binned < mci%n_dim) then write (msg_buffer, "(A,2(1x,I0,1x,A))") & "Integrator: Midpoint rule:", & mci%n_dim_binned, "binned dimensions" else write (msg_buffer, "(A,2(1x,I0,1x,A))") & "Integrator: Midpoint rule" end if call msg_message (unit = unit) end subroutine mci_midpoint_startup_message @ %def mci_midpoint_startup_message @ Log entry: just headline. <>= procedure :: write_log_entry => mci_midpoint_write_log_entry <>= subroutine mci_midpoint_write_log_entry (mci, u) class(mci_midpoint_t), intent(in) :: mci integer, intent(in) :: u write (u, "(1x,A)") "MC Integrator is Midpoint rule" end subroutine mci_midpoint_write_log_entry @ %def mci_midpoint_write_log_entry @ MD5 sum: nothing. <>= procedure :: compute_md5sum => mci_midpoint_compute_md5sum <>= subroutine mci_midpoint_compute_md5sum (mci, pacify) class(mci_midpoint_t), intent(inout) :: mci logical, intent(in), optional :: pacify end subroutine mci_midpoint_compute_md5sum @ %def mci_midpoint_compute_md5sum @ The number of channels must be one. <>= procedure :: set_dimensions => mci_midpoint_set_dimensions <>= subroutine mci_midpoint_set_dimensions (mci, n_dim, n_channel) class(mci_midpoint_t), intent(inout) :: mci integer, intent(in) :: n_dim integer, intent(in) :: n_channel if (n_channel == 1) then mci%n_channel = n_channel mci%n_dim = n_dim allocate (mci%dim_is_binned (mci%n_dim)) mci%dim_is_binned = .true. mci%n_dim_binned = count (mci%dim_is_binned) allocate (mci%n_bin (mci%n_dim)) mci%n_bin = 0 else call msg_fatal ("Attempt to initialize single-channel integrator & &for multiple channels") end if end subroutine mci_midpoint_set_dimensions @ %def mci_midpoint_set_dimensions @ Declare particular dimensions as flat. These dimensions will not be binned. <>= procedure :: declare_flat_dimensions => mci_midpoint_declare_flat_dimensions <>= subroutine mci_midpoint_declare_flat_dimensions (mci, dim_flat) class(mci_midpoint_t), intent(inout) :: mci integer, dimension(:), intent(in) :: dim_flat integer :: d mci%n_dim_binned = mci%n_dim - size (dim_flat) do d = 1, size (dim_flat) mci%dim_is_binned(dim_flat(d)) = .false. end do mci%n_dim_binned = count (mci%dim_is_binned) end subroutine mci_midpoint_declare_flat_dimensions @ %def mci_midpoint_declare_flat_dimensions @ Declare particular channels as equivalent. This has no effect. <>= procedure :: declare_equivalences => mci_midpoint_ignore_equivalences <>= subroutine mci_midpoint_ignore_equivalences (mci, channel, dim_offset) class(mci_midpoint_t), intent(inout) :: mci type(phs_channel_t), dimension(:), intent(in) :: channel integer, intent(in) :: dim_offset end subroutine mci_midpoint_ignore_equivalences @ %def mci_midpoint_ignore_equivalences @ Allocate instance with matching type. <>= procedure :: allocate_instance => mci_midpoint_allocate_instance <>= subroutine mci_midpoint_allocate_instance (mci, mci_instance) class(mci_midpoint_t), intent(in) :: mci class(mci_instance_t), intent(out), pointer :: mci_instance allocate (mci_midpoint_instance_t :: mci_instance) end subroutine mci_midpoint_allocate_instance @ %def mci_midpoint_allocate_instance @ Integrate. The number of dimensions is arbitrary. We make sure that the number of calls is evenly distributed among the dimensions. The actual number of calls will typically be smaller than the requested number, but never smaller than 1. The sampling over a variable number of dimensions implies a variable number of nested loops. We implement this by a recursive subroutine, one loop in each recursion level. The number of iterations [[n_it]] is ignored. Also, the error is set to zero in the current implementation. With this integrator, we allow the calculation to abort immediately when forced by a signal. There is no state that we can save, hence we do not catch an interrupt. <>= procedure :: integrate => mci_midpoint_integrate <>= subroutine mci_midpoint_integrate (mci, instance, sampler, n_it, n_calls, & results, pacify) class(mci_midpoint_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls logical, intent(in), optional :: pacify class(mci_results_t), intent(inout), optional :: results real(default), dimension(:), allocatable :: x real(default) :: integral, integral_pos, integral_neg integer :: n_bin select type (instance) type is (mci_midpoint_instance_t) allocate (x (mci%n_dim)) integral = 0 integral_pos = 0 integral_neg = 0 select case (mci%n_dim_binned) case (1) n_bin = n_calls case (2:) n_bin = max (int (n_calls ** (1. / mci%n_dim_binned)), 1) end select where (mci%dim_is_binned) mci%n_bin = n_bin elsewhere mci%n_bin = 1 end where mci%n_calls = product (mci%n_bin) mci%n_calls_pos = 0 mci%n_calls_nul = 0 mci%n_calls_neg = 0 mci%calls_known = .true. call sample_dim (mci%n_dim) mci%integral = integral / mci%n_calls mci%integral_pos = integral_pos / mci%n_calls mci%integral_neg = integral_neg / mci%n_calls mci%integral_known = .true. call instance%set_max () if (present (results)) then call results%record (1, mci%n_calls, & mci%integral, mci%error, mci%efficiency) end if end select contains recursive subroutine sample_dim (d) integer, intent(in) :: d integer :: i real(default) :: value do i = 1, mci%n_bin(d) x(d) = (i - 0.5_default) / mci%n_bin(d) if (d > 1) then call sample_dim (d - 1) else if (signal_is_pending ()) return call instance%evaluate (sampler, 1, x) value = instance%get_value () if (value > 0) then mci%n_calls_pos = mci%n_calls_pos + 1 integral = integral + value integral_pos = integral_pos + value else if (value == 0) then mci%n_calls_nul = mci%n_calls_nul + 1 else mci%n_calls_neg = mci%n_calls_neg + 1 integral = integral + value integral_neg = integral_neg + value end if end if end do end subroutine sample_dim end subroutine mci_midpoint_integrate @ %def mci_midpoint_integrate @ Simulation initializer and finalizer: nothing to do here. <>= procedure :: prepare_simulation => mci_midpoint_ignore_prepare_simulation <>= subroutine mci_midpoint_ignore_prepare_simulation (mci) class(mci_midpoint_t), intent(inout) :: mci end subroutine mci_midpoint_ignore_prepare_simulation @ %def mci_midpoint_ignore_prepare_simulation @ Generate weighted event. <>= procedure :: generate_weighted_event => mci_midpoint_generate_weighted_event <>= subroutine mci_midpoint_generate_weighted_event (mci, instance, sampler) class(mci_midpoint_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler real(default), dimension(mci%n_dim) :: x select type (instance) type is (mci_midpoint_instance_t) call mci%rng%generate (x) call instance%evaluate (sampler, 1, x) instance%excess_weight = 0 end select end subroutine mci_midpoint_generate_weighted_event @ %def mci_midpoint_generate_weighted_event @ For unweighted events, we generate weighted events and apply a simple rejection step to the relative event weight, until an event passes. Note that we use the [[max_abs]] value stored in the configuration record, not the one stored in the instance. The latter may change during event generation. After an event generation pass is over, we may update the value for a subsequent pass. <>= procedure :: generate_unweighted_event => & mci_midpoint_generate_unweighted_event <>= subroutine mci_midpoint_generate_unweighted_event (mci, instance, sampler) class(mci_midpoint_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler real(default) :: x, norm, int select type (instance) type is (mci_midpoint_instance_t) if (mci%max_known .and. mci%max_abs > 0) then norm = abs (mci%max_abs * instance%safety_factor) REJECTION: do call mci%generate_weighted_event (instance, sampler) if (sampler%is_valid ()) then call mci%rng%generate (x) int = abs (instance%integrand) if (x * norm <= int) then if (norm > 0 .and. norm < int) then instance%excess_weight = int / norm - 1 end if exit REJECTION end if end if if (signal_is_pending ()) return end do REJECTION else call msg_fatal ("Unweighted event generation: & &maximum of integrand is zero or unknown") end if end select end subroutine mci_midpoint_generate_unweighted_event @ %def mci_midpoint_generate_unweighted_event @ Rebuild an event, using the [[state]] input. <>= procedure :: rebuild_event => mci_midpoint_rebuild_event <>= subroutine mci_midpoint_rebuild_event (mci, instance, sampler, state) class(mci_midpoint_t), intent(inout) :: mci class(mci_instance_t), intent(inout) :: instance class(mci_sampler_t), intent(inout) :: sampler class(mci_state_t), intent(in) :: state select type (instance) type is (mci_midpoint_instance_t) call instance%recall (sampler, state) end select end subroutine mci_midpoint_rebuild_event @ %def mci_midpoint_rebuild_event @ \subsection{Integrator instance} Covering the case of flat dimensions, we store a complete [[x]] array. This is filled when generating events. <>= public :: mci_midpoint_instance_t <>= type, extends (mci_instance_t) :: mci_midpoint_instance_t type(mci_midpoint_t), pointer :: mci => null () logical :: max_known = .false. real(default) :: max = 0 real(default) :: min = 0 real(default) :: max_abs = 0 real(default) :: min_abs = 0 real(default) :: safety_factor = 1 real(default) :: excess_weight = 0 contains <> end type mci_midpoint_instance_t @ %def mci_midpoint_instance_t @ Output. <>= procedure :: write => mci_midpoint_instance_write <>= subroutine mci_midpoint_instance_write (object, unit, pacify) class(mci_midpoint_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify integer :: u u = given_output_unit (unit) write (u, "(1x,A,9(1x,F12.10))") "x =", object%x(:,1) write (u, "(1x,A,ES19.12)") "Integrand = ", object%integrand write (u, "(1x,A,ES19.12)") "Weight = ", object%mci_weight if (object%safety_factor /= 1) then write (u, "(1x,A,ES19.12)") "Safety f = ", object%safety_factor end if if (object%excess_weight /= 0) then write (u, "(1x,A,ES19.12)") "Excess = ", object%excess_weight end if if (object%max_known) then write (u, "(1x,A,ES19.12)") "Maximum = ", object%max write (u, "(1x,A,ES19.12)") "Minimum = ", object%min if (object%min /= object%min_abs) then write (u, "(1x,A,ES19.12)") "Max.(abs) = ", object%max_abs write (u, "(1x,A,ES19.12)") "Min.(abs) = ", object%min_abs end if end if end subroutine mci_midpoint_instance_write @ %def mci_midpoint_instance_write @ The finalizer is empty. <>= procedure :: final => mci_midpoint_instance_final <>= subroutine mci_midpoint_instance_final (object) class(mci_midpoint_instance_t), intent(inout) :: object end subroutine mci_midpoint_instance_final @ %def mci_midpoint_instance_final @ Initializer. <>= procedure :: init => mci_midpoint_instance_init <>= subroutine mci_midpoint_instance_init (mci_instance, mci) class(mci_midpoint_instance_t), intent(out) :: mci_instance class(mci_t), intent(in), target :: mci call mci_instance%base_init (mci) select type (mci) type is (mci_midpoint_t) mci_instance%mci => mci call mci_instance%get_max () mci_instance%selected_channel = 1 end select end subroutine mci_midpoint_instance_init @ %def mci_midpoint_instance_init @ Copy the stored extrema of the integrand in the instance record. <>= procedure :: get_max => mci_midpoint_instance_get_max <>= subroutine mci_midpoint_instance_get_max (instance) class(mci_midpoint_instance_t), intent(inout) :: instance associate (mci => instance%mci) if (mci%max_known) then instance%max_known = .true. instance%max = mci%max instance%min = mci%min instance%max_abs = mci%max_abs instance%min_abs = mci%min_abs end if end associate end subroutine mci_midpoint_instance_get_max @ %def mci_midpoint_instance_get_max @ Reverse operations: recall the extrema, but only if they are wider than the extrema already stored in the configuration. Also recalculate the efficiency value. <>= procedure :: set_max => mci_midpoint_instance_set_max <>= subroutine mci_midpoint_instance_set_max (instance) class(mci_midpoint_instance_t), intent(inout) :: instance associate (mci => instance%mci) if (instance%max_known) then if (mci%max_known) then mci%max = max (mci%max, instance%max) mci%min = min (mci%min, instance%min) mci%max_abs = max (mci%max_abs, instance%max_abs) mci%min_abs = min (mci%min_abs, instance%min_abs) else mci%max = instance%max mci%min = instance%min mci%max_abs = instance%max_abs mci%min_abs = instance%min_abs mci%max_known = .true. end if if (mci%max_abs /= 0) then if (mci%integral_neg == 0) then mci%efficiency = mci%integral / mci%max_abs mci%efficiency_known = .true. else if (mci%n_calls /= 0) then mci%efficiency = & (mci%integral_pos - mci%integral_neg) / mci%max_abs mci%efficiency_known = .true. end if end if end if end associate end subroutine mci_midpoint_instance_set_max @ %def mci_midpoint_instance_set_max @ The weight is the Jacobian of the mapping for the only channel. <>= procedure :: compute_weight => mci_midpoint_instance_compute_weight <>= subroutine mci_midpoint_instance_compute_weight (mci, c) class(mci_midpoint_instance_t), intent(inout) :: mci integer, intent(in) :: c select case (c) case (1) mci%mci_weight = mci%f(1) case default call msg_fatal ("MCI midpoint integrator: only single channel supported") end select end subroutine mci_midpoint_instance_compute_weight @ %def mci_midpoint_instance_compute_weight @ Record the integrand. Update stored values for maximum and minimum. <>= procedure :: record_integrand => mci_midpoint_instance_record_integrand <>= subroutine mci_midpoint_instance_record_integrand (mci, integrand) class(mci_midpoint_instance_t), intent(inout) :: mci real(default), intent(in) :: integrand mci%integrand = integrand if (mci%max_known) then mci%max = max (mci%max, integrand) mci%min = min (mci%min, integrand) mci%max_abs = max (mci%max_abs, abs (integrand)) mci%min_abs = min (mci%min_abs, abs (integrand)) else mci%max = integrand mci%min = integrand mci%max_abs = abs (integrand) mci%min_abs = abs (integrand) mci%max_known = .true. end if end subroutine mci_midpoint_instance_record_integrand @ %def mci_midpoint_instance_record_integrand @ We store the safety factor, otherwise nothing to do here. <>= procedure :: init_simulation => mci_midpoint_instance_init_simulation procedure :: final_simulation => mci_midpoint_instance_final_simulation <>= subroutine mci_midpoint_instance_init_simulation (instance, safety_factor) class(mci_midpoint_instance_t), intent(inout) :: instance real(default), intent(in), optional :: safety_factor if (present (safety_factor)) instance%safety_factor = safety_factor end subroutine mci_midpoint_instance_init_simulation subroutine mci_midpoint_instance_final_simulation (instance) class(mci_midpoint_instance_t), intent(inout) :: instance end subroutine mci_midpoint_instance_final_simulation @ %def mci_midpoint_instance_init_simulation @ %def mci_midpoint_instance_final_simulation @ Return excess weight for the current event. <>= procedure :: get_event_excess => mci_midpoint_instance_get_event_excess <>= function mci_midpoint_instance_get_event_excess (mci) result (excess) class(mci_midpoint_instance_t), intent(in) :: mci real(default) :: excess excess = mci%excess_weight end function mci_midpoint_instance_get_event_excess @ %def mci_midpoint_instance_get_event_excess @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[mci_midpoint_ut.f90]]>>= <> module mci_midpoint_ut use unit_tests use mci_midpoint_uti <> <> contains <> end module mci_midpoint_ut @ %def mci_midpoint_ut @ <<[[mci_midpoint_uti.f90]]>>= <> module mci_midpoint_uti <> use io_units use rng_base use mci_base use mci_midpoint use rng_base_ut, only: rng_test_t <> <> <> contains <> end module mci_midpoint_uti @ %def mci_midpoint_ut @ API: driver for the unit tests below. <>= public :: mci_midpoint_test <>= subroutine mci_midpoint_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine mci_midpoint_test @ %def mci_midpoint_test @ \subsubsection{Test sampler} A test sampler object should implement a function with known integral that we can use to check the integrator. This is the function $f(x) = 3 x^2$ with integral $\int_0^1 f(x)\,dx=1$ and maximum $f(1)=3$. If the integration dimension is greater than one, the function is extended as a constant in the other dimension(s). Mimicking the behavior of a process object, we store the argument and result inside the sampler, so we can [[fetch]] results. <>= type, extends (mci_sampler_t) :: test_sampler_1_t real(default), dimension(:), allocatable :: x real(default) :: val contains <> end type test_sampler_1_t @ %def test_sampler_1_t @ Output: There is nothing stored inside, so just print an informative line. <>= procedure :: write => test_sampler_1_write <>= subroutine test_sampler_1_write (object, unit, testflag) class(test_sampler_1_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Test sampler: f(x) = 3 x^2" end subroutine test_sampler_1_write @ %def test_sampler_1_write @ Evaluation: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure :: evaluate => test_sampler_1_evaluate <>= subroutine test_sampler_1_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_1_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f if (allocated (sampler%x)) deallocate (sampler%x) allocate (sampler%x (size (x_in))) sampler%x = x_in sampler%val = 3 * x_in(1) ** 2 call sampler%fetch (val, x, f) end subroutine test_sampler_1_evaluate @ %def test_sampler_1_evaluate @ The point is always valid. <>= procedure :: is_valid => test_sampler_1_is_valid <>= function test_sampler_1_is_valid (sampler) result (valid) class(test_sampler_1_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_1_is_valid @ %def test_sampler_1_is_valid @ Rebuild: compute all but the function value. <>= procedure :: rebuild => test_sampler_1_rebuild <>= subroutine test_sampler_1_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_1_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f if (allocated (sampler%x)) deallocate (sampler%x) allocate (sampler%x (size (x_in))) sampler%x = x_in sampler%val = val x(:,1) = sampler%x f = 1 end subroutine test_sampler_1_rebuild @ %def test_sampler_1_rebuild @ Extract the results. <>= procedure :: fetch => test_sampler_1_fetch <>= subroutine test_sampler_1_fetch (sampler, val, x, f) class(test_sampler_1_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x(:,1) = sampler%x f = 1 end subroutine test_sampler_1_fetch @ %def test_sampler_1_fetch @ This is the function $f(x) = 3 x^2 + 2 y$ with integral $\int_0^1 f(x,y)\,dx\,dy=2$ and maximum $f(1)=5$. <>= type, extends (mci_sampler_t) :: test_sampler_2_t real(default) :: val real(default), dimension(2) :: x contains <> end type test_sampler_2_t @ %def test_sampler_2_t @ Output: There is nothing stored inside, so just print an informative line. <>= procedure :: write => test_sampler_2_write <>= subroutine test_sampler_2_write (object, unit, testflag) class(test_sampler_2_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Test sampler: f(x) = 3 x^2 + 2 y" end subroutine test_sampler_2_write @ %def test_sampler_2_write @ Evaluate: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure :: evaluate => test_sampler_2_evaluate <>= subroutine test_sampler_2_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f sampler%x = x_in sampler%val = 3 * x_in(1) ** 2 + 2 * x_in(2) call sampler%fetch (val, x, f) end subroutine test_sampler_2_evaluate @ %def test_sampler_2_evaluate @ The point is always valid. <>= procedure :: is_valid => test_sampler_2_is_valid <>= function test_sampler_2_is_valid (sampler) result (valid) class(test_sampler_2_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_2_is_valid @ %def test_sampler_2_is_valid @ Rebuild: compute all but the function value. <>= procedure :: rebuild => test_sampler_2_rebuild <>= subroutine test_sampler_2_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f sampler%x = x_in sampler%val = val x(:,1) = sampler%x f = 1 end subroutine test_sampler_2_rebuild @ %def test_sampler_2_rebuild <>= procedure :: fetch => test_sampler_2_fetch <>= subroutine test_sampler_2_fetch (sampler, val, x, f) class(test_sampler_2_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x(:,1) = sampler%x f = 1 end subroutine test_sampler_2_fetch @ %def test_sampler_2_fetch @ This is the function $f(x) = (1 - 3 x^2)\,\theta(x-1/2)$ with integral $\int_0^1 f(x)\,dx=-3/8$, minimum $f(1)=-2$ and maximum $f(1/2)=1/4$. If the integration dimension is greater than one, the function is extended as a constant in the other dimension(s). <>= type, extends (mci_sampler_t) :: test_sampler_4_t real(default) :: val real(default), dimension(:), allocatable :: x contains <> end type test_sampler_4_t @ %def test_sampler_4_t @ Output: There is nothing stored inside, so just print an informative line. <>= procedure :: write => test_sampler_4_write <>= subroutine test_sampler_4_write (object, unit, testflag) class(test_sampler_4_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Test sampler: f(x) = 1 - 3 x^2" end subroutine test_sampler_4_write @ %def test_sampler_4_write @ Evaluation: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure :: evaluate => test_sampler_4_evaluate <>= subroutine test_sampler_4_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_4_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f if (x_in(1) >= .5_default) then sampler%val = 1 - 3 * x_in(1) ** 2 else sampler%val = 0 end if if (.not. allocated (sampler%x)) allocate (sampler%x (size (x_in))) sampler%x = x_in call sampler%fetch (val, x, f) end subroutine test_sampler_4_evaluate @ %def test_sampler_4_evaluate @ The point is always valid. <>= procedure :: is_valid => test_sampler_4_is_valid <>= function test_sampler_4_is_valid (sampler) result (valid) class(test_sampler_4_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_4_is_valid @ %def test_sampler_4_is_valid @ Rebuild: compute all but the function value. <>= procedure :: rebuild => test_sampler_4_rebuild <>= subroutine test_sampler_4_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_4_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f sampler%x = x_in sampler%val = val x(:,1) = sampler%x f = 1 end subroutine test_sampler_4_rebuild @ %def test_sampler_4_rebuild <>= procedure :: fetch => test_sampler_4_fetch <>= subroutine test_sampler_4_fetch (sampler, val, x, f) class(test_sampler_4_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x(:,1) = sampler%x f = 1 end subroutine test_sampler_4_fetch @ %def test_sampler_4_fetch @ \subsubsection{One-dimensional integration} Construct an integrator and use it for a one-dimensional sampler. <>= call test (mci_midpoint_1, "mci_midpoint_1", & "one-dimensional integral", & u, results) <>= public :: mci_midpoint_1 <>= subroutine mci_midpoint_1 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler write (u, "(A)") "* Test output: mci_midpoint_1" write (u, "(A)") "* Purpose: integrate function in one dimension" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_midpoint_t :: mci) call mci%set_dimensions (1, 1) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_1_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for x = 0.8" write (u, "(A)") call mci_instance%evaluate (sampler, 1, [0.8_default]) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for x = 0.7" write (u, "(A)") call mci_instance%evaluate (sampler, 1, [0.7_default]) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for x = 0.9" write (u, "(A)") call mci_instance%evaluate (sampler, 1, [0.9_default]) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_calls = 1000" write (u, "(A)") call mci%integrate (mci_instance, sampler, 1, 1000) call mci%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_midpoint_1" end subroutine mci_midpoint_1 @ %def mci_midpoint_1 @ \subsubsection{Two-dimensional integration} Construct an integrator and use it for a two-dimensional sampler. <>= call test (mci_midpoint_2, "mci_midpoint_2", & "two-dimensional integral", & u, results) <>= public :: mci_midpoint_2 <>= subroutine mci_midpoint_2 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler write (u, "(A)") "* Test output: mci_midpoint_2" write (u, "(A)") "* Purpose: integrate function in two dimensions" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_midpoint_t :: mci) call mci%set_dimensions (2, 1) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_2_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for x = 0.8, y = 0.2" write (u, "(A)") call mci_instance%evaluate (sampler, 1, [0.8_default, 0.2_default]) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_calls = 1000" write (u, "(A)") call mci%integrate (mci_instance, sampler, 1, 1000) call mci%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_midpoint_2" end subroutine mci_midpoint_2 @ %def mci_midpoint_2 @ \subsubsection{Two-dimensional integration with flat dimension} Construct an integrator and use it for a two-dimensional sampler, where the function is constant in the second dimension. <>= call test (mci_midpoint_3, "mci_midpoint_3", & "two-dimensional integral with flat dimension", & u, results) <>= public :: mci_midpoint_3 <>= subroutine mci_midpoint_3 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler write (u, "(A)") "* Test output: mci_midpoint_3" write (u, "(A)") "* Purpose: integrate function with one flat dimension" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_midpoint_t :: mci) select type (mci) type is (mci_midpoint_t) call mci%set_dimensions (2, 1) call mci%declare_flat_dimensions ([2]) end select call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_1_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for x = 0.8, y = 0.2" write (u, "(A)") call mci_instance%evaluate (sampler, 1, [0.8_default, 0.2_default]) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_calls = 1000" write (u, "(A)") call mci%integrate (mci_instance, sampler, 1, 1000) call mci%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_midpoint_3" end subroutine mci_midpoint_3 @ %def mci_midpoint_3 @ \subsubsection{Integrand with sign flip} Construct an integrator and use it for a one-dimensional sampler. <>= call test (mci_midpoint_4, "mci_midpoint_4", & "integrand with sign flip", & u, results) <>= public :: mci_midpoint_4 <>= subroutine mci_midpoint_4 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler write (u, "(A)") "* Test output: mci_midpoint_4" write (u, "(A)") "* Purpose: integrate function with sign flip & &in one dimension" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_midpoint_t :: mci) call mci%set_dimensions (1, 1) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_4_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Evaluate for x = 0.8" write (u, "(A)") call mci_instance%evaluate (sampler, 1, [0.8_default]) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_calls = 1000" write (u, "(A)") call mci%integrate (mci_instance, sampler, 1, 1000) call mci%write (u) call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_midpoint_4" end subroutine mci_midpoint_4 @ %def mci_midpoint_4 @ \subsubsection{Weighted events} Generate weighted events. Without rejection, we do not need to know maxima and minima, so we can start generating events immediately. We have two dimensions. <>= call test (mci_midpoint_5, "mci_midpoint_5", & "weighted events", & u, results) <>= public :: mci_midpoint_5 <>= subroutine mci_midpoint_5 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng class(mci_state_t), allocatable :: state write (u, "(A)") "* Test output: mci_midpoint_5" write (u, "(A)") "* Purpose: generate weighted events" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_midpoint_t :: mci) call mci%set_dimensions (2, 1) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_2_t :: sampler) write (u, "(A)") "* Initialize random-number generator" write (u, "(A)") allocate (rng_test_t :: rng) call rng%init () call mci%import_rng (rng) write (u, "(A)") "* Generate weighted event" write (u, "(A)") call mci%generate_weighted_event (mci_instance, sampler) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Generate weighted event" write (u, "(A)") call mci%generate_weighted_event (mci_instance, sampler) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Store data" write (u, "(A)") allocate (state) call mci_instance%store (state) call mci_instance%final () deallocate (mci_instance) call state%write (u) write (u, "(A)") write (u, "(A)") "* Recall data and rebuild event" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) call mci%rebuild_event (mci_instance, sampler, state) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () deallocate (mci_instance) call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_midpoint_5" end subroutine mci_midpoint_5 @ %def mci_midpoint_5 @ \subsubsection{Unweighted events} Generate unweighted events. The integrand has a sign flip in it. <>= call test (mci_midpoint_6, "mci_midpoint_6", & "unweighted events", & u, results) <>= public :: mci_midpoint_6 <>= subroutine mci_midpoint_6 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_midpoint_6" write (u, "(A)") "* Purpose: generate unweighted events" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_midpoint_t :: mci) call mci%set_dimensions (1, 1) write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_4_t :: sampler) write (u, "(A)") "* Initialize random-number generator" write (u, "(A)") allocate (rng_test_t :: rng) call rng%init () call mci%import_rng (rng) write (u, "(A)") "* Integrate (determine maximum of integrand" write (u, "(A)") call mci%integrate (mci_instance, sampler, 1, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Generate unweighted event" write (u, "(A)") call mci%generate_unweighted_event (mci_instance, sampler) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () deallocate (mci_instance) call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_midpoint_6" end subroutine mci_midpoint_6 @ %def mci_midpoint_6 @ \subsubsection{Excess weight} Generate unweighted events. With only 2 points for integration, the maximum of the integrand is too low, and we produce excess weight. <>= call test (mci_midpoint_7, "mci_midpoint_7", & "excess weight", & u, results) <>= public :: mci_midpoint_7 <>= subroutine mci_midpoint_7 (u) integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_midpoint_7" write (u, "(A)") "* Purpose: generate unweighted event & &with excess weight" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_midpoint_t :: mci) call mci%set_dimensions (1, 1) write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_4_t :: sampler) write (u, "(A)") "* Initialize random-number generator" write (u, "(A)") allocate (rng_test_t :: rng) call rng%init () call mci%import_rng (rng) write (u, "(A)") "* Integrate (determine maximum of integrand" write (u, "(A)") call mci%integrate (mci_instance, sampler, 1, 2) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Generate unweighted event" write (u, "(A)") call mci_instance%init_simulation () call mci%generate_unweighted_event (mci_instance, sampler) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Use getter methods" write (u, "(A)") write (u, "(1x,A,1x,ES19.12)") "weight =", mci_instance%get_event_weight () write (u, "(1x,A,1x,ES19.12)") "excess =", mci_instance%get_event_excess () write (u, "(A)") write (u, "(A)") "* Apply safety factor" write (u, "(A)") call mci_instance%init_simulation (safety_factor = 2.1_default) write (u, "(A)") "* Generate unweighted event" write (u, "(A)") call mci%generate_unweighted_event (mci_instance, sampler) call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Use getter methods" write (u, "(A)") write (u, "(1x,A,1x,ES19.12)") "weight =", mci_instance%get_event_weight () write (u, "(1x,A,1x,ES19.12)") "excess =", mci_instance%get_event_excess () write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () deallocate (mci_instance) call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_midpoint_7" end subroutine mci_midpoint_7 @ %def mci_midpoint_7 @ \clearpage %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{\vamp\ interface} The standard method for integration is \vamp: the multi-channel version of the VEGAS algorithm. Each parameterization (channel) of the hypercube is binned in each dimension. The binning is equally equidistant, but an iteration of the integration procedure, the binning is updated for each dimension, according to the variance distribution of the integrand, summed over all other dimension. In the next iteration, the binning approximates (hopefully) follows the integrand more closely, and the accuracy of the result is increased. Furthermore, the relative weight of the individual channels is also updated after an iteration. The bin distribution is denoted as the grid for a channel, which we can write to file and reuse later. In our implementation we specify the generic \vamp\ algorithm more tightly: the number of bins is equal for all dimensions, the initial weights are all equal. The user controls whether to update bins and/or weights after each iteration. The integration is organized in passes, each one consisting of several iterations with a common number of calls to the integrand. The first passes are intended as warmup, so the results are displayed but otherwise discarded. In the final pass, the integration estimates for the individual iterations are averaged for the final result. <<[[mci_vamp.f90]]>>= <> module mci_vamp <> <> use io_units use constants, only: zero use format_utils, only: pac_fmt use format_utils, only: write_separator use format_defs, only: FMT_12, FMT_14, FMT_17, FMT_19 use diagnostics use md5 use phs_base use rng_base use rng_tao use vamp !NODEP! use exceptions !NODEP! use mci_base <> <> <> <> contains <> end module mci_vamp @ %def mci_vamp @ \subsection{Grid parameters} This is a transparent container. It holds the parameters that are stored in grid files, and are checked when grid files are read. <>= public :: grid_parameters_t <>= type :: grid_parameters_t integer :: threshold_calls = 0 integer :: min_calls_per_channel = 10 integer :: min_calls_per_bin = 10 integer :: min_bins = 3 integer :: max_bins = 20 logical :: stratified = .true. logical :: use_vamp_equivalences = .true. real(default) :: channel_weights_power = 0.25_default real(default) :: accuracy_goal = 0 real(default) :: error_goal = 0 real(default) :: rel_error_goal = 0 contains <> end type grid_parameters_t @ %def grid_parameters_t @ I/O: <>= procedure :: write => grid_parameters_write <>= subroutine grid_parameters_write (object, unit) class(grid_parameters_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(3x,A,I0)") "threshold_calls = ", & object%threshold_calls write (u, "(3x,A,I0)") "min_calls_per_channel = ", & object%min_calls_per_channel write (u, "(3x,A,I0)") "min_calls_per_bin = ", & object%min_calls_per_bin write (u, "(3x,A,I0)") "min_bins = ", & object%min_bins write (u, "(3x,A,I0)") "max_bins = ", & object%max_bins write (u, "(3x,A,L1)") "stratified = ", & object%stratified write (u, "(3x,A,L1)") "use_vamp_equivalences = ", & object%use_vamp_equivalences write (u, "(3x,A,F10.7)") "channel_weights_power = ", & object%channel_weights_power if (object%accuracy_goal > 0) then write (u, "(3x,A,F10.7)") "accuracy_goal = ", & object%accuracy_goal end if if (object%error_goal > 0) then write (u, "(3x,A,F10.7)") "error_goal = ", & object%error_goal end if if (object%rel_error_goal > 0) then write (u, "(3x,A,F10.7)") "rel_error_goal = ", & object%rel_error_goal end if end subroutine grid_parameters_write @ %def grid_parameters_write @ \subsection{History parameters} The history parameters are also stored in a transparent container. This is not a part of the grid definition, and should not be included in the MD5 sum. <>= public :: history_parameters_t <>= type :: history_parameters_t logical :: global = .true. logical :: global_verbose = .false. logical :: channel = .false. logical :: channel_verbose = .false. contains <> end type history_parameters_t @ %def history_parameters_t @ I/O: <>= procedure :: write => history_parameters_write <>= subroutine history_parameters_write (object, unit) class(history_parameters_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(3x,A,L1)") "history(global) = ", object%global write (u, "(3x,A,L1)") "history(global) verb. = ", object%global_verbose write (u, "(3x,A,L1)") "history(channels) = ", object%channel write (u, "(3x,A,L1)") "history(chann.) verb. = ", object%channel_verbose end subroutine history_parameters_write @ %def history_parameters_write @ \subsection{Integration pass} We store the parameters for each integration pass in a linked list. <>= type :: pass_t integer :: i_pass = 0 integer :: i_first_it = 0 integer :: n_it = 0 integer :: n_calls = 0 integer :: n_bins = 0 logical :: adapt_grids = .false. logical :: adapt_weights = .false. logical :: is_final_pass = .false. logical :: integral_defined = .false. integer, dimension(:), allocatable :: calls integer, dimension(:), allocatable :: calls_valid real(default), dimension(:), allocatable :: integral real(default), dimension(:), allocatable :: error real(default), dimension(:), allocatable :: efficiency type(vamp_history), dimension(:), allocatable :: v_history type(vamp_history), dimension(:,:), allocatable :: v_histories type(pass_t), pointer :: next => null () contains <> end type pass_t @ %def pass_t @ Finalizer. The VAMP histories contain a pointer array. <>= procedure :: final => pass_final <>= subroutine pass_final (object) class(pass_t), intent(inout) :: object if (allocated (object%v_history)) then call vamp_delete_history (object%v_history) end if if (allocated (object%v_histories)) then call vamp_delete_history (object%v_histories) end if end subroutine pass_final @ %def pass_final @ Output. Note that the precision of the numerical values should match the precision for comparing output from file with data. <>= procedure :: write => pass_write <>= subroutine pass_write (object, unit, pacify) class(pass_t), intent(in) :: object integer, intent(in) :: unit logical, intent(in), optional :: pacify integer :: u, i character(len=7) :: fmt call pac_fmt (fmt, FMT_17, FMT_14, pacify) u = given_output_unit (unit) write (u, "(3x,A,I0)") "n_it = ", object%n_it write (u, "(3x,A,I0)") "n_calls = ", object%n_calls write (u, "(3x,A,I0)") "n_bins = ", object%n_bins write (u, "(3x,A,L1)") "adapt grids = ", object%adapt_grids write (u, "(3x,A,L1)") "adapt weights = ", object%adapt_weights if (object%integral_defined) then write (u, "(3x,A)") "Results: [it, calls, valid, integral, error, efficiency]" do i = 1, object%n_it write (u, "(5x,I0,2(1x,I0),3(1x," // fmt // "))") & i, object%calls(i), object%calls_valid(i), object%integral(i), object%error(i), & object%efficiency(i) end do else write (u, "(3x,A)") "Results: [undefined]" end if end subroutine pass_write @ %def pass_write @ Read and reconstruct the pass. <>= procedure :: read => pass_read <>= subroutine pass_read (object, u, n_pass, n_it) class(pass_t), intent(out) :: object integer, intent(in) :: u, n_pass, n_it integer :: i, j character(80) :: buffer object%i_pass = n_pass + 1 object%i_first_it = n_it + 1 call read_ival (u, object%n_it) call read_ival (u, object%n_calls) call read_ival (u, object%n_bins) call read_lval (u, object%adapt_grids) call read_lval (u, object%adapt_weights) allocate (object%calls (object%n_it), source = 0) allocate (object%calls_valid (object%n_it), source = 0) allocate (object%integral (object%n_it), source = 0._default) allocate (object%error (object%n_it), source = 0._default) allocate (object%efficiency (object%n_it), source = 0._default) read (u, "(A)") buffer select case (trim (adjustl (buffer))) case ("Results: [it, calls, valid, integral, error, efficiency]") do i = 1, object%n_it read (u, *) & j, object%calls(i), object%calls_valid(i), object%integral(i), object%error(i), & object%efficiency(i) end do object%integral_defined = .true. case ("Results: [undefined]") object%integral_defined = .false. case default call msg_fatal ("Reading integration pass: corrupted file") end select end subroutine pass_read @ %def pass_read @ Write the VAMP history for this pass. (The subroutine writes the whole array at once.) <>= procedure :: write_history => pass_write_history <>= subroutine pass_write_history (pass, unit) class(pass_t), intent(in) :: pass integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) if (allocated (pass%v_history)) then call vamp_write_history (u, pass%v_history) else write (u, "(1x,A)") "Global history: [undefined]" end if if (allocated (pass%v_histories)) then write (u, "(1x,A)") "Channel histories:" call vamp_write_history (u, pass%v_histories) else write (u, "(1x,A)") "Channel histories: [undefined]" end if end subroutine pass_write_history @ %def pass_write_history @ Given a number of calls and iterations, compute remaining data. <>= procedure :: configure => pass_configure <>= subroutine pass_configure (pass, n_it, n_calls, min_calls, & min_bins, max_bins, min_channel_calls) class(pass_t), intent(inout) :: pass integer, intent(in) :: n_it, n_calls, min_channel_calls integer, intent(in) :: min_calls, min_bins, max_bins pass%n_it = n_it if (min_calls /= 0) then pass%n_bins = max (min_bins, & min (n_calls / min_calls, max_bins)) else pass%n_bins = max_bins end if pass%n_calls = max (n_calls, max (min_calls, min_channel_calls)) if (pass%n_calls /= n_calls) then write (msg_buffer, "(A,I0)") "VAMP: too few calls, resetting " & // "n_calls to ", pass%n_calls call msg_warning () end if allocate (pass%calls (n_it), source = 0) allocate (pass%calls_valid (n_it), source = 0) allocate (pass%integral (n_it), source = 0._default) allocate (pass%error (n_it), source = 0._default) allocate (pass%efficiency (n_it), source = 0._default) end subroutine pass_configure @ %def pass_configure @ Allocate the VAMP history and give options. We assume that the [[configure]] routine above has been executed, so the number of iterations is known. <>= procedure :: configure_history => pass_configure_history <>= subroutine pass_configure_history (pass, n_channels, par) class(pass_t), intent(inout) :: pass integer, intent(in) :: n_channels type(history_parameters_t), intent(in) :: par if (par%global) then allocate (pass%v_history (pass%n_it)) call vamp_create_history (pass%v_history, & verbose = par%global_verbose) end if if (par%channel) then allocate (pass%v_histories (pass%n_it, n_channels)) call vamp_create_history (pass%v_histories, & verbose = par%channel_verbose) end if end subroutine pass_configure_history @ %def pass_configure_history @ Given two pass objects, compare them. All parameters must match. Where integrations are done in both (number of calls nonzero), the results must be equal (up to numerical noise). The allocated array sizes might be different, but should match up to the common [[n_it]] value. <>= interface operator (.matches.) module procedure pass_matches end interface operator (.matches.) <>= function pass_matches (pass, ref) result (ok) type(pass_t), intent(in) :: pass, ref integer :: n logical :: ok ok = .true. if (ok) ok = pass%i_pass == ref%i_pass if (ok) ok = pass%i_first_it == ref%i_first_it if (ok) ok = pass%n_it == ref%n_it if (ok) ok = pass%n_calls == ref%n_calls if (ok) ok = pass%n_bins == ref%n_bins if (ok) ok = pass%adapt_grids .eqv. ref%adapt_grids if (ok) ok = pass%adapt_weights .eqv. ref%adapt_weights if (ok) ok = pass%integral_defined .eqv. ref%integral_defined if (pass%integral_defined) then n = pass%n_it if (ok) ok = all (pass%calls(:n) == ref%calls(:n)) if (ok) ok = all (pass%calls_valid(:n) == ref%calls_valid (:n)) if (ok) ok = all (pass%integral(:n) .matches. ref%integral(:n)) if (ok) ok = all (pass%error(:n) .matches. ref%error(:n)) if (ok) ok = all (pass%efficiency(:n) .matches. ref%efficiency(:n)) end if end function pass_matches @ %def pass_matches @ Update a pass object, given a reference. The parameters must match, except for the [[n_it]] entry. The number of complete iterations must be less or equal to the reference, and the number of complete iterations in the reference must be no larger than [[n_it]]. Where results are present in both passes, they must match. Where results are present in the reference only, the pass is updated accordingly. <>= procedure :: update => pass_update <>= subroutine pass_update (pass, ref, ok) class(pass_t), intent(inout) :: pass type(pass_t), intent(in) :: ref logical, intent(out) :: ok integer :: n, n_ref ok = .true. if (ok) ok = pass%i_pass == ref%i_pass if (ok) ok = pass%i_first_it == ref%i_first_it if (ok) ok = pass%n_calls == ref%n_calls if (ok) ok = pass%n_bins == ref%n_bins if (ok) ok = pass%adapt_grids .eqv. ref%adapt_grids if (ok) ok = pass%adapt_weights .eqv. ref%adapt_weights if (ok) then if (ref%integral_defined) then if (.not. allocated (pass%calls)) then allocate (pass%calls (pass%n_it), source = 0) allocate (pass%calls_valid (pass%n_it), source = 0) allocate (pass%integral (pass%n_it), source = 0._default) allocate (pass%error (pass%n_it), source = 0._default) allocate (pass%efficiency (pass%n_it), source = 0._default) end if n = count (pass%calls /= 0) n_ref = count (ref%calls /= 0) ok = n <= n_ref .and. n_ref <= pass%n_it if (ok) ok = all (pass%calls(:n) == ref%calls(:n)) if (ok) ok = all (pass%calls_valid(:n) == ref%calls_valid(:n)) if (ok) ok = all (pass%integral(:n) .matches. ref%integral(:n)) if (ok) ok = all (pass%error(:n) .matches. ref%error(:n)) if (ok) ok = all (pass%efficiency(:n) .matches. ref%efficiency(:n)) if (ok) then pass%calls(n+1:n_ref) = ref%calls(n+1:n_ref) pass%calls_valid(n+1:n_ref) = ref%calls_valid(n+1:n_ref) pass%integral(n+1:n_ref) = ref%integral(n+1:n_ref) pass%error(n+1:n_ref) = ref%error(n+1:n_ref) pass%efficiency(n+1:n_ref) = ref%efficiency(n+1:n_ref) pass%integral_defined = any (pass%calls /= 0) end if end if end if end subroutine pass_update @ %def pass_update @ Match two real numbers: they are equal up to a tolerance, which is $10^{-8}$, matching the number of digits that are output by [[pass_write]]. In particular, if one number is exactly zero, the other one must also be zero. <>= interface operator (.matches.) module procedure real_matches end interface operator (.matches.) <>= elemental function real_matches (x, y) result (ok) real(default), intent(in) :: x, y logical :: ok real(default), parameter :: tolerance = 1.e-8_default ok = abs (x - y) <= tolerance * max (abs (x), abs (y)) end function real_matches @ %def real_matches @ Return the index of the most recent complete integration. If there is none, return zero. <>= procedure :: get_integration_index => pass_get_integration_index <>= function pass_get_integration_index (pass) result (n) class (pass_t), intent(in) :: pass integer :: n integer :: i n = 0 if (allocated (pass%calls)) then do i = 1, pass%n_it if (pass%calls(i) == 0) exit n = i end do end if end function pass_get_integration_index @ %def pass_get_integration_index @ Return the most recent integral and error, if available. <>= procedure :: get_calls => pass_get_calls procedure :: get_calls_valid => pass_get_calls_valid procedure :: get_integral => pass_get_integral procedure :: get_error => pass_get_error procedure :: get_efficiency => pass_get_efficiency <>= function pass_get_calls (pass) result (calls) class(pass_t), intent(in) :: pass integer :: calls integer :: n n = pass%get_integration_index () if (n /= 0) then calls = pass%calls(n) else calls = 0 end if end function pass_get_calls function pass_get_calls_valid (pass) result (calls_valid) class(pass_t), intent(in) :: pass integer :: calls_valid integer :: n n = pass%get_integration_index () if (n /= 0) then calls_valid = pass%calls_valid(n) else calls_valid = 0 end if end function pass_get_calls_valid function pass_get_integral (pass) result (integral) class(pass_t), intent(in) :: pass real(default) :: integral integer :: n n = pass%get_integration_index () if (n /= 0) then integral = pass%integral(n) else integral = 0 end if end function pass_get_integral function pass_get_error (pass) result (error) class(pass_t), intent(in) :: pass real(default) :: error integer :: n n = pass%get_integration_index () if (n /= 0) then error = pass%error(n) else error = 0 end if end function pass_get_error function pass_get_efficiency (pass) result (efficiency) class(pass_t), intent(in) :: pass real(default) :: efficiency integer :: n n = pass%get_integration_index () if (n /= 0) then efficiency = pass%efficiency(n) else efficiency = 0 end if end function pass_get_efficiency @ %def pass_get_calls @ %def pass_get_calls_valid @ %def pass_get_integral @ %def pass_get_error @ %def pass_get_efficiency @ \subsection{Integrator} <>= public :: mci_vamp_t <>= type, extends (mci_t) :: mci_vamp_t logical, dimension(:), allocatable :: dim_is_flat type(grid_parameters_t) :: grid_par type(history_parameters_t) :: history_par integer :: min_calls = 0 type(pass_t), pointer :: first_pass => null () type(pass_t), pointer :: current_pass => null () type(vamp_equivalences_t) :: equivalences logical :: rebuild = .true. logical :: check_grid_file = .true. logical :: grid_filename_set = .false. logical :: negative_weights = .false. logical :: verbose = .false. type(string_t) :: grid_filename character(32) :: md5sum_adapted = "" contains <> end type mci_vamp_t @ %def mci_vamp_t @ Reset: delete integration-pass entries. <>= procedure :: reset => mci_vamp_reset <>= subroutine mci_vamp_reset (object) class(mci_vamp_t), intent(inout) :: object type(pass_t), pointer :: current_pass do while (associated (object%first_pass)) current_pass => object%first_pass object%first_pass => current_pass%next call current_pass%final () deallocate (current_pass) end do object%current_pass => null () end subroutine mci_vamp_reset @ %def mci_vamp_reset @ Finalizer: reset and finalize the equivalences list. <>= procedure :: final => mci_vamp_final <>= subroutine mci_vamp_final (object) class(mci_vamp_t), intent(inout) :: object call object%reset () call vamp_equivalences_final (object%equivalences) call object%base_final () end subroutine mci_vamp_final @ %def mci_vamp_final @ Output. Do not output the grids themselves, this may result in tons of data. <>= procedure :: write => mci_vamp_write <>= subroutine mci_vamp_write (object, unit, pacify, md5sum_version) class(mci_vamp_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify logical, intent(in), optional :: md5sum_version type(pass_t), pointer :: current_pass integer :: u, i u = given_output_unit (unit) write (u, "(1x,A)") "VAMP integrator:" call object%base_write (u, pacify, md5sum_version) if (allocated (object%dim_is_flat)) then write (u, "(3x,A,999(1x,I0))") "Flat dimensions =", & pack ([(i, i = 1, object%n_dim)], object%dim_is_flat) end if write (u, "(1x,A)") "Grid parameters:" call object%grid_par%write (u) write (u, "(3x,A,I0)") "min_calls = ", object%min_calls write (u, "(3x,A,L1)") "negative weights = ", & object%negative_weights write (u, "(3x,A,L1)") "verbose = ", & object%verbose if (object%grid_par%use_vamp_equivalences) then call vamp_equivalences_write (object%equivalences, u) end if current_pass => object%first_pass do while (associated (current_pass)) write (u, "(1x,A,I0,A)") "Integration pass:" call current_pass%write (u, pacify) current_pass => current_pass%next end do if (object%md5sum_adapted /= "") then write (u, "(1x,A,A,A)") "MD5 sum (including results) = '", & object%md5sum_adapted, "'" end if end subroutine mci_vamp_write @ %def mci_vamp_write @ Write the history parameters. <>= procedure :: write_history_parameters => mci_vamp_write_history_parameters <>= subroutine mci_vamp_write_history_parameters (mci, unit) class(mci_vamp_t), intent(in) :: mci integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "VAMP history parameters:" call mci%history_par%write (unit) end subroutine mci_vamp_write_history_parameters @ %def mci_vamp_write_history_parameters @ Write the history, iterating over passes. We keep this separate from the generic [[write]] routine. <>= procedure :: write_history => mci_vamp_write_history <>= subroutine mci_vamp_write_history (mci, unit) class(mci_vamp_t), intent(in) :: mci integer, intent(in), optional :: unit type(pass_t), pointer :: current_pass integer :: i_pass integer :: u u = given_output_unit (unit) if (associated (mci%first_pass)) then write (u, "(1x,A)") "VAMP history (global):" i_pass = 0 current_pass => mci%first_pass do while (associated (current_pass)) i_pass = i_pass + 1 write (u, "(1x,A,I0,':')") "Pass #", i_pass call current_pass%write_history (u) current_pass => current_pass%next end do end if end subroutine mci_vamp_write_history @ %def mci_vamp_write_history @ Compute the MD5 sum, including the configuration MD5 sum and the printout, which incorporates the current results. <>= procedure :: compute_md5sum => mci_vamp_compute_md5sum <>= subroutine mci_vamp_compute_md5sum (mci, pacify) class(mci_vamp_t), intent(inout) :: mci logical, intent(in), optional :: pacify integer :: u mci%md5sum_adapted = "" u = free_unit () open (u, status = "scratch", action = "readwrite") write (u, "(A)") mci%md5sum call mci%write (u, pacify, md5sum_version = .true.) rewind (u) mci%md5sum_adapted = md5sum (u) close (u) end subroutine mci_vamp_compute_md5sum @ %def mci_vamp_compute_md5sum @ Return the MD5 sum: If available, return the adapted one. <>= procedure :: get_md5sum => mci_vamp_get_md5sum <>= pure function mci_vamp_get_md5sum (mci) result (md5sum) class(mci_vamp_t), intent(in) :: mci character(32) :: md5sum if (mci%md5sum_adapted /= "") then md5sum = mci%md5sum_adapted else md5sum = mci%md5sum end if end function mci_vamp_get_md5sum @ %def mci_vamp_get_md5sum @ Startup message: short version. <>= procedure :: startup_message => mci_vamp_startup_message <>= subroutine mci_vamp_startup_message (mci, unit, n_calls) class(mci_vamp_t), intent(in) :: mci integer, intent(in), optional :: unit, n_calls integer :: num_calls, n_bins if (present (n_calls)) then num_calls = n_calls else num_calls = 0 end if if (mci%min_calls /= 0) then n_bins = max (mci%grid_par%min_bins, & min (num_calls / mci%min_calls, & mci%grid_par%max_bins)) else n_bins = mci%grid_par%max_bins end if call mci%base_startup_message (unit = unit, n_calls = n_calls) if (mci%grid_par%use_vamp_equivalences) then write (msg_buffer, "(A,2(1x,I0,1x,A))") & "Integrator: Using VAMP channel equivalences" call msg_message (unit = unit) end if write (msg_buffer, "(A,2(1x,I0,1x,A),L1)") & "Integrator:", num_calls, & "initial calls,", n_bins, & "bins, stratified = ", & mci%grid_par%stratified call msg_message (unit = unit) write (msg_buffer, "(A,2(1x,I0,1x,A))") & "Integrator: VAMP" call msg_message (unit = unit) end subroutine mci_vamp_startup_message @ %def mci_vamp_startup_message @ Log entry: just headline. <>= procedure :: write_log_entry => mci_vamp_write_log_entry <>= subroutine mci_vamp_write_log_entry (mci, u) class(mci_vamp_t), intent(in) :: mci integer, intent(in) :: u write (u, "(1x,A)") "MC Integrator is VAMP" call write_separator (u) call mci%write_history (u) call write_separator (u) if (mci%grid_par%use_vamp_equivalences) then call vamp_equivalences_write (mci%equivalences, u) else write (u, "(3x,A)") "No VAMP equivalences have been used" end if call write_separator (u) call mci%write_chain_weights (u) end subroutine mci_vamp_write_log_entry @ %def mci_vamp_write_log_entry @ Set the MCI index (necessary for processes with multiple components). We append the index to the grid filename, just before the final dotted suffix. <>= procedure :: record_index => mci_vamp_record_index <>= subroutine mci_vamp_record_index (mci, i_mci) class(mci_vamp_t), intent(inout) :: mci integer, intent(in) :: i_mci type(string_t) :: basename, suffix character(32) :: buffer if (mci%grid_filename_set) then basename = mci%grid_filename call split (basename, suffix, ".", back=.true.) write (buffer, "(I0)") i_mci if (basename /= "") then mci%grid_filename = basename // ".m" // trim (buffer) // "." // suffix else mci%grid_filename = suffix // ".m" // trim (buffer) // ".vg" end if end if end subroutine mci_vamp_record_index @ %def mci_vamp_record_index @ Set the grid parameters. <>= procedure :: set_grid_parameters => mci_vamp_set_grid_parameters <>= subroutine mci_vamp_set_grid_parameters (mci, grid_par) class(mci_vamp_t), intent(inout) :: mci type(grid_parameters_t), intent(in) :: grid_par mci%grid_par = grid_par mci%min_calls = grid_par%min_calls_per_bin * mci%n_channel end subroutine mci_vamp_set_grid_parameters @ %def mci_vamp_set_grid_parameters @ Set the history parameters. <>= procedure :: set_history_parameters => mci_vamp_set_history_parameters <>= subroutine mci_vamp_set_history_parameters (mci, history_par) class(mci_vamp_t), intent(inout) :: mci type(history_parameters_t), intent(in) :: history_par mci%history_par = history_par end subroutine mci_vamp_set_history_parameters @ %def mci_vamp_set_history_parameters @ Set the rebuild flag, also the flag for checking the grid file. <>= procedure :: set_rebuild_flag => mci_vamp_set_rebuild_flag <>= subroutine mci_vamp_set_rebuild_flag (mci, rebuild, check_grid_file) class(mci_vamp_t), intent(inout) :: mci logical, intent(in) :: rebuild logical, intent(in) :: check_grid_file mci%rebuild = rebuild mci%check_grid_file = check_grid_file end subroutine mci_vamp_set_rebuild_flag @ %def mci_vamp_set_rebuild_flag @ Set the filename. <>= procedure :: set_grid_filename => mci_vamp_set_grid_filename <>= subroutine mci_vamp_set_grid_filename (mci, name, run_id) class(mci_vamp_t), intent(inout) :: mci type(string_t), intent(in) :: name type(string_t), intent(in), optional :: run_id if (present (run_id)) then mci%grid_filename = name // "." // run_id // ".vg" else mci%grid_filename = name // ".vg" end if mci%grid_filename_set = .true. end subroutine mci_vamp_set_grid_filename @ %def mci_vamp_set_grid_filename @ To simplify the interface, we prepend a grid path in a separate subroutine. <>= procedure :: prepend_grid_path => mci_vamp_prepend_grid_path <>= subroutine mci_vamp_prepend_grid_path (mci, prefix) class(mci_vamp_t), intent(inout) :: mci type(string_t), intent(in) :: prefix if (mci%grid_filename_set) then mci%grid_filename = prefix // "/" // mci%grid_filename else call msg_warning ("Cannot add prefix to invalid grid filename!") end if end subroutine mci_vamp_prepend_grid_path @ %def mci_vamp_prepend_grid_path @ Declare particular dimensions as flat. <>= procedure :: declare_flat_dimensions => mci_vamp_declare_flat_dimensions <>= subroutine mci_vamp_declare_flat_dimensions (mci, dim_flat) class(mci_vamp_t), intent(inout) :: mci integer, dimension(:), intent(in) :: dim_flat integer :: d allocate (mci%dim_is_flat (mci%n_dim), source = .false.) do d = 1, size (dim_flat) mci%dim_is_flat(dim_flat(d)) = .true. end do end subroutine mci_vamp_declare_flat_dimensions @ %def mci_vamp_declare_flat_dimensions @ Declare equivalences. We have an array of channel equivalences, provided by the phase-space module. Here, we translate this into the [[vamp_equivalences]] array. <>= procedure :: declare_equivalences => mci_vamp_declare_equivalences <>= subroutine mci_vamp_declare_equivalences (mci, channel, dim_offset) class(mci_vamp_t), intent(inout) :: mci type(phs_channel_t), dimension(:), intent(in) :: channel integer, intent(in) :: dim_offset integer, dimension(:), allocatable :: perm, mode integer :: n_channels, n_dim, n_equivalences integer :: c, i, j, left, right integer :: n_dim_perm n_channels = mci%n_channel n_dim = mci%n_dim n_equivalences = 0 do c = 1, n_channels n_equivalences = n_equivalences + size (channel(c)%eq) end do call vamp_equivalences_init (mci%equivalences, & n_equivalences, n_channels, n_dim) allocate (perm (n_dim)) allocate (mode (n_dim)) perm = [(i, i = 1, n_dim)] mode = VEQ_IDENTITY c = 1 j = 0 do i = 1, n_equivalences if (j < size (channel(c)%eq)) then j = j + 1 else c = c + 1 j = 1 end if associate (eq => channel(c)%eq(j)) left = c right = eq%c n_dim_perm = size (eq%perm) perm(dim_offset + 1:dim_offset + n_dim_perm) = eq%perm + dim_offset mode(dim_offset + 1:dim_offset + n_dim_perm) = eq%mode call vamp_equivalence_set (mci%equivalences, & i, left, right, perm, mode) end associate end do call vamp_equivalences_complete (mci%equivalences) end subroutine mci_vamp_declare_equivalences @ %def mci_vamp_declare_equivalences @ Allocate instance with matching type. <>= procedure :: allocate_instance => mci_vamp_allocate_instance <>= subroutine mci_vamp_allocate_instance (mci, mci_instance) class(mci_vamp_t), intent(in) :: mci class(mci_instance_t), intent(out), pointer :: mci_instance allocate (mci_vamp_instance_t :: mci_instance) end subroutine mci_vamp_allocate_instance @ %def mci_vamp_allocate_instance @ Allocate a new integration pass. We can preset everything that does not depend on the number of iterations and calls. This is postponed to the [[integrate]] method. In the final pass, we do not check accuracy goal etc., since we can assume that the user wants to perform and average all iterations in this pass. <>= procedure :: add_pass => mci_vamp_add_pass <>= subroutine mci_vamp_add_pass (mci, adapt_grids, adapt_weights, final_pass) class(mci_vamp_t), intent(inout) :: mci logical, intent(in), optional :: adapt_grids, adapt_weights, final_pass integer :: i_pass, i_it type(pass_t), pointer :: new allocate (new) if (associated (mci%current_pass)) then i_pass = mci%current_pass%i_pass + 1 i_it = mci%current_pass%i_first_it + mci%current_pass%n_it mci%current_pass%next => new else i_pass = 1 i_it = 1 mci%first_pass => new end if mci%current_pass => new new%i_pass = i_pass new%i_first_it = i_it if (present (adapt_grids)) then new%adapt_grids = adapt_grids else new%adapt_grids = .false. end if if (present (adapt_weights)) then new%adapt_weights = adapt_weights else new%adapt_weights = .false. end if if (present (final_pass)) then new%is_final_pass = final_pass else new%is_final_pass = .false. end if end subroutine mci_vamp_add_pass @ %def mci_vamp_add_pass @ Update the list of integration passes. All passes except for the last one must match exactly. For the last one, integration results are updated. The reference output may contain extra passes, these are ignored. <>= procedure :: update_from_ref => mci_vamp_update_from_ref <>= subroutine mci_vamp_update_from_ref (mci, mci_ref, success) class(mci_vamp_t), intent(inout) :: mci class(mci_t), intent(in) :: mci_ref logical, intent(out) :: success type(pass_t), pointer :: current_pass, ref_pass select type (mci_ref) type is (mci_vamp_t) current_pass => mci%first_pass ref_pass => mci_ref%first_pass success = .true. do while (success .and. associated (current_pass)) if (associated (ref_pass)) then if (associated (current_pass%next)) then success = current_pass .matches. ref_pass else call current_pass%update (ref_pass, success) if (current_pass%integral_defined) then mci%integral = current_pass%get_integral () mci%error = current_pass%get_error () mci%efficiency = current_pass%get_efficiency () mci%integral_known = .true. mci%error_known = .true. mci%efficiency_known = .true. end if end if current_pass => current_pass%next ref_pass => ref_pass%next else success = .false. end if end do end select end subroutine mci_vamp_update_from_ref @ %def mci_vamp_update @ Update the MCI record (i.e., the integration passes) by reading from input stream. The stream should contain a [[write]] output from a previous run. We first check the MD5 sum of the configuration parameters. If that matches, we proceed directly to the stored integration passes. If successful, we may continue to read the file; the position will be after a blank line that must follow the MCI record. <>= procedure :: update => mci_vamp_update <>= subroutine mci_vamp_update (mci, u, success) class(mci_vamp_t), intent(inout) :: mci integer, intent(in) :: u logical, intent(out) :: success character(80) :: buffer character(32) :: md5sum_file type(mci_vamp_t) :: mci_file integer :: n_pass, n_it call read_sval (u, md5sum_file) if (mci%check_grid_file) then success = md5sum_file == mci%md5sum else success = .true. end if if (success) then read (u, *) read (u, "(A)") buffer if (trim (adjustl (buffer)) == "VAMP integrator:") then n_pass = 0 n_it = 0 do read (u, "(A)") buffer select case (trim (adjustl (buffer))) case ("") exit case ("Integration pass:") call mci_file%add_pass () call mci_file%current_pass%read (u, n_pass, n_it) n_pass = n_pass + 1 n_it = n_it + mci_file%current_pass%n_it end select end do call mci%update_from_ref (mci_file, success) call mci_file%final () else call msg_fatal ("VAMP: reading grid file: corrupted data") end if end if end subroutine mci_vamp_update @ %def mci_vamp_update @ Read / write grids from / to file. Bug fix for 2.2.5: after reading grids from file, channel weights must be copied back to the [[mci_instance]] record. <>= procedure :: write_grids => mci_vamp_write_grids procedure :: read_grids_header => mci_vamp_read_grids_header procedure :: read_grids_data => mci_vamp_read_grids_data procedure :: read_grids => mci_vamp_read_grids <>= subroutine mci_vamp_write_grids (mci, instance) class(mci_vamp_t), intent(in) :: mci class(mci_instance_t), intent(inout) :: instance integer :: u select type (instance) type is (mci_vamp_instance_t) if (mci%grid_filename_set) then if (instance%grids_defined) then u = free_unit () open (u, file = char (mci%grid_filename), & action = "write", status = "replace") write (u, "(1x,A,A,A)") "MD5sum = '", mci%md5sum, "'" write (u, *) call mci%write (u) write (u, *) write (u, "(1x,A)") "VAMP grids:" call vamp_write_grids (instance%grids, u, & write_integrals = .true.) close (u) else call msg_bug ("VAMP: write grids: grids undefined") end if else call msg_bug ("VAMP: write grids: filename undefined") end if end select end subroutine mci_vamp_write_grids subroutine mci_vamp_read_grids_header (mci, success) class(mci_vamp_t), intent(inout) :: mci logical, intent(out) :: success logical :: exist integer :: u success = .false. if (mci%grid_filename_set) then inquire (file = char (mci%grid_filename), exist = exist) if (exist) then u = free_unit () open (u, file = char (mci%grid_filename), & action = "read", status = "old") call mci%update (u, success) close (u) if (.not. success) then write (msg_buffer, "(A,A,A)") & "VAMP: parameter mismatch, discarding grid file '", & char (mci%grid_filename), "'" call msg_message () end if end if else call msg_bug ("VAMP: read grids: filename undefined") end if end subroutine mci_vamp_read_grids_header subroutine mci_vamp_read_grids_data (mci, instance, read_integrals) class(mci_vamp_t), intent(in) :: mci class(mci_instance_t), intent(inout) :: instance logical, intent(in), optional :: read_integrals integer :: u character(80) :: buffer select type (instance) type is (mci_vamp_instance_t) if (.not. instance%grids_defined) then u = free_unit () open (u, file = char (mci%grid_filename), & action = "read", status = "old") do read (u, "(A)") buffer if (trim (adjustl (buffer)) == "VAMP grids:") exit end do call vamp_read_grids (instance%grids, u, read_integrals) close (u) call instance%set_channel_weights (instance%grids%weights) instance%grids_defined = .true. else call msg_bug ("VAMP: read grids: grids already defined") end if end select end subroutine mci_vamp_read_grids_data subroutine mci_vamp_read_grids (mci, instance, success) class(mci_vamp_t), intent(inout) :: mci class(mci_instance_t), intent(inout) :: instance logical, intent(out) :: success logical :: exist integer :: u character(80) :: buffer select type (instance) type is (mci_vamp_instance_t) success = .false. if (mci%grid_filename_set) then if (.not. instance%grids_defined) then inquire (file = char (mci%grid_filename), exist = exist) if (exist) then u = free_unit () open (u, file = char (mci%grid_filename), & action = "read", status = "old") call mci%update (u, success) if (success) then read (u, "(A)") buffer if (trim (adjustl (buffer)) == "VAMP grids:") then call vamp_read_grids (instance%grids, u) else call msg_fatal ("VAMP: reading grid file: & &corrupted grid data") end if else write (msg_buffer, "(A,A,A)") & "VAMP: parameter mismatch, discarding grid file '", & char (mci%grid_filename), "'" call msg_message () end if close (u) instance%grids_defined = success end if else call msg_bug ("VAMP: read grids: grids already defined") end if else call msg_bug ("VAMP: read grids: filename undefined") end if end select end subroutine mci_vamp_read_grids @ %def mci_vamp_write_grids @ %def mci_vamp_read_grids_header @ %def mci_vamp_read_grids_data @ %def mci_vamp_read_grids @ Auxiliary: Read real, integer, string value. We search for an equals sign, the value must follow. <>= subroutine read_rval (u, rval) integer, intent(in) :: u real(default), intent(out) :: rval character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) rval end subroutine read_rval subroutine read_ival (u, ival) integer, intent(in) :: u integer, intent(out) :: ival character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) ival end subroutine read_ival subroutine read_sval (u, sval) integer, intent(in) :: u character(*), intent(out) :: sval character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) sval end subroutine read_sval subroutine read_lval (u, lval) integer, intent(in) :: u logical, intent(out) :: lval character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) lval end subroutine read_lval @ %def read_rval read_ival read_sval read_lval @ Integrate. Perform a new integration pass (possibly reusing previous results), which may consist of several iterations. Note: we record the integral once per iteration. The integral stored in the [[mci]] record itself is the last integral of the current iteration, no averaging done. The [[results]] record may average results. In case we read the integration from file and we added new iterations to the pass preserving number of calls, we need to reshape the grids in order to incorporate the correct number of calls. Else the grids would be sampled with the number of calls from the grids file, which does not need to coincide with the number of calls from the pass. Note: recording the efficiency is not supported yet. <>= procedure :: integrate => mci_vamp_integrate <>= subroutine mci_vamp_integrate (mci, instance, sampler, & n_it, n_calls, results, pacify) class(mci_vamp_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls class(mci_results_t), intent(inout), optional :: results logical, intent(in), optional :: pacify integer :: it logical :: reshape, from_file, success select type (instance) type is (mci_vamp_instance_t) if (associated (mci%current_pass)) then mci%current_pass%integral_defined = .false. call mci%current_pass%configure (n_it, n_calls, & mci%min_calls, mci%grid_par%min_bins, & mci%grid_par%max_bins, & mci%grid_par%min_calls_per_channel * mci%n_channel) call mci%current_pass%configure_history & (mci%n_channel, mci%history_par) instance%pass_complete = .false. instance%it_complete = .false. call instance%new_pass (reshape) if (.not. instance%grids_defined .or. instance%grids_from_file) then if (mci%grid_filename_set .and. .not. mci%rebuild) then call mci%read_grids_header (success) from_file = success if (.not. instance%grids_defined .and. success) then call mci%read_grids_data (instance) end if else from_file = .false. end if else from_file = .false. end if if (from_file) then if (.not. mci%check_grid_file) & call msg_warning ("Reading grid file: MD5 sum check disabled") call msg_message ("VAMP: " & // "using grids and results from file '" & // char (mci%grid_filename) // "'") else if (.not. instance%grids_defined) then call instance%create_grids () end if do it = 1, instance%n_it if (signal_is_pending ()) return reshape = reshape .or. & (instance%grids_from_file .and. n_it > mci%current_pass%get_integration_index ()) instance%grids_from_file = from_file .and. & it <= mci%current_pass%get_integration_index () if (.not. instance%grids_from_file) then instance%it_complete = .false. call instance%adapt_grids () if (signal_is_pending ()) return call instance%adapt_weights () if (signal_is_pending ()) return call instance%discard_integrals (reshape) if (mci%grid_par%use_vamp_equivalences) then call instance%sample_grids (mci%rng, sampler, & mci%equivalences) else call instance%sample_grids (mci%rng, sampler) end if if (signal_is_pending ()) return instance%it_complete = .true. if (instance%integral /= 0) then mci%current_pass%calls(it) = instance%calls mci%current_pass%calls_valid(it) = instance%calls_valid mci%current_pass%integral(it) = instance%integral if (abs (instance%error / instance%integral) & > epsilon (1._default)) then mci%current_pass%error(it) = instance%error end if mci%current_pass%efficiency(it) = instance%efficiency end if mci%current_pass%integral_defined = .true. end if if (present (results)) then if (mci%has_chains ()) then call mci%collect_chain_weights (instance%w) call results%record (1, & n_calls = mci%current_pass%calls(it), & n_calls_valid = mci%current_pass%calls_valid(it), & integral = mci%current_pass%integral(it), & error = mci%current_pass%error(it), & efficiency = mci%current_pass%efficiency(it), & ! TODO Insert pos. and neg. Efficiency from VAMP. efficiency_pos = 0._default, & efficiency_neg = 0._default, & chain_weights = mci%chain_weights, & suppress = pacify) else call results%record (1, & n_calls = mci%current_pass%calls(it), & n_calls_valid = mci%current_pass%calls_valid(it), & integral = mci%current_pass%integral(it), & error = mci%current_pass%error(it), & efficiency = mci%current_pass%efficiency(it), & ! TODO Insert pos. and neg. Efficiency from VAMP. efficiency_pos = 0._default, & efficiency_neg = 0._default, & suppress = pacify) end if end if if (.not. instance%grids_from_file & .and. mci%grid_filename_set) then call mci%write_grids (instance) end if call instance%allow_adaptation () reshape = .false. if (.not. mci%current_pass%is_final_pass) then call mci%check_goals (it, success) if (success) exit end if end do if (signal_is_pending ()) return instance%pass_complete = .true. mci%integral = mci%current_pass%get_integral() mci%error = mci%current_pass%get_error() mci%efficiency = mci%current_pass%get_efficiency() mci%integral_known = .true. mci%error_known = .true. mci%efficiency_known = .true. call mci%compute_md5sum (pacify) else call msg_bug ("MCI integrate: current_pass object not allocated") end if end select end subroutine mci_vamp_integrate @ %def mci_vamp_integrate @ Check whether we are already finished with this pass. <>= procedure :: check_goals => mci_vamp_check_goals <>= subroutine mci_vamp_check_goals (mci, it, success) class(mci_vamp_t), intent(inout) :: mci integer, intent(in) :: it logical, intent(out) :: success success = .false. if (mci%error_reached (it)) then mci%current_pass%n_it = it call msg_message ("VAMP: error goal reached; & &skipping iterations") success = .true. return end if if (mci%rel_error_reached (it)) then mci%current_pass%n_it = it call msg_message ("VAMP: relative error goal reached; & &skipping iterations") success = .true. return end if if (mci%accuracy_reached (it)) then mci%current_pass%n_it = it call msg_message ("VAMP: accuracy goal reached; & &skipping iterations") success = .true. return end if end subroutine mci_vamp_check_goals @ %def mci_vamp_check_goals @ Return true if the error, relative error, or accuracy goal has been reached, if any. <>= procedure :: error_reached => mci_vamp_error_reached procedure :: rel_error_reached => mci_vamp_rel_error_reached procedure :: accuracy_reached => mci_vamp_accuracy_reached <>= function mci_vamp_error_reached (mci, it) result (flag) class(mci_vamp_t), intent(in) :: mci integer, intent(in) :: it logical :: flag real(default) :: error_goal, error error_goal = mci%grid_par%error_goal if (error_goal > 0) then associate (pass => mci%current_pass) if (pass%integral_defined) then error = abs (pass%error(it)) flag = error < error_goal else flag = .false. end if end associate else flag = .false. end if end function mci_vamp_error_reached function mci_vamp_rel_error_reached (mci, it) result (flag) class(mci_vamp_t), intent(in) :: mci integer, intent(in) :: it logical :: flag real(default) :: rel_error_goal, rel_error rel_error_goal = mci%grid_par%rel_error_goal if (rel_error_goal > 0) then associate (pass => mci%current_pass) if (pass%integral_defined) then if (pass%integral(it) /= 0) then rel_error = abs (pass%error(it) / pass%integral(it)) flag = rel_error < rel_error_goal else flag = .true. end if else flag = .false. end if end associate else flag = .false. end if end function mci_vamp_rel_error_reached function mci_vamp_accuracy_reached (mci, it) result (flag) class(mci_vamp_t), intent(in) :: mci integer, intent(in) :: it logical :: flag real(default) :: accuracy_goal, accuracy accuracy_goal = mci%grid_par%accuracy_goal if (accuracy_goal > 0) then associate (pass => mci%current_pass) if (pass%integral_defined) then if (pass%integral(it) /= 0) then accuracy = abs (pass%error(it) / pass%integral(it)) & * sqrt (real (pass%calls(it), default)) flag = accuracy < accuracy_goal else flag = .true. end if else flag = .false. end if end associate else flag = .false. end if end function mci_vamp_accuracy_reached @ %def mci_vamp_error_reached @ %def mci_vamp_rel_error_reached @ %def mci_vamp_accuracy_reached @ Prepare an event generation pass. Should be called before a sequence of events is generated, then we should call the corresponding finalizer. The pass-specific data of the previous integration pass are retained, but we reset the number of iterations and calls to zero. The latter now counts the number of events (calls to the sampling function, actually). <>= procedure :: prepare_simulation => mci_vamp_prepare_simulation <>= subroutine mci_vamp_prepare_simulation (mci) class(mci_vamp_t), intent(inout) :: mci logical :: success if (mci%grid_filename_set) then call mci%read_grids_header (success) call mci%compute_md5sum () if (.not. success) then call msg_fatal ("Simulate: " & // "reading integration grids from file '" & // char (mci%grid_filename) // "' failed") end if else call msg_bug ("VAMP: simulation: no grids, no grid filename") end if end subroutine mci_vamp_prepare_simulation @ %def mci_vamp_prepare_simulation @ Generate weighted event. Note that the event weight ([[vamp_weight]]) is not just the MCI weight. [[vamp_next_event]] selects a channel based on the channel weights multiplied by the (previously recorded) maximum integrand value of the channel. The MCI weight is renormalized accordingly, to cancel this effect on the result. <>= procedure :: generate_weighted_event => mci_vamp_generate_weighted_event <>= subroutine mci_vamp_generate_weighted_event (mci, instance, sampler) class(mci_vamp_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler class(vamp_data_t), allocatable :: data type(exception) :: vamp_exception select type (instance) type is (mci_vamp_instance_t) instance%vamp_weight_set = .false. allocate (mci_workspace_t :: data) select type (data) type is (mci_workspace_t) data%sampler => sampler data%instance => instance end select select type (rng => mci%rng) type is (rng_tao_t) if (instance%grids_defined) then call vamp_next_event ( & instance%vamp_x, & rng%state, & instance%grids, & vamp_sampling_function, & data, & phi = phi_trivial, & weight = instance%vamp_weight, & exc = vamp_exception) call handle_vamp_exception (vamp_exception, mci%verbose) instance%vamp_excess = 0 instance%vamp_weight_set = .true. else call msg_bug ("VAMP: generate event: grids undefined") end if class default call msg_fatal ("VAMP event generation: & &random-number generator must be TAO") end select end select end subroutine mci_vamp_generate_weighted_event @ %def mci_vamp_generate_weighted_event @ Generate unweighted event. <>= procedure :: generate_unweighted_event => & mci_vamp_generate_unweighted_event <>= subroutine mci_vamp_generate_unweighted_event (mci, instance, sampler) class(mci_vamp_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler class(vamp_data_t), allocatable :: data logical :: positive type(exception) :: vamp_exception select type (instance) type is (mci_vamp_instance_t) instance%vamp_weight_set = .false. allocate (mci_workspace_t :: data) select type (data) type is (mci_workspace_t) data%sampler => sampler data%instance => instance end select select type (rng => mci%rng) type is (rng_tao_t) if (instance%grids_defined) then REJECTION: do call vamp_next_event ( & instance%vamp_x, & rng%state, & instance%grids, & vamp_sampling_function, & data, & phi = phi_trivial, & excess = instance%vamp_excess, & positive = positive, & exc = vamp_exception) if (signal_is_pending ()) return if (sampler%is_valid ()) exit REJECTION end do REJECTION call handle_vamp_exception (vamp_exception, mci%verbose) if (positive) then instance%vamp_weight = 1 else if (instance%negative_weights) then instance%vamp_weight = -1 else call msg_fatal ("VAMP: event with negative weight generated") instance%vamp_weight = 0 end if instance%vamp_weight_set = .true. else call msg_bug ("VAMP: generate event: grids undefined") end if class default call msg_fatal ("VAMP event generation: & &random-number generator must be TAO") end select end select end subroutine mci_vamp_generate_unweighted_event @ %def mci_vamp_generate_unweighted_event @ Rebuild an event, using the [[state]] input. Note: This feature is currently unused. <>= procedure :: rebuild_event => mci_vamp_rebuild_event <>= subroutine mci_vamp_rebuild_event (mci, instance, sampler, state) class(mci_vamp_t), intent(inout) :: mci class(mci_instance_t), intent(inout) :: instance class(mci_sampler_t), intent(inout) :: sampler class(mci_state_t), intent(in) :: state call msg_bug ("MCI vamp rebuild event not implemented yet") end subroutine mci_vamp_rebuild_event @ %def mci_vamp_rebuild_event @ Pacify: override the default no-op, since VAMP numerics might need some massage. <>= procedure :: pacify => mci_vamp_pacify <>= subroutine mci_vamp_pacify (object, efficiency_reset, error_reset) class(mci_vamp_t), intent(inout) :: object logical, intent(in), optional :: efficiency_reset, error_reset logical :: err_reset type(pass_t), pointer :: current_pass err_reset = .false. if (present (error_reset)) err_reset = error_reset current_pass => object%first_pass do while (associated (current_pass)) if (allocated (current_pass%error) .and. err_reset) then current_pass%error = 0 end if if (allocated (current_pass%efficiency) .and. err_reset) then current_pass%efficiency = 1 end if current_pass => current_pass%next end do end subroutine mci_vamp_pacify @ %def mci_vamp_pacify @ \subsection{Sampler as Workspace} In the full setup, the sampling function requires the process instance object as workspace. We implement this by (i) implementing the process instance as a type extension of the abstract [[sampler_t]] object used by the MCI implementation and (ii) providing such an object as an extra argument to the sampling function that VAMP can call. To minimize cross-package dependencies, we use an abstract type [[vamp_workspace]] that VAMP declares and extend this by including a pointer to the [[sampler]] and [[instance]] objects. In the body of the sampling function, we dereference this pointer and can then work with the contents. <>= type, extends (vamp_data_t) :: mci_workspace_t class(mci_sampler_t), pointer :: sampler => null () class(mci_vamp_instance_t), pointer :: instance => null () end type mci_workspace_t @ %def mci_workspace_t @ \subsection{Integrator instance} The history entries should point to the corresponding history entry in the [[pass_t]] object. If there is none, we may allocate a local history, which is then just transient. <>= public :: mci_vamp_instance_t <>= type, extends (mci_instance_t) :: mci_vamp_instance_t type(mci_vamp_t), pointer :: mci => null () logical :: grids_defined = .false. logical :: grids_from_file = .false. integer :: n_it = 0 integer :: it = 0 logical :: pass_complete = .false. integer :: n_calls = 0 integer :: calls = 0 integer :: calls_valid = 0 logical :: it_complete = .false. logical :: enable_adapt_grids = .false. logical :: enable_adapt_weights = .false. logical :: allow_adapt_grids = .false. logical :: allow_adapt_weights = .false. integer :: n_adapt_grids = 0 integer :: n_adapt_weights = 0 logical :: generating_events = .false. real(default) :: safety_factor = 1 type(vamp_grids) :: grids real(default) :: g = 0 real(default), dimension(:), allocatable :: gi real(default) :: integral = 0 real(default) :: error = 0 real(default) :: efficiency = 0 real(default), dimension(:), allocatable :: vamp_x logical :: vamp_weight_set = .false. real(default) :: vamp_weight = 0 real(default) :: vamp_excess = 0 logical :: allocate_global_history = .false. type(vamp_history), dimension(:), pointer :: v_history => null () logical :: allocate_channel_history = .false. type(vamp_history), dimension(:,:), pointer :: v_histories => null () contains <> end type mci_vamp_instance_t @ %def mci_vamp_instance_t @ Output. <>= procedure :: write => mci_vamp_instance_write <>= subroutine mci_vamp_instance_write (object, unit, pacify) class(mci_vamp_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify integer :: u, i character(len=7) :: fmt call pac_fmt (fmt, FMT_17, FMT_14, pacify) u = given_output_unit (unit) write (u, "(3x,A," // FMT_19 // ")") "Integrand = ", object%integrand write (u, "(3x,A," // FMT_19 // ")") "Weight = ", object%mci_weight if (object%vamp_weight_set) then write (u, "(3x,A," // FMT_19 // ")") "VAMP wgt = ", object%vamp_weight if (object%vamp_excess /= 0) then write (u, "(3x,A," // FMT_19 // ")") "VAMP exc = ", & object%vamp_excess end if end if write (u, "(3x,A,L1)") "adapt grids = ", object%enable_adapt_grids write (u, "(3x,A,L1)") "adapt weights = ", object%enable_adapt_weights if (object%grids_defined) then if (object%grids_from_file) then write (u, "(3x,A)") "VAMP grids: read from file" else write (u, "(3x,A)") "VAMP grids: defined" end if else write (u, "(3x,A)") "VAMP grids: [undefined]" end if write (u, "(3x,A,I0)") "n_it = ", object%n_it write (u, "(3x,A,I0)") "it = ", object%it write (u, "(3x,A,L1)") "pass complete = ", object%it_complete write (u, "(3x,A,I0)") "n_calls = ", object%n_calls write (u, "(3x,A,I0)") "calls = ", object%calls write (u, "(3x,A,I0)") "calls_valid = ", object%calls_valid write (u, "(3x,A,L1)") "it complete = ", object%it_complete write (u, "(3x,A,I0)") "n adapt.(g) = ", object%n_adapt_grids write (u, "(3x,A,I0)") "n adapt.(w) = ", object%n_adapt_weights write (u, "(3x,A,L1)") "gen. events = ", object%generating_events write (u, "(3x,A,L1)") "neg. weights = ", object%negative_weights if (object%safety_factor /= 1) write & (u, "(3x,A," // fmt // ")") "safety f = ", object%safety_factor write (u, "(3x,A," // fmt // ")") "integral = ", object%integral write (u, "(3x,A," // fmt // ")") "error = ", object%error write (u, "(3x,A," // fmt // ")") "eff. = ", object%efficiency write (u, "(3x,A)") "weights:" do i = 1, size (object%w) write (u, "(5x,I0,1x," // FMT_12 // ")") i, object%w(i) end do end subroutine mci_vamp_instance_write @ %def mci_vamp_instance_write @ Write the grids to the specified unit. <>= procedure :: write_grids => mci_vamp_instance_write_grids <>= subroutine mci_vamp_instance_write_grids (object, unit) class(mci_vamp_instance_t), intent(in) :: object integer, intent(in), optional :: unit integer :: u u = given_output_unit (unit) if (object%grids_defined) then call vamp_write_grids (object%grids, u, write_integrals = .true.) end if end subroutine mci_vamp_instance_write_grids @ %def mci_vamp_instance_write_grids @ Finalizer: the history arrays are pointer arrays and need finalization. <>= procedure :: final => mci_vamp_instance_final <>= subroutine mci_vamp_instance_final (object) class(mci_vamp_instance_t), intent(inout) :: object if (object%allocate_global_history) then if (associated (object%v_history)) then call vamp_delete_history (object%v_history) deallocate (object%v_history) end if end if if (object%allocate_channel_history) then if (associated (object%v_histories)) then call vamp_delete_history (object%v_histories) deallocate (object%v_histories) end if end if if (object%grids_defined) then call vamp_delete_grids (object%grids) object%grids_defined = .false. end if end subroutine mci_vamp_instance_final @ %def mci_vamp_instance_final @ Initializer. <>= procedure :: init => mci_vamp_instance_init <>= subroutine mci_vamp_instance_init (mci_instance, mci) class(mci_vamp_instance_t), intent(out) :: mci_instance class(mci_t), intent(in), target :: mci call mci_instance%base_init (mci) select type (mci) type is (mci_vamp_t) mci_instance%mci => mci allocate (mci_instance%gi (mci%n_channel)) mci_instance%allocate_global_history = .not. mci%history_par%global mci_instance%allocate_channel_history = .not. mci%history_par%channel mci_instance%negative_weights = mci%negative_weights end select end subroutine mci_vamp_instance_init @ %def mci_vamp_instance_init @ Prepare a new integration pass: write the pass-specific settings to the [[instance]] object. This should be called initially, together with the [[create_grids]] procedure, and whenever we start a new integration pass. Set [[reshape]] if the number of calls is different than previously (unless it was zero, indicating the first pass). We link VAMP histories to the allocated histories in the current pass object, so the recorded results are persistent. However, if there are no histories present there, we allocate them locally. In that case, the histories will disappear together with the MCI instance object. <>= procedure :: new_pass => mci_vamp_instance_new_pass <>= subroutine mci_vamp_instance_new_pass (instance, reshape) class(mci_vamp_instance_t), intent(inout) :: instance logical, intent(out) :: reshape type(pass_t), pointer :: current associate (mci => instance%mci) current => mci%current_pass instance%n_it = current%n_it if (instance%n_calls == 0) then reshape = .false. instance%n_calls = current%n_calls else if (instance%n_calls == current%n_calls) then reshape = .false. else reshape = .true. instance%n_calls = current%n_calls end if instance%it = 0 instance%calls = 0 instance%calls_valid = 0 instance%enable_adapt_grids = current%adapt_grids instance%enable_adapt_weights = current%adapt_weights instance%generating_events = .false. if (instance%allocate_global_history) then if (associated (instance%v_history)) then call vamp_delete_history (instance%v_history) deallocate (instance%v_history) end if allocate (instance%v_history (instance%n_it)) call vamp_create_history (instance%v_history, verbose = .false.) else instance%v_history => current%v_history end if if (instance%allocate_channel_history) then if (associated (instance%v_histories)) then call vamp_delete_history (instance%v_histories) deallocate (instance%v_histories) end if allocate (instance%v_histories (instance%n_it, mci%n_channel)) call vamp_create_history (instance%v_histories, verbose = .false.) else instance%v_histories => current%v_histories end if end associate end subroutine mci_vamp_instance_new_pass @ %def mci_vamp_instance_new_pass @ Create a grid set within the [[instance]] object, using the data of the current integration pass. Also reset counters that track this grid set. <>= procedure :: create_grids => mci_vamp_instance_create_grids <>= subroutine mci_vamp_instance_create_grids (instance) class(mci_vamp_instance_t), intent(inout) :: instance type (pass_t), pointer :: current integer, dimension(:), allocatable :: num_div real(default), dimension(:,:), allocatable :: region associate (mci => instance%mci) current => mci%current_pass allocate (num_div (mci%n_dim)) allocate (region (2, mci%n_dim)) region(1,:) = 0 region(2,:) = 1 num_div = current%n_bins instance%n_adapt_grids = 0 instance%n_adapt_weights = 0 if (.not. instance%grids_defined) then call vamp_create_grids (instance%grids, & region, & current%n_calls, & weights = instance%w, & num_div = num_div, & stratified = mci%grid_par%stratified) instance%grids_defined = .true. else call msg_bug ("VAMP: create grids: grids already defined") end if end associate end subroutine mci_vamp_instance_create_grids @ %def mci_vamp_instance_create_grids @ Reset a grid set, so we can start a fresh integration pass. In effect, we delete results of previous integrations, but keep the grid shapes, weights, and variance arrays, so adaptation is still possible. The grids are prepared for a specific number of calls (per iteration) and sampling mode (stratified/importance). The [[vamp_discard_integrals]] implementation will reshape the grids only if the argument [[num_calls]] is present. <>= procedure :: discard_integrals => mci_vamp_instance_discard_integrals <>= subroutine mci_vamp_instance_discard_integrals (instance, reshape) class(mci_vamp_instance_t), intent(inout) :: instance logical, intent(in) :: reshape instance%calls = 0 instance%calls_valid = 0 instance%integral = 0 instance%error = 0 instance%efficiency = 0 associate (mci => instance%mci) if (instance%grids_defined) then if (mci%grid_par%use_vamp_equivalences) then if (reshape) then call vamp_discard_integrals (instance%grids, & num_calls = instance%n_calls, & stratified = mci%grid_par%stratified, & eq = mci%equivalences) else call vamp_discard_integrals (instance%grids, & stratified = mci%grid_par%stratified, & eq = mci%equivalences) end if else if (reshape) then call vamp_discard_integrals (instance%grids, & num_calls = instance%n_calls, & stratified = mci%grid_par%stratified) else call vamp_discard_integrals (instance%grids, & stratified = mci%grid_par%stratified) end if end if else call msg_bug ("VAMP: discard integrals: grids undefined") end if end associate end subroutine mci_vamp_instance_discard_integrals @ %def mci_vamp_instance_discard_integrals @ After grids are created (with equidistant binning and equal weight), adaptation is redundant. Therefore, we should allow it only after a complete integration step has been performed, calling this. <>= procedure :: allow_adaptation => mci_vamp_instance_allow_adaptation <>= subroutine mci_vamp_instance_allow_adaptation (instance) class(mci_vamp_instance_t), intent(inout) :: instance instance%allow_adapt_grids = .true. instance%allow_adapt_weights = .true. end subroutine mci_vamp_instance_allow_adaptation @ %def mci_vamp_instance_allow_adaptation @ Adapt grids. <>= procedure :: adapt_grids => mci_vamp_instance_adapt_grids <>= subroutine mci_vamp_instance_adapt_grids (instance) class(mci_vamp_instance_t), intent(inout) :: instance if (instance%enable_adapt_grids .and. instance%allow_adapt_grids) then if (instance%grids_defined) then call vamp_refine_grids (instance%grids) instance%n_adapt_grids = instance%n_adapt_grids + 1 else call msg_bug ("VAMP: adapt grids: grids undefined") end if end if end subroutine mci_vamp_instance_adapt_grids @ %def mci_vamp_instance_adapt_grids @ Adapt weights. Use the variance array returned by \vamp\ for recalculating the weight array. The parameter [[channel_weights_power]] dampens fluctuations. If the number of calls in a given channel falls below a user-defined threshold, the weight is not lowered further but kept at this threshold. The other channel weights are reduced accordingly. <>= procedure :: adapt_weights => mci_vamp_instance_adapt_weights <>= subroutine mci_vamp_instance_adapt_weights (instance) class(mci_vamp_instance_t), intent(inout) :: instance real(default) :: w_sum, w_avg_ch, sum_w_underflow, w_min real(default), dimension(:), allocatable :: weights integer :: n_ch, ch, n_underflow logical, dimension(:), allocatable :: mask, underflow type(exception) :: vamp_exception logical :: wsum_non_zero if (instance%enable_adapt_weights .and. instance%allow_adapt_weights) then associate (mci => instance%mci) if (instance%grids_defined) then allocate (weights (size (instance%grids%weights))) weights = instance%grids%weights & * vamp_get_variance (instance%grids%grids) & ** mci%grid_par%channel_weights_power w_sum = sum (weights) if (w_sum /= 0) then weights = weights / w_sum if (mci%n_chain /= 0) then allocate (mask (mci%n_channel)) do ch = 1, mci%n_chain mask = mci%chain == ch n_ch = count (mask) if (n_ch /= 0) then w_avg_ch = sum (weights, mask) / n_ch where (mask) weights = w_avg_ch end if end do end if if (mci%grid_par%threshold_calls /= 0) then w_min = & real (mci%grid_par%threshold_calls, default) & / instance%n_calls allocate (underflow (mci%n_channel)) underflow = weights /= 0 .and. abs (weights) < w_min n_underflow = count (underflow) sum_w_underflow = sum (weights, mask=underflow) if (sum_w_underflow /= 1) then where (underflow) weights = w_min elsewhere weights = weights & * (1 - n_underflow * w_min) / (1 - sum_w_underflow) end where end if end if end if call instance%set_channel_weights (weights, wsum_non_zero) if (wsum_non_zero) call vamp_update_weights & (instance%grids, weights, exc = vamp_exception) call handle_vamp_exception (vamp_exception, mci%verbose) else call msg_bug ("VAMP: adapt weights: grids undefined") end if end associate instance%n_adapt_weights = instance%n_adapt_weights + 1 end if end subroutine mci_vamp_instance_adapt_weights @ %def mci_vamp_instance_adapt_weights @ Integration: sample the VAMP grids. The number of calls etc. are already stored inside the grids. We provide the random-number generator, the sampling function, and a link to the workspace object, which happens to contain a pointer to the sampler object. The sampler object thus becomes the workspace of the sampling function. Note: in the current implementation, the random-number generator must be the TAO generator. This explicit dependence should be removed from the VAMP implementation. <>= procedure :: sample_grids => mci_vamp_instance_sample_grids <>= subroutine mci_vamp_instance_sample_grids (instance, rng, sampler, eq) class(mci_vamp_instance_t), intent(inout), target :: instance class(rng_t), intent(inout) :: rng class(mci_sampler_t), intent(inout), target :: sampler type(vamp_equivalences_t), intent(in), optional :: eq class(vamp_data_t), allocatable :: data type(exception) :: vamp_exception allocate (mci_workspace_t :: data) select type (data) type is (mci_workspace_t) data%sampler => sampler data%instance => instance end select select type (rng) type is (rng_tao_t) instance%it = instance%it + 1 instance%calls = 0 if (instance%grids_defined) then call vamp_sample_grids ( & rng%state, & instance%grids, & vamp_sampling_function, & data, & 1, & eq = eq, & history = instance%v_history(instance%it:), & histories = instance%v_histories(instance%it:,:), & integral = instance%integral, & std_dev = instance%error, & exc = vamp_exception, & negative_weights = instance%negative_weights) call handle_vamp_exception (vamp_exception, instance%mci%verbose) instance%efficiency = instance%get_efficiency () else call msg_bug ("VAMP: sample grids: grids undefined") end if class default call msg_fatal ("VAMP integration: random-number generator must be TAO") end select end subroutine mci_vamp_instance_sample_grids @ %def mci_vamp_instance_sample_grids @ Compute the reweighting efficiency for the current grids, suitable averaged over all active channels. <>= procedure :: get_efficiency_array => mci_vamp_instance_get_efficiency_array procedure :: get_efficiency => mci_vamp_instance_get_efficiency <>= function mci_vamp_instance_get_efficiency_array (mci) result (efficiency) class(mci_vamp_instance_t), intent(in) :: mci real(default), dimension(:), allocatable :: efficiency allocate (efficiency (mci%mci%n_channel)) if (.not. mci%negative_weights) then where (mci%grids%grids%f_max /= 0) efficiency = mci%grids%grids%mu(1) / abs (mci%grids%grids%f_max) elsewhere efficiency = 0 end where else where (mci%grids%grids%f_max /= 0) efficiency = & (mci%grids%grids%mu_plus(1) - mci%grids%grids%mu_minus(1)) & / abs (mci%grids%grids%f_max) elsewhere efficiency = 0 end where end if end function mci_vamp_instance_get_efficiency_array function mci_vamp_instance_get_efficiency (mci) result (efficiency) class(mci_vamp_instance_t), intent(in) :: mci real(default) :: efficiency real(default), dimension(:), allocatable :: weight real(default) :: norm allocate (weight (mci%mci%n_channel)) weight = mci%grids%weights * abs (mci%grids%grids%f_max) norm = sum (weight) if (norm /= 0) then efficiency = dot_product (mci%get_efficiency_array (), weight) / norm else efficiency = 1 end if end function mci_vamp_instance_get_efficiency @ %def mci_vamp_instance_get_efficiency_array @ %def mci_vamp_instance_get_efficiency @ Prepare an event generation pass. Should be called before a sequence of events is generated, then we should call the corresponding finalizer. The pass-specific data of the previous integration pass are retained, but we reset the number of iterations and calls to zero. The latter now counts the number of events (calls to the sampling function, actually). <>= procedure :: init_simulation => mci_vamp_instance_init_simulation <>= subroutine mci_vamp_instance_init_simulation (instance, safety_factor) class(mci_vamp_instance_t), intent(inout) :: instance real(default), intent(in), optional :: safety_factor associate (mci => instance%mci) allocate (instance%vamp_x (mci%n_dim)) instance%it = 0 instance%calls = 0 instance%generating_events = .true. if (present (safety_factor)) instance%safety_factor = safety_factor if (.not. instance%grids_defined) then if (mci%grid_filename_set) then if (.not. mci%check_grid_file) & call msg_warning ("Reading grid file: MD5 sum check disabled") call msg_message ("Simulate: " & // "using integration grids from file '" & // char (mci%grid_filename) // "'") call mci%read_grids_data (instance) if (instance%safety_factor /= 1) then write (msg_buffer, "(A,ES10.3,A)") "Simulate: & &applying safety factor", instance%safety_factor, & " to event rejection" call msg_message () instance%grids%grids%f_max = & instance%grids%grids%f_max * instance%safety_factor end if else call msg_bug ("VAMP: simulation: no grids, no grid filename") end if end if end associate end subroutine mci_vamp_instance_init_simulation @ %def mci_vamp_init_simulation @ Finalize an event generation pass. Should be called before a sequence of events is generated, then we should call the corresponding finalizer. <>= procedure :: final_simulation => mci_vamp_instance_final_simulation <>= subroutine mci_vamp_instance_final_simulation (instance) class(mci_vamp_instance_t), intent(inout) :: instance if (allocated (instance%vamp_x)) deallocate (instance%vamp_x) end subroutine mci_vamp_instance_final_simulation @ %def mci_vamp_instance_final_simulation @ \subsection{Sampling function} The VAMP sampling function has a well-defined interface which we have to implement. The [[data]] argument allows us to pass pointers to the [[sampler]] and [[instance]] objects, so we can access configuration data and fill point-dependent contents within these objects. The [[weights]] and [[channel]] argument must be present in the call. Note: this is the place where we must look for external signals, i.e., interrupt from the OS. We would like to raise a \vamp\ exception which is then caught by [[vamp_sample_grids]] as the caller, so it dumps its current state and returns (with the signal still pending). \whizard\ will then terminate gracefully. Of course, VAMP should be able to resume from the dump. In the current implementation, we handle the exception in place and terminate immediately. The incomplete current integration pass is lost. <>= function vamp_sampling_function & (xi, data, weights, channel, grids) result (f) real(default) :: f real(default), dimension(:), intent(in) :: xi class(vamp_data_t), intent(in) :: data real(default), dimension(:), intent(in), optional :: weights integer, intent(in), optional :: channel type(vamp_grid), dimension(:), intent(in), optional :: grids type(exception) :: exc logical :: verbose character(*), parameter :: FN = "WHIZARD sampling function" class(mci_instance_t), pointer :: instance select type (data) type is (mci_workspace_t) instance => data%instance select type (instance) class is (mci_vamp_instance_t) verbose = instance%mci%verbose call instance%evaluate (data%sampler, channel, xi) if (signal_is_pending ()) then call raise_exception (exc, EXC_FATAL, FN, "signal received") call handle_vamp_exception (exc, verbose) call terminate_now_if_signal () end if instance%calls = instance%calls + 1 if (data%sampler%is_valid ()) & & instance%calls_valid = instance%calls_valid + 1 f = instance%get_value () call terminate_now_if_single_event () class default call msg_bug("VAMP: " // FN // ": unknown MCI instance type") end select end select end function vamp_sampling_function @ %def vamp_sampling_function @ This is supposed to be the mapping between integration channels. The VAMP event generating procedures technically require it, but it is meaningless in our setup where all transformations happen inside the sampler object. So, this implementation is trivial: <>= pure function phi_trivial (xi, channel_dummy) result (x) real(default), dimension(:), intent(in) :: xi integer, intent(in) :: channel_dummy real(default), dimension(size(xi)) :: x x = xi end function phi_trivial @ %def phi_trivial @ \subsection{Integrator instance: evaluation} Here, we compute the multi-channel reweighting factor for the current channel, that accounts for the Jacobians of the transformations from/to all other channels. The computation of the VAMP probabilities may consume considerable time, therefore we enable parallel evaluation. (Collecting the contributions to [[mci%g]] is a reduction, which we should also implement via OpenMP.) <>= procedure :: compute_weight => mci_vamp_instance_compute_weight <>= subroutine mci_vamp_instance_compute_weight (mci, c) class(mci_vamp_instance_t), intent(inout) :: mci integer, intent(in) :: c integer :: i mci%selected_channel = c !$OMP PARALLEL PRIVATE(i) SHARED(mci) !$OMP DO do i = 1, mci%mci%n_channel if (mci%w(i) /= 0) then mci%gi(i) = vamp_probability (mci%grids%grids(i), mci%x(:,i)) else mci%gi(i) = 0 end if end do !$OMP END DO !$OMP END PARALLEL mci%g = 0 if (mci%gi(c) /= 0) then do i = 1, mci%mci%n_channel if (mci%w(i) /= 0 .and. mci%f(i) /= 0) then mci%g = mci%g + mci%w(i) * mci%gi(i) / mci%f(i) end if end do end if if (mci%g /= 0) then mci%mci_weight = mci%gi(c) / mci%g else mci%mci_weight = 0 end if end subroutine mci_vamp_instance_compute_weight @ %def mci_vamp_instance_compute_weight @ Record the integrand. <>= procedure :: record_integrand => mci_vamp_instance_record_integrand <>= subroutine mci_vamp_instance_record_integrand (mci, integrand) class(mci_vamp_instance_t), intent(inout) :: mci real(default), intent(in) :: integrand mci%integrand = integrand end subroutine mci_vamp_instance_record_integrand @ %def mci_vamp_instance_record_integrand @ Get the event weight. The default routine returns the same value that we would use for integration. This is correct if we select the integration channel according to the channel weight. [[vamp_next_event]] does differently, so we should rather rely on the weight that VAMP returns. This is the value stored in [[vamp_weight]]. We override the default TBP accordingly. <>= procedure :: get_event_weight => mci_vamp_instance_get_event_weight procedure :: get_event_excess => mci_vamp_instance_get_event_excess <>= function mci_vamp_instance_get_event_weight (mci) result (value) class(mci_vamp_instance_t), intent(in) :: mci real(default) :: value if (mci%vamp_weight_set) then value = mci%vamp_weight else call msg_bug ("VAMP: attempt to read undefined event weight") end if end function mci_vamp_instance_get_event_weight function mci_vamp_instance_get_event_excess (mci) result (value) class(mci_vamp_instance_t), intent(in) :: mci real(default) :: value if (mci%vamp_weight_set) then value = mci%vamp_excess else call msg_bug ("VAMP: attempt to read undefined event excess weight") end if end function mci_vamp_instance_get_event_excess @ %def mci_vamp_instance_get_event_excess @ \subsection{VAMP exceptions} A VAMP routine may have raised an exception. Turn this into a WHIZARD error message. An external signal could raise a fatal exception, but this should be delayed and handled by the correct termination routine. <>= subroutine handle_vamp_exception (exc, verbose) type(exception), intent(in) :: exc logical, intent(in) :: verbose integer :: exc_level if (verbose) then exc_level = EXC_INFO else exc_level = EXC_ERROR end if if (exc%level >= exc_level) then write (msg_buffer, "(A,':',1x,A)") trim (exc%origin), trim (exc%message) select case (exc%level) case (EXC_INFO); call msg_message () case (EXC_WARN); call msg_warning () case (EXC_ERROR); call msg_error () case (EXC_FATAL) if (signal_is_pending ()) then call msg_message () else call msg_fatal () end if end select end if end subroutine handle_vamp_exception @ %def handle_vamp_exception @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[mci_vamp_ut.f90]]>>= <> module mci_vamp_ut use unit_tests use mci_vamp_uti <> <> contains <> end module mci_vamp_ut @ %def mci_vamp_ut @ <<[[mci_vamp_uti.f90]]>>= <> module mci_vamp_uti <> <> use io_units use constants, only: PI, TWOPI use rng_base use rng_tao use phs_base use mci_base use vamp, only: vamp_write_grids !NODEP! use mci_vamp <> <> <> contains <> end module mci_vamp_uti @ %def mci_vamp_ut @ API: driver for the unit tests below. <>= public :: mci_vamp_test <>= subroutine mci_vamp_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine mci_vamp_test @ %def mci_vamp_test @ \subsubsection{Test sampler} A test sampler object should implement a function with known integral that we can use to check the integrator. In mode [[1]], the function is $f(x) = 3 x^2$ with integral $\int_0^1 f(x)\,dx=1$ and maximum $f(1)=3$. If the integration dimension is greater than one, the function is extended as a constant in the other dimension(s). In mode [[2]], the function is $11 x^{10}$, also with integral $1$. Mode [[4]] includes ranges of zero and negative function value, the integral is negative. The results should be identical to the results of [[mci_midpoint_4]], where the same function is evaluated. The function is $f(x) = (1 - 3 x^2)\,\theta(x-1/2)$ with integral $\int_0^1 f(x)\,dx=-3/8$, minimum $f(1)=-2$ and maximum $f(1/2)=1/4$. <>= type, extends (mci_sampler_t) :: test_sampler_1_t real(default), dimension(:), allocatable :: x real(default) :: val integer :: mode = 1 contains <> end type test_sampler_1_t @ %def test_sampler_1_t @ Output: There is nothing stored inside, so just print an informative line. <>= procedure :: write => test_sampler_1_write <>= subroutine test_sampler_1_write (object, unit, testflag) class(test_sampler_1_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) select case (object%mode) case (1) write (u, "(1x,A)") "Test sampler: f(x) = 3 x^2" case (2) write (u, "(1x,A)") "Test sampler: f(x) = 11 x^10" case (3) write (u, "(1x,A)") "Test sampler: f(x) = 11 x^10 * 2 * cos^2 (2 pi y)" case (4) write (u, "(1x,A)") "Test sampler: f(x) = (1 - 3 x^2) theta(x - 1/2)" end select end subroutine test_sampler_1_write @ %def test_sampler_1_write @ Evaluation: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure :: evaluate => test_sampler_1_evaluate <>= subroutine test_sampler_1_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_1_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f if (allocated (sampler%x)) deallocate (sampler%x) allocate (sampler%x (size (x_in))) sampler%x = x_in select case (sampler%mode) case (1) sampler%val = 3 * x_in(1) ** 2 case (2) sampler%val = 11 * x_in(1) ** 10 case (3) sampler%val = 11 * x_in(1) ** 10 * 2 * cos (twopi * x_in(2)) ** 2 case (4) if (x_in(1) >= .5_default) then sampler%val = 1 - 3 * x_in(1) ** 2 else sampler%val = 0 end if end select call sampler%fetch (val, x, f) end subroutine test_sampler_1_evaluate @ %def test_sampler_1_evaluate @ The point is always valid. <>= procedure :: is_valid => test_sampler_1_is_valid <>= function test_sampler_1_is_valid (sampler) result (valid) class(test_sampler_1_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_1_is_valid @ %def test_sampler_1_is_valid @ Rebuild: compute all but the function value. <>= procedure :: rebuild => test_sampler_1_rebuild <>= subroutine test_sampler_1_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_1_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f if (allocated (sampler%x)) deallocate (sampler%x) allocate (sampler%x (size (x_in))) sampler%x = x_in sampler%val = val x(:,1) = sampler%x f = 1 end subroutine test_sampler_1_rebuild @ %def test_sampler_1_rebuild @ Extract the results. <>= procedure :: fetch => test_sampler_1_fetch <>= subroutine test_sampler_1_fetch (sampler, val, x, f) class(test_sampler_1_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x(:,1) = sampler%x f = 1 end subroutine test_sampler_1_fetch @ %def test_sampler_1_fetch @ \subsubsection{Two-channel, two dimension test sampler} This sampler implements the function \begin{equation} f(x, y) = 4\sin^2(\pi x)\sin^2(\pi y) + 2\sin^2(\pi v) \end{equation} where \begin{align} x &= u^v &u &= xy \\ y &= u^{(1-v)} &v &= \frac12\left(1 + \frac{\log(x/y)}{\log xy}\right) \end{align} Each term contributes $1$ to the integral. The first term in the function is peaked along a cross aligned to the coordinates $x$ and $y$, while the second term is peaked along the diagonal $x=y$. The Jacobian is \begin{equation} \frac{\partial(x,y)}{\partial(u,v)} = |\log u| \end{equation} <>= type, extends (mci_sampler_t) :: test_sampler_2_t real(default), dimension(:,:), allocatable :: x real(default), dimension(:), allocatable :: f real(default) :: val contains <> end type test_sampler_2_t @ %def test_sampler_2_t @ Output: There is nothing stored inside, so just print an informative line. <>= procedure :: write => test_sampler_2_write <>= subroutine test_sampler_2_write (object, unit, testflag) class(test_sampler_2_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Two-channel test sampler 2" end subroutine test_sampler_2_write @ %def test_sampler_2_write @ Kinematics: compute $x$ and Jacobians, given the input parameter array. <>= procedure :: compute => test_sampler_2_compute <>= subroutine test_sampler_2_compute (sampler, c, x_in) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default) :: xx, yy, uu, vv if (.not. allocated (sampler%x)) & allocate (sampler%x (size (x_in), 2)) if (.not. allocated (sampler%f)) & allocate (sampler%f (2)) select case (c) case (1) xx = x_in(1) yy = x_in(2) uu = xx * yy vv = (1 + log (xx/yy) / log (xx*yy)) / 2 case (2) uu = x_in(1) vv = x_in(2) xx = uu ** vv yy = uu ** (1 - vv) end select sampler%val = (2 * sin (pi * xx) * sin (pi * yy)) ** 2 & + 2 * sin (pi * vv) ** 2 sampler%f(1) = 1 sampler%f(2) = abs (log (uu)) sampler%x(:,1) = [xx, yy] sampler%x(:,2) = [uu, vv] end subroutine test_sampler_2_compute @ %def test_sampler_kinematics @ Evaluation: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure :: evaluate => test_sampler_2_evaluate <>= subroutine test_sampler_2_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) call sampler%fetch (val, x, f) end subroutine test_sampler_2_evaluate @ %def test_sampler_2_evaluate @ The point is always valid. <>= procedure :: is_valid => test_sampler_2_is_valid <>= function test_sampler_2_is_valid (sampler) result (valid) class(test_sampler_2_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_2_is_valid @ %def test_sampler_2_is_valid @ Rebuild: compute all but the function value. <>= procedure :: rebuild => test_sampler_2_rebuild <>= subroutine test_sampler_2_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) x = sampler%x f = sampler%f end subroutine test_sampler_2_rebuild @ %def test_sampler_2_rebuild @ Extract the results. <>= procedure :: fetch => test_sampler_2_fetch <>= subroutine test_sampler_2_fetch (sampler, val, x, f) class(test_sampler_2_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x = sampler%x f = sampler%f end subroutine test_sampler_2_fetch @ %def test_sampler_2_fetch @ \subsubsection{Two-channel, one dimension test sampler} This sampler implements the function \begin{equation} f(x, y) = a * 5 x^4 + b * 5 (1-x)^4 \end{equation} Each term contributes $1$ to the integral, multiplied by $a$ or $b$, respectively. The first term is peaked at $x=1$, the second one at $x=0$.. We implement the two mappings \begin{equation} x = u^{1/5} \quad\text{and}\quad x = 1 - v^{1/5}, \end{equation} with Jacobians \begin{equation} \frac{\partial(x)}{\partial(u)} = u^{-4/5}/5 \quad\text{and}\quad v^{-4/5}/5, \end{equation} respectively. The first mapping concentrates points near $x=1$, the second one near $x=0$. <>= type, extends (mci_sampler_t) :: test_sampler_3_t real(default), dimension(:,:), allocatable :: x real(default), dimension(:), allocatable :: f real(default) :: val real(default) :: a = 1 real(default) :: b = 1 contains <> end type test_sampler_3_t @ %def test_sampler_3_t @ Output: display $a$ and $b$ <>= procedure :: write => test_sampler_3_write <>= subroutine test_sampler_3_write (object, unit, testflag) class(test_sampler_3_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Two-channel test sampler 3" write (u, "(3x,A,F5.2)") "a = ", object%a write (u, "(3x,A,F5.2)") "b = ", object%b end subroutine test_sampler_3_write @ %def test_sampler_3_write @ Kinematics: compute $x$ and Jacobians, given the input parameter array. <>= procedure :: compute => test_sampler_3_compute <>= subroutine test_sampler_3_compute (sampler, c, x_in) class(test_sampler_3_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default) :: u, v, xx if (.not. allocated (sampler%x)) & allocate (sampler%x (size (x_in), 2)) if (.not. allocated (sampler%f)) & allocate (sampler%f (2)) select case (c) case (1) u = x_in(1) xx = u ** 0.2_default v = (1 - xx) ** 5._default case (2) v = x_in(1) xx = 1 - v ** 0.2_default u = xx ** 5._default end select sampler%val = sampler%a * 5 * xx ** 4 + sampler%b * 5 * (1 - xx) ** 4 sampler%f(1) = 0.2_default * u ** (-0.8_default) sampler%f(2) = 0.2_default * v ** (-0.8_default) sampler%x(:,1) = [u] sampler%x(:,2) = [v] end subroutine test_sampler_3_compute @ %def test_sampler_kineamtics @ Evaluation: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure :: evaluate => test_sampler_3_evaluate <>= subroutine test_sampler_3_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_3_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) call sampler%fetch (val, x, f) end subroutine test_sampler_3_evaluate @ %def test_sampler_3_evaluate @ The point is always valid. <>= procedure :: is_valid => test_sampler_3_is_valid <>= function test_sampler_3_is_valid (sampler) result (valid) class(test_sampler_3_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_3_is_valid @ %def test_sampler_3_is_valid @ Rebuild: compute all but the function value. <>= procedure :: rebuild => test_sampler_3_rebuild <>= subroutine test_sampler_3_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_3_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) x = sampler%x f = sampler%f end subroutine test_sampler_3_rebuild @ %def test_sampler_3_rebuild @ Extract the results. <>= procedure :: fetch => test_sampler_3_fetch <>= subroutine test_sampler_3_fetch (sampler, val, x, f) class(test_sampler_3_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x = sampler%x f = sampler%f end subroutine test_sampler_3_fetch @ %def test_sampler_3_fetch @ \subsubsection{One-dimensional integration} Construct an integrator and use it for a one-dimensional sampler. Note: We would like to check the precise contents of the grid allocated during integration, but the output format for reals is very long (for good reasons), so the last digits in the grid content display are numerical noise. So, we just check the integration results. <>= call test (mci_vamp_1, "mci_vamp_1", & "one-dimensional integral", & u, results) <>= public :: mci_vamp_1 <>= subroutine mci_vamp_1 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_1" write (u, "(A)") "* Purpose: integrate function in one dimension & &(single channel)" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 1) select type (mci) type is (mci_vamp_t) grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_1_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_calls = 1000" write (u, "(A)") " (lower precision to avoid" write (u, "(A)") " numerical noise)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass () end select call mci%integrate (mci_instance, sampler, 1, 1000, pacify = .true.) call mci%write (u, .true.) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u, .true.) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_1" end subroutine mci_vamp_1 @ %def mci_vamp_1 @ \subsubsection{Multiple iterations} Construct an integrator and use it for a one-dimensional sampler. Integrate with five iterations without grid adaptation. <>= call test (mci_vamp_2, "mci_vamp_2", & "multiple iterations", & u, results) <>= public :: mci_vamp_2 <>= subroutine mci_vamp_2 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_2" write (u, "(A)") "* Purpose: integrate function in one dimension & &(single channel)" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 1) select type (mci) type is (mci_vamp_t) grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_1_t :: sampler) select type (sampler) type is (test_sampler_1_t) sampler%mode = 2 end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 100" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .false.) end select call mci%integrate (mci_instance, sampler, 3, 100) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_2" end subroutine mci_vamp_2 @ %def mci_vamp_2 @ \subsubsection{Grid adaptation} Construct an integrator and use it for a one-dimensional sampler. Integrate with three iterations and in-between grid adaptations. <>= call test (mci_vamp_3, "mci_vamp_3", & "grid adaptation", & u, results) <>= public :: mci_vamp_3 <>= subroutine mci_vamp_3 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_3" write (u, "(A)") "* Purpose: integrate function in one dimension & &(single channel)" write (u, "(A)") "* and adapt grid" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 1) select type (mci) type is (mci_vamp_t) grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_1_t :: sampler) select type (sampler) type is (test_sampler_1_t) sampler%mode = 2 end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 100" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 3, 100) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_3" end subroutine mci_vamp_3 @ %def mci_vamp_3 @ \subsubsection{Two-dimensional integral} Construct an integrator and use it for a two-dimensional sampler. Integrate with three iterations and in-between grid adaptations. <>= call test (mci_vamp_4, "mci_vamp_4", & "two-dimensional integration", & u, results) <>= public :: mci_vamp_4 <>= subroutine mci_vamp_4 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_4" write (u, "(A)") "* Purpose: integrate function in two dimensions & &(single channel)" write (u, "(A)") "* and adapt grid" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 1) select type (mci) type is (mci_vamp_t) grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_1_t :: sampler) select type (sampler) type is (test_sampler_1_t) sampler%mode = 3 end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_4" end subroutine mci_vamp_4 @ %def mci_vamp_4 @ \subsubsection{Two-channel integral} Construct an integrator and use it for a two-dimensional sampler with two channels. Integrate with three iterations and in-between grid adaptations. <>= call test (mci_vamp_5, "mci_vamp_5", & "two-dimensional integration", & u, results) <>= public :: mci_vamp_5 <>= subroutine mci_vamp_5 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_5" write (u, "(A)") "* Purpose: integrate function in two dimensions & &(two channels)" write (u, "(A)") "* and adapt grid" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_2_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_5" end subroutine mci_vamp_5 @ %def mci_vamp_5 @ \subsubsection{Weight adaptation} Construct an integrator and use it for a one-dimensional sampler with two channels. Integrate with three iterations and in-between weight adaptations. <>= call test (mci_vamp_6, "mci_vamp_6", & "weight adaptation", & u, results) <>= public :: mci_vamp_6 <>= subroutine mci_vamp_6 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_6" write (u, "(A)") "* Purpose: integrate function in one dimension & &(two channels)" write (u, "(A)") "* and adapt weights" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_3_t :: sampler) select type (sampler) type is (test_sampler_3_t) sampler%a = 0.9_default sampler%b = 0.1_default end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_weights = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () deallocate (mci_instance) deallocate (mci) write (u, "(A)") write (u, "(A)") "* Re-initialize with chained channels" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 2) call mci%declare_chains ([1,1]) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_weights = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_6" end subroutine mci_vamp_6 @ %def mci_vamp_6 @ \subsubsection{Equivalences} Construct an integrator and use it for a one-dimensional sampler with two channels. Integrate with three iterations and in-between grid adaptations. Apply an equivalence between the two channels, so the binning of the two channels is forced to coincide. Compare this with the behavior without equivalences. <>= call test (mci_vamp_7, "mci_vamp_7", & "use channel equivalences", & u, results) <>= public :: mci_vamp_7 <>= subroutine mci_vamp_7 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler type(phs_channel_t), dimension(:), allocatable :: channel class(rng_t), allocatable :: rng real(default), dimension(:,:), allocatable :: x integer :: u_grid, iostat, i, div, ch character(16) :: buffer write (u, "(A)") "* Test output: mci_vamp_7" write (u, "(A)") "* Purpose: check effect of channel equivalences" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_3_t :: sampler) select type (sampler) type is (test_sampler_3_t) sampler%a = 0.7_default sampler%b = 0.3_default end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 2 and n_calls = 1000, & &adapt grids" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 2, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Write grids and extract binning" write (u, "(A)") u_grid = free_unit () open (u_grid, status = "scratch", action = "readwrite") select type (mci_instance) type is (mci_vamp_instance_t) call vamp_write_grids (mci_instance%grids, u_grid) end select rewind (u_grid) allocate (x (0:20, 2)) do div = 1, 2 FIND_BINS1: do read (u_grid, "(A)") buffer if (trim (adjustl (buffer)) == "begin d%x") then do read (u_grid, *, iostat = iostat) i, x(i,div) if (iostat /= 0) exit FIND_BINS1 end do end if end do FIND_BINS1 end do close (u_grid) write (u, "(1x,A,L1)") "Equal binning in both channels = ", & all (x(:,1) == x(:,2)) deallocate (x) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () deallocate (mci_instance) deallocate (mci) write (u, "(A)") write (u, "(A)") "* Re-initialize integrator, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .true. call mci%set_grid_parameters (grid_par) end select write (u, "(A)") "* Define equivalences" write (u, "(A)") allocate (channel (2)) do ch = 1, 2 allocate (channel(ch)%eq (2)) do i = 1, 2 associate (eq => channel(ch)%eq(i)) call eq%init (1) eq%c = i eq%perm = [1] eq%mode = [0] end associate end do write (u, "(1x,I0,':')", advance = "no") ch call channel(ch)%write (u) end do call mci%declare_equivalences (channel, dim_offset = 0) allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 2 and n_calls = 1000, & &adapt grids" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 2, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Write grids and extract binning" write (u, "(A)") u_grid = free_unit () open (u_grid, status = "scratch", action = "readwrite") select type (mci_instance) type is (mci_vamp_instance_t) call vamp_write_grids (mci_instance%grids, u_grid) end select rewind (u_grid) allocate (x (0:20, 2)) do div = 1, 2 FIND_BINS2: do read (u_grid, "(A)") buffer if (trim (adjustl (buffer)) == "begin d%x") then do read (u_grid, *, iostat = iostat) i, x(i,div) if (iostat /= 0) exit FIND_BINS2 end do end if end do FIND_BINS2 end do close (u_grid) write (u, "(1x,A,L1)") "Equal binning in both channels = ", & all (x(:,1) == x(:,2)) deallocate (x) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_7" end subroutine mci_vamp_7 @ %def mci_vamp_7 @ \subsubsection{Multiple passes} Integrate with three passes and different settings for weight and grid adaptation. <>= call test (mci_vamp_8, "mci_vamp_8", & "integration passes", & u, results) <>= public :: mci_vamp_8 <>= subroutine mci_vamp_8 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_8" write (u, "(A)") "* Purpose: integrate function in one dimension & &(two channels)" write (u, "(A)") "* in three passes" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_3_t :: sampler) select type (sampler) type is (test_sampler_3_t) sampler%a = 0.9_default sampler%b = 0.1_default end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with grid and weight adaptation" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true., adapt_weights = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with grid adaptation" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Integrate without adaptation" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass () end select call mci%integrate (mci_instance, sampler, 3, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_8" end subroutine mci_vamp_8 @ %def mci_vamp_8 @ \subsubsection{Weighted events} Construct an integrator and use it for a two-dimensional sampler with two channels. Integrate and generate a weighted event. <>= call test (mci_vamp_9, "mci_vamp_9", & "weighted event", & u, results) <>= public :: mci_vamp_9 <>= subroutine mci_vamp_9 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_9" write (u, "(A)") "* Purpose: integrate function in two dimensions & &(two channels)" write (u, "(A)") "* and generate a weighted event" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_2_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") call mci%add_pass () call mci%integrate (mci_instance, sampler, 1, 1000) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Generate a weighted event" write (u, "(A)") call mci_instance%init_simulation () call mci%generate_weighted_event (mci_instance, sampler) write (u, "(1x,A)") "MCI instance:" call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final_simulation () call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_9" end subroutine mci_vamp_9 @ %def mci_vamp_9 @ \subsubsection{Grids I/O} Construct an integrator and allocate grids. Write grids to file, read them in again and compare. <>= call test (mci_vamp_10, "mci_vamp_10", & "grids I/O", & u, results) <>= public :: mci_vamp_10 <>= subroutine mci_vamp_10 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng type(string_t) :: file1, file2 character(80) :: buffer1, buffer2 integer :: u1, u2, iostat1, iostat2 logical :: equal, success write (u, "(A)") "* Test output: mci_vamp_10" write (u, "(A)") "* Purpose: write and read VAMP grids" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) mci%md5sum = "1234567890abcdef1234567890abcdef" call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_2_t :: sampler) call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") call mci%add_pass () call mci%integrate (mci_instance, sampler, 1, 1000) write (u, "(A)") "* Write grids to file" write (u, "(A)") file1 = "mci_vamp_10.1" select type (mci) type is (mci_vamp_t) call mci%set_grid_filename (file1) call mci%write_grids (mci_instance) end select call mci_instance%final () call mci%final () deallocate (mci) write (u, "(A)") "* Read grids from file" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_vamp_t) call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) mci%md5sum = "1234567890abcdef1234567890abcdef" call mci%allocate_instance (mci_instance) call mci_instance%init (mci) select type (mci) type is (mci_vamp_t) call mci%set_grid_filename (file1) call mci%add_pass () call mci%current_pass%configure (1, 1000, & mci%min_calls, & mci%grid_par%min_bins, mci%grid_par%max_bins, & mci%grid_par%min_calls_per_channel * mci%n_channel) call mci%read_grids_header (success) call mci%compute_md5sum () call mci%read_grids_data (mci_instance, read_integrals = .true.) end select write (u, "(1x,A,L1)") "success = ", success write (u, "(A)") write (u, "(A)") "* Write grids again" write (u, "(A)") file2 = "mci_vamp_10.2" select type (mci) type is (mci_vamp_t) call mci%set_grid_filename (file2) call mci%write_grids (mci_instance) end select u1 = free_unit () open (u1, file = char (file1) // ".vg", action = "read", status = "old") u2 = free_unit () open (u2, file = char (file2) // ".vg", action = "read", status = "old") equal = .true. iostat1 = 0 iostat2 = 0 do while (equal .and. iostat1 == 0 .and. iostat2 == 0) read (u1, "(A)", iostat = iostat1) buffer1 read (u2, "(A)", iostat = iostat2) buffer2 equal = buffer1 == buffer2 .and. iostat1 == iostat2 end do close (u1) close (u2) if (equal) then write (u, "(1x,A)") "Success: grid files are identical" else write (u, "(1x,A)") "Failure: grid files differ" end if write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_10" end subroutine mci_vamp_10 @ %def mci_vamp_10 @ \subsubsection{Weighted events with grid I/O} Construct an integrator and use it for a two-dimensional sampler with two channels. Integrate, write grids, and generate a weighted event using the grids from file. <>= call test (mci_vamp_11, "mci_vamp_11", & "weighted events with grid I/O", & u, results) <>= public :: mci_vamp_11 <>= subroutine mci_vamp_11 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_11" write (u, "(A)") "* Purpose: integrate function in two dimensions & &(two channels)" write (u, "(A)") "* and generate a weighted event" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) call mci%set_grid_filename (var_str ("mci_vamp_11")) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_2_t :: sampler) write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") call mci%add_pass () call mci%integrate (mci_instance, sampler, 1, 1000) write (u, "(A)") "* Reset instance" write (u, "(A)") call mci_instance%final () call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Generate a weighted event" write (u, "(A)") call mci_instance%init_simulation () call mci%generate_weighted_event (mci_instance, sampler) write (u, "(A)") "* Cleanup" call mci_instance%final_simulation () call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_11" end subroutine mci_vamp_11 @ %def mci_vamp_11 @ \subsubsection{Unweighted events with grid I/O} Construct an integrator and use it for a two-dimensional sampler with two channels. <>= call test (mci_vamp_12, "mci_vamp_12", & "unweighted events with grid I/O", & u, results) <>= public :: mci_vamp_12 <>= subroutine mci_vamp_12 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_12" write (u, "(A)") "* Purpose: integrate function in two dimensions & &(two channels)" write (u, "(A)") "* and generate an unweighted event" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) call mci%set_grid_filename (var_str ("mci_vamp_12")) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_2_t :: sampler) write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 1000" write (u, "(A)") call mci%add_pass () call mci%integrate (mci_instance, sampler, 1, 1000) write (u, "(A)") "* Reset instance" write (u, "(A)") call mci_instance%final () call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Generate an unweighted event" write (u, "(A)") call mci_instance%init_simulation () call mci%generate_unweighted_event (mci_instance, sampler) write (u, "(1x,A)") "MCI instance:" call mci_instance%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final_simulation () call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_12" end subroutine mci_vamp_12 @ %def mci_vamp_12 @ \subsubsection{Update integration results} Compare two [[mci]] objects; match the two and update the first if successful. <>= call test (mci_vamp_13, "mci_vamp_13", & "updating integration results", & u, results) <>= public :: mci_vamp_13 <>= subroutine mci_vamp_13 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci, mci_ref logical :: success write (u, "(A)") "* Test output: mci_vamp_13" write (u, "(A)") "* Purpose: match and update integrators" write (u, "(A)") write (u, "(A)") "* Initialize integrator with no passes" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (2, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) end select call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize reference" write (u, "(A)") allocate (mci_vamp_t :: mci_ref) call mci_ref%set_dimensions (2, 2) select type (mci_ref) type is (mci_vamp_t) call mci_ref%set_grid_parameters (grid_par) end select select type (mci_ref) type is (mci_vamp_t) call mci_ref%add_pass (adapt_grids = .true.) call mci_ref%current_pass%configure (2, 1000, 0, 1, 5, 0) mci_ref%current_pass%calls = [77, 77] mci_ref%current_pass%integral = [1.23_default, 3.45_default] mci_ref%current_pass%error = [0.23_default, 0.45_default] mci_ref%current_pass%efficiency = [0.1_default, 0.6_default] mci_ref%current_pass%integral_defined = .true. call mci_ref%add_pass () call mci_ref%current_pass%configure (2, 2000, 0, 1, 7, 0) mci_ref%current_pass%calls = [99, 0] mci_ref%current_pass%integral = [7.89_default, 0._default] mci_ref%current_pass%error = [0.89_default, 0._default] mci_ref%current_pass%efficiency = [0.86_default, 0._default] mci_ref%current_pass%integral_defined = .true. end select call mci_ref%write (u) write (u, "(A)") write (u, "(A)") "* Update integrator (no-op, should succeed)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%update_from_ref (mci_ref, success) end select write (u, "(1x,A,L1)") "success = ", success write (u, "(A)") call mci%write (u) write (u, "(A)") write (u, "(A)") "* Add pass to integrator" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) call mci%current_pass%configure (2, 1000, 0, 1, 5, 0) mci%current_pass%calls = [77, 77] mci%current_pass%integral = [1.23_default, 3.45_default] mci%current_pass%error = [0.23_default, 0.45_default] mci%current_pass%efficiency = [0.1_default, 0.6_default] mci%current_pass%integral_defined = .true. end select write (u, "(A)") "* Update integrator (no-op, should succeed)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%update_from_ref (mci_ref, success) end select write (u, "(1x,A,L1)") "success = ", success write (u, "(A)") call mci%write (u) write (u, "(A)") write (u, "(A)") "* Add pass to integrator, wrong parameters" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass () call mci%current_pass%configure (2, 1000, 0, 1, 7, 0) end select write (u, "(A)") "* Update integrator (should fail)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%update_from_ref (mci_ref, success) end select write (u, "(1x,A,L1)") "success = ", success write (u, "(A)") call mci%write (u) write (u, "(A)") write (u, "(A)") "* Reset and add passes to integrator" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%reset () call mci%add_pass (adapt_grids = .true.) call mci%current_pass%configure (2, 1000, 0, 1, 5, 0) mci%current_pass%calls = [77, 77] mci%current_pass%integral = [1.23_default, 3.45_default] mci%current_pass%error = [0.23_default, 0.45_default] mci%current_pass%efficiency = [0.1_default, 0.6_default] mci%current_pass%integral_defined = .true. call mci%add_pass () call mci%current_pass%configure (2, 2000, 0, 1, 7, 0) end select write (u, "(A)") "* Update integrator (should succeed)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%update_from_ref (mci_ref, success) end select write (u, "(1x,A,L1)") "success = ", success write (u, "(A)") call mci%write (u) write (u, "(A)") write (u, "(A)") "* Update again (no-op, should succeed)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%update_from_ref (mci_ref, success) end select write (u, "(1x,A,L1)") "success = ", success write (u, "(A)") call mci%write (u) write (u, "(A)") write (u, "(A)") "* Add extra result to integrator" write (u, "(A)") select type (mci) type is (mci_vamp_t) mci%current_pass%calls(2) = 1234 end select write (u, "(A)") "* Update integrator (should fail)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%update_from_ref (mci_ref, success) end select write (u, "(1x,A,L1)") "success = ", success write (u, "(A)") call mci%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci%final () call mci_ref%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_13" end subroutine mci_vamp_13 @ %def mci_vamp_13 @ \subsubsection{Accuracy Goal} Integrate with multiple iterations. Skip iterations once an accuracy goal has been reached. <>= call test (mci_vamp_14, "mci_vamp_14", & "accuracy goal", & u, results) <>= public :: mci_vamp_14 <>= subroutine mci_vamp_14 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_14" write (u, "(A)") "* Purpose: integrate function in one dimension & &(single channel)" write (u, "(A)") "* and check accuracy goal" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 1) select type (mci) type is (mci_vamp_t) grid_par%use_vamp_equivalences = .false. grid_par%accuracy_goal = 5E-2_default call mci%set_grid_parameters (grid_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_1_t :: sampler) select type (sampler) type is (test_sampler_1_t) sampler%mode = 2 end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 5 and n_calls = 100" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 5, 100) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_14" end subroutine mci_vamp_14 @ %def mci_vamp_14 @ \subsubsection{VAMP history} Integrate with three passes and different settings for weight and grid adaptation. Then show the VAMP history. <>= call test (mci_vamp_15, "mci_vamp_15", & "VAMP history", & u, results) <>= public :: mci_vamp_15 <>= subroutine mci_vamp_15 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par type(history_parameters_t) :: history_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_15" write (u, "(A)") "* Purpose: integrate function in one dimension & &(two channels)" write (u, "(A)") "* in three passes, show history" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") history_par%channel = .true. allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 2) select type (mci) type is (mci_vamp_t) grid_par%stratified = .false. grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) call mci%set_history_parameters (history_par) end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_3_t :: sampler) select type (sampler) type is (test_sampler_3_t) sampler%a = 0.9_default sampler%b = 0.1_default end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Pass 1: grid and weight adaptation" select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true., adapt_weights = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) write (u, "(A)") write (u, "(A)") "* Pass 2: grid adaptation" select type (mci) type is (mci_vamp_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000) write (u, "(A)") write (u, "(A)") "* Pass 3: without adaptation" select type (mci) type is (mci_vamp_t) call mci%add_pass () end select call mci%integrate (mci_instance, sampler, 3, 1000) write (u, "(A)") write (u, "(A)") "* Contents of MCI record, with history" write (u, "(A)") call mci%write (u) select type (mci) type is (mci_vamp_t) call mci%write_history (u) end select write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_15" end subroutine mci_vamp_15 @ %def mci_vamp_15 @ \subsubsection{One-dimensional integration with sign change} Construct an integrator and use it for a one-dimensional sampler. <>= call test (mci_vamp_16, "mci_vamp_16", & "1-D integral with sign change", & u, results) <>= public :: mci_vamp_16 <>= subroutine mci_vamp_16 (u) integer, intent(in) :: u type(grid_parameters_t) :: grid_par class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng write (u, "(A)") "* Test output: mci_vamp_16" write (u, "(A)") "* Purpose: integrate function in one dimension & &(single channel)" write (u, "(A)") write (u, "(A)") "* Initialize integrator" write (u, "(A)") allocate (mci_vamp_t :: mci) call mci%set_dimensions (1, 1) select type (mci) type is (mci_vamp_t) grid_par%use_vamp_equivalences = .false. call mci%set_grid_parameters (grid_par) mci%negative_weights = .true. end select allocate (rng_tao_t :: rng) call rng%init () call mci%import_rng (rng) call mci%write (u) write (u, "(A)") write (u, "(A)") "* Initialize instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") "* Initialize test sampler" write (u, "(A)") allocate (test_sampler_1_t :: sampler) select type (sampler) type is (test_sampler_1_t) sampler%mode = 4 end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_calls = 1000" write (u, "(A)") " (lower precision to avoid" write (u, "(A)") " numerical noise)" write (u, "(A)") select type (mci) type is (mci_vamp_t) call mci%add_pass () end select call mci%integrate (mci_instance, sampler, 1, 1000, pacify = .true.) call mci%write (u, .true.) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u, .true.) write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp_16" end subroutine mci_vamp_16 @ %def mci_vamp_16 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% \section{Multi-channel integration with VAMP2} \label{sec:vegas-integration} The multi-channel integration uses VEGAS as backbone integrator. The base interface for the multi-channel integration is given by [[mci_base]] module. We interface the VAMP2 interface given by [[vamp2]] module. <<[[mci_vamp2.f90]]>>= <> module mci_vamp2 <> <> use io_units use format_utils, only: pac_fmt use format_utils, only: write_separator, write_indent use format_defs, only: FMT_12, FMT_14, FMT_17, FMT_19 use constants, only: tiny_13 use diagnostics use md5 use phs_base use rng_base use os_interface, only: mpi_get_comm_id use rng_stream, only: rng_stream_t use mci_base use vegas, only: VEGAS_MODE_IMPORTANCE, VEGAS_MODE_IMPORTANCE_ONLY use vamp2 <> <> <> <> <> contains <> end module mci_vamp2 @ %def mci_vamp2 <>= @ <>= use mpi_f08 !NODEP! @ %def mpi_f08 @ \subsection{Type: mci\_vamp2\_func\_t} \label{sec:mci-vamp2-func} <>= type, extends (vamp2_func_t) :: mci_vamp2_func_t private real(default) :: integrand = 0. class(mci_sampler_t), pointer :: sampler => null () class(mci_vamp2_instance_t), pointer :: instance => null () contains <> end type mci_vamp2_func_t @ %def mci_vamp2_func_t @ Set instance and sampler aka workspace. Also, reset number of [[n_calls]]. <>= procedure, public :: set_workspace => mci_vamp2_func_set_workspace <>= subroutine mci_vamp2_func_set_workspace (self, instance, sampler) class(mci_vamp2_func_t), intent(inout) :: self class(mci_vamp2_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler self%instance => instance self%sampler => sampler end subroutine mci_vamp2_func_set_workspace @ %def mci_vamp2_func_set_workspace @ Get the different channel probabilities. <>= procedure, public :: get_probabilities => mci_vamp2_func_get_probabilities <>= function mci_vamp2_func_get_probabilities (self) result (gi) class(mci_vamp2_func_t), intent(inout) :: self real(default), dimension(self%n_channel) :: gi gi = self%gi end function mci_vamp2_func_get_probabilities @ %def mci_vamp2_func_get_probabilities @ Get multi-channel weight. <>= procedure, public :: get_weight => mci_vamp2_func_get_weight <>= real(default) function mci_vamp2_func_get_weight (self) result (g) class(mci_vamp2_func_t), intent(in) :: self g = self%g end function mci_vamp2_func_get_weight @ %def mci_vamp2_func_get_weight @ Set integrand. <>= procedure, public :: set_integrand => mci_vamp2_func_set_integrand <>= subroutine mci_vamp2_func_set_integrand (self, integrand) class(mci_vamp2_func_t), intent(inout) :: self real(default), intent(in) :: integrand self%integrand = integrand end subroutine mci_vamp2_func_set_integrand @ %def mci_vamp2_func_set_integrand @ Evaluate the mappings. <>= procedure, public :: evaluate_maps => mci_vamp2_func_evaluate_maps <>= subroutine mci_vamp2_func_evaluate_maps (self, x) class(mci_vamp2_func_t), intent(inout) :: self real(default), dimension(:), intent(in) :: x select type (self) type is (mci_vamp2_func_t) call self%instance%evaluate (self%sampler, self%current_channel, x) end select self%valid_x = self%instance%valid self%xi = self%instance%x self%det = self%instance%f end subroutine mci_vamp2_func_evaluate_maps @ %def mci_vamp2_func_evaluate_maps @ Evaluate the function, more or less. <>= procedure, public :: evaluate_func => mci_vamp2_func_evaluate_func <>= real(default) function mci_vamp2_func_evaluate_func (self, x) result (f) class(mci_vamp2_func_t), intent(in) :: self real(default), dimension(:), intent(in) :: x f = self%integrand if (signal_is_pending ()) then call msg_message ("VAMP2: function evaluate_func: signal received") call terminate_now_if_signal () end if call terminate_now_if_single_event () end function mci_vamp2_func_evaluate_func @ %def mci_vamp2_func_evaluate_func @ \subsection{Type: mci\_vamp2\_config\_t} We extend [[vamp2_config_t]]. <>= public :: mci_vamp2_config_t <>= type, extends (vamp2_config_t) :: mci_vamp2_config_t ! end type mci_vamp2_config_t @ %def mci_vamp2_config_t @ \subsection{Integration pass} The list of passes is organized in a separate container. We store the parameters and results for each integration pass in [[pass_t]] and the linked list is stored in [[list_pass_t]]. <>= type :: list_pass_t type(pass_t), pointer :: first => null () type(pass_t), pointer :: current => null () contains <> end type list_pass_t @ %def list_pass_t @ Finalizer. Deallocate each element of the list beginning by the first. <>= procedure :: final => list_pass_final <>= subroutine list_pass_final (self) class(list_pass_t), intent(inout) :: self type(pass_t), pointer :: current current => self%first do while (associated (current)) self%first => current%next deallocate (current) current => self%first end do end subroutine list_pass_final @ %def pass_final @ Add a new pass. <>= procedure :: add => list_pass_add <>= subroutine list_pass_add (self, adapt_grids, adapt_weights, final_pass) class(list_pass_t), intent(inout) :: self logical, intent(in), optional :: adapt_grids, adapt_weights, final_pass type(pass_t), pointer :: new_pass allocate (new_pass) new_pass%i_pass = 1 new_pass%i_first_it = 1 new_pass%adapt_grids = .false.; if (present (adapt_grids)) & & new_pass%adapt_grids = adapt_grids new_pass%adapt_weights = .false.; if (present (adapt_weights)) & & new_pass%adapt_weights = adapt_weights new_pass%is_final_pass = .false.; if (present (final_pass)) & & new_pass%is_final_pass = final_pass if (.not. associated (self%first)) then self%first => new_pass else new_pass%i_pass = new_pass%i_pass + self%current%i_pass new_pass%i_first_it = self%current%i_first_it + self%current%n_it self%current%next => new_pass end if self%current => new_pass end subroutine list_pass_add @ %def list_pass_add @ Update list from a reference. All passes except for the last one must match exactly. For the last one, integration results are updated. The reference output may contain extra passes, these are ignored. <>= procedure :: update_from_ref => list_pass_update_from_ref <>= subroutine list_pass_update_from_ref (self, ref, success) class(list_pass_t), intent(inout) :: self type(list_pass_t), intent(in) :: ref logical, intent(out) :: success type(pass_t), pointer :: current, ref_current current => self%first ref_current => ref%first success = .true. do while (success .and. associated (current)) if (associated (ref_current)) then if (associated (current%next)) then success = current .matches. ref_current else call current%update (ref_current, success) end if current => current%next ref_current => ref_current%next else success = .false. end if end do end subroutine list_pass_update_from_ref @ %def list_pass_update_from_ref <>= procedure :: has_last_integral => list_pass_has_last_integral procedure :: get_last_integral => list_pass_get_last_integral <>= function list_pass_has_last_integral(self) result (flag) class(list_pass_t), intent(in) :: self logical :: flag flag = associated(self%current) if (flag) flag = self%current%integral_defined end function list_pass_has_last_integral subroutine list_pass_get_last_integral(self, integral, error, efficiency) class(list_pass_t), intent(in) :: self real(default), intent(out) :: integral real(default), intent(out) :: error real(default), intent(out) :: efficiency if (self%has_last_integral()) then integral = self%current%get_integral() error = self%current%get_error() efficiency = self%current%get_efficiency() else integral = 0 error = 0 efficiency = 0 end if end subroutine list_pass_get_last_integral @ %def list_pass_has_last_integral list_pass_get_last_integral @ Output. Write the complete linked list to the specified unit. <>= procedure :: write => list_pass_write <>= subroutine list_pass_write (self, unit, pacify) class(list_pass_t), intent(in) :: self integer, intent(in) :: unit logical, intent(in), optional :: pacify type(pass_t), pointer :: current current => self%first do while (associated (current)) write (unit, "(1X,A)") "Integration pass:" call current%write (unit, pacify) current => current%next end do end subroutine list_pass_write @ %def list_pass_write @ The parameters and results are stored in the nodes [[pass_t]] of the linked list. <>= type :: pass_t integer :: i_pass = 0 integer :: i_first_it = 0 integer :: n_it = 0 integer :: n_calls = 0 logical :: adapt_grids = .false. logical :: adapt_weights = .false. logical :: is_final_pass = .false. logical :: integral_defined = .false. integer, dimension(:), allocatable :: calls integer, dimension(:), allocatable :: calls_valid real(default), dimension(:), allocatable :: integral real(default), dimension(:), allocatable :: error real(default), dimension(:), allocatable :: efficiency type(pass_t), pointer :: next => null () contains <> end type pass_t @ %def pass_t @ Output. Note that the precision of the numerical values should match the precision for comparing output from file with data. <>= procedure :: write => pass_write <>= subroutine pass_write (self, unit, pacify) class(pass_t), intent(in) :: self integer, intent(in) :: unit logical, intent(in), optional :: pacify integer :: u, i real(default) :: pac_error character(len=7) :: fmt call pac_fmt (fmt, FMT_17, FMT_14, pacify) u = given_output_unit (unit) write (u, "(3X,A,I0)") "n_it = ", self%n_it write (u, "(3X,A,I0)") "n_calls = ", self%n_calls write (u, "(3X,A,L1)") "adapt grids = ", self%adapt_grids write (u, "(3X,A,L1)") "adapt weights = ", self%adapt_weights if (self%integral_defined) then write (u, "(3X,A)") "Results: [it, calls, valid, integral, error, efficiency]" do i = 1, self%n_it if (abs (self%error(i)) > tiny_13) then pac_error = self%error(i) else pac_error = 0 end if write (u, "(5x,I0,2(1x,I0),3(1x," // fmt // "))") & i, self%calls(i), self%calls_valid(i), self%integral(i), & pac_error, self%efficiency(i) end do else write (u, "(3x,A)") "Results: [undefined]" end if end subroutine pass_write @ %def pass_write @ Read and reconstruct the pass. <>= procedure :: read => pass_read <>= subroutine pass_read (self, u, n_pass, n_it) class(pass_t), intent(out) :: self integer, intent(in) :: u, n_pass, n_it integer :: i, j character(80) :: buffer self%i_pass = n_pass + 1 self%i_first_it = n_it + 1 call read_ival (u, self%n_it) call read_ival (u, self%n_calls) call read_lval (u, self%adapt_grids) call read_lval (u, self%adapt_weights) allocate (self%calls (self%n_it), source = 0) allocate (self%calls_valid (self%n_it), source = 0) allocate (self%integral (self%n_it), source = 0._default) allocate (self%error (self%n_it), source = 0._default) allocate (self%efficiency (self%n_it), source = 0._default) read (u, "(A)") buffer select case (trim (adjustl (buffer))) case ("Results: [it, calls, valid, integral, error, efficiency]") do i = 1, self%n_it read (u, *) & j, self%calls(i), self%calls_valid(i), self%integral(i), self%error(i), & self%efficiency(i) end do self%integral_defined = .true. case ("Results: [undefined]") self%integral_defined = .false. case default call msg_fatal ("Reading integration pass: corrupted file") end select end subroutine pass_read @ %def pass_read @ Auxiliary: Read real, integer, string value. We search for an equals sign, the value must follow. <>= subroutine read_rval (u, rval) integer, intent(in) :: u real(default), intent(out) :: rval character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) rval end subroutine read_rval subroutine read_ival (u, ival) integer, intent(in) :: u integer, intent(out) :: ival character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) ival end subroutine read_ival subroutine read_sval (u, sval) integer, intent(in) :: u character(*), intent(out) :: sval character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) sval end subroutine read_sval subroutine read_lval (u, lval) integer, intent(in) :: u logical, intent(out) :: lval character(80) :: buffer read (u, "(A)") buffer buffer = adjustl (buffer(scan (buffer, "=") + 1:)) read (buffer, *) lval end subroutine read_lval @ %def read_rval read_ival read_sval read_lval @ Configure. We adjust the number of [[n_calls]], if it is lower than [[n_calls_min_per_channel]] times [[b_channel]], and print a warning message. <>= procedure :: configure => pass_configure <>= subroutine pass_configure (pass, n_it, n_calls, n_calls_min) class(pass_t), intent(inout) :: pass integer, intent(in) :: n_it integer, intent(in) :: n_calls integer, intent(in) :: n_calls_min pass%n_it = n_it pass%n_calls = max (n_calls, n_calls_min) if (pass%n_calls /= n_calls) then write (msg_buffer, "(A,I0)") "VAMP2: too few calls, resetting " & // "n_calls to ", pass%n_calls call msg_warning () end if allocate (pass%calls (n_it), source = 0) allocate (pass%calls_valid (n_it), source = 0) allocate (pass%integral (n_it), source = 0._default) allocate (pass%error (n_it), source = 0._default) allocate (pass%efficiency (n_it), source = 0._default) end subroutine pass_configure @ %def pass_configure @ Given two pass objects, compare them. All parameters must match. Where integrations are done in both (number of calls nonzero), the results must be equal (up to numerical noise). The allocated array sizes might be different, but should match up to the common [[n_it]] value. <>= interface operator (.matches.) module procedure pass_matches end interface operator (.matches.) <>= function pass_matches (pass, ref) result (ok) type(pass_t), intent(in) :: pass, ref integer :: n logical :: ok ok = .true. if (ok) ok = pass%i_pass == ref%i_pass if (ok) ok = pass%i_first_it == ref%i_first_it if (ok) ok = pass%n_it == ref%n_it if (ok) ok = pass%n_calls == ref%n_calls if (ok) ok = pass%adapt_grids .eqv. ref%adapt_grids if (ok) ok = pass%adapt_weights .eqv. ref%adapt_weights if (ok) ok = pass%integral_defined .eqv. ref%integral_defined if (pass%integral_defined) then n = pass%n_it if (ok) ok = all (pass%calls(:n) == ref%calls(:n)) if (ok) ok = all (pass%calls_valid(:n) == ref%calls_valid(:n)) if (ok) ok = all (pass%integral(:n) .matches. ref%integral(:n)) if (ok) ok = all (pass%error(:n) .matches. ref%error(:n)) if (ok) ok = all (pass%efficiency(:n) .matches. ref%efficiency(:n)) end if end function pass_matches @ %def pass_matches @ Update a pass object, given a reference. The parameters must match, except for the [[n_it]] entry. The number of complete iterations must be less or equal to the reference, and the number of complete iterations in the reference must be no larger than [[n_it]]. Where results are present in both passes, they must match. Where results are present in the reference only, the pass is updated accordingly. <>= procedure :: update => pass_update <>= subroutine pass_update (pass, ref, ok) class(pass_t), intent(inout) :: pass type(pass_t), intent(in) :: ref logical, intent(out) :: ok integer :: n, n_ref ok = .true. if (ok) ok = pass%i_pass == ref%i_pass if (ok) ok = pass%i_first_it == ref%i_first_it if (ok) ok = pass%n_calls == ref%n_calls if (ok) ok = pass%adapt_grids .eqv. ref%adapt_grids if (ok) ok = pass%adapt_weights .eqv. ref%adapt_weights if (ok) then if (ref%integral_defined) then if (.not. allocated (pass%calls)) then allocate (pass%calls (pass%n_it), source = 0) allocate (pass%calls_valid (pass%n_it), source = 0) allocate (pass%integral (pass%n_it), source = 0._default) allocate (pass%error (pass%n_it), source = 0._default) allocate (pass%efficiency (pass%n_it), source = 0._default) end if n = count (pass%calls /= 0) n_ref = count (ref%calls /= 0) ok = n <= n_ref .and. n_ref <= pass%n_it if (ok) ok = all (pass%calls(:n) == ref%calls(:n)) if (ok) ok = all (pass%calls_valid(:n) == ref%calls_valid(:n)) if (ok) ok = all (pass%integral(:n) .matches. ref%integral(:n)) if (ok) ok = all (pass%error(:n) .matches. ref%error(:n)) if (ok) ok = all (pass%efficiency(:n) .matches. ref%efficiency(:n)) if (ok) then pass%calls(n+1:n_ref) = ref%calls(n+1:n_ref) pass%calls_valid(n+1:n_ref) = ref%calls_valid(n+1:n_ref) pass%integral(n+1:n_ref) = ref%integral(n+1:n_ref) pass%error(n+1:n_ref) = ref%error(n+1:n_ref) pass%efficiency(n+1:n_ref) = ref%efficiency(n+1:n_ref) pass%integral_defined = any (pass%calls /= 0) end if end if end if end subroutine pass_update @ %def pass_update @ Match two real numbers: they are equal up to a tolerance, which is $10^{-8}$, matching the number of digits that are output by [[pass_write]]. In particular, if one number is exactly zero, the other one must also be zero. <>= interface operator (.matches.) module procedure real_matches end interface operator (.matches.) <>= elemental function real_matches (x, y) result (ok) real(default), intent(in) :: x, y logical :: ok real(default), parameter :: tolerance = 1.e-8_default ok = abs (x - y) <= tolerance * max (abs (x), abs (y)) end function real_matches @ %def real_matches @ Return the index of the most recent complete integration. If there is none, return zero. <>= procedure :: get_integration_index => pass_get_integration_index <>= function pass_get_integration_index (pass) result (n) class (pass_t), intent(in) :: pass integer :: n integer :: i n = 0 if (allocated (pass%calls)) then do i = 1, pass%n_it if (pass%calls(i) == 0) exit n = i end do end if end function pass_get_integration_index @ %def pass_get_integration_index @ Return the most recent integral and error, if available. <>= procedure :: get_calls => pass_get_calls procedure :: get_calls_valid => pass_get_calls_valid procedure :: get_integral => pass_get_integral procedure :: get_error => pass_get_error procedure :: get_efficiency => pass_get_efficiency <>= function pass_get_calls (pass) result (calls) class(pass_t), intent(in) :: pass integer :: calls integer :: n n = pass%get_integration_index () calls = 0 if (n /= 0) then calls = pass%calls(n) end if end function pass_get_calls function pass_get_calls_valid (pass) result (valid) class(pass_t), intent(in) :: pass integer :: valid integer :: n n = pass%get_integration_index () valid = 0 if (n /= 0) then valid = pass%calls_valid(n) end if end function pass_get_calls_valid function pass_get_integral (pass) result (integral) class(pass_t), intent(in) :: pass real(default) :: integral integer :: n n = pass%get_integration_index () integral = 0 if (n /= 0) then integral = pass%integral(n) end if end function pass_get_integral function pass_get_error (pass) result (error) class(pass_t), intent(in) :: pass real(default) :: error integer :: n n = pass%get_integration_index () error = 0 if (n /= 0) then error = pass%error(n) end if end function pass_get_error function pass_get_efficiency (pass) result (efficiency) class(pass_t), intent(in) :: pass real(default) :: efficiency integer :: n n = pass%get_integration_index () efficiency = 0 if (n /= 0) then efficiency = pass%efficiency(n) end if end function pass_get_efficiency @ %def pass_get_calls @ %def pass_get_calls_valid @ %def pass_get_integral @ %def pass_get_error @ %def pass_get_efficiency @ \subsection{Integrator} \label{sec:integrator} We store the different passes of integration, adaptation and actual sampling, in a linked list. We store the total number of calls [[n_calls]] and the minimal number of calls [[n_calls_min]]. The latter is calculated based on [[n_channel]] and [[min_calls_per_channel]]. If [[n_calls]] is smaller than [[n_calls_min]], then we replace [[n_calls]] with [[n_min_calls]]. <>= public :: mci_vamp2_t <>= type, extends(mci_t) :: mci_vamp2_t type(mci_vamp2_config_t) :: config type(vamp2_t) :: integrator type(vamp2_equivalences_t) :: equivalences logical :: integrator_defined = .false. logical :: integrator_from_file = .false. logical :: adapt_grids = .false. logical :: adapt_weights = .false. integer :: n_adapt_grids = 0 integer :: n_adapt_weights = 0 integer :: n_calls = 0 type(list_pass_t) :: list_pass logical :: rebuild = .true. logical :: check_grid_file = .true. logical :: grid_filename_set = .false. logical :: negative_weights = .false. logical :: verbose = .false. logical :: pass_complete = .false. logical :: it_complete = .false. type(string_t) :: grid_filename integer :: grid_checkpoint = 1 logical :: binary_grid_format = .false. type(string_t) :: parallel_method character(32) :: md5sum_adapted = "" contains <> end type mci_vamp2_t @ %def mci_vamp2_t @ Finalizer: call to base and list finalizer. <>= procedure, public :: final => mci_vamp2_final <>= subroutine mci_vamp2_final (object) class(mci_vamp2_t), intent(inout) :: object call object%list_pass%final () call object%base_final () end subroutine mci_vamp2_final @ %def mci_vamp2_final @ Output. Do not output the grids themselves, this may result in tons of data. <>= procedure, public :: write => mci_vamp2_write <>= subroutine mci_vamp2_write (object, unit, pacify, md5sum_version) class(mci_vamp2_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify logical, intent(in), optional :: md5sum_version integer :: u, i u = given_output_unit (unit) write (u, "(1X,A)") "VAMP2 integrator:" call object%base_write (u, pacify, md5sum_version) write (u, "(1X,A)") "Grid config:" call object%config%write (u) write (u, "(3X,A,L1)") "Integrator defined = ", object%integrator_defined write (u, "(3X,A,L1)") "Integrator from file = ", object%integrator_from_file write (u, "(3X,A,L1)") "Adapt grids = ", object%adapt_grids write (u, "(3X,A,L1)") "Adapt weights = ", object%adapt_weights write (u, "(3X,A,I0)") "No. of adapt grids = ", object%n_adapt_grids write (u, "(3X,A,I0)") "No. of adapt weights = ", object%n_adapt_weights write (u, "(3X,A,L1)") "Verbose = ", object%verbose if (object%config%equivalences) then call object%equivalences%write (u) end if call object%list_pass%write (u, pacify) if (object%md5sum_adapted /= "") then write (u, "(1X,A,A,A)") "MD5 sum (including results) = '", & & object%md5sum_adapted, "'" end if end subroutine mci_vamp2_write @ %def mci_vamp2_write @ Compute the (adapted) MD5 sum, including the configuration MD5 sum and the printout, which incorporates the current results. <>= procedure, public :: compute_md5sum => mci_vamp2_compute_md5sum <>= subroutine mci_vamp2_compute_md5sum (mci, pacify) class(mci_vamp2_t), intent(inout) :: mci logical, intent(in), optional :: pacify integer :: u mci%md5sum_adapted = "" u = free_unit () open (u, status = "scratch", action = "readwrite") write (u, "(A)") mci%md5sum call mci%write (u, pacify, md5sum_version = .true.) rewind (u) mci%md5sum_adapted = md5sum (u) close (u) end subroutine mci_vamp2_compute_md5sum @ %def mci_vamp2_compute_md5sum @ Return the MD5 sum: If available, return the adapted one. <>= procedure, public :: get_md5sum => mci_vamp2_get_md5sum <>= pure function mci_vamp2_get_md5sum (mci) result (md5sum) class(mci_vamp2_t), intent(in) :: mci character(32) :: md5sum if (mci%md5sum_adapted /= "") then md5sum = mci%md5sum_adapted else md5sum = mci%md5sum end if end function mci_vamp2_get_md5sum @ %def mci_vamp_get_md5sum @ Startup message: short version. Make a call to the base function and print additional information about the multi-channel parameters. <>= procedure, public :: startup_message => mci_vamp2_startup_message <>= subroutine mci_vamp2_startup_message (mci, unit, n_calls) class(mci_vamp2_t), intent(in) :: mci integer, intent(in), optional :: unit, n_calls integer :: num_calls, n_bins num_calls = 0; if (present (n_calls)) num_calls = n_calls n_bins = mci%config%n_bins_max call mci%base_startup_message (unit = unit, n_calls = n_calls) if (mci%config%equivalences) then write (msg_buffer, "(A)") & "Integrator: Using VAMP2 channel equivalences" call msg_message (unit = unit) end if if (mci%binary_grid_format) then write (msg_buffer, "(A,A,A,A)") & "Integrator: Write grid header to '" // char (mci%get_grid_filename ()) // & "' and grids to '" // char (mci%get_grid_filename (binary_grid_format = .true.)) // "'" else write (msg_buffer, "(A,A,A)") & "Integrator: Write grid header and grids to '" // char (mci%get_grid_filename ()) // "'" end if call msg_message (unit = unit) select case (mci%grid_checkpoint) case (0) write (msg_buffer, "(A)") & "Integrator: Grid checkpoint after each pass" case (1) write (msg_buffer, "(A)") & "Integrator: Grid checkpoint after each iteration" case (2:) write (msg_buffer, "(A,1X,I0,1X,A)") & "Integrator: Grid checkpoint after", mci%grid_checkpoint, & "iterations and after each pass" case default call msg_bug ("Integrator: Cannot assign grid checkpoint (value is negative).") end select call msg_message (unit = unit) write (msg_buffer, "(A,2(1x,I0,1x,A),L1)") & "Integrator:", num_calls, & "initial calls,", n_bins, & "max. bins, stratified = ", & mci%config%stratified call msg_message (unit = unit) write (msg_buffer, "(A,2(1x,I0,1x,A))") & "Integrator: VAMP2" call msg_message (unit = unit) end subroutine mci_vamp2_startup_message @ %def mci_vamp2_startup_message @ Log entry: just headline. <>= procedure, public :: write_log_entry => mci_vamp2_write_log_entry <>= subroutine mci_vamp2_write_log_entry (mci, u) class(mci_vamp2_t), intent(in) :: mci integer, intent(in) :: u write (u, "(1x,A)") "MC Integrator is VAMP2" call write_separator (u) if (mci%config%equivalences) then call mci%equivalences%write (u) else write (u, "(3x,A)") "No channel equivalences have been used." end if call write_separator (u) call mci%write_chain_weights (u) end subroutine mci_vamp2_write_log_entry @ %def mci_vamp2_write_log_entry @ Set the MCI index (necessary for processes with multiple components). We append the index to the grid filename, just before the final dotted suffix. <>= procedure, public :: record_index => mci_vamp2_record_index <>= subroutine mci_vamp2_record_index (mci, i_mci) class(mci_vamp2_t), intent(inout) :: mci integer, intent(in) :: i_mci type(string_t) :: basename, suffix character(32) :: buffer if (mci%grid_filename_set) then write (buffer, "(I0)") i_mci mci%grid_filename = mci%grid_filename // ".m" // trim (buffer) end if end subroutine mci_vamp2_record_index @ %def mci_vamp2_record_index @ Set the configuration object. We adjust the maximum number of bins [[n_bins_max]] according to [[n_calls]] <>= procedure, public :: set_config => mci_vamp2_set_config <>= subroutine mci_vamp2_set_config (mci, config) class(mci_vamp2_t), intent(inout) :: mci type(mci_vamp2_config_t), intent(in) :: config mci%config = config end subroutine mci_vamp2_set_config @ %def mci_vamp2_set_config @ Set the the rebuild flag, also the for checking the grid. <>= procedure, public :: set_rebuild_flag => mci_vamp2_set_rebuild_flag <>= subroutine mci_vamp2_set_rebuild_flag (mci, rebuild, check_grid_file) class(mci_vamp2_t), intent(inout) :: mci logical, intent(in) :: rebuild logical, intent(in) :: check_grid_file mci%rebuild = rebuild mci%check_grid_file = check_grid_file end subroutine mci_vamp2_set_rebuild_flag @ %def mci_vegaa_set_rebuild_flag @ Set the filename. <>= procedure, public :: set_grid_filename => mci_vamp2_set_grid_filename procedure, public :: get_grid_filename => mci_vamp2_get_grid_filename <>= subroutine mci_vamp2_set_grid_filename (mci, name, run_id) class(mci_vamp2_t), intent(inout) :: mci type(string_t), intent(in) :: name type(string_t), intent(in), optional :: run_id mci%grid_filename = name if (present (run_id)) then mci%grid_filename = name // "." // run_id end if mci%grid_filename_set = .true. end subroutine mci_vamp2_set_grid_filename type(string_t) function mci_vamp2_get_grid_filename (mci, binary_grid_format) & result (filename) class(mci_vamp2_t), intent(in) :: mci logical, intent(in), optional :: binary_grid_format filename = mci%grid_filename // ".vg2" if (present (binary_grid_format)) then if (binary_grid_format) then filename = mci%grid_filename // ".vgx2" end if end if end function mci_vamp2_get_grid_filename @ %def mci_vamp2_set_grid_filename, mci_vamp2_get_grid_filename @ To simplify the interface, we prepend a grid path in a separate subroutine. <>= procedure :: prepend_grid_path => mci_vamp2_prepend_grid_path <>= subroutine mci_vamp2_prepend_grid_path (mci, prefix) class(mci_vamp2_t), intent(inout) :: mci type(string_t), intent(in) :: prefix if (.not. mci%grid_filename_set) then call msg_warning ("VAMP2: Cannot add prefix to invalid integrator filename!") end if mci%grid_filename = prefix // "/" // mci%grid_filename end subroutine mci_vamp2_prepend_grid_path @ %def mci_vamp2_prepend_grid_path @ Not implemented. <>= procedure, public :: declare_flat_dimensions => mci_vamp2_declare_flat_dimensions <>= subroutine mci_vamp2_declare_flat_dimensions (mci, dim_flat) class(mci_vamp2_t), intent(inout) :: mci integer, dimension(:), intent(in) :: dim_flat end subroutine mci_vamp2_declare_flat_dimensions @ %def mci_vamp2_declare_flat_dimensions @ <>= procedure, public :: declare_equivalences => mci_vamp2_declare_equivalences <>= subroutine mci_vamp2_declare_equivalences (mci, channel, dim_offset) class(mci_vamp2_t), intent(inout) :: mci type(phs_channel_t), dimension(:), intent(in) :: channel integer, intent(in) :: dim_offset integer, dimension(:), allocatable :: perm, mode integer :: n_channels, n_dim, n_equivalences integer :: c, i, j, dest, src integer :: n_dim_perm n_channels = mci%n_channel n_dim = mci%n_dim n_equivalences = 0 do c = 1, n_channels n_equivalences = n_equivalences + size (channel(c)%eq) end do mci%equivalences = vamp2_equivalences_t (& n_eqv = n_equivalences, n_channel = n_channels, n_dim = n_dim) allocate (perm (n_dim)) allocate (mode (n_dim)) perm = [(i, i = 1, n_dim)] mode = 0 c = 1 j = 0 do i = 1, n_equivalences if (j < size (channel(c)%eq)) then j = j + 1 else c = c + 1 j = 1 end if associate (eq => channel(c)%eq(j)) dest = c src = eq%c n_dim_perm = size (eq%perm) perm(dim_offset+1:dim_offset+n_dim_perm) = eq%perm + dim_offset mode(dim_offset+1:dim_offset+n_dim_perm) = eq%mode call mci%equivalences%set_equivalence & (i, dest, src, perm, mode) end associate end do call mci%equivalences%freeze () end subroutine mci_vamp2_declare_equivalences @ %def mci_vamp2_declare_quivalences @ Allocate instance with matching type. <>= procedure, public :: allocate_instance => mci_vamp2_allocate_instance <>= subroutine mci_vamp2_allocate_instance (mci, mci_instance) class(mci_vamp2_t), intent(in) :: mci class(mci_instance_t), intent(out), pointer :: mci_instance allocate (mci_vamp2_instance_t :: mci_instance) end subroutine mci_vamp2_allocate_instance @ %def mci_vamp2_allocate_instance @ Allocate a new integration pass. We can preset everything that does not depend on the number of iterations and calls. This is postponed to the integrate method. In the final pass, we do not check accuracy goal etc., since we can assume that the user wants to perform and average all iterations in this pass. <>= procedure, public :: add_pass => mci_vamp2_add_pass <>= subroutine mci_vamp2_add_pass (mci, adapt_grids, adapt_weights, final_pass) class(mci_vamp2_t), intent(inout) :: mci logical, intent(in), optional :: adapt_grids, adapt_weights, final_pass call mci%list_pass%add (adapt_grids, adapt_weights, final_pass) end subroutine mci_vamp2_add_pass @ %def mci_vamp2_add_pass @ Update the list of integration passes. <>= procedure, public :: update_from_ref => mci_vamp2_update_from_ref <>= subroutine mci_vamp2_update_from_ref (mci, mci_ref, success) class(mci_vamp2_t), intent(inout) :: mci class(mci_t), intent(in) :: mci_ref logical, intent(out) :: success select type (mci_ref) type is (mci_vamp2_t) call mci%list_pass%update_from_ref (mci_ref%list_pass, success) if (mci%list_pass%has_last_integral()) then call mci%list_pass%get_last_integral( & integral = mci%integral, & error = mci%error, & efficiency = mci%efficiency) mci%integral_known = .true. mci%error_known = .true. mci%efficiency_known = .true. end if end select end subroutine mci_vamp2_update_from_ref @ %def mci_vamp2_update_from_ref @ Update the MCI record (i.e., the integration passes) by reading from input stream. The stream should contain a write output from a previous run. We first check the MD5 sum of the configuration parameters. If that matches, we proceed directly to the stored integration passes. If successful, we may continue to read the file; the position will be after a blank line that must follow the MCI record. <>= procedure, public :: update => mci_vamp2_update <>= subroutine mci_vamp2_update (mci, u, success) class(mci_vamp2_t), intent(inout) :: mci integer, intent(in) :: u logical, intent(out) :: success character(80) :: buffer character(32) :: md5sum_file type(mci_vamp2_t) :: mci_file integer :: n_pass, n_it call read_sval (u, md5sum_file) success = .true.; if (mci%check_grid_file) & & success = (md5sum_file == mci%md5sum) if (success) then read (u, *) read (u, "(A)") buffer if (trim (adjustl (buffer)) /= "VAMP2 integrator:") then call msg_fatal ("VAMP2: reading grid file: corrupted data") end if n_pass = 0 n_it = 0 do read (u, "(A)") buffer select case (trim (adjustl (buffer))) case ("") exit case ("Integration pass:") call mci_file%list_pass%add () call mci_file%list_pass%current%read (u, n_pass, n_it) n_pass = n_pass + 1 n_it = n_it + mci_file%list_pass%current%n_it end select end do call mci%update_from_ref (mci_file, success) call mci_file%final () end if end subroutine mci_vamp2_update @ %def mci_vamp2_update @ Read / write grids from / to file. We split the reading process in two parts. First, we check on the header where we check (and update) all relevant pass data using [[mci_vamp2_update]]. In the second part we only read the integrator data. We implement [[mci_vamp2_read]] for completeness. The writing of the MCI object is split into two parts, a header with the relevant process configuration regarding the integration and the results of the different passes and their iterations. The other part is the actual grid. The header will always be written in ASCII format, including a md5 hash, in order to testify against unwilling changes to the setup. The grid part can be either added to the ASCII file, or to an additional binary file. <>= procedure :: write_grids => mci_vamp2_write_grids procedure :: read_header => mci_vamp2_read_header procedure :: read_data => mci_vamp2_read_data procedure, private :: advance_to_data => mci_vamp2_advance_to_data <>= subroutine mci_vamp2_write_grids (mci) class(mci_vamp2_t), intent(in) :: mci integer :: u if (.not. mci%grid_filename_set) then call msg_bug ("VAMP2: write grids: filename undefined") end if if (.not. mci%integrator_defined) then call msg_bug ("VAMP2: write grids: grids undefined") end if open (newunit = u, file = char (mci%get_grid_filename ()), & action = "write", status = "replace") write (u, "(1X,A,A,A)") "MD5sum = '", mci%md5sum, "'" write (u, *) call mci%write (u) write (u, *) if (mci%binary_grid_format) then write (u, "(1X,2A)") "VAMP2 grids: binary file: ", & char (mci%get_grid_filename (binary_grid_format = .true.)) close (u) open (newunit = u, & file = char (mci%get_grid_filename (binary_grid_format = .true.)), & action = "write", & access = "stream", & form = "unformatted", & status = "replace") call mci%integrator%write_binary_grids (u) else write (u, "(1X,A)") "VAMP2 grids:" call mci%integrator%write_grids (u) end if close (u) end subroutine mci_vamp2_write_grids subroutine mci_vamp2_read_header (mci, success) class(mci_vamp2_t), intent(inout) :: mci logical, intent(out) :: success logical :: exist, binary_grid_format, exist_binary integer :: u success = .false. if (.not. mci%grid_filename_set) then call msg_bug ("VAMP2: read grids: filename undefined") end if !! First, check for existence of the (usual) grid file. inquire (file = char (mci%get_grid_filename ()), exist = exist) if (.not. exist) return !! success = .false. open (newunit = u, file = char (mci%get_grid_filename ()), & action = "read", status = "old") !! Second, check for existence of a (possible) binary grid file. call mci%advance_to_data (u, binary_grid_format) rewind (u) !! Rewind header file, after line search. if (binary_grid_format) then inquire (file = char (mci%get_grid_filename (binary_grid_format = .true.)), & exist = exist) if (.not. exist) then write (msg_buffer, "(3A)") & "VAMP2: header: binary grid file not found, discarding grid file '", & char (mci%get_grid_filename ()), "'." call msg_message () return !! success = .false. end if end if !! The grid file (ending *.vg) exists and, if binary file is listed, it exists, too. call mci%update (u, success) close (u) if (.not. success) then write (msg_buffer, "(A,A,A)") & "VAMP2: header: parameter mismatch, discarding pass from file '", & char (mci%get_grid_filename ()), "'." call msg_message () end if end subroutine mci_vamp2_read_header subroutine mci_vamp2_read_data (mci) class(mci_vamp2_t), intent(inout) :: mci integer :: u logical :: binary_grid_format if (mci%integrator_defined) then call msg_bug ("VAMP2: read grids: grids already defined") end if open (newunit = u, & file = char (mci%get_grid_filename ()), & action = "read", & status = "old") call mci%advance_to_data (u, binary_grid_format) if (binary_grid_format) then close (u) write (msg_buffer, "(3A)") & "VAMP2: Reading from binary grid file '", & char (mci%get_grid_filename (binary_grid_format = .true.)), "'" call msg_message () open (newunit = u, & file = char (mci%get_grid_filename (binary_grid_format = .true.)), & action = "read", & access = "stream", & form = "unformatted", & status = "old") call mci%integrator%read_binary_grids (u) else call mci%integrator%read_grids (u) end if mci%integrator_defined = .true. close (u) end subroutine mci_vamp2_read_data subroutine mci_vamp2_advance_to_data (mci, u, binary_grid_format) class(mci_vamp2_t), intent(in) :: mci integer, intent(in) :: u logical, intent(out) :: binary_grid_format character(80) :: buffer type(string_t) :: search_string_binary, search_string_ascii search_string_binary = "VAMP2 grids: binary file: " // & mci%get_grid_filename (binary_grid_format = .true.) search_string_ascii = "VAMP2 grids:" SEARCH: do read (u, "(A)") buffer if (trim (adjustl (buffer)) == char (search_string_binary)) then binary_grid_format = .true. exit SEARCH else if (trim (adjustl (buffer)) == char (search_string_ascii)) then binary_grid_format = .false. exit SEARCH end if end do SEARCH end subroutine mci_vamp2_advance_to_data @ %def mci_vamp2_write_grids @ %def mci_vamp2_read_header @ %def mci_vamp2_read_data @ \subsubsection{Interface: VAMP2} \label{sec:interface-vamp2} We define the interfacing procedures, as such, initialising the VAMP2 integrator or resetting the results. Initialise the VAMP2 integrator which is stored within the [[mci]] object, using the data of the current integration pass. Furthermore, reset the counters that track this set of integrator. <>= procedure, public :: init_integrator => mci_vamp2_init_integrator <>= subroutine mci_vamp2_init_integrator (mci) class(mci_vamp2_t), intent(inout) :: mci type (pass_t), pointer :: current integer :: ch, vegas_mode current => mci%list_pass%current vegas_mode = merge (VEGAS_MODE_IMPORTANCE, VEGAS_MODE_IMPORTANCE_ONLY,& & mci%config%stratified) mci%n_adapt_grids = 0 mci%n_adapt_weights = 0 if (mci%integrator_defined) then call msg_bug ("VAMP2: init integrator: & & integrator is already initialised.") end if mci%integrator = vamp2_t (mci%n_channel, mci%n_dim, & & n_bins_max = mci%config%n_bins_max, & & iterations = 1, & & mode = vegas_mode) if (mci%has_chains ()) call mci%integrator%set_chain (mci%n_chain, mci%chain) call mci%integrator%set_config (mci%config) mci%integrator_defined = .true. end subroutine mci_vamp2_init_integrator @ %def mci_vamp2_init_integrator @ Reset a grid set. Purge the accumulated results. <>= procedure, public :: reset_result => mci_vamp2_reset_result <>= subroutine mci_vamp2_reset_result (mci) class(mci_vamp2_t), intent(inout) :: mci if (.not. mci%integrator_defined) then call msg_bug ("VAMP2: reset results: integrator undefined") end if call mci%integrator%reset_result () end subroutine mci_vamp2_reset_result @ %def mci_vamp2_reset_result @ Set calls per channel. The number of calls to each channel is defined by the channel weight \begin{equation} \alpha_i = \frac{N_i}{\sum N_i}. \end{equation} <>= procedure, public :: set_calls => mci_vamp2_set_calls <>= subroutine mci_vamp2_set_calls (mci, n_calls) class(mci_vamp2_t), intent(inout) :: mci integer :: n_calls if (.not. mci%integrator_defined) then call msg_bug ("VAMP2: set calls: grids undefined") end if call mci%integrator%set_calls (n_calls) end subroutine mci_vamp2_set_calls @ %def mci_vamp2_set_calls \subsubsection{Integration} Initialize. We prepare the integrator from a previous pass, or from file, or with new objects. At the end, we update the number of calls either when we got the integration grids from file and we added new iterations to the current pass, or we allocated a new integrator. <>= procedure, private :: init_integration => mci_vamp2_init_integration <>= subroutine mci_vamp2_init_integration (mci, n_it, n_calls, instance) class(mci_vamp2_t), intent(inout) :: mci integer, intent(in) :: n_it integer, intent(in) :: n_calls class(mci_instance_t), intent(inout) :: instance logical :: from_file, success if (.not. associated (mci%list_pass%current)) then call msg_bug ("MCI integrate: current_pass object not allocated") end if associate (current_pass => mci%list_pass%current) current_pass%integral_defined = .false. mci%config%n_calls_min = mci%config%n_calls_min_per_channel * mci%config%n_channel call current_pass%configure (n_it, n_calls, mci%config%n_calls_min) mci%adapt_grids = current_pass%adapt_grids mci%adapt_weights = current_pass%adapt_weights mci%pass_complete = .false. mci%it_complete = .false. from_file = .false. if (.not. mci%integrator_defined .or. mci%integrator_from_file) then if (mci%grid_filename_set .and. .not. mci%rebuild) then call mci%read_header (success) from_file = success if (.not. mci%integrator_defined .and. success) & call mci%read_data () end if end if if (from_file) then if (.not. mci%check_grid_file) & & call msg_warning ("Reading grid file: MD5 sum check disabled") call msg_message ("VAMP2: " & // "Using grids and results from file ’" & // char (mci%get_grid_filename ()) // "’.") else if (.not. mci%integrator_defined) then call msg_message ("VAMP2: " & // "Initialize new grids and write to file '" & // char (mci%get_grid_filename ()) // "'.") call mci%init_integrator () end if mci%integrator_from_file = from_file if (.not. mci%integrator_from_file .or. (n_it > current_pass%get_integration_index ())) then call mci%integrator%set_calls (current_pass%n_calls) end if call mci%integrator%set_equivalences (mci%equivalences) end associate <> end subroutine mci_vamp2_init_integration @ %def mci_vamp2_init @ Allocate request object and load into integrator object. <>= if (mci%parallel_method /= "") then call mci%integrator%allocate_request (method = char (mci%parallel_method)) else call msg_message ("VAMP2: Use default parallel method: simple.") call mci%integrator%allocate_request (method = "simple") end if @ Integrate. Perform a new integration pass (possibly reusing previous results), which may consist of several iterations. We reinitialise the sampling new each time and set the workspace again. Note: we record the integral once per iteration. The integral stored in the mci record itself is the last integral of the current iteration, no averaging done. The results record may average results. Note: recording the efficiency is not supported yet. <>= procedure, public :: integrate => mci_vamp2_integrate <>= subroutine mci_vamp2_integrate (mci, instance, sampler, & n_it, n_calls, results, pacify) class(mci_vamp2_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler integer, intent(in) :: n_it integer, intent(in) :: n_calls class(mci_results_t), intent(inout), optional :: results logical, intent(in), optional :: pacify integer :: it logical :: from_file, success <> <> call mci%init_integration (n_it, n_calls, instance) from_file = mci%integrator_from_file select type (instance) type is (mci_vamp2_instance_t) call instance%set_workspace (sampler) end select associate (current_pass => mci%list_pass%current) do it = 1, current_pass%n_it if (signal_is_pending ()) return mci%integrator_from_file = from_file .and. & it <= current_pass%get_integration_index () if (.not. mci%integrator_from_file) then mci%it_complete = .false. select type (instance) type is (mci_vamp2_instance_t) call mci%integrator%integrate (instance%func, mci%rng, & & iterations = 1, & & reset_result = .true., & & refine_grids = mci%adapt_grids, & & adapt_weights = mci%adapt_weights, & & verbose = mci%verbose) end select if (signal_is_pending ()) return mci%it_complete = .true. integral = mci%integrator%get_integral () calls = mci%integrator%get_n_calls () select type (instance) type is (mci_vamp2_instance_t) calls_valid = instance%func%get_n_calls () call instance%func%reset_n_calls () end select error = sqrt (mci%integrator%get_variance ()) efficiency = mci%integrator%get_efficiency () <> if (integral /= 0) then current_pass%integral(it) = integral current_pass%calls(it) = calls current_pass%calls_valid(it) = calls_valid current_pass%error(it) = error current_pass%efficiency(it) = efficiency end if current_pass%integral_defined = .true. end if if (present (results)) then if (mci%has_chains ()) then call mci%collect_chain_weights (instance%w) call results%record (1, & n_calls = current_pass%calls(it), & n_calls_valid = current_pass%calls_valid(it), & integral = current_pass%integral(it), & error = current_pass%error(it), & efficiency = current_pass%efficiency(it), & efficiency_pos = current_pass%efficiency(it), & efficiency_neg = 0._default, & chain_weights = mci%chain_weights, & suppress = pacify) else call results%record (1, & n_calls = current_pass%calls(it), & n_calls_valid = current_pass%calls_valid(it), & integral = current_pass%integral(it), & error = current_pass%error(it), & efficiency = current_pass%efficiency(it), & efficiency_pos = current_pass%efficiency(it), & efficiency_neg = 0._default, & suppress = pacify) end if end if if (.not. mci%integrator_from_file & .and. mci%grid_filename_set) then <> call checkpoint_and_write_grids (it = it, & final_it = (it == current_pass%n_it)) end if if (.not. current_pass%is_final_pass) then call check_goals (it, success) if (success) exit end if end do if (signal_is_pending ()) return mci%pass_complete = .true. mci%integral = current_pass%get_integral() mci%error = current_pass%get_error() mci%efficiency = current_pass%get_efficiency() mci%integral_known = .true. mci%error_known = .true. mci%efficiency_known = .true. call mci%compute_md5sum (pacify) end associate contains <> end subroutine mci_vamp2_integrate @ %def mci_vamp2_integrate <>= real(default) :: integral, error, efficiency integer :: calls, calls_valid @ <>= @ <>= @ <>= @ <>= integer :: rank, n_size type(MPI_Request), dimension(6) :: request @ MPI procedure-specific initialization. <>= call MPI_Comm_size (MPI_COMM_WORLD, n_size) call MPI_Comm_rank (MPI_COMM_WORLD, rank) @ We broadcast the current results to all worker, such that they can store them in to the pass list. <>= call MPI_Ibcast (integral, 1, MPI_DOUBLE_PRECISION, 0, MPI_COMM_WORLD, request(1)) call MPI_Ibcast (calls, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, request(2)) call MPI_Ibcast (calls_valid, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, request(3)) call MPI_Ibcast (error, 1, MPI_DOUBLE_PRECISION, 0, MPI_COMM_WORLD, request(4)) call MPI_Ibcast (efficiency, 1, MPI_DOUBLE_PRECISION, 0, MPI_COMM_WORLD, request(5)) call MPI_Waitall (5, request, MPI_STATUSES_IGNORE) @ We only allow the master to write the grids to file. <>= if (rank == 0) & @ Write grids to [[grid_filename]] at a given checkpoint. We qualify each iteration and pass as possible checkpoint. However, we allow the user to alter the checkpoint behavior: \begin{itemize} \item after every iteration, \item after every pass, \item after a \(N\) iterations and every pass. \end{itemize} The user sets the Sindarin variable [[vamp_grid_checkpoint]] to an integer value where the value 0 represents each pass, value 1 each iteration, and a value \(> 1\) means after \(N\) iterations (or at the last iteration of a pass). <>= subroutine checkpoint_and_write_grids (it, final_it) integer, intent(in) :: it logical, intent(in) :: final_it select case (mci%grid_checkpoint) case (0) if (.not. final_it) return case (1) case(2:) if (.not. (final_it & .or. mod (it, mci%grid_checkpoint) == 0)) return case default call msg_bug ("VAMP2: Grid checkpoint must be a positive integer.") end select call mci%write_grids () end subroutine checkpoint_and_write_grids @ Check whether we are already finished with this pass. <>= subroutine check_goals (it, success) integer, intent(in) :: it logical, intent(out) :: success success = .false. associate (current_pass => mci%list_pass%current) if (error_reached (it)) then current_pass%n_it = it call msg_message ("VAMP2: error goal reached; & &skipping iterations") success = .true. return end if if (rel_error_reached (it)) then current_pass%n_it = it call msg_message ("VAMP2: relative error goal reached; & &skipping iterations") success = .true. return end if if (accuracy_reached (it)) then current_pass%n_it = it call msg_message ("VAMP2: accuracy goal reached; & &skipping iterations") success = .true. return end if end associate end subroutine check_goals @ %def mci_vamp2_check_goals @ Return true if the error, relative error or accurary goals hase been reached, if any. <>= function error_reached (it) result (flag) integer, intent(in) :: it logical :: flag real(default) :: error_goal, error error_goal = mci%config%error_goal flag = .false. associate (current_pass => mci%list_pass%current) if (error_goal > 0 .and. current_pass%integral_defined) then error = abs (current_pass%error(it)) flag = error < error_goal end if end associate end function error_reached function rel_error_reached (it) result (flag) integer, intent(in) :: it logical :: flag real(default) :: rel_error_goal, rel_error rel_error_goal = mci%config%rel_error_goal flag = .false. associate (current_pass => mci%list_pass%current) if (rel_error_goal > 0 .and. current_pass%integral_defined) then rel_error = abs (current_pass%error(it) / current_pass%integral(it)) flag = rel_error < rel_error_goal end if end associate end function rel_error_reached function accuracy_reached (it) result (flag) integer, intent(in) :: it logical :: flag real(default) :: accuracy_goal, accuracy accuracy_goal = mci%config%accuracy_goal flag = .false. associate (current_pass => mci%list_pass%current) if (accuracy_goal > 0 .and. current_pass%integral_defined) then if (current_pass%integral(it) /= 0) then accuracy = abs (current_pass%error(it) / current_pass%integral(it)) & * sqrt (real (current_pass%calls(it), default)) flag = accuracy < accuracy_goal else flag = .true. end if end if end associate end function accuracy_reached @ %def error_reached, rel_error_reached, accuracy_reached @ \subsection{Event generation} Prepare simulation. We check the grids and reread them from file, if necessary. <>= procedure, public :: prepare_simulation => mci_vamp2_prepare_simulation <>= subroutine mci_vamp2_prepare_simulation (mci) class(mci_vamp2_t), intent(inout) :: mci logical :: success if (.not. mci%grid_filename_set) then call msg_bug ("VAMP2: preapre simulation: integrator filename not set.") end if call mci%read_header (success) call mci%compute_md5sum () if (.not. success) then call msg_fatal ("Simulate: " & // "reading integration grids from file ’" & // char (mci%get_grid_filename ()) // "’ failed") end if if (.not. mci%integrator_defined) then call mci%read_data () end if call groom_rng (mci%rng) contains subroutine groom_rng (rng) class(rng_t), intent(inout) :: rng integer :: i, rank, n_size call mpi_get_comm_id (n_size, rank) do i = 2, rank + 1 select type (rng) type is (rng_stream_t) call rng%next_substream () if (i == rank) & call msg_message ("MCI: Advance RNG for parallel event simulation") class default call msg_bug ("Use of any random number generator & &beside rng_stream for parallel event generation not supported.") end select end do end subroutine groom_rng end subroutine mci_vamp2_prepare_simulation @ %def mci_vamp2_prepare_simulation @ Generate an unweighted event. We only set the workspace again before generating an event. <>= procedure, public :: generate_weighted_event => mci_vamp2_generate_weighted_event <>= subroutine mci_vamp2_generate_weighted_event (mci, instance, sampler) class(mci_vamp2_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler if (.not. mci%integrator_defined) then call msg_bug ("VAMP2: generate weighted event: undefined integrator") end if select type (instance) type is (mci_vamp2_instance_t) instance%event_generated = .false. call instance%set_workspace (sampler) call mci%integrator%generate_weighted (& & instance%func, mci%rng, instance%event_x) instance%event_weight = mci%integrator%get_evt_weight () instance%event_excess = 0 instance%n_events = instance%n_events + 1 instance%event_generated = .true. end select end subroutine mci_vamp2_generate_weighted_event @ %def mci_vamp2_generate_weighted_event @ We apply an additional rescaling factor for [[f_max]] (either for the positive or negative distribution). <>= procedure, public :: generate_unweighted_event => mci_vamp2_generate_unweighted_event <>= subroutine mci_vamp2_generate_unweighted_event (mci, instance, sampler) class(mci_vamp2_t), intent(inout) :: mci class(mci_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler if (.not. mci%integrator_defined) then call msg_bug ("VAMP2: generate unweighted event: undefined integrator") end if select type (instance) type is (mci_vamp2_instance_t) instance%event_generated = .false. call instance%set_workspace (sampler) generate: do call mci%integrator%generate_unweighted (& & instance%func, mci%rng, instance%event_x, & & opt_event_rescale = instance%event_rescale_f_max) instance%event_excess = mci%integrator%get_evt_weight_excess () if (signal_is_pending ()) return if (sampler%is_valid ()) exit generate end do generate if (mci%integrator%get_evt_weight () < 0.) then if (.not. mci%negative_weights) then call msg_fatal ("VAMP2: cannot sample negative weights!") end if instance%event_weight = -1._default else instance%event_weight = 1._default end if instance%n_events = instance%n_events + 1 instance%event_generated = .true. end select end subroutine mci_vamp2_generate_unweighted_event @ %def mci_vamp2_generate_unweighted_event @ <>= procedure, public :: rebuild_event => mci_vamp2_rebuild_event <>= subroutine mci_vamp2_rebuild_event (mci, instance, sampler, state) class(mci_vamp2_t), intent(inout) :: mci class(mci_instance_t), intent(inout) :: instance class(mci_sampler_t), intent(inout) :: sampler class(mci_state_t), intent(in) :: state call msg_bug ("VAMP2: rebuild event not implemented yet.") end subroutine mci_vamp2_rebuild_event @ %def mci_vamp2_rebuild_event @ \subsection{Integrator instance} \label{sec:nistance} We store all information relevant for simulation. The event weight is stored, when a weighted event is generated, and the event excess, when a larger weight occurs than actual stored max. weight. We give the possibility to rescale the [[f_max]] within the integrator object with [[event_rescale_f_max]]. <>= public :: mci_vamp2_instance_t <>= type, extends (mci_instance_t) :: mci_vamp2_instance_t class(mci_vamp2_func_t), allocatable :: func real(default), dimension(:), allocatable :: gi integer :: n_events = 0 logical :: event_generated = .false. real(default) :: event_weight = 0. real(default) :: event_excess = 0. real(default) :: event_rescale_f_max = 1. real(default), dimension(:), allocatable :: event_x contains <> end type mci_vamp2_instance_t @ %def mci_vamp2_instance_t @ Output. <>= procedure, public :: write => mci_vamp2_instance_write <>= subroutine mci_vamp2_instance_write (object, unit, pacify) class(mci_vamp2_instance_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: pacify integer :: u, ch, j character(len=7) :: fmt call pac_fmt (fmt, FMT_17, FMT_14, pacify) u = given_output_unit (unit) write (u, "(1X,A)") "MCI VAMP2 instance:" write (u, "(1X,A,I0)") & & "Selected channel = ", object%selected_channel write (u, "(1X,A25,1X," // fmt // ")") & & "Integrand = ", object%integrand write (u, "(1X,A25,1X," // fmt // ")") & & "MCI weight = ", object%mci_weight write (u, "(1X,A,L1)") & & "Valid = ", object%valid write (u, "(1X,A)") "MCI a-priori weight:" do ch = 1, size (object%w) write (u, "(3X,I25,1X," // fmt // ")") ch, object%w(ch) end do write (u, "(1X,A)") "MCI jacobian:" do ch = 1, size (object%w) write (u, "(3X,I25,1X," // fmt // ")") ch, object%f(ch) end do write (u, "(1X,A)") "MCI mapped x:" do ch = 1, size (object%w) do j = 1, size (object%x, 1) write (u, "(3X,2(1X,I8),1X," // fmt // ")") j, ch, object%x(j, ch) end do end do write (u, "(1X,A)") "MCI channel weight:" do ch = 1, size (object%w) write (u, "(3X,I25,1X," // fmt // ")") ch, object%gi(ch) end do write (u, "(1X,A,I0)") & & "Number of event = ", object%n_events write (u, "(1X,A,L1)") & & "Event generated = ", object%event_generated write (u, "(1X,A25,1X," // fmt // ")") & & "Event weight = ", object%event_weight write (u, "(1X,A25,1X," // fmt // ")") & & "Event excess = ", object%event_excess write (u, "(1X,A25,1X," // fmt // ")") & & "Event rescale f max = ", object%event_rescale_f_max write (u, "(1X,A,L1)") & & "Negative (event) weight = ", object%negative_weights write (u, "(1X,A)") "MCI event" do j = 1, size (object%event_x) write (u, "(3X,I25,1X," // fmt // ")") j, object%event_x(j) end do end subroutine mci_vamp2_instance_write @ %def mci_vamp2_instance_write @ Finalizer. We are only using allocatable, so there is nothing to do here. <>= procedure, public :: final => mci_vamp2_instance_final <>= subroutine mci_vamp2_instance_final (object) class(mci_vamp2_instance_t), intent(inout) :: object ! end subroutine mci_vamp2_instance_final @ %def mci_vamp2_instance_final @ Initializer. <>= procedure, public :: init => mci_vamp2_instance_init <>= subroutine mci_vamp2_instance_init (mci_instance, mci) class(mci_vamp2_instance_t), intent(out) :: mci_instance class(mci_t), intent(in), target :: mci call mci_instance%base_init (mci) allocate (mci_instance%gi(mci%n_channel), source=0._default) allocate (mci_instance%event_x(mci%n_dim), source=0._default) allocate (mci_vamp2_func_t :: mci_instance%func) call mci_instance%func%init (n_dim = mci%n_dim, n_channel = mci%n_channel) end subroutine mci_vamp2_instance_init @ %def mci_vamp2_instance_init @ Set workspace for [[mci_vamp2_func_t]]. <>= procedure, public :: set_workspace => mci_vamp2_instance_set_workspace <>= subroutine mci_vamp2_instance_set_workspace (instance, sampler) class(mci_vamp2_instance_t), intent(inout), target :: instance class(mci_sampler_t), intent(inout), target :: sampler call instance%func%set_workspace (instance, sampler) end subroutine mci_vamp2_instance_set_workspace @ %def mci_vmp2_instance_set_workspace @ \subsubsection{Evaluation} Compute multi-channel weight. The computation of the multi-channel weight is done by the VAMP2 function. We retrieve the information. <>= procedure, public :: compute_weight => mci_vamp2_instance_compute_weight <>= subroutine mci_vamp2_instance_compute_weight (mci, c) class(mci_vamp2_instance_t), intent(inout) :: mci integer, intent(in) :: c mci%gi = mci%func%get_probabilities () mci%mci_weight = mci%func%get_weight () end subroutine mci_vamp2_instance_compute_weight @ %def mci_vamp2_instance_compute_weight @ Record the integrand. <>= procedure, public :: record_integrand => mci_vamp2_instance_record_integrand <>= subroutine mci_vamp2_instance_record_integrand (mci, integrand) class(mci_vamp2_instance_t), intent(inout) :: mci real(default), intent(in) :: integrand mci%integrand = integrand call mci%func%set_integrand (integrand) end subroutine mci_vamp2_instance_record_integrand @ %def mci_vamp2_instance_record_integrand @ \subsubsection{Event simulation} In contrast to VAMP, we reset only counters and set the safety factor, which will then will be applied each time an event is generated. In that way we do not rescale the actual values in the integrator, but more the current value! <>= procedure, public :: init_simulation => mci_vamp2_instance_init_simulation <>= subroutine mci_vamp2_instance_init_simulation (instance, safety_factor) class(mci_vamp2_instance_t), intent(inout) :: instance real(default), intent(in), optional :: safety_factor if (present (safety_factor)) instance%event_rescale_f_max = safety_factor instance%n_events = 0 instance%event_generated = .false. if (instance%event_rescale_f_max /= 1) then write (msg_buffer, "(A,ES10.3,A)") "Simulate: & &applying safety factor ", instance%event_rescale_f_max, & & " to event rejection." call msg_message () end if end subroutine mci_vamp2_instance_init_simulation @ %def mci_vamp2_instance_init_simulation @ <>= procedure, public :: final_simulation => mci_vamp2_instance_final_simulation <>= subroutine mci_vamp2_instance_final_simulation (instance) class(mci_vamp2_instance_t), intent(inout) :: instance ! end subroutine mci_vamp2_instance_final_simulation @ %def mci_vamp2_instance_final @ <>= procedure, public :: get_event_weight => mci_vamp2_instance_get_event_weight <>= function mci_vamp2_instance_get_event_weight (mci) result (weight) class(mci_vamp2_instance_t), intent(in) :: mci real(default) :: weight if (.not. mci%event_generated) then call msg_bug ("VAMP2: get event weight: no event generated") end if weight = mci%event_weight end function mci_vamp2_instance_get_event_weight @ %def mci_vamp2_instance_get_event_weight @ <>= procedure, public :: get_event_excess => mci_vamp2_instance_get_event_excess <>= function mci_vamp2_instance_get_event_excess (mci) result (excess) class(mci_vamp2_instance_t), intent(in) :: mci real(default) :: excess if (.not. mci%event_generated) then call msg_bug ("VAMP2: get event excess: no event generated") end if excess = mci%event_excess end function mci_vamp2_instance_get_event_excess @ %def mci_vamp2_instance_get_event_excess @ \clearpage \subsection{Unit tests} \label{sec:mic-vamp2-ut} Test module, followed by the corresponding implementation module. <<[[mci_vamp2_ut.f90]]>>= <> module mci_vamp2_ut use unit_tests use mci_vamp2_uti <> <> contains <> end module mci_vamp2_ut @ %def mci_vamp2_ut @ <<[[mci_vamp2_uti.f90]]>>= <> module mci_vamp2_uti <> <> use io_units use constants, only: PI, TWOPI use rng_base use rng_tao use rng_stream use mci_base use mci_vamp2 <> <> <> contains <> end module mci_vamp2_uti @ %def mci_vamp2_uti @ API: driver for the unit tests below. <>= public :: mci_vamp2_test <>= subroutine mci_vamp2_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine mci_vamp2_test @ %def mci_vamp2_test @ \subsubsection{Test sampler} \label{sec:mci-vamp2-test-sampler} A test sampler object should implement a function with known integral that we can use to check the integrator. In mode [[1]], the function is $f(x) = 3 x^2$ with integral $\int_0^1 f(x)\,dx=1$ and maximum $f(1)=3$. If the integration dimension is greater than one, the function is extended as a constant in the other dimension(s). In mode [[2]], the function is $11 x^{10}$, also with integral $1$. Mode [[4]] includes ranges of zero and negative function value, the integral is negative. The results should be identical to the results of [[mci_midpoint_4]], where the same function is evaluated. The function is $f(x) = (1 - 3 x^2)\,\theta(x-1/2)$ with integral $\int_0^1 f(x)\,dx=-3/8$, minimum $f(1)=-2$ and maximum $f(1/2)=1/4$. <>= type, extends (mci_sampler_t) :: test_sampler_1_t real(default), dimension(:), allocatable :: x real(default) :: val integer :: mode = 1 contains <> end type test_sampler_1_t @ %def test_sampler_1_t @ Output: There is nothing stored inside, so just print an informative line. <>= procedure, public :: write => test_sampler_1_write <>= subroutine test_sampler_1_write (object, unit, testflag) class(test_sampler_1_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) select case (object%mode) case (1) write (u, "(1x,A)") "Test sampler: f(x) = 3 x^2" case (2) write (u, "(1x,A)") "Test sampler: f(x) = 11 x^10" case (3) write (u, "(1x,A)") "Test sampler: f(x) = 11 x^10 * 2 * cos^2 (2 pi y)" case (4) write (u, "(1x,A)") "Test sampler: f(x) = (1 - 3 x^2) theta(x - 1/2)" end select end subroutine test_sampler_1_write @ %def test_sampler_1_write @ Evaluation: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure, public :: evaluate => test_sampler_1_evaluate <>= subroutine test_sampler_1_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_1_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f if (allocated (sampler%x)) deallocate (sampler%x) allocate (sampler%x (size (x_in))) sampler%x = x_in select case (sampler%mode) case (1) sampler%val = 3 * x_in(1) ** 2 case (2) sampler%val = 11 * x_in(1) ** 10 case (3) sampler%val = 11 * x_in(1) ** 10 * 2 * cos (twopi * x_in(2)) ** 2 case (4) if (x_in(1) >= .5_default) then sampler%val = 1 - 3 * x_in(1) ** 2 else sampler%val = 0 end if end select call sampler%fetch (val, x, f) end subroutine test_sampler_1_evaluate @ %def test_sampler_1_evaluate @ The point is always valid. <>= procedure, public :: is_valid => test_sampler_1_is_valid <>= function test_sampler_1_is_valid (sampler) result (valid) class(test_sampler_1_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_1_is_valid @ %def test_sampler_1_is_valid @ Rebuild: compute all but the function value. <>= procedure, public :: rebuild => test_sampler_1_rebuild <>= subroutine test_sampler_1_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_1_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f if (allocated (sampler%x)) deallocate (sampler%x) allocate (sampler%x (size (x_in))) sampler%x = x_in sampler%val = val x(:,1) = sampler%x f = 1 end subroutine test_sampler_1_rebuild @ %def test_sampler_1_rebuild @ Extract the results. <>= procedure, public :: fetch => test_sampler_1_fetch <>= subroutine test_sampler_1_fetch (sampler, val, x, f) class(test_sampler_1_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x(:,1) = sampler%x f = 1 end subroutine test_sampler_1_fetch @ %def test_sampler_1_fetch @ \subsubsection{Two-channel, two dimension test sampler} This sampler implements the function \begin{equation} f(x, y) = 4\sin^2(\pi x)\sin^2(\pi y) + 2\sin^2(\pi v) \end{equation} where \begin{align} x &= u^v &u &= xy \\ y &= u^{(1-v)} &v &= \frac12\left(1 + \frac{\log(x/y)}{\log xy}\right) \end{align} Each term contributes $1$ to the integral. The first term in the function is peaked along a cross aligned to the coordinates $x$ and $y$, while the second term is peaked along the diagonal $x=y$. The Jacobian is \begin{equation} \frac{\partial(x,y)}{\partial(u,v)} = |\log u| \end{equation} <>= type, extends (mci_sampler_t) :: test_sampler_2_t real(default), dimension(:,:), allocatable :: x real(default), dimension(:), allocatable :: f real(default) :: val contains <> end type test_sampler_2_t @ %def test_sampler_2_t @ Output: There is nothing stored inside, so just print an informative line. <>= procedure, public :: write => test_sampler_2_write <>= subroutine test_sampler_2_write (object, unit, testflag) class(test_sampler_2_t), intent(in) :: object integer, intent(in), optional :: unit logical, intent(in), optional :: testflag integer :: u u = given_output_unit (unit) write (u, "(1x,A)") "Two-channel test sampler 2" end subroutine test_sampler_2_write @ %def test_sampler_2_write @ Kinematics: compute $x$ and Jacobians, given the input parameter array. <>= procedure, public :: compute => test_sampler_2_compute <>= subroutine test_sampler_2_compute (sampler, c, x_in) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default) :: xx, yy, uu, vv if (.not. allocated (sampler%x)) & allocate (sampler%x (size (x_in), 2)) if (.not. allocated (sampler%f)) & allocate (sampler%f (2)) select case (c) case (1) xx = x_in(1) yy = x_in(2) uu = xx * yy vv = (1 + log (xx/yy) / log (xx*yy)) / 2 case (2) uu = x_in(1) vv = x_in(2) xx = uu ** vv yy = uu ** (1 - vv) end select sampler%val = (2 * sin (pi * xx) * sin (pi * yy)) ** 2 & + 2 * sin (pi * vv) ** 2 sampler%f(1) = 1 sampler%f(2) = abs (log (uu)) sampler%x(:,1) = [xx, yy] sampler%x(:,2) = [uu, vv] end subroutine test_sampler_2_compute @ %def test_sampler_kinematics @ Evaluation: compute the function value. The output $x$ parameter (only one channel) is identical to the input $x$, and the Jacobian is 1. <>= procedure, public :: evaluate => test_sampler_2_evaluate <>= subroutine test_sampler_2_evaluate (sampler, c, x_in, val, x, f) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) call sampler%fetch (val, x, f) end subroutine test_sampler_2_evaluate @ %def test_sampler_2_evaluate @ The point is always valid. <>= procedure, public :: is_valid => test_sampler_2_is_valid <>= function test_sampler_2_is_valid (sampler) result (valid) class(test_sampler_2_t), intent(in) :: sampler logical :: valid valid = .true. end function test_sampler_2_is_valid @ %def test_sampler_2_is_valid @ Rebuild: compute all but the function value. <>= procedure, public :: rebuild => test_sampler_2_rebuild <>= subroutine test_sampler_2_rebuild (sampler, c, x_in, val, x, f) class(test_sampler_2_t), intent(inout) :: sampler integer, intent(in) :: c real(default), dimension(:), intent(in) :: x_in real(default), intent(in) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f call sampler%compute (c, x_in) x = sampler%x f = sampler%f end subroutine test_sampler_2_rebuild @ %def test_sampler_2_rebuild @ Extract the results. <>= procedure, public :: fetch => test_sampler_2_fetch <>= subroutine test_sampler_2_fetch (sampler, val, x, f) class(test_sampler_2_t), intent(in) :: sampler real(default), intent(out) :: val real(default), dimension(:,:), intent(out) :: x real(default), dimension(:), intent(out) :: f val = sampler%val x = sampler%x f = sampler%f end subroutine test_sampler_2_fetch @ %def test_sampler_2_fetch @ \subsubsection{One-dimensional integration} \label{sec:mci-vamp2-one-dim} Construct an integrator and use it for a one-dimensional sampler. <>= call test (mci_vamp2_1, "mci_vamp2_1", "one-dimensional integral", u, results) <>= public :: mci_vamp2_1 <>= subroutine mci_vamp2_1 (u) integer, intent(in) :: u type(mci_vamp2_config_t) :: config class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable, target :: mci_sampler class(rng_t), allocatable :: rng type(string_t) :: filename write (u, "(A)") "* Test output: mci_vamp2_1" write (u, "(A)") "* Purpose: integrate function in one dimension (single channel)" write (u, "(A)") write (u, "(A)") "* Initialise integrator" write (u, "(A)") allocate (mci_vamp2_t :: mci) call mci%set_dimensions (1, 1) filename = "mci_vamp2_1" select type (mci) type is (mci_vamp2_t) call mci%set_config (config) call mci%set_grid_filename (filename) end select allocate (rng_stream_t :: rng) call rng%init () call mci%import_rng (rng) call mci%write (u, pacify = .true.) write (u, "(A)") write (u, "(A)") "* Initialise instance" write (u, "(A)") call mci%allocate_instance (mci_instance) call mci_instance%init (mci) write (u, "(A)") write (u, "(A)") "* Initialise test sampler" write (u, "(A)") allocate (test_sampler_1_t :: mci_sampler) call mci_sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_calls = 1000" write (u, "(A)") " (lower precision to avoid" write (u, "(A)") " numerical noise)" write (u, "(A)") select type (mci) type is (mci_vamp2_t) call mci%add_pass () end select call mci%integrate (mci_instance, mci_sampler, 1, 1000, pacify = .true.) call mci%write (u, pacify = .true.) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u, pacify = .true.) write (u, "(A)") write (u, "(A)") "* Dump channel weights and grids to file" write (u, "(A)") mci%md5sum = "1234567890abcdef1234567890abcdef" select type (mci) type is (mci_vamp2_t) call mci%write_grids () end select write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp2_1" end subroutine mci_vamp2_1 @ %def mci_vamp2_test1 @ \subsubsection{Multiple iterations} Construct an integrator and use it for a one-dimensional sampler. Integrate with five iterations without grid adaptation. <>= call test (mci_vamp2_2, "mci_vamp2_2", & "multiple iterations", & u, results) <>= public :: mci_vamp2_2 <>= subroutine mci_vamp2_2 (u) type(mci_vamp2_config_t) :: config integer, intent(in) :: u class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng type(string_t) :: filename write (u, "(A)") "* Test output: mci_vamp2_2" write (u, "(A)") "* Purpose: integrate function in one dimension & &(single channel), but multiple iterations." write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp2_t :: mci) call mci%set_dimensions (1, 1) filename = "mci_vamp2_2" select type (mci) type is (mci_vamp2_t) call mci%set_config (config) call mci%set_grid_filename (filename) end select allocate (rng_stream_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_1_t :: sampler) select type (sampler) type is (test_sampler_1_t) sampler%mode = 2 end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 100" write (u, "(A)") select type (mci) type is (mci_vamp2_t) call mci%add_pass (adapt_grids = .false.) end select call mci%integrate (mci_instance, sampler, 3, 1000, pacify = .true.) call mci%write (u, pacify = .true.) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u, pacify = .true.) write (u, "(A)") write (u, "(A)") "* Dump channel weights and grids to file" write (u, "(A)") mci%md5sum = "1234567890abcdef1234567890abcdef" select type (mci) type is (mci_vamp2_t) call mci%write_grids () end select write (u, "(A)") write (u, "(A)") "* Cleanup" call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp2_2" end subroutine mci_vamp2_2 @ %def mci_vamp2_2 @ \subsubsection{Grid adaptation} Construct an integrator and use it for a one-dimensional sampler. Integrate with three iterations and in-between grid adaptations. <>= call test (mci_vamp2_3, "mci_vamp2_3", & "grid adaptation", & u, results) <>= public :: mci_vamp2_3 <>= subroutine mci_vamp2_3 (u) integer, intent(in) :: u type(mci_vamp2_config_t) :: config class(mci_t), allocatable, target :: mci class(mci_instance_t), pointer :: mci_instance => null () class(mci_sampler_t), allocatable :: sampler class(rng_t), allocatable :: rng type(string_t) :: filename write (u, "(A)") "* Test output: mci_vamp2_3" write (u, "(A)") "* Purpose: integrate function in one dimension & &(single channel)" write (u, "(A)") "* and adapt grid" write (u, "(A)") write (u, "(A)") "* Initialize integrator, sampler, instance" write (u, "(A)") allocate (mci_vamp2_t :: mci) call mci%set_dimensions (1, 1) filename = "mci_vamp2_3" select type (mci) type is (mci_vamp2_t) call mci%set_grid_filename (filename) call mci%set_config (config) end select allocate (rng_stream_t :: rng) call rng%init () call mci%import_rng (rng) call mci%allocate_instance (mci_instance) call mci_instance%init (mci) allocate (test_sampler_1_t :: sampler) select type (sampler) type is (test_sampler_1_t) sampler%mode = 2 end select call sampler%write (u) write (u, "(A)") write (u, "(A)") "* Integrate with n_it = 3 and n_calls = 100" write (u, "(A)") select type (mci) type is (mci_vamp2_t) call mci%add_pass (adapt_grids = .true.) end select call mci%integrate (mci_instance, sampler, 3, 1000, pacify = .true.) call mci%write (u, pacify = .true.) write (u, "(A)") write (u, "(A)") "* Contents of mci_instance:" write (u, "(A)") call mci_instance%write (u, pacify = .true.) write (u, "(A)") write (u, "(A)") "* Dump channel weights and grids to file" write (u, "(A)") mci%md5sum = "1234567890abcdef1234567890abcdef" select type (mci) type is (mci_vamp2_t) call mci%write_grids () end select write (u, "(A)") write (u, "(A)") "* Cleanup" write (u, "(A)") call mci_instance%final () call mci%final () write (u, "(A)") write (u, "(A)") "* Test output end: mci_vamp2_3" end subroutine mci_vamp2_3 @ %def mci_vamp2_3 @ \section{Dispatch} @ <<[[dispatch_mci.f90]]>>= <> module dispatch_mci <> use diagnostics use os_interface use variables use mci_base use mci_none use mci_midpoint use mci_vamp use mci_vamp2 <> <> <> contains <> end module dispatch_mci @ %def dispatch_mci @ Allocate an integrator according to the variable [[$integration_method]]. <>= public :: dispatch_mci_s <>= subroutine dispatch_mci_s (mci, var_list, process_id, is_nlo) class(mci_t), allocatable, intent(out) :: mci type(var_list_t), intent(in) :: var_list type(string_t), intent(in) :: process_id logical, intent(in), optional :: is_nlo type(string_t) :: run_id type(string_t) :: integration_method type(grid_parameters_t) :: grid_par type(history_parameters_t) :: history_par type(mci_vamp2_config_t) :: mci_vamp2_config integer :: grid_checkpoint logical :: rebuild_grids, check_grid_file, negative_weights, verbose logical :: dispatch_nlo, binary_grid_format type(string_t) :: grid_path, parallel_method dispatch_nlo = .false.; if (present (is_nlo)) dispatch_nlo = is_nlo integration_method = & var_list%get_sval (var_str ("$integration_method")) select case (char (integration_method)) case ("none") allocate (mci_none_t :: mci) case ("midpoint") allocate (mci_midpoint_t :: mci) case ("vamp", "default") call unpack_options_vamp () allocate (mci_vamp_t :: mci) select type (mci) type is (mci_vamp_t) call mci%set_grid_parameters (grid_par) if (run_id /= "") then call mci%set_grid_filename (process_id, run_id) else call mci%set_grid_filename (process_id) end if grid_path = var_list%get_sval (var_str ("$integrate_workspace")) if (grid_path /= "") then call setup_grid_path (grid_path) call mci%prepend_grid_path (grid_path) end if call mci%set_history_parameters (history_par) call mci%set_rebuild_flag (rebuild_grids, check_grid_file) mci%negative_weights = negative_weights mci%verbose = verbose end select case ("vamp2") call unpack_options_vamp2 () allocate (mci_vamp2_t :: mci) select type (mci) type is (mci_vamp2_t) call mci%set_config (mci_vamp2_config) if (run_id /= "") then call mci%set_grid_filename (process_id, run_id) else call mci%set_grid_filename (process_id) end if grid_path = var_list%get_sval (var_str ("$integrate_workspace")) if (grid_path /= "") then call setup_grid_path (grid_path) call mci%prepend_grid_path (grid_path) end if call mci%set_rebuild_flag (rebuild_grids, check_grid_file) mci%negative_weights = negative_weights mci%verbose = verbose mci%grid_checkpoint = grid_checkpoint mci%binary_grid_format = binary_grid_format mci%parallel_method = parallel_method end select case default call msg_fatal ("Integrator '" & // char (integration_method) // "' not implemented") end select contains <> end subroutine dispatch_mci_s @ %def dispatch_mci_s @ <>= subroutine unpack_options_vamp () grid_par%threshold_calls = & var_list%get_ival (var_str ("threshold_calls")) grid_par%min_calls_per_channel = & var_list%get_ival (var_str ("min_calls_per_channel")) grid_par%min_calls_per_bin = & var_list%get_ival (var_str ("min_calls_per_bin")) grid_par%min_bins = & var_list%get_ival (var_str ("min_bins")) grid_par%max_bins = & var_list%get_ival (var_str ("max_bins")) grid_par%stratified = & var_list%get_lval (var_str ("?stratified")) select case (char (var_list%get_sval (var_str ("$phs_method")))) case ("rambo") grid_par%use_vamp_equivalences = .false. case default grid_par%use_vamp_equivalences = & var_list%get_lval (var_str ("?use_vamp_equivalences")) end select grid_par%channel_weights_power = & var_list%get_rval (var_str ("channel_weights_power")) grid_par%accuracy_goal = & var_list%get_rval (var_str ("accuracy_goal")) grid_par%error_goal = & var_list%get_rval (var_str ("error_goal")) grid_par%rel_error_goal = & var_list%get_rval (var_str ("relative_error_goal")) history_par%global = & var_list%get_lval (var_str ("?vamp_history_global")) history_par%global_verbose = & var_list%get_lval (var_str ("?vamp_history_global_verbose")) history_par%channel = & var_list%get_lval (var_str ("?vamp_history_channels")) history_par%channel_verbose = & var_list%get_lval (var_str ("?vamp_history_channels_verbose")) verbose = & var_list%get_lval (var_str ("?vamp_verbose")) check_grid_file = & var_list%get_lval (var_str ("?check_grid_file")) run_id = & var_list%get_sval (var_str ("$run_id")) rebuild_grids = & var_list%get_lval (var_str ("?rebuild_grids")) negative_weights = & var_list%get_lval (var_str ("?negative_weights")) .or. dispatch_nlo end subroutine unpack_options_vamp subroutine unpack_options_vamp2 () mci_vamp2_config%n_bins_max = & var_list%get_ival (var_str ("max_bins")) mci_vamp2_config%n_calls_min_per_channel = & var_list%get_ival (var_str ("min_calls_per_channel")) mci_vamp2_config%n_calls_threshold = & var_list%get_ival (var_str ("threshold_calls")) mci_vamp2_config%beta = & var_list%get_rval (var_str ("channel_weights_power")) mci_vamp2_config%stratified = & var_list%get_lval (var_str ("?stratified")) select case (char (var_list%get_sval (var_str ("$phs_method")))) case ("rambo") mci_vamp2_config%equivalences = .false. case default mci_vamp2_config%equivalences = & var_list%get_lval (var_str ("?use_vamp_equivalences")) end select mci_vamp2_config%accuracy_goal = & var_list%get_rval (var_str ("accuracy_goal")) mci_vamp2_config%error_goal = & var_list%get_rval (var_str ("error_goal")) mci_vamp2_config%rel_error_goal = & var_list%get_rval (var_str ("relative_error_goal")) verbose = & var_list%get_lval (var_str ("?vamp_verbose")) check_grid_file = & var_list%get_lval (var_str ("?check_grid_file")) run_id = & var_list%get_sval (var_str ("$run_id")) rebuild_grids = & var_list%get_lval (var_str ("?rebuild_grids")) negative_weights = & var_list%get_lval (var_str ("?negative_weights")) .or. dispatch_nlo grid_checkpoint = & var_list%get_ival (var_str ("vamp_grid_checkpoint")) select case (char (var_list%get_sval (var_str ("$vamp_grid_format")))) case ("binary","Binary","BINARY") binary_grid_format = .true. case ("ascii","Ascii","ASCII") binary_grid_format = .false. case default binary_grid_format = .false. end select select case (char (var_list%get_sval (var_str ("$vamp_parallel_method")))) case ("simple","Simple","SIMPLE") parallel_method = var_str ("simple") case ("load","Load","LOAD") parallel_method = var_str ("load") case default parallel_method = var_str ("simple") end select end subroutine unpack_options_vamp2 @ @ Make sure that the VAMP grid subdirectory, if requested, exists before it is used. Also include a sanity check on the directory name. <>= character(*), parameter :: ALLOWED_IN_DIRNAME = & "abcdefghijklmnopqrstuvwxyz& &ABCDEFGHIJKLMNOPQRSTUVWXYZ& &1234567890& &.,_-+=" @ %def ALLOWED_IN_DIRNAME <>= public :: setup_grid_path <>= subroutine setup_grid_path (grid_path) type(string_t), intent(in) :: grid_path if (verify (grid_path, ALLOWED_IN_DIRNAME) == 0) then call msg_message ("Integrator: preparing VAMP grid directory '" & // char (grid_path) // "'") call os_system_call ("mkdir -p '" // grid_path // "'") else call msg_fatal ("Integrator: VAMP grid_path '" & // char (grid_path) // "' contains illegal characters") end if end subroutine setup_grid_path @ %def setup_grid_path @ \subsection{Unit tests} Test module, followed by the corresponding implementation module. <<[[dispatch_mci_ut.f90]]>>= <> module dispatch_mci_ut use unit_tests use dispatch_mci_uti <> <> contains <> end module dispatch_mci_ut @ %def dispatch_mci_ut @ <<[[dispatch_mci_uti.f90]]>>= <> module dispatch_mci_uti <> <> use variables use mci_base use mci_none use mci_midpoint use mci_vamp use dispatch_mci <> <> contains <> end module dispatch_mci_uti @ %def dispatch_mci_ut @ API: driver for the unit tests below. <>= public ::dispatch_mci_test <>= subroutine dispatch_mci_test (u, results) integer, intent(in) :: u type(test_results_t), intent(inout) :: results <> end subroutine dispatch_mci_test @ %def dispatch_mci_test @ \subsubsection{Select type: integrator core} <>= call test (dispatch_mci_1, "dispatch_mci_1", & "integration method", & u, results) <>= public :: dispatch_mci_1 <>= subroutine dispatch_mci_1 (u) integer, intent(in) :: u type(var_list_t) :: var_list class(mci_t), allocatable :: mci type(string_t) :: process_id write (u, "(A)") "* Test output: dispatch_mci_1" write (u, "(A)") "* Purpose: select integration method" write (u, "(A)") call var_list%init_defaults (0) process_id = "dispatch_mci_1" write (u, "(A)") "* Allocate MCI as none_t" write (u, "(A)") call var_list%set_string (& var_str ("$integration_method"), & var_str ("none"), is_known = .true.) call dispatch_mci_s (mci, var_list, process_id) select type (mci) type is (mci_none_t) call mci%write (u) end select call mci%final () deallocate (mci) write (u, "(A)") write (u, "(A)") "* Allocate MCI as midpoint_t" write (u, "(A)") call var_list%set_string (& var_str ("$integration_method"), & var_str ("midpoint"), is_known = .true.) call dispatch_mci_s (mci, var_list, process_id) select type (mci) type is (mci_midpoint_t) call mci%write (u) end select call mci%final () deallocate (mci) write (u, "(A)") write (u, "(A)") "* Allocate MCI as vamp_t" write (u, "(A)") call var_list%set_string (& var_str ("$integration_method"), & var_str ("vamp"), is_known = .true.) call var_list%set_int (var_str ("threshold_calls"), & 1, is_known = .true.) call var_list%set_int (var_str ("min_calls_per_channel"), & 2, is_known = .true.) call var_list%set_int (var_str ("min_calls_per_bin"), & 3, is_known = .true.) call var_list%set_int (var_str ("min_bins"), & 4, is_known = .true.) call var_list%set_int (var_str ("max_bins"), & 5, is_known = .true.) call var_list%set_log (var_str ("?stratified"), & .false., is_known = .true.) call var_list%set_log (var_str ("?use_vamp_equivalences"),& .false., is_known = .true.) call var_list%set_real (var_str ("channel_weights_power"),& 4._default, is_known = .true.) call var_list%set_log (& var_str ("?vamp_history_global_verbose"), & .true., is_known = .true.) call var_list%set_log (& var_str ("?vamp_history_channels"), & .true., is_known = .true.) call var_list%set_log (& var_str ("?vamp_history_channels_verbose"), & .true., is_known = .true.) call var_list%set_log (var_str ("?stratified"), & .false., is_known = .true.) call dispatch_mci_s (mci, var_list, process_id) select type (mci) type is (mci_vamp_t) call mci%write (u) call mci%write_history_parameters (u) end select call mci%final () deallocate (mci) write (u, "(A)") write (u, "(A)") "* Allocate MCI as vamp_t, allow for negative weights" write (u, "(A)") call var_list%set_string (& var_str ("$integration_method"), & var_str ("vamp"), is_known = .true.) call var_list%set_log (var_str ("?negative_weights"), & .true., is_known = .true.) call dispatch_mci_s (mci, var_list, process_id) select type (mci) type is (mci_vamp_t) call mci%write (u) call mci%write_history_parameters (u) end select call mci%final () deallocate (mci) call var_list%final () write (u, "(A)") write (u, "(A)") "* Test output end: dispatch_mci_1" end subroutine dispatch_mci_1 @ %def dispatch_mci_1 Index: trunk/share/tests/functional_tests/ref-output-double/openloops_3.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-double/openloops_3.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-double/openloops_3.ref (revision 8760) @@ -1,1186 +1,1186 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true $method = "openloops" openmp_num_threads = 1 ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true seed = 2222 sqrts = 5.00000E+02 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false ?fixed_order_nlo_events = true ?negative_weights = true ?unweighted = false SM.mtop => 1.73200E+02 SM.wtop => 0.00000E+00 | Process library 'openloops_3_lib': recorded process 'openloops_3_p1' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2222 | Initializing integration for process openloops_3_p1: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p1' | Library name = 'openloops_3_lib' | Process index = 1 | Process components: | 1: 'openloops_3_p1_i1': e+, e- => t, tbar [openloops] | 2: 'openloops_3_p1_i2': e+, e- => t, tbar, gl [inactive], [real] | 3: 'openloops_3_p1_i3': e+, e- => t, tbar [inactive], [virtual] | 4: 'openloops_3_p1_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 6.257E+02 2.89E+01 4.61 0.46 55.5 |-----------------------------------------------------------------------------| 1 100 6.257E+02 2.89E+01 4.61 0.46 55.5 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 6.257E+02 2.89E+01 4.61 0.00 55.5 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p1' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p1.m1.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2223 | Events: writing to ASCII file 'openloops_3_p1.debug' | Events: generating 1 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p1.debug' seed = 3333 | Process library 'openloops_3_lib': unloading | Process library 'openloops_3_lib': open | Process library 'openloops_3_lib': recorded process 'openloops_3_p2' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 3333 | Initializing integration for process openloops_3_p2: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p2.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p2' | Library name = 'openloops_3_lib' | Process index = 2 | Process components: | 1: 'openloops_3_p2_i1': e+, e- => t, tbar [inactive] | 2: 'openloops_3_p2_i2': e+, e- => t, tbar, gl [openloops], [real] | 3: 'openloops_3_p2_i3': e+, e- => t, tbar [inactive], [virtual] | 4: 'openloops_3_p2_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -7.301E+01 4.28E+00 5.86 0.59 39.2 |-----------------------------------------------------------------------------| 1 100 -7.301E+01 4.28E+00 5.86 0.59 39.2 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 -7.301E+01 4.28E+00 5.86 0.00 0.0 |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p2' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p2.m2.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 3334 | Events: writing to ASCII file 'openloops_3_p2.debug' | Events: generating 3 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p2.debug' seed = 4444 | Process library 'openloops_3_lib': unloading | Process library 'openloops_3_lib': open | Process library 'openloops_3_lib': recorded process 'openloops_3_p3' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 4444 | Initializing integration for process openloops_3_p3: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p3.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p3' | Library name = 'openloops_3_lib' | Process index = 3 | Process components: | 1: 'openloops_3_p3_i1': e+, e- => t, tbar [inactive] | 2: 'openloops_3_p3_i2': e+, e- => t, tbar, gl [inactive], [real] | 3: 'openloops_3_p3_i3': e+, e- => t, tbar [openloops], [virtual] | 4: 'openloops_3_p3_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.387E+02 7.85E+00 5.66 0.57 44.8 |-----------------------------------------------------------------------------| 1 100 1.387E+02 7.85E+00 5.66 0.57 44.8 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.387E+02 7.85E+00 5.66 0.00 44.8 |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p3' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p3.m3.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 4445 | Events: writing to ASCII file 'openloops_3_p3.debug' | Events: generating 1 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p3.debug' | There were no errors and 3 warning(s). | WHIZARD run finished. |=============================================================================| ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.66014E-02 Squared matrix el. (prc) = 2.66014E-02 Event weight (ref) = 5.94404E+02 Event weight (prc) = 5.94404E+02 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p1' TAO random-number generator: seed = 145620996 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p1' TAO random-number generator: seed = 145620997 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p1" process_num_id* => [unknown integer] sqme* => 2.66014E-02 sqme_ref* => 2.66014E-02 event_index* => 1 event_weight* => 5.94404E+02 event_weight_ref* => 5.94404E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02;-3.0933754E+01, 1.7292509E+02,-4.0518856E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02; 3.0933754E+01,-1.7292509E+02, 4.0518856E+01| 2.9998240E+04| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = -5.17360E-03 Event weight (ref) = -9.77307E+01 Event weight (prc) = -1.15603E+02 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823953E+01 9.319924E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034760697E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888582E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = 7.697589E+01 4.999534E+01 9.008650E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823953E+01 9.319924E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => -5.17360E-03 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => -1.15603E+02 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02; 1.6597780E+02, 4.6491044E+01,-5.2836666E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02;-1.6597780E+02,-4.6491044E+01, 5.2836666E+01| 2.9998240E+04| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = 4.96367E-04 Event weight (ref) = -9.77307E+01 Event weight (prc) = 1.10912E+01 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823953E+01 9.319924E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034760697E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888582E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = 7.697589E+01 4.999534E+01 9.008650E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823953E+01 9.319924E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => 4.96367E-04 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => 1.10912E+01 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 1.8711950E+02; 4.8885819E+01,-1.4740977E+01,-4.9074930E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.2065264E+02;-1.2586171E+02,-3.5254367E+01, 4.0066280E+01| 2.9998240E+04| 4) 5 prt(o:21| 9.2227858E+01; 7.6975890E+01, 4.9995344E+01, 9.0086499E+00| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = 3.03476E-04 Event weight (ref) = -9.77307E+01 Event weight (prc) = 6.78112E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823953E+01 9.319924E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034760697E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888582E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = 7.697589E+01 4.999534E+01 9.008650E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823953E+01 9.319924E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222786E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => 3.03476E-04 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => 6.78112E+00 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.2065264E+02; 1.2586171E+02, 3.5254367E+01,-4.0066280E+01| 2.9998240E+04| 3) 4 prt(o:-6| 1.8711950E+02;-6.8239535E+01, 9.3199242E+00,-1.6491615E+01| 2.9998240E+04| 4) 5 prt(o:21| 9.2227858E+01;-5.7622174E+01,-4.4574291E+01, 5.6557895E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.22409E-02 Squared matrix el. (prc) = 1.22409E-02 Event weight (ref) = 2.73522E+02 Event weight (prc) = 2.73522E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p3' TAO random-number generator: seed = 291241988 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p3' TAO random-number generator: seed = 291241989 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p3" process_num_id* => [unknown integer] sqme* => 1.22409E-02 sqme_ref* => 1.22409E-02 event_index* => 1 event_weight* => 2.73522E+02 event_weight_ref* => 2.73522E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02;-9.6029292E+01, 1.9046186E+01,-1.5138487E+02| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02; 9.6029292E+01,-1.9046186E+01, 1.5138487E+02| 2.9998240E+04| 4) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-double/nlo_7.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-double/nlo_7.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-double/nlo_7.ref (revision 8760) @@ -1,8792 +1,8792 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true openmp_num_threads = 1 SM.ms => 0.00000E+00 SM.mc => 0.00000E+00 SM.mb => 0.00000E+00 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $method = "dummy" ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true sqrts = 5.00000E+02 jet_algorithm = 2 jet_r = 5.00000E-01 seed = 1558 n_events = 10 $sample_normalization = "sigma" ?unweighted = false ?negative_weights = true ?keep_failed_events = true ?fixed_order_nlo_events = true ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false | Process library 'nlo_7_lib': recorded process 'nlo_7_p1' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1558 | Initializing integration for process nlo_7_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p1' | Library name = 'nlo_7_lib' | Process index = 1 | Process components: | 1: 'nlo_7_p1_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [dummy] | 2: 'nlo_7_p1_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_7_p1_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [virtual] | 4: 'nlo_7_p1_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.054E+05 7.27E+03 6.90 0.69 68.0 |-----------------------------------------------------------------------------| 1 100 1.054E+05 7.27E+03 6.90 0.69 68.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.054E+05 7.27E+03 6.90 0.00 68.0 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| | Starting simulation for process 'nlo_7_p1' | Simulate: using integration grids from file 'nlo_7_p1.m1.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1559 | Events: writing to ASCII file 'nlo_7_p1.debug' | Events: generating 10 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p1.debug' | Process library 'nlo_7_lib': unloading | Process library 'nlo_7_lib': open | Process library 'nlo_7_lib': recorded process 'nlo_7_p2' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1560 | Initializing integration for process nlo_7_p2: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p2.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p2' | Library name = 'nlo_7_lib' | Process index = 2 | Process components: | 1: 'nlo_7_p2_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive] | 2: 'nlo_7_p2_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [dummy], [real] | 3: 'nlo_7_p2_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [virtual] | 4: 'nlo_7_p2_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.817E+07 6.57E+06 36.18 3.62 5.2 |-----------------------------------------------------------------------------| 1 100 1.817E+07 6.57E+06 36.18 3.62 5.2 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.817E+07 6.57E+06 36.18 0.00 5.2 |=============================================================================| | Starting simulation for process 'nlo_7_p2' | Simulate: using integration grids from file 'nlo_7_p2.m2.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1561 | Events: writing to ASCII file 'nlo_7_p2.debug' | Events: generating 30 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p2.debug' | Process library 'nlo_7_lib': unloading | Process library 'nlo_7_lib': open | Process library 'nlo_7_lib': recorded process 'nlo_7_p3' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1562 | Initializing integration for process nlo_7_p3: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p3.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p3' | Library name = 'nlo_7_lib' | Process index = 3 | Process components: | 1: 'nlo_7_p3_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive] | 2: 'nlo_7_p3_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_7_p3_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [dummy], [virtual] | 4: 'nlo_7_p3_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 7.843E+01 6.45E+00 8.22 0.82 59.0 |-----------------------------------------------------------------------------| 1 100 7.843E+01 6.45E+00 8.22 0.82 59.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 7.843E+01 6.45E+00 8.22 0.00 59.0 |=============================================================================| | Starting simulation for process 'nlo_7_p3' | Simulate: using integration grids from file 'nlo_7_p3.m3.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1563 | Events: writing to ASCII file 'nlo_7_p3.debug' | Events: generating 10 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p3.debug' | WHIZARD run finished. |=============================================================================| Contents of nlo_7_p1.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 1 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.5000000E+02; 2.3030328E+02, 2.0093120E+01,-9.5166522E+01| 0.0000000E+00| 3) 4 prt(o:2| 2.5000000E+02;-2.3030328E+02,-2.0093120E+01, 9.5166522E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 6 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 6 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 2 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-2.1900152E+02,-1.6025552E+01,-1.1950530E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 2.1900152E+02, 1.6025552E+01, 1.1950530E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 3 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-5| 2.5000000E+02; 1.1488797E+02,-1.0151895E+02,-1.9747065E+02| 0.0000000E+00| 3) 4 prt(o:5| 2.5000000E+02;-1.1488797E+02, 1.0151895E+02, 1.9747065E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 12 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 12 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-8.0922467E+01, 7.8108474E+01,-2.2327253E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 8.0922467E+01,-7.8108474E+01, 2.2327253E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 15 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 15 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 5 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.5000000E+02; 2.1721823E+02, 6.8664192E+01, 1.0296343E+02| 0.0000000E+00| 3) 4 prt(o:2| 2.5000000E+02;-2.1721823E+02,-6.8664192E+01,-1.0296343E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 6 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-1.7188357E+02,-1.4357975E+02, 1.1108958E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 1.7188357E+02, 1.4357975E+02,-1.1108958E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 21 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 21 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 7 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.8588362E+02, 1.5153486E+02, 7.0600756E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.8588362E+02,-1.5153486E+02,-7.0600756E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 24 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 24 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 8 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-1.3809822E+02,-1.9874706E+02, 6.2677654E+01| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 1.3809822E+02, 1.9874706E+02,-6.2677654E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 9 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-3| 2.5000000E+02;-2.2331587E+02,-3.6246582E+01, 1.0637766E+02| 0.0000000E+00| 3) 4 prt(o:3| 2.5000000E+02; 2.2331587E+02, 3.6246582E+01,-1.0637766E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 30 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 30 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 10 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-5| 2.5000000E+02; 7.6696234E+01, 1.9465831E+02, 1.3684236E+02| 0.0000000E+00| 3) 4 prt(o:5| 2.5000000E+02;-7.6696234E+01,-1.9465831E+02,-1.3684236E+02| 0.0000000E+00| 4) ======================================================================== Contents of nlo_7_p2.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.43649E+00 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.69268E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104538E+01 P = 1.133141E+01 -2.020971E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596783E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358322E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104538E+01 P = -8.581747E+00 2.829876E+01 9.452489E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608387E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104538E+01 P = 1.133141E+01 -2.020971E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596783E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.43649E+00 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.69268E+04 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.7405031E+01, 2.2771282E+02,-6.8229998E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.7405031E+01,-2.2771282E+02, 6.8229998E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.34436E+03 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.51997E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104538E+01 P = 1.133141E+01 -2.020971E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596783E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358322E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104538E+01 P = -8.581747E+00 2.829876E+01 9.452489E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608387E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104538E+01 P = 1.133141E+01 -2.020971E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596783E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34436E+03 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.51997E+07 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 3.1045383E+01;-8.5817467E+00, 2.8298761E+01, 9.4524892E+00| 0.0000000E+00| 3) 4 prt(o:2| 2.4414256E+02;-7.5591449E+01,-2.2237756E+02, 6.6631385E+01| 0.0000000E+00| 4) 5 prt(o:21| 2.2481206E+02; 8.4173195E+01, 1.9407880E+02,-7.6083874E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.34436E+03 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.51997E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104538E+01 P = 1.133141E+01 -2.020971E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596783E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358322E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104538E+01 P = -8.581747E+00 2.829876E+01 9.452489E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608387E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104538E+01 P = 1.133141E+01 -2.020971E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596783E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34436E+03 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.51997E+07 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4414256E+02; 7.5591449E+01, 2.2237756E+02,-6.6631385E+01| 0.0000000E+00| 3) 4 prt(o:4| 3.1045383E+01; 1.1331408E+01,-2.0209712E+01, 2.0663556E+01| 0.0000000E+00| 4) 5 prt(o:21| 2.2481206E+02;-8.6922856E+01,-2.0216785E+02, 4.5967829E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 2.04961E+00 Event weight (ref) = 1.22098E+08 Event weight (prc) = 1.83043E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889131E+00 1.179585E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = 3.745224E+01 -2.434743E+01 -1.479390E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365137348E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534418E+00 -6.315651E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = -1.140194E+01 2.199272E+01 -4.000804E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889131E+00 1.179585E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = 3.745224E+01 -2.434743E+01 -1.479390E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 2.04961E+00 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 1.83043E+05 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.2470250E+02, 2.0311083E+01,-1.0768586E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.2470250E+02,-2.0311083E+01, 1.0768586E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 1.36514E+03 Event weight (ref) = 1.22098E+08 Event weight (prc) = 1.21915E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889131E+00 1.179585E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = 3.745224E+01 -2.434743E+01 -1.479390E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365137348E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534418E+00 -6.315651E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = -1.140194E+01 2.199272E+01 -4.000804E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889131E+00 1.179585E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = 3.745224E+01 -2.434743E+01 -1.479390E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.36514E+03 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 1.21915E+08 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.1343989E+02;-2.0386618E+02,-2.5344182E+00,-6.3156514E+01| 0.0000000E+00| 3) 4 prt(o:2| 2.3950347E+02; 2.1526812E+02,-1.9458299E+01, 1.0316455E+02| 0.0000000E+00| 4) 5 prt(o:21| 4.7056634E+01;-1.1401937E+01, 2.1992717E+01,-4.0008037E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 1.36514E+03 Event weight (ref) = 1.22098E+08 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889131E+00 1.179585E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = 3.745224E+01 -2.434743E+01 -1.479390E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365137348E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534418E+00 -6.315651E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = -1.140194E+01 2.199272E+01 -4.000804E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889131E+00 1.179585E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705663E+01 P = 3.745224E+01 -2.434743E+01 -1.479390E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.36514E+03 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 0.00000E+00 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.3950347E+02;-2.1526812E+02, 1.9458299E+01,-1.0316455E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.1343989E+02; 1.7781588E+02, 4.8891306E+00, 1.1795845E+02| 0.0000000E+00| 4) 5 prt(o:21| 4.7056634E+01; 3.7452236E+01,-2.4347430E+01,-1.4793902E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50431E+02 Squared matrix el. (prc) = 1.34286E+00 Event weight (ref) = 4.69427E+06 Event weight (prc) = 2.51716E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161620E+01 -2.197846E+02 -8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634918E+01 2.179771E+02 8.860502E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = 4.732982E+00 1.807517E+00 3.481319E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636849E+01 -2.180363E+02 -8.844249E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161620E+01 2.197846E+02 8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = -4.752284E+00 -1.748281E+00 -1.660124E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161620E+01 -2.197846E+02 -8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634918E+01 2.179771E+02 8.860502E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = 4.732982E+00 1.807517E+00 3.481319E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34286E+00 sqme_ref* => 2.50431E+02 event_index* => 3 event_weight* => 2.51716E+04 event_weight_ref* => 4.69427E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.2322269E+01,-2.2195145E+02,-8.9482095E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.2322269E+01, 2.2195145E+02, 8.9482095E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50431E+02 Squared matrix el. (prc) = 1.24544E+02 Event weight (ref) = 4.69427E+06 Event weight (prc) = 2.33455E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161620E+01 -2.197846E+02 -8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634918E+01 2.179771E+02 8.860502E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = 4.732982E+00 1.807517E+00 3.481319E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636849E+01 -2.180363E+02 -8.844249E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161620E+01 2.197846E+02 8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = -4.752284E+00 -1.748281E+00 -1.660124E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161620E+01 -2.197846E+02 -8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634918E+01 2.179771E+02 8.860502E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = 4.732982E+00 1.807517E+00 3.481319E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.24544E+02 sqme_ref* => 2.50431E+02 event_index* => 3 event_weight* => 2.33455E+06 event_weight_ref* => 4.69427E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4737431E+02; 7.6368487E+01,-2.1803630E+02,-8.8442489E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4755931E+02;-7.1616203E+01, 2.1978458E+02, 8.8608501E+01| 0.0000000E+00| 4) 5 prt(o:21| 5.0663845E+00;-4.7522843E+00,-1.7482808E+00,-1.6601239E-01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50431E+02 Squared matrix el. (prc) = 1.24544E+02 Event weight (ref) = 4.69427E+06 Event weight (prc) = 2.33455E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161620E+01 -2.197846E+02 -8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634918E+01 2.179771E+02 8.860502E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = 4.732982E+00 1.807517E+00 3.481319E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636849E+01 -2.180363E+02 -8.844249E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161620E+01 2.197846E+02 8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = -4.752284E+00 -1.748281E+00 -1.660124E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161620E+01 -2.197846E+02 -8.860850E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634918E+01 2.179771E+02 8.860502E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066384E+00 P = 4.732982E+00 1.807517E+00 3.481319E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.24544E+02 sqme_ref* => 2.50431E+02 event_index* => 3 event_weight* => 2.33455E+06 event_weight_ref* => 4.69427E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4755931E+02; 7.1616203E+01,-2.1978458E+02,-8.8608501E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4737431E+02;-7.6349185E+01, 2.1797707E+02, 8.8605020E+01| 0.0000000E+00| 4) 5 prt(o:21| 5.0663845E+00; 4.7329822E+00, 1.8075174E+00, 3.4813190E-03| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449131E+01 -1.603243E+01 -1.720328E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -9.525489E+01 1.836134E+01 -2.011885E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746684E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -2.435277E+01 -1.603513E+01 9.468484E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449131E+01 -1.603243E+01 -1.720328E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -9.525489E+01 1.836134E+01 -2.011885E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.3221583E+02,-2.5714252E+00, 2.1216117E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.3221583E+02, 2.5714252E+00,-2.1216117E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449131E+01 -1.603243E+01 -1.720328E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -9.525489E+01 1.836134E+01 -2.011885E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746684E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -2.435277E+01 -1.603513E+01 9.468484E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449131E+01 -1.603243E+01 -1.720328E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -9.525489E+01 1.836134E+01 -2.011885E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.7450546E+02; 1.4409897E+02, 1.3706220E+01, 9.7466837E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.2642183E+02;-1.1974620E+02, 2.3289072E+00,-1.9215168E+02| 0.0000000E+00| 4) 5 prt(o:21| 9.9072709E+01;-2.4352765E+01,-1.6035127E+01, 9.4684841E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449131E+01 -1.603243E+01 -1.720328E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -9.525489E+01 1.836134E+01 -2.011885E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746684E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -2.435277E+01 -1.603513E+01 9.468484E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449131E+01 -1.603243E+01 -1.720328E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907271E+01 P = -9.525489E+01 1.836134E+01 -2.011885E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.2642183E+02; 1.1974620E+02,-2.3289072E+00, 1.9215168E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.7450546E+02;-2.4491308E+01,-1.6032433E+01,-1.7203283E+02| 0.0000000E+00| 4) 5 prt(o:21| 9.9072709E+01;-9.5254893E+01, 1.8361340E+01,-2.0118851E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624319E+02 P = -1.118934E+02 -6.145651E+01 -1.004345E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = -5.490218E+01 -4.506135E+01 -5.177896E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624319E+02 P = 1.138997E+02 6.273778E+01 9.733940E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = 5.289586E+01 4.378008E+01 5.487411E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624319E+02 P = -1.118934E+02 -6.145651E+01 -1.004345E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = -5.490218E+01 -4.506135E+01 -5.177896E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.6701515E+02, 1.0665808E+02, 1.5241389E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.6701515E+02,-1.0665808E+02,-1.5241389E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624319E+02 P = -1.118934E+02 -6.145651E+01 -1.004345E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = -5.490218E+01 -4.506135E+01 -5.177896E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624319E+02 P = 1.138997E+02 6.273778E+01 9.733940E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = 5.289586E+01 4.378008E+01 5.487411E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624319E+02 P = -1.118934E+02 -6.145651E+01 -1.004345E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = -5.490218E+01 -4.506135E+01 -5.177896E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.6243194E+02; 1.1389972E+02, 6.2737778E+01, 9.7339402E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4967133E+02;-1.6679558E+02,-1.0651786E+02,-1.5221351E+02| 0.0000000E+00| 4) 5 prt(o:21| 8.7896734E+01; 5.2895859E+01, 4.3780084E+01, 5.4874112E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624319E+02 P = -1.118934E+02 -6.145651E+01 -1.004345E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = -5.490218E+01 -4.506135E+01 -5.177896E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245438249E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624319E+02 P = 1.138997E+02 6.273778E+01 9.733940E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = 5.289586E+01 4.378008E+01 5.487411E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624319E+02 P = -1.118934E+02 -6.145651E+01 -1.004345E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789673E+01 P = -5.490218E+01 -4.506135E+01 -5.177896E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4967133E+02; 1.6679558E+02, 1.0651786E+02, 1.5221351E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.6243194E+02;-1.1189340E+02,-6.1456514E+01,-1.0043455E+02| 0.0000000E+00| 4) 5 prt(o:21| 8.7896734E+01;-5.4902181E+01,-4.5061348E+01,-5.1778965E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 3.89002E-01 Event weight (ref) = 7.29176E+03 Event weight (prc) = 7.29176E+03 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072802E+02 P = 1.303455E+02 1.319191E+02 -9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380968E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 8.429274E+00 4.691884E+01 -1.221948E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825241768E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284389E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072802E+02 P = -1.303455E+02 -1.319191E+02 9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 1.906585E+00 -3.645820E+01 3.067716E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072802E+02 P = 1.303455E+02 1.319191E+02 -9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380968E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 8.429274E+00 4.691884E+01 -1.221948E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 3.89002E-01 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 7.29176E+03 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.5720930E+02, 1.5910720E+02,-1.1166976E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.5720930E+02,-1.5910720E+02, 1.1166976E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 1.82524E+02 Event weight (ref) = 7.29176E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072802E+02 P = 1.303455E+02 1.319191E+02 -9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380968E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 8.429274E+00 4.691884E+01 -1.221948E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825241768E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284389E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072802E+02 P = -1.303455E+02 -1.319191E+02 9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 1.906585E+00 -3.645820E+01 3.067716E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072802E+02 P = 1.303455E+02 1.319191E+02 -9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380968E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 8.429274E+00 4.691884E+01 -1.221948E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.82524E+02 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4503410E+02; 1.2843893E+02, 1.6837731E+02,-1.2326489E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.0728023E+02;-1.3034551E+02,-1.3191910E+02, 9.2587736E+01| 0.0000000E+00| 4) 5 prt(o:21| 4.7685675E+01; 1.9065855E+00,-3.6458203E+01, 3.0677157E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 1.82524E+02 Event weight (ref) = 7.29176E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072802E+02 P = 1.303455E+02 1.319191E+02 -9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380968E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 8.429274E+00 4.691884E+01 -1.221948E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825241768E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284389E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072802E+02 P = -1.303455E+02 -1.319191E+02 9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 1.906585E+00 -3.645820E+01 3.067716E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072802E+02 P = 1.303455E+02 1.319191E+02 -9.258774E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380968E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768567E+01 P = 8.429274E+00 4.691884E+01 -1.221948E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.82524E+02 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.0728023E+02; 1.3034551E+02, 1.3191910E+02,-9.2587736E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4503410E+02;-1.3877479E+02,-1.7883795E+02, 9.3809684E+01| 0.0000000E+00| 4) 5 prt(o:21| 4.7685675E+01; 8.4292744E+00, 4.6918842E+01,-1.2219477E+00| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 8.24902E-01 Event weight (ref) = 1.54626E+04 Event weight (prc) = 1.54626E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101357E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710020E+00 6.366710E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476105E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702687783E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763857E+00 -8.718461E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101357E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981896E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101357E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710020E+00 6.366710E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476105E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 8.24902E-01 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 1.54626E+04 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.2301966E+01,-2.2379372E+02, 1.0917415E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.2301966E+01, 2.2379372E+02,-1.0917415E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 4.70269E+03 Event weight (ref) = 1.54626E+04 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101357E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710020E+00 6.366710E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476105E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702687783E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763857E+00 -8.718461E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101357E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981896E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101357E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710020E+00 6.366710E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476105E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 4.70269E+03 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.0673036E+02;-9.7638567E+00,-8.7184612E+01,-6.0785523E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1013565E+02; 1.8745753E+01, 1.8810816E+02,-9.1765523E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.8313399E+02;-8.9818963E+00,-1.0092354E+02, 1.5255105E+02| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 4.70269E+03 Event weight (ref) = 1.54626E+04 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101357E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710020E+00 6.366710E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476105E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702687783E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763857E+00 -8.718461E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101357E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981896E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101357E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710020E+00 6.366710E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476105E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 4.70269E+03 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1013565E+02;-1.8745753E+01,-1.8810816E+02, 9.1765523E+01| 0.0000000E+00| 3) 4 prt(o:4| 1.0673036E+02; 1.7100197E+00, 6.3667102E+00,-1.0652657E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.8313399E+02; 1.7035733E+01, 1.8174145E+02, 1.4761047E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708634E+01 P = 2.761834E+01 5.055249E+01 -7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373976E+02 -8.535079E+01 1.490682E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479830E+01 -7.091819E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702687783E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473684E+01 2.000447E+02 -5.273244E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708634E+01 P = -2.761834E+01 -5.055249E+01 7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541761E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708634E+01 P = 2.761834E+01 5.055249E+01 -7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373976E+02 -8.535079E+01 1.490682E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479830E+01 -7.091819E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.1117985E+01, 1.3017405E+02,-2.0123854E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.1117985E+01,-1.3017405E+02, 2.0123854E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708634E+01 P = 2.761834E+01 5.055249E+01 -7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373976E+02 -8.535079E+01 1.490682E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479830E+01 -7.091819E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702687783E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473684E+01 2.000447E+02 -5.273244E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708634E+01 P = -2.761834E+01 -5.055249E+01 7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541761E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708634E+01 P = 2.761834E+01 5.055249E+01 -7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373976E+02 -8.535079E+01 1.490682E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479830E+01 -7.091819E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1996406E+02;-7.4736839E+01, 2.0004470E+02,-5.2732440E+01| 0.0000000E+00| 3) 4 prt(o:4| 9.7086339E+01;-2.7618339E+01,-5.0552489E+01, 7.8150051E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.8294960E+02; 1.0235518E+02,-1.4949221E+02,-2.5417610E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708634E+01 P = 2.761834E+01 5.055249E+01 -7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373976E+02 -8.535079E+01 1.490682E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479830E+01 -7.091819E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702687783E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473684E+01 2.000447E+02 -5.273244E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708634E+01 P = -2.761834E+01 -5.055249E+01 7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541761E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708634E+01 P = 2.761834E+01 5.055249E+01 -7.815005E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373976E+02 -8.535079E+01 1.490682E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479830E+01 -7.091819E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 9.7086339E+01; 2.7618339E+01, 5.0552489E+01,-7.8150051E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1996406E+02; 1.3739756E+02,-8.5350786E+01, 1.4906824E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.8294960E+02;-1.6501590E+02, 3.4798298E+01,-7.0918190E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.58453E-01 Event weight (ref) = 2.97017E+03 Event weight (prc) = 2.97017E+03 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544064E+01 1.134704E+02 -4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168157E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865396E+01 4.554310E+01 -4.859091E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087759033E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691045E+02 -5.336320E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544064E+01 -1.134704E+02 4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536296E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544064E+01 1.134704E+02 -4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168157E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865396E+01 4.554310E+01 -4.859091E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.58453E-01 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 2.97017E+03 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-1.3197112E+02, 1.9849802E+02,-7.5380093E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 1.3197112E+02,-1.9849802E+02, 7.5380093E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.08776E+02 Event weight (ref) = 2.97017E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544064E+01 1.134704E+02 -4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168157E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865396E+01 4.554310E+01 -4.859091E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087759033E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691045E+02 -5.336320E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544064E+01 -1.134704E+02 4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536296E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544064E+01 1.134704E+02 -4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168157E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865396E+01 4.554310E+01 -4.859091E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.08776E+02 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 0.00000E+00 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4620692E+02;-1.7080360E+02, 1.6910454E+02,-5.3363200E+01| 0.0000000E+00| 3) 4 prt(o:4| 1.4291127E+02; 7.5440645E+01,-1.1347042E+02, 4.3090660E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.1088181E+02; 9.5362959E+01,-5.5634123E+01, 1.0272540E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.08776E+02 Event weight (ref) = 2.97017E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544064E+01 1.134704E+02 -4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168157E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865396E+01 4.554310E+01 -4.859091E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087759033E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691045E+02 -5.336320E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544064E+01 -1.134704E+02 4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536296E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544064E+01 1.134704E+02 -4.309066E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168157E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865396E+01 4.554310E+01 -4.859091E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.08776E+02 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 0.00000E+00 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.4291127E+02;-7.5440645E+01, 1.1347042E+02,-4.3090660E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4620692E+02; 1.6409460E+02,-1.5901352E+02, 9.1681566E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.1088181E+02;-8.8653958E+01, 4.5543102E+01,-4.8590906E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206966E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217388E+01 6.239808E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087759033E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686717E+01 1.081329E+02 -9.603930E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016600E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206966E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217388E+01 6.239808E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 8.7439956E+00, 8.9899620E+01,-2.3311285E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-8.7439956E+00,-8.9899620E+01, 2.3311285E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206966E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217388E+01 6.239808E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087759033E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686717E+01 1.081329E+02 -9.603930E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016600E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206966E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217388E+01 6.239808E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.5540318E+02;-5.6867166E+01, 1.0813292E+02,-9.6039298E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1681660E+02;-7.5833735E+00,-7.7966919E+01, 2.0217094E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.2778022E+02; 6.4450540E+01,-3.0165996E+01,-1.0613164E+02| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206966E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217388E+01 6.239808E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087759033E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686717E+01 1.081329E+02 -9.603930E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016600E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206966E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217388E+01 6.239808E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1681660E+02; 7.5833735E+00, 7.7966919E+01,-2.0217094E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.5540318E+02; 6.7793791E+01, 4.2069661E+00, 1.3977286E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.2778022E+02;-7.5377165E+01,-8.2173885E+01, 6.2398082E+01| 0.0000000E+00| 5) ======================================================================== Total number of regions: 10 alr || flst_real || i_real || em || mul || nreg || ftuples || flst_born || i_born 1 || [ 11,-11, -4, 4, 21] || 1 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -4, 4] || 1 2 || [ 11,-11, -4, 4, 21] || 1 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -4, 4] || 1 3 || [ 11,-11, -2, 2, 21] || 2 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -2, 2] || 2 4 || [ 11,-11, -2, 2, 21] || 2 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -2, 2] || 2 5 || [ 11,-11, -5, 5, 21] || 3 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -5, 5] || 3 6 || [ 11,-11, -5, 5, 21] || 3 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -5, 5] || 3 7 || [ 11,-11, -3, 3, 21] || 4 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -3, 3] || 4 8 || [ 11,-11, -3, 3, 21] || 4 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -3, 3] || 4 9 || [ 11,-11, -1, 1, 21] || 5 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -1, 1] || 5 10 || [ 11,-11, -1, 1, 21] || 5 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -1, 1] || 5 ------------------------------------------------------------------------ Contents of nlo_7_p3.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.08358E-03 Squared matrix el. (prc) = 4.08358E-03 Event weight (ref) = 1.26569E+02 Event weight (prc) = 1.26569E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.08358E-03 sqme_ref* => 4.08358E-03 event_index* => 1 event_weight* => 1.26569E+02 event_weight_ref* => 1.26569E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 9.8408256E+01, 1.8165098E+02, 1.4077903E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-9.8408256E+01,-1.8165098E+02,-1.4077903E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.22190E-03 Squared matrix el. (prc) = 4.22190E-03 Event weight (ref) = 1.30782E+02 Event weight (prc) = 1.30782E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 6 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 6 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.22190E-03 sqme_ref* => 4.22190E-03 event_index* => 2 event_weight* => 1.30782E+02 event_weight_ref* => 1.30782E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.1286322E+02, 9.7428599E+01,-8.7732069E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.1286322E+02,-9.7428599E+01, 8.7732069E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 3 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 5.9262301E+01, 1.1991279E+02,-2.1120820E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-5.9262301E+01,-1.1991279E+02, 2.1120820E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 12 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 12 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-8.6412667E+01, 1.6275399E+02,-1.6894966E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 8.6412667E+01,-1.6275399E+02, 1.6894966E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.25951E-03 Squared matrix el. (prc) = 4.25951E-03 Event weight (ref) = 1.31947E+02 Event weight (prc) = 1.31947E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 15 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 15 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.25951E-03 sqme_ref* => 4.25951E-03 event_index* => 5 event_weight* => 1.31947E+02 event_weight_ref* => 1.31947E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 2.0159526E+02, 1.3452992E+02,-6.1327417E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-2.0159526E+02,-1.3452992E+02, 6.1327417E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-4.8740427E+00,-1.0688732E+02, 2.2594544E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 4.8740427E+00, 1.0688732E+02,-2.2594544E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 21 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 21 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.4549469E+01,-1.1200036E+02,-2.2215590E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.4549469E+01, 1.1200036E+02, 2.2215590E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.20249E-03 Squared matrix el. (prc) = 4.20249E-03 Event weight (ref) = 1.30180E+02 Event weight (prc) = 1.30180E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 24 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 24 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.20249E-03 sqme_ref* => 4.20249E-03 event_index* => 8 event_weight* => 1.30180E+02 event_weight_ref* => 1.30180E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-4.5418669E+01, 2.2544353E+02,-9.8042649E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 4.5418669E+01,-2.2544353E+02, 9.8042649E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.22672E-03 Squared matrix el. (prc) = 4.22672E-03 Event weight (ref) = 1.31006E+02 Event weight (prc) = 1.31006E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.22672E-03 sqme_ref* => 4.22672E-03 event_index* => 9 event_weight* => 1.31006E+02 event_weight_ref* => 1.31006E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.6634004E+02, 1.6619702E+02, 8.4909020E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.6634004E+02,-1.6619702E+02,-8.4909020E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.29218E-03 Squared matrix el. (prc) = 4.29218E-03 Event weight (ref) = 1.32959E+02 Event weight (prc) = 1.32959E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 30 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 30 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.29218E-03 sqme_ref* => 4.29218E-03 event_index* => 10 event_weight* => 1.32959E+02 event_weight_ref* => 1.32959E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-7.3495680E+01, 2.3878223E+02, 9.0240776E+00| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 7.3495680E+01,-2.3878223E+02,-9.0240776E+00| 0.0000000E+00| 4) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-double/nlo_9.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-double/nlo_9.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-double/nlo_9.ref (revision 8760) @@ -1,4800 +1,4800 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true openmp_num_threads = 1 SM.ms => 0.00000E+00 SM.mc => 0.00000E+00 SM.mb => 0.00000E+00 SM.me => 0.00000E+00 [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) [user variable] elec = PDG(11, -11) $exclude_gauge_splittings = "t" $method = "dummy" $rng_method = "rng_stream" $integration_method = "vamp2" sqrts = 1.30000E+04 ?combined_nlo_integration = false ?use_vamp_equivalences = false seed = 3991 n_events = 2 $sample_normalization = "sigma" ?unweighted = false ?negative_weights = true ?keep_failed_events = true ?fixed_order_nlo_events = true ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false | Process library 'nlo_9_lib': recorded process 'nlo_9_p1' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3991 | Initializing integration for process nlo_9_p1: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Initialized builtin PDF CTEQ6L | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p1' | Library name = 'nlo_9_lib' | Process index = 1 | Process components: | 1: 'nlo_9_p1_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy] | 2: 'nlo_9_p1_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p1_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p1_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p1_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 4 dimensions | Integrator: Write grid header and grids to 'nlo_9_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 96 1.827E+07 7.39E+06 40.46 3.96 4.1 |-----------------------------------------------------------------------------| 1 96 1.827E+07 7.39E+06 40.46 3.96 4.1 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.827E+07 7.39E+06 40.46 0.00 4.1 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| | Starting simulation for process 'nlo_9_p1' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3992 | Events: writing to ASCII file 'nlo_9_p1.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p1.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p2' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3993 | Initializing integration for process nlo_9_p2: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p2.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p2' | Library name = 'nlo_9_lib' | Process index = 2 | Process components: | 1: 'nlo_9_p2_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p2_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [dummy], [real] | 3: 'nlo_9_p2_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p2_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p2_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 7 dimensions | Integrator: Write grid header and grids to 'nlo_9_p2.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p2.m2.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.432E+10 7.73E+09 53.98 5.40 5.0 |-----------------------------------------------------------------------------| 1 100 1.432E+10 7.73E+09 53.98 5.40 5.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.432E+10 7.73E+09 53.98 0.00 5.0 |=============================================================================| | Starting simulation for process 'nlo_9_p2' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3994 | Events: writing to ASCII file 'nlo_9_p2.debug' | Events: generating 8 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p2.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p3' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3995 | Initializing integration for process nlo_9_p3: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p3.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p3' | Library name = 'nlo_9_lib' | Process index = 3 | Process components: | 1: 'nlo_9_p3_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p3_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p3_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy], [virtual] | 4: 'nlo_9_p3_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p3_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 4 dimensions | Integrator: Write grid header and grids to 'nlo_9_p3.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p3.m3.vg2'. | VAMP2: set chain: use chained weights. 1 96 1.148E+05 9.41E+04 81.94 8.03 2.6 |-----------------------------------------------------------------------------| 1 96 1.148E+05 9.41E+04 81.94 8.03 2.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.148E+05 9.41E+04 81.94 0.00 2.6 |=============================================================================| | Starting simulation for process 'nlo_9_p3' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3996 | Events: writing to ASCII file 'nlo_9_p3.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p3.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p4' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3997 | Initializing integration for process nlo_9_p4: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p4.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p4.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p4' | Library name = 'nlo_9_lib' | Process index = 4 | Process components: | 1: 'nlo_9_p4_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p4_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p4_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p4_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p4_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p4' part 'dglap' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: Write grid header and grids to 'nlo_9_p4.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p4.m4.vg2'. | VAMP2: set chain: use chained weights. 1 100 2.155E+08 2.04E+08 94.81 9.48 2.1 |-----------------------------------------------------------------------------| 1 100 2.155E+08 2.04E+08 94.81 9.48 2.1 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.155E+08 2.04E+08 94.81 0.00 2.1 |=============================================================================| | Starting simulation for process 'nlo_9_p4' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3998 | Events: writing to ASCII file 'nlo_9_p4.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p4.debug' | There were no errors and 4 warning(s). | WHIZARD run finished. |=============================================================================| Contents of nlo_9_p1.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.70571E+04 Squared matrix el. (prc) = 3.70571E+04 Event weight (ref) = 2.59265E+07 Event weight (prc) = 2.59265E+07 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 3270494107.0, 1218490942.0, 3220277207.0, 2821320218.0, 4220147848.0, 1218259235.0, ] Beginning substream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Initial stream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 870276730.0, 1525774502.0, 3988227742.0, 3787208568.0, 2984262882.0, 2541051477.0, ] Beginning substream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Initial stream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.48247E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p1" process_num_id* => [unknown integer] sqme* => 3.70571E+04 sqme_ref* => 3.70571E+04 event_index* => 1 event_weight* => 2.59265E+07 event_weight_ref* => 2.59265E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-2|-6.8868056E+00; 0.0000000E+00, 0.0000000E+00,-6.8868056E+00| 0.0000000E+00| 3) 4 prt(i:2|-3.2641096E+02; 0.0000000E+00, 0.0000000E+00, 3.2641096E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4931132E+03; 0.0000000E+00, 0.0000000E+00, 6.4931132E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.1735890E+03; 0.0000000E+00, 0.0000000E+00,-6.1735890E+03| 0.0000000E+00| 6) 7 prt(o:11| 6.6717870E+01; 3.6985611E+01, 7.0258495E-01,-5.5523374E+01| 0.0000000E+00| 7) 8 prt(o:-11| 2.6657990E+02;-3.6985611E+01,-7.0258495E-01,-2.6400078E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 6.87216E-01 Squared matrix el. (prc) = 6.87216E-01 Event weight (ref) = 2.69210E+03 Event weight (prc) = 2.69210E+03 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 1817174340.0, 4169406181.0, 394187331.0, 860033000.0, 2212227538.0, 3653581942.0, ] Beginning substream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Initial stream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 976955966.0, 3946182281.0, 2474115998.0, 1111192673.0, 3759619853.0, 3640289132.0, ] Beginning substream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Initial stream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(1) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(1) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 2.19506E+03 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p1" process_num_id* => [unknown integer] sqme* => 6.87216E-01 sqme_ref* => 6.87216E-01 event_index* => 2 event_weight* => 2.69210E+03 event_weight_ref* => 2.69210E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-1|-3.8204346E+02; 0.0000000E+00, 0.0000000E+00,-3.8204346E+02| 0.0000000E+00| 3) 4 prt(i:1|-3.1529664E+03; 0.0000000E+00, 0.0000000E+00, 3.1529664E+03| 0.0000000E+00| 4) 5 prt(o:92| 6.1179565E+03; 0.0000000E+00, 0.0000000E+00, 6.1179565E+03| 0.0000000E+00| 5) 6 prt(o:-92| 3.3470336E+03; 0.0000000E+00, 0.0000000E+00,-3.3470336E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.1875968E+03;-8.3458144E+02, 6.3031503E+02,-1.9213944E+03| 0.0000000E+00| 7) 8 prt(o:-11| 1.3474130E+03; 8.3458144E+02,-6.3031503E+02,-8.4952849E+02| 0.0000000E+00| 8) ======================================================================== Contents of nlo_9_p2.debug: Total number of regions: 30 alr || flst_real || i_real || em || mul || nreg || ftuples || flst_born || i_born 1 || [ -4, 4, 11,-11, 21] || 1 || 0 || 1 || 1 || {(0,5)} || [ -4, 4, 11,-11] || 1 2 || [ -4, 21, 11,-11, -4] || 2 || 2 || 1 || 1 || {(2,5)} || [ -4, 4, 11,-11] || 1 3 || [ -2, 2, 11,-11, 21] || 3 || 0 || 1 || 1 || {(0,5)} || [ -2, 2, 11,-11] || 2 4 || [ -2, 21, 11,-11, -2] || 4 || 2 || 1 || 1 || {(2,5)} || [ -2, 2, 11,-11] || 2 5 || [ 2, -2, 11,-11, 21] || 5 || 0 || 1 || 1 || {(0,5)} || [ 2, -2, 11,-11] || 3 6 || [ 2, 21, 11,-11, 2] || 6 || 2 || 1 || 1 || {(2,5)} || [ 2, -2, 11,-11] || 3 7 || [ 4, -4, 11,-11, 21] || 7 || 0 || 1 || 1 || {(0,5)} || [ 4, -4, 11,-11] || 4 8 || [ 4, 21, 11,-11, 4] || 8 || 2 || 1 || 1 || {(2,5)} || [ 4, -4, 11,-11] || 4 9 || [ -5, 5, 11,-11, 21] || 9 || 0 || 1 || 1 || {(0,5)} || [ -5, 5, 11,-11] || 5 10 || [ -5, 21, 11,-11, -5] || 10 || 2 || 1 || 1 || {(2,5)} || [ -5, 5, 11,-11] || 5 11 || [ -3, 3, 11,-11, 21] || 11 || 0 || 1 || 1 || {(0,5)} || [ -3, 3, 11,-11] || 6 12 || [ -3, 21, 11,-11, -3] || 12 || 2 || 1 || 1 || {(2,5)} || [ -3, 3, 11,-11] || 6 13 || [ -1, 1, 11,-11, 21] || 13 || 0 || 1 || 1 || {(0,5)} || [ -1, 1, 11,-11] || 7 14 || [ -1, 21, 11,-11, -1] || 14 || 2 || 1 || 1 || {(2,5)} || [ -1, 1, 11,-11] || 7 15 || [ 1, -1, 11,-11, 21] || 15 || 0 || 1 || 1 || {(0,5)} || [ 1, -1, 11,-11] || 8 16 || [ 1, 21, 11,-11, 1] || 16 || 2 || 1 || 1 || {(2,5)} || [ 1, -1, 11,-11] || 8 17 || [ 3, -3, 11,-11, 21] || 17 || 0 || 1 || 1 || {(0,5)} || [ 3, -3, 11,-11] || 9 18 || [ 3, 21, 11,-11, 3] || 18 || 2 || 1 || 1 || {(2,5)} || [ 3, -3, 11,-11] || 9 19 || [ 5, -5, 11,-11, 21] || 19 || 0 || 1 || 1 || {(0,5)} || [ 5, -5, 11,-11] || 10 20 || [ 5, 21, 11,-11, 5] || 20 || 2 || 1 || 1 || {(2,5)} || [ 5, -5, 11,-11] || 10 21 || [ 21, -4, 11,-11, -4] || 21 || 1 || 1 || 1 || {(1,5)} || [ 4, -4, 11,-11] || 4 22 || [ 21, -2, 11,-11, -2] || 22 || 1 || 1 || 1 || {(1,5)} || [ 2, -2, 11,-11] || 3 23 || [ 21, 2, 11,-11, 2] || 23 || 1 || 1 || 1 || {(1,5)} || [ -2, 2, 11,-11] || 2 24 || [ 21, 4, 11,-11, 4] || 24 || 1 || 1 || 1 || {(1,5)} || [ -4, 4, 11,-11] || 1 25 || [ 21, -5, 11,-11, -5] || 25 || 1 || 1 || 1 || {(1,5)} || [ 5, -5, 11,-11] || 10 26 || [ 21, -3, 11,-11, -3] || 26 || 1 || 1 || 1 || {(1,5)} || [ 3, -3, 11,-11] || 9 27 || [ 21, -1, 11,-11, -1] || 27 || 1 || 1 || 1 || {(1,5)} || [ 1, -1, 11,-11] || 8 28 || [ 21, 1, 11,-11, 1] || 28 || 1 || 1 || 1 || {(1,5)} || [ -1, 1, 11,-11] || 7 29 || [ 21, 3, 11,-11, 3] || 29 || 1 || 1 || 1 || {(1,5)} || [ -3, 3, 11,-11] || 6 30 || [ 21, 5, 11,-11, 5] || 30 || 1 || 1 || 1 || {(1,5)} || [ -5, 5, 11,-11] || 5 ------------------------------------------------------------------------ ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30887E+06 Squared matrix el. (prc) = 7.40063E+03 Event weight (ref) = 1.00516E+09 Event weight (prc) = 8.95291E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229867199E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.30010E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 7.40063E+03 sqme_ref* => 8.30887E+06 event_index* => 1 event_weight* => 8.95291E+05 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-6.3427874E+00; 0.0000000E+00, 0.0000000E+00,-6.3427874E+00| 0.0000000E+00| 3) 4 prt(i:4|-3.4090636E+02; 0.0000000E+00, 0.0000000E+00, 3.4090636E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4936572E+03; 0.0000000E+00, 0.0000000E+00, 6.4936572E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.1590936E+03; 0.0000000E+00, 0.0000000E+00,-6.1590936E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.5798314E+01; 1.2978902E+01,-2.2934559E+01,-2.4229598E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1145084E+02;-1.2978902E+01, 2.2934559E+01,-3.1033398E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30887E+06 Squared matrix el. (prc) = 2.16231E+05 Event weight (ref) = 1.00516E+09 Event weight (prc) = 2.61585E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229867199E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 2.16231E+05 sqme_ref* => 8.30887E+06 event_index* => 1 event_weight* => 2.61585E+07 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-1|-6.3910149E+00; 0.0000000E+00, 0.0000000E+00,-6.3910149E+00| 0.0000000E+00| 3) 4 prt(i:1|-4.3483016E+02; 0.0000000E+00, 0.0000000E+00, 4.3483016E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.0651698E+03; 0.0000000E+00, 0.0000000E+00,-6.0651698E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393842E+01; 1.1353672E+01,-2.4091465E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600055E+01, 2.1780554E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:21| 9.3653407E+01; 3.2463826E+00, 2.3109106E+00,-9.3568591E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30887E+06 Squared matrix el. (prc) = 1.85537E+06 Event weight (ref) = 1.00516E+09 Event weight (prc) = 2.24453E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229867199E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 1.85537E+06 sqme_ref* => 8.30887E+06 event_index* => 1 event_weight* => 2.24453E+08 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:1|-6.3910149E+00; 0.0000000E+00, 0.0000000E+00,-6.3910149E+00| 0.0000000E+00| 3) 4 prt(i:21|-4.3483016E+02; 0.0000000E+00, 0.0000000E+00, 4.3483016E+02| 0.0000000E+00| 4) 5 prt(o:-92| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:93| 6.0651698E+03; 0.0000000E+00, 0.0000000E+00,-6.0651698E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393842E+01; 1.1353672E+01,-2.4091465E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600055E+01, 2.1780554E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:1| 9.3653407E+01; 3.2463826E+00, 2.3109106E+00,-9.3568591E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30887E+06 Squared matrix el. (prc) = 6.22987E+06 Event weight (ref) = 1.00516E+09 Event weight (prc) = 7.53658E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229867199E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348302E+02 P = 0.000000E+00 0.000000E+00 -4.348302E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178055E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365341E+01 P = 3.246383E+00 2.310911E+00 -9.356859E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.22987E+06 sqme_ref* => 8.30887E+06 event_index* => 1 event_weight* => 7.53658E+08 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:21|-6.3910149E+00; 0.0000000E+00, 0.0000000E+00,-6.3910149E+00| 0.0000000E+00| 3) 4 prt(i:2|-4.3483016E+02; 0.0000000E+00, 0.0000000E+00, 4.3483016E+02| 0.0000000E+00| 4) 5 prt(o:93| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.0651698E+03; 0.0000000E+00, 0.0000000E+00,-6.0651698E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393842E+01; 1.1353672E+01,-2.4091465E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600055E+01, 2.1780554E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:2| 9.3653407E+01; 3.2463826E+00, 2.3109106E+00,-9.3568591E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88562E+06 Squared matrix el. (prc) = -7.22694E+03 Event weight (ref) = 3.07002E+08 Event weight (prc) = -2.81358E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865080099E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.11989E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => -7.22694E+03 sqme_ref* => 7.88562E+06 event_index* => 2 event_weight* => -2.81358E+05 event_weight_ref* => 3.07002E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-1.0203303E+03; 0.0000000E+00, 0.0000000E+00,-1.0203303E+03| 0.0000000E+00| 3) 4 prt(i:4|-2.0378805E+00; 0.0000000E+00, 0.0000000E+00, 2.0378805E+00| 0.0000000E+00| 4) 5 prt(o:92| 5.4796697E+03; 0.0000000E+00, 0.0000000E+00, 5.4796697E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4979621E+03; 0.0000000E+00, 0.0000000E+00,-6.4979621E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.8155129E+02;-2.0762780E+01, 3.5003646E+01, 2.7859430E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4081694E+02; 2.0762780E+01,-3.5003646E+01, 7.3969817E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88562E+06 Squared matrix el. (prc) = 2.23961E+05 Event weight (ref) = 3.07002E+08 Event weight (prc) = 8.71920E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865080099E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 2.23961E+05 sqme_ref* => 7.88562E+06 event_index* => 2 event_weight* => 8.71920E+06 event_weight_ref* => 3.07002E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:2|-1.0761180E+03; 0.0000000E+00, 0.0000000E+00,-1.0761180E+03| 0.0000000E+00| 3) 4 prt(i:-2|-2.1012440E+00; 0.0000000E+00, 0.0000000E+00, 2.1012440E+00| 0.0000000E+00| 4) 5 prt(o:-92| 5.4238820E+03; 0.0000000E+00, 0.0000000E+00, 5.4238820E+03| 0.0000000E+00| 5) 6 prt(o:92| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797003E+02;-2.2099735E+01, 3.3747852E+01, 2.7502731E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523149E+02; 1.9415332E+01,-3.6269296E+01, 7.4409513E+02| 0.0000000E+00| 8) 9 prt(o:21| 5.5017737E+01; 2.6844031E+00, 2.5214442E+00, 5.4894332E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88562E+06 Squared matrix el. (prc) = 6.98238E+06 Event weight (ref) = 3.07002E+08 Event weight (prc) = 2.71837E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865080099E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.98238E+06 sqme_ref* => 7.88562E+06 event_index* => 2 event_weight* => 2.71837E+08 event_weight_ref* => 3.07002E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:1|-1.0761180E+03; 0.0000000E+00, 0.0000000E+00,-1.0761180E+03| 0.0000000E+00| 3) 4 prt(i:21|-2.1012440E+00; 0.0000000E+00, 0.0000000E+00, 2.1012440E+00| 0.0000000E+00| 4) 5 prt(o:-92| 5.4238820E+03; 0.0000000E+00, 0.0000000E+00, 5.4238820E+03| 0.0000000E+00| 5) 6 prt(o:93| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797003E+02;-2.2099735E+01, 3.3747852E+01, 2.7502731E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523149E+02; 1.9415332E+01,-3.6269296E+01, 7.4409513E+02| 0.0000000E+00| 8) 9 prt(o:1| 5.5017737E+01; 2.6844031E+00, 2.5214442E+00, 5.4894332E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88562E+06 Squared matrix el. (prc) = 6.86508E+05 Event weight (ref) = 3.07002E+08 Event weight (prc) = 2.67270E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865080099E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209974E+01 3.374785E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941533E+01 -3.626930E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501774E+01 P = 2.684403E+00 2.521444E+00 5.489433E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.86508E+05 sqme_ref* => 7.88562E+06 event_index* => 2 event_weight* => 2.67270E+07 event_weight_ref* => 3.07002E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:21|-1.0761180E+03; 0.0000000E+00, 0.0000000E+00,-1.0761180E+03| 0.0000000E+00| 3) 4 prt(i:-1|-2.1012440E+00; 0.0000000E+00, 0.0000000E+00, 2.1012440E+00| 0.0000000E+00| 4) 5 prt(o:93| 5.4238820E+03; 0.0000000E+00, 0.0000000E+00, 5.4238820E+03| 0.0000000E+00| 5) 6 prt(o:92| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797003E+02;-2.2099735E+01, 3.3747852E+01, 2.7502731E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523149E+02; 1.9415332E+01,-3.6269296E+01, 7.4409513E+02| 0.0000000E+00| 8) 9 prt(o:-1| 5.5017737E+01; 2.6844031E+00, 2.5214442E+00, 5.4894332E+01| 0.0000000E+00| 9) ======================================================================== Contents of nlo_9_p3.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.12930E+01 Squared matrix el. (prc) = 2.12930E+01 Event weight (ref) = 6.36286E+03 Event weight (prc) = 6.36286E+03 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 6 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 2596865362.0, 2097861302.0, 1710419373.0, 4132755378.0, 3334395289.0, 3898036172.0, ] Beginning substream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Initial stream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-2) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 2690940837.0, 944023296.0, 3856628408.0, 3483223282.0, 1004971824.0, 2058251242.0, ] Beginning substream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Initial stream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.44812E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p3" process_num_id* => [unknown integer] sqme* => 2.12930E+01 sqme_ref* => 2.12930E+01 event_index* => 1 event_weight* => 6.36286E+03 event_weight_ref* => 6.36286E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-2.1850027E+03; 0.0000000E+00, 0.0000000E+00,-2.1850027E+03| 0.0000000E+00| 3) 4 prt(i:4|-1.0213593E+00; 0.0000000E+00, 0.0000000E+00, 1.0213593E+00| 0.0000000E+00| 4) 5 prt(o:92| 4.3149973E+03; 0.0000000E+00, 0.0000000E+00, 4.3149973E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4989786E+03; 0.0000000E+00, 0.0000000E+00,-6.4989786E+03| 0.0000000E+00| 6) 7 prt(o:11| 1.9276312E+03; 2.5248333E+01,-1.7044627E+01, 1.9273905E+03| 0.0000000E+00| 7) 8 prt(o:-11| 2.5839283E+02;-2.5248333E+01, 1.7044627E+01, 2.5659084E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.24170E+01 Squared matrix el. (prc) = 4.24170E+01 Event weight (ref) = 1.65951E+03 Event weight (prc) = 1.65951E+03 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 6 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 1150698303.0, 3394442877.0, 1602037449.0, 443345876.0, 714281248.0, 3904759980.0, ] Beginning substream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Initial stream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 845567059.0, 1878523320.0, 621290442.0, 2282089536.0, 2749647619.0, 2527962339.0, ] Beginning substream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Initial stream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.09908E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p3" process_num_id* => [unknown integer] sqme* => 4.24170E+01 sqme_ref* => 4.24170E+01 event_index* => 2 event_weight* => 1.65951E+03 event_weight_ref* => 1.65951E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-5.4466623E+01; 0.0000000E+00, 0.0000000E+00,-5.4466623E+01| 0.0000000E+00| 3) 4 prt(i:4|-3.8001808E+01; 0.0000000E+00, 0.0000000E+00, 3.8001808E+01| 0.0000000E+00| 4) 5 prt(o:92| 6.4455334E+03; 0.0000000E+00, 0.0000000E+00, 6.4455334E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4619982E+03; 0.0000000E+00, 0.0000000E+00,-6.4619982E+03| 0.0000000E+00| 6) 7 prt(o:11| 5.1146524E+01;-2.4957136E+01,-2.6645778E+01, 3.5820536E+01| 0.0000000E+00| 7) 8 prt(o:-11| 4.1321907E+01; 2.4957136E+01, 2.6645778E+01,-1.9355720E+01| 0.0000000E+00| 8) ======================================================================== Contents of nlo_9_p4.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.05161E-13 Squared matrix el. (prc) = 1.05161E-13 Event weight (ref) = 7.75946E-13 Event weight (prc) = 7.75946E-13 ------------------------------------------------------------------------ Selected MCI group = 4 Selected term = 7 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 112567446.0, 2537546482.0, 955490456.0, 493528515.0, 744046788.0, 3090452419.0, ] Beginning substream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Initial stream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 1453789347.0, 653147693.0, 3790828741.0, 3331230639.0, 15326295.0, 3964323346.0, ] Beginning substream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Initial stream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.25213E+04 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p4" process_num_id* => [unknown integer] sqme* => 1.05161E-13 sqme_ref* => 1.05161E-13 event_index* => 1 event_weight* => 7.75946E-13 event_weight_ref* => 7.75946E-13 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-6.2455844E+03; 0.0000000E+00, 0.0000000E+00,-6.2455844E+03| 0.0000000E+00| 3) 4 prt(i:4|-6.2757411E+03; 0.0000000E+00, 0.0000000E+00, 6.2757411E+03| 0.0000000E+00| 4) 5 prt(o:92| 2.5441558E+02; 0.0000000E+00, 0.0000000E+00, 2.5441558E+02| 0.0000000E+00| 5) 6 prt(o:-92| 2.2425890E+02; 0.0000000E+00, 0.0000000E+00,-2.2425890E+02| 0.0000000E+00| 6) 7 prt(o:11| 6.2672848E+03;-1.9090987E+02, 5.6213367E+03,-2.7645949E+03| 0.0000000E+00| 7) 8 prt(o:-11| 6.2540408E+03; 1.9090987E+02,-5.6213367E+03, 2.7344382E+03| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.58498E-02 Squared matrix el. (prc) = 7.58498E-02 Event weight (ref) = 7.08197E+01 Event weight (prc) = 7.08197E+01 ------------------------------------------------------------------------ Selected MCI group = 4 Selected term = 7 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 2964943828.0, 3006961225.0, 2205962508.0, 235002314.0, 4260252546.0, 4030348999.0, ] Beginning substream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Initial stream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-2) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 2927356149.0, 2992177383.0, 3989844751.0, 720065746.0, 2244661502.0, 4119271164.0, ] Beginning substream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Initial stream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 3.47756E+03 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p4" process_num_id* => [unknown integer] sqme* => 7.58498E-02 sqme_ref* => 7.58498E-02 event_index* => 2 event_weight* => 7.08197E+01 event_weight_ref* => 7.08197E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-2.6130095E+03; 0.0000000E+00, 0.0000000E+00,-2.6130095E+03| 0.0000000E+00| 3) 4 prt(i:4|-1.1570394E+03; 0.0000000E+00, 0.0000000E+00, 1.1570394E+03| 0.0000000E+00| 4) 5 prt(o:92| 3.8869905E+03; 0.0000000E+00, 0.0000000E+00, 3.8869905E+03| 0.0000000E+00| 5) 6 prt(o:-92| 5.3429606E+03; 0.0000000E+00, 0.0000000E+00,-5.3429606E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.5040593E+03; 7.8357558E+02, 4.7248514E+02, 2.3308968E+03| 0.0000000E+00| 7) 8 prt(o:-11| 1.2659896E+03;-7.8357558E+02,-4.7248514E+02,-8.7492676E+02| 0.0000000E+00| 8) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-quad/openloops_3.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-quad/openloops_3.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-quad/openloops_3.ref (revision 8760) @@ -1,1186 +1,1186 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true $method = "openloops" openmp_num_threads = 1 ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true seed = 2222 sqrts = 5.00000E+02 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false ?fixed_order_nlo_events = true ?negative_weights = true ?unweighted = false SM.mtop => 1.73200E+02 SM.wtop => 0.00000E+00 | Process library 'openloops_3_lib': recorded process 'openloops_3_p1' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2222 | Initializing integration for process openloops_3_p1: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p1' | Library name = 'openloops_3_lib' | Process index = 1 | Process components: | 1: 'openloops_3_p1_i1': e+, e- => t, tbar [openloops] | 2: 'openloops_3_p1_i2': e+, e- => t, tbar, gl [inactive], [real] | 3: 'openloops_3_p1_i3': e+, e- => t, tbar [inactive], [virtual] | 4: 'openloops_3_p1_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 6.257E+02 2.89E+01 4.61 0.46 55.5 |-----------------------------------------------------------------------------| 1 100 6.257E+02 2.89E+01 4.61 0.46 55.5 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 6.257E+02 2.89E+01 4.61 0.00 55.5 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p1' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p1.m1.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2223 | Events: writing to ASCII file 'openloops_3_p1.debug' | Events: generating 1 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p1.debug' seed = 3333 | Process library 'openloops_3_lib': unloading | Process library 'openloops_3_lib': open | Process library 'openloops_3_lib': recorded process 'openloops_3_p2' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 3333 | Initializing integration for process openloops_3_p2: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p2.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p2' | Library name = 'openloops_3_lib' | Process index = 2 | Process components: | 1: 'openloops_3_p2_i1': e+, e- => t, tbar [inactive] | 2: 'openloops_3_p2_i2': e+, e- => t, tbar, gl [openloops], [real] | 3: 'openloops_3_p2_i3': e+, e- => t, tbar [inactive], [virtual] | 4: 'openloops_3_p2_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -7.301E+01 4.28E+00 5.86 0.59 39.2 |-----------------------------------------------------------------------------| 1 100 -7.301E+01 4.28E+00 5.86 0.59 39.2 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 -7.301E+01 4.28E+00 5.86 0.00 0.0 |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p2' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p2.m2.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 3334 | Events: writing to ASCII file 'openloops_3_p2.debug' | Events: generating 3 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p2.debug' seed = 4444 | Process library 'openloops_3_lib': unloading | Process library 'openloops_3_lib': open | Process library 'openloops_3_lib': recorded process 'openloops_3_p3' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 4444 | Initializing integration for process openloops_3_p3: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p3.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p3' | Library name = 'openloops_3_lib' | Process index = 3 | Process components: | 1: 'openloops_3_p3_i1': e+, e- => t, tbar [inactive] | 2: 'openloops_3_p3_i2': e+, e- => t, tbar, gl [inactive], [real] | 3: 'openloops_3_p3_i3': e+, e- => t, tbar [openloops], [virtual] | 4: 'openloops_3_p3_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.387E+02 7.85E+00 5.66 0.57 44.8 |-----------------------------------------------------------------------------| 1 100 1.387E+02 7.85E+00 5.66 0.57 44.8 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.387E+02 7.85E+00 5.66 0.00 44.8 |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p3' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p3.m3.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 4445 | Events: writing to ASCII file 'openloops_3_p3.debug' | Events: generating 1 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p3.debug' | There were no errors and 3 warning(s). | WHIZARD run finished. |=============================================================================| ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.66014E-02 Squared matrix el. (prc) = 2.66014E-02 Event weight (ref) = 5.94404E+02 Event weight (prc) = 5.94404E+02 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p1' TAO random-number generator: seed = 145620996 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p1' TAO random-number generator: seed = 145620997 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p1" process_num_id* => [unknown integer] sqme* => 2.66014E-02 sqme_ref* => 2.66014E-02 event_index* => 1 event_weight* => 5.94404E+02 event_weight_ref* => 5.94404E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02;-3.0933754E+01, 1.7292509E+02,-4.0518856E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02; 3.0933754E+01,-1.7292509E+02, 4.0518856E+01| 2.9998240E+04| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = -5.17360E-03 Event weight (ref) = -9.77307E+01 Event weight (prc) = -1.15603E+02 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034761904E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888583E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = 7.697588E+01 4.999534E+01 9.008653E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => -5.17360E-03 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => -1.15603E+02 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02; 1.6597780E+02, 4.6491044E+01,-5.2836666E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02;-1.6597780E+02,-4.6491044E+01, 5.2836666E+01| 2.9998240E+04| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = 4.96367E-04 Event weight (ref) = -9.77307E+01 Event weight (prc) = 1.10912E+01 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034761904E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888583E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = 7.697588E+01 4.999534E+01 9.008653E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => 4.96367E-04 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => 1.10912E+01 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 1.8711951E+02; 4.8885826E+01,-1.4740977E+01,-4.9074934E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.2065264E+02;-1.2586171E+02,-3.5254367E+01, 4.0066281E+01| 2.9998240E+04| 4) 5 prt(o:21| 9.2227854E+01; 7.6975885E+01, 4.9995344E+01, 9.0086533E+00| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = 3.03476E-04 Event weight (ref) = -9.77307E+01 Event weight (prc) = 6.78112E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034761904E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888583E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = 7.697588E+01 4.999534E+01 9.008653E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => 3.03476E-04 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => 6.78112E+00 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.2065264E+02; 1.2586171E+02, 3.5254367E+01,-4.0066281E+01| 2.9998240E+04| 3) 4 prt(o:-6| 1.8711951E+02;-6.8239543E+01, 9.3199232E+00,-1.6491614E+01| 2.9998240E+04| 4) 5 prt(o:21| 9.2227854E+01;-5.7622167E+01,-4.4574291E+01, 5.6557895E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.22409E-02 Squared matrix el. (prc) = 1.22409E-02 Event weight (ref) = 2.73522E+02 Event weight (prc) = 2.73522E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p3' TAO random-number generator: seed = 291241988 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p3' TAO random-number generator: seed = 291241989 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p3" process_num_id* => [unknown integer] sqme* => 1.22409E-02 sqme_ref* => 1.22409E-02 event_index* => 1 event_weight* => 2.73522E+02 event_weight_ref* => 2.73522E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02;-9.6029292E+01, 1.9046186E+01,-1.5138487E+02| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02; 9.6029292E+01,-1.9046186E+01, 1.5138487E+02| 2.9998240E+04| 4) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-quad/nlo_7.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-quad/nlo_7.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-quad/nlo_7.ref (revision 8760) @@ -1,8792 +1,8792 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true openmp_num_threads = 1 SM.ms => 0.00000E+00 SM.mc => 0.00000E+00 SM.mb => 0.00000E+00 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $method = "dummy" ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true sqrts = 5.00000E+02 jet_algorithm = 2 jet_r = 5.00000E-01 seed = 1558 n_events = 10 $sample_normalization = "sigma" ?unweighted = false ?negative_weights = true ?keep_failed_events = true ?fixed_order_nlo_events = true ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false | Process library 'nlo_7_lib': recorded process 'nlo_7_p1' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1558 | Initializing integration for process nlo_7_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p1' | Library name = 'nlo_7_lib' | Process index = 1 | Process components: | 1: 'nlo_7_p1_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [dummy] | 2: 'nlo_7_p1_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_7_p1_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [virtual] | 4: 'nlo_7_p1_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.054E+05 7.27E+03 6.90 0.69 68.0 |-----------------------------------------------------------------------------| 1 100 1.054E+05 7.27E+03 6.90 0.69 68.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.054E+05 7.27E+03 6.90 0.00 68.0 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| | Starting simulation for process 'nlo_7_p1' | Simulate: using integration grids from file 'nlo_7_p1.m1.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1559 | Events: writing to ASCII file 'nlo_7_p1.debug' | Events: generating 10 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p1.debug' | Process library 'nlo_7_lib': unloading | Process library 'nlo_7_lib': open | Process library 'nlo_7_lib': recorded process 'nlo_7_p2' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1560 | Initializing integration for process nlo_7_p2: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p2.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p2' | Library name = 'nlo_7_lib' | Process index = 2 | Process components: | 1: 'nlo_7_p2_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive] | 2: 'nlo_7_p2_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [dummy], [real] | 3: 'nlo_7_p2_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [virtual] | 4: 'nlo_7_p2_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.817E+07 6.57E+06 36.18 3.62 5.2 |-----------------------------------------------------------------------------| 1 100 1.817E+07 6.57E+06 36.18 3.62 5.2 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.817E+07 6.57E+06 36.18 0.00 5.2 |=============================================================================| | Starting simulation for process 'nlo_7_p2' | Simulate: using integration grids from file 'nlo_7_p2.m2.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1561 | Events: writing to ASCII file 'nlo_7_p2.debug' | Events: generating 30 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p2.debug' | Process library 'nlo_7_lib': unloading | Process library 'nlo_7_lib': open | Process library 'nlo_7_lib': recorded process 'nlo_7_p3' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1562 | Initializing integration for process nlo_7_p3: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p3.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p3' | Library name = 'nlo_7_lib' | Process index = 3 | Process components: | 1: 'nlo_7_p3_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive] | 2: 'nlo_7_p3_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_7_p3_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [dummy], [virtual] | 4: 'nlo_7_p3_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 7.843E+01 6.45E+00 8.22 0.82 59.0 |-----------------------------------------------------------------------------| 1 100 7.843E+01 6.45E+00 8.22 0.82 59.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 7.843E+01 6.45E+00 8.22 0.00 59.0 |=============================================================================| | Starting simulation for process 'nlo_7_p3' | Simulate: using integration grids from file 'nlo_7_p3.m3.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1563 | Events: writing to ASCII file 'nlo_7_p3.debug' | Events: generating 10 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p3.debug' | WHIZARD run finished. |=============================================================================| Contents of nlo_7_p1.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 1 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.5000000E+02; 2.3030328E+02, 2.0093120E+01,-9.5166522E+01| 0.0000000E+00| 3) 4 prt(o:2| 2.5000000E+02;-2.3030328E+02,-2.0093120E+01, 9.5166522E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 6 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 6 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 2 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-2.1900152E+02,-1.6025552E+01,-1.1950530E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 2.1900152E+02, 1.6025552E+01, 1.1950530E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 3 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-5| 2.5000000E+02; 1.1488797E+02,-1.0151895E+02,-1.9747065E+02| 0.0000000E+00| 3) 4 prt(o:5| 2.5000000E+02;-1.1488797E+02, 1.0151895E+02, 1.9747065E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 12 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 12 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-8.0922467E+01, 7.8108474E+01,-2.2327253E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 8.0922467E+01,-7.8108474E+01, 2.2327253E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 15 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 15 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 5 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.5000000E+02; 2.1721823E+02, 6.8664192E+01, 1.0296343E+02| 0.0000000E+00| 3) 4 prt(o:2| 2.5000000E+02;-2.1721823E+02,-6.8664192E+01,-1.0296343E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 6 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-1.7188357E+02,-1.4357975E+02, 1.1108958E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 1.7188357E+02, 1.4357975E+02,-1.1108958E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 21 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 21 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 7 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.8588362E+02, 1.5153486E+02, 7.0600756E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.8588362E+02,-1.5153486E+02,-7.0600756E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 24 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 24 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 8 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-1.3809822E+02,-1.9874706E+02, 6.2677654E+01| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 1.3809822E+02, 1.9874706E+02,-6.2677654E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 9 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-3| 2.5000000E+02;-2.2331587E+02,-3.6246582E+01, 1.0637766E+02| 0.0000000E+00| 3) 4 prt(o:3| 2.5000000E+02; 2.2331587E+02, 3.6246582E+01,-1.0637766E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 30 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 30 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 10 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-5| 2.5000000E+02; 7.6696234E+01, 1.9465831E+02, 1.3684236E+02| 0.0000000E+00| 3) 4 prt(o:5| 2.5000000E+02;-7.6696234E+01,-1.9465831E+02,-1.3684236E+02| 0.0000000E+00| 4) ======================================================================== Contents of nlo_7_p2.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.43649E+00 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.69268E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358864E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104539E+01 P = -8.581748E+00 2.829877E+01 9.452491E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608388E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.43649E+00 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.69268E+04 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.7405031E+01, 2.2771282E+02,-6.8229998E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.7405031E+01,-2.2771282E+02, 6.8229998E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.34436E+03 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.51997E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358864E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104539E+01 P = -8.581748E+00 2.829877E+01 9.452491E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608388E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34436E+03 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.51997E+07 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 3.1045389E+01;-8.5817480E+00, 2.8298767E+01, 9.4524908E+00| 0.0000000E+00| 3) 4 prt(o:2| 2.4414255E+02;-7.5591448E+01,-2.2237756E+02, 6.6631385E+01| 0.0000000E+00| 4) 5 prt(o:21| 2.2481206E+02; 8.4173196E+01, 1.9407879E+02,-7.6083875E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.34436E+03 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.51997E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358864E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104539E+01 P = -8.581748E+00 2.829877E+01 9.452491E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608388E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34436E+03 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.51997E+07 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4414255E+02; 7.5591448E+01, 2.2237756E+02,-6.6631385E+01| 0.0000000E+00| 3) 4 prt(o:4| 3.1045389E+01; 1.1331410E+01,-2.0209717E+01, 2.0663560E+01| 0.0000000E+00| 4) 5 prt(o:21| 2.2481206E+02;-8.6922858E+01,-2.0216784E+02, 4.5967825E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 2.04961E+00 Event weight (ref) = 1.22098E+08 Event weight (prc) = 1.83043E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365136458E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534399E+00 -6.315655E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = -1.140192E+01 2.199270E+01 -4.000800E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 2.04961E+00 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 1.83043E+05 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.2470250E+02, 2.0311083E+01,-1.0768586E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.2470250E+02,-2.0311083E+01, 1.0768586E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 1.36514E+03 Event weight (ref) = 1.22098E+08 Event weight (prc) = 1.21915E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365136458E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534399E+00 -6.315655E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = -1.140192E+01 2.199270E+01 -4.000800E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.36514E+03 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 1.21915E+08 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.1343993E+02;-2.0386621E+02,-2.5343987E+00,-6.3156555E+01| 0.0000000E+00| 3) 4 prt(o:2| 2.3950348E+02; 2.1526813E+02,-1.9458300E+01, 1.0316455E+02| 0.0000000E+00| 4) 5 prt(o:21| 4.7056589E+01;-1.1401918E+01, 2.1992698E+01,-4.0008000E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 1.36514E+03 Event weight (ref) = 1.22098E+08 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365136458E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534399E+00 -6.315655E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = -1.140192E+01 2.199270E+01 -4.000800E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.36514E+03 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 0.00000E+00 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.3950348E+02;-2.1526813E+02, 1.9458300E+01,-1.0316455E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.1343993E+02; 1.7781593E+02, 4.8891091E+00, 1.1795845E+02| 0.0000000E+00| 4) 5 prt(o:21| 4.7056589E+01; 3.7452196E+01,-2.4347409E+01,-1.4793894E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50428E+02 Squared matrix el. (prc) = 1.34286E+00 Event weight (ref) = 4.69422E+06 Event weight (prc) = 2.51716E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636844E+01 -2.180363E+02 -8.844250E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161621E+01 2.197846E+02 8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = -4.752234E+00 -1.748261E+00 -1.660102E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34286E+00 sqme_ref* => 2.50428E+02 event_index* => 3 event_weight* => 2.51716E+04 event_weight_ref* => 4.69422E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.2322269E+01,-2.2195145E+02,-8.9482095E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.2322269E+01, 2.2195145E+02, 8.9482095E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50428E+02 Squared matrix el. (prc) = 1.24543E+02 Event weight (ref) = 4.69422E+06 Event weight (prc) = 2.33452E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636844E+01 -2.180363E+02 -8.844250E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161621E+01 2.197846E+02 8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = -4.752234E+00 -1.748261E+00 -1.660102E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.24543E+02 sqme_ref* => 2.50428E+02 event_index* => 3 event_weight* => 2.33452E+06 event_weight_ref* => 4.69422E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4737434E+02; 7.6368444E+01,-2.1803635E+02,-8.8442500E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4755933E+02;-7.1616210E+01, 2.1978461E+02, 8.8608510E+01| 0.0000000E+00| 4) 5 prt(o:21| 5.0663301E+00;-4.7522336E+00,-1.7482610E+00,-1.6601020E-01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50428E+02 Squared matrix el. (prc) = 1.24543E+02 Event weight (ref) = 4.69422E+06 Event weight (prc) = 2.33452E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636844E+01 -2.180363E+02 -8.844250E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161621E+01 2.197846E+02 8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = -4.752234E+00 -1.748261E+00 -1.660102E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.24543E+02 sqme_ref* => 2.50428E+02 event_index* => 3 event_weight* => 2.33452E+06 event_weight_ref* => 4.69422E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4755933E+02; 7.1616210E+01,-2.1978461E+02,-8.8608510E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4737434E+02;-7.6349142E+01, 2.1797711E+02, 8.8605029E+01| 0.0000000E+00| 4) 5 prt(o:21| 5.0663301E+00; 4.7329317E+00, 1.8074970E+00, 3.4808790E-03| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746688E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -2.435277E+01 -1.603512E+01 9.468480E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.3221583E+02,-2.5714252E+00, 2.1216117E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.3221583E+02, 2.5714252E+00,-2.1216117E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746688E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -2.435277E+01 -1.603512E+01 9.468480E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.7450549E+02; 1.4409898E+02, 1.3706217E+01, 9.7466877E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.2642183E+02;-1.1974620E+02, 2.3289073E+00,-1.9215168E+02| 0.0000000E+00| 4) 5 prt(o:21| 9.9072675E+01;-2.4352772E+01,-1.6035124E+01, 9.4684805E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746688E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -2.435277E+01 -1.603512E+01 9.468480E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.2642183E+02; 1.1974620E+02,-2.3289073E+00, 1.9215168E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.7450549E+02;-2.4491339E+01,-1.6032429E+01,-1.7203285E+02| 0.0000000E+00| 4) 5 prt(o:21| 9.9072675E+01;-9.5254864E+01, 1.8361336E+01,-2.0118828E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624320E+02 P = 1.138997E+02 6.273779E+01 9.733942E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = 5.289584E+01 4.378007E+01 5.487409E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.6701515E+02, 1.0665808E+02, 1.5241389E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.6701515E+02,-1.0665808E+02,-1.5241389E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624320E+02 P = 1.138997E+02 6.273779E+01 9.733942E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = 5.289584E+01 4.378007E+01 5.487409E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.6243197E+02; 1.1389974E+02, 6.2737795E+01, 9.7339424E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4967133E+02;-1.6679558E+02,-1.0651786E+02,-1.5221351E+02| 0.0000000E+00| 4) 5 prt(o:21| 8.7896698E+01; 5.2895836E+01, 4.3780068E+01, 5.4874089E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425039E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624320E+02 P = 1.138997E+02 6.273779E+01 9.733942E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = 5.289584E+01 4.378007E+01 5.487409E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4967133E+02; 1.6679558E+02, 1.0651786E+02, 1.5221351E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.6243197E+02;-1.1189342E+02,-6.1456531E+01,-1.0043457E+02| 0.0000000E+00| 4) 5 prt(o:21| 8.7896698E+01;-5.4902158E+01,-4.5061332E+01,-5.1778943E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 3.89002E-01 Event weight (ref) = 7.29176E+03 Event weight (prc) = 7.29176E+03 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825239682E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284390E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072803E+02 P = -1.303455E+02 -1.319191E+02 9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 1.906577E+00 -3.645817E+01 3.067713E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 3.89002E-01 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 7.29176E+03 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.5720930E+02, 1.5910720E+02,-1.1166976E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.5720930E+02,-1.5910720E+02, 1.1166976E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 1.82524E+02 Event weight (ref) = 7.29176E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825239682E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284390E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072803E+02 P = -1.303455E+02 -1.319191E+02 9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 1.906577E+00 -3.645817E+01 3.067713E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.82524E+02 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4503411E+02; 1.2843896E+02, 1.6837730E+02,-1.2326488E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.0728027E+02;-1.3034554E+02,-1.3191913E+02, 9.2587754E+01| 0.0000000E+00| 4) 5 prt(o:21| 4.7685630E+01; 1.9065767E+00,-3.6458169E+01, 3.0677127E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 1.82524E+02 Event weight (ref) = 7.29176E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825239682E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284390E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072803E+02 P = -1.303455E+02 -1.319191E+02 9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 1.906577E+00 -3.645817E+01 3.067713E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.82524E+02 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.0728027E+02; 1.3034554E+02, 1.3191913E+02,-9.2587754E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4503411E+02;-1.3877481E+02,-1.7883793E+02, 9.3809705E+01| 0.0000000E+00| 4) 5 prt(o:21| 4.7685630E+01; 8.4292718E+00, 4.6918797E+01,-1.2219511E+00| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 8.24902E-01 Event weight (ref) = 1.54626E+04 Event weight (prc) = 1.54626E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688751E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763859E+00 -8.718463E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101356E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981894E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 8.24902E-01 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 1.54626E+04 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.2301966E+01,-2.2379372E+02, 1.0917415E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.2301966E+01, 2.2379372E+02,-1.0917415E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 4.70269E+03 Event weight (ref) = 1.54626E+04 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688751E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763859E+00 -8.718463E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101356E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981894E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 4.70269E+03 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.0673038E+02;-9.7638590E+00,-8.7184634E+01,-6.0785524E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1013565E+02; 1.8745753E+01, 1.8810815E+02,-9.1765521E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.8313397E+02;-8.9818936E+00,-1.0092352E+02, 1.5255105E+02| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 4.70269E+03 Event weight (ref) = 1.54626E+04 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688751E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763859E+00 -8.718463E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101356E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981894E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 4.70269E+03 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1013565E+02;-1.8745753E+01,-1.8810815E+02, 9.1765521E+01| 0.0000000E+00| 3) 4 prt(o:4| 1.0673038E+02; 1.7100212E+00, 6.3667233E+00,-1.0652659E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.8313397E+02; 1.7035731E+01, 1.8174143E+02, 1.4761067E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688751E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473681E+01 2.000447E+02 -5.273248E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708635E+01 P = -2.761834E+01 -5.055249E+01 7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541757E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.1117985E+01, 1.3017405E+02,-2.0123854E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.1117985E+01,-1.3017405E+02, 2.0123854E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688751E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473681E+01 2.000447E+02 -5.273248E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708635E+01 P = -2.761834E+01 -5.055249E+01 7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541757E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1996406E+02;-7.4736813E+01, 2.0004470E+02,-5.2732481E+01| 0.0000000E+00| 3) 4 prt(o:4| 9.7086346E+01;-2.7618341E+01,-5.0552492E+01, 7.8150056E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.8294959E+02; 1.0235515E+02,-1.4949221E+02,-2.5417575E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688751E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473681E+01 2.000447E+02 -5.273248E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708635E+01 P = -2.761834E+01 -5.055249E+01 7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541757E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 9.7086346E+01; 2.7618341E+01, 5.0552492E+01,-7.8150056E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1996406E+02; 1.3739753E+02,-8.5350807E+01, 1.4906827E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.8294959E+02;-1.6501587E+02, 3.4798315E+01,-7.0918215E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.58453E-01 Event weight (ref) = 2.97017E+03 Event weight (prc) = 2.97017E+03 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691046E+02 -5.336321E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544066E+01 -1.134704E+02 4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536293E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.58453E-01 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 2.97017E+03 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-1.3197112E+02, 1.9849802E+02,-7.5380093E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 1.3197112E+02,-1.9849802E+02, 7.5380093E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.08776E+02 Event weight (ref) = 2.97017E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691046E+02 -5.336321E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544066E+01 -1.134704E+02 4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536293E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.08776E+02 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 0.00000E+00 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4620692E+02;-1.7080359E+02, 1.6910456E+02,-5.3363212E+01| 0.0000000E+00| 3) 4 prt(o:4| 1.4291130E+02; 7.5440660E+01,-1.1347044E+02, 4.3090669E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.1088177E+02; 9.5362927E+01,-5.5634116E+01, 1.0272543E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.08776E+02 Event weight (ref) = 2.97017E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691046E+02 -5.336321E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544066E+01 -1.134704E+02 4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536293E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.08776E+02 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 0.00000E+00 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.4291130E+02;-7.5440660E+01, 1.1347044E+02,-4.3090669E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4620692E+02; 1.6409459E+02,-1.5901354E+02, 9.1681560E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.1088177E+02;-8.8653929E+01, 4.5543100E+01,-4.8590891E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686716E+01 1.081329E+02 -9.603933E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016601E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 8.7439956E+00, 8.9899620E+01,-2.3311285E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-8.7439956E+00,-8.9899620E+01, 2.3311285E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686716E+01 1.081329E+02 -9.603933E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016601E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.5540321E+02;-5.6867161E+01, 1.0813292E+02,-9.6039332E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1681660E+02;-7.5833736E+00,-7.7966919E+01, 2.0217094E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.2778019E+02; 6.4450535E+01,-3.0166005E+01,-1.0613161E+02| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686716E+01 1.081329E+02 -9.603933E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016601E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1681660E+02; 7.5833736E+00, 7.7966919E+01,-2.0217094E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.5540321E+02; 6.7793786E+01, 4.2069508E+00, 1.3977289E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.2778019E+02;-7.5377159E+01,-8.2173870E+01, 6.2398052E+01| 0.0000000E+00| 5) ======================================================================== Total number of regions: 10 alr || flst_real || i_real || em || mul || nreg || ftuples || flst_born || i_born 1 || [ 11,-11, -4, 4, 21] || 1 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -4, 4] || 1 2 || [ 11,-11, -4, 4, 21] || 1 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -4, 4] || 1 3 || [ 11,-11, -2, 2, 21] || 2 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -2, 2] || 2 4 || [ 11,-11, -2, 2, 21] || 2 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -2, 2] || 2 5 || [ 11,-11, -5, 5, 21] || 3 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -5, 5] || 3 6 || [ 11,-11, -5, 5, 21] || 3 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -5, 5] || 3 7 || [ 11,-11, -3, 3, 21] || 4 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -3, 3] || 4 8 || [ 11,-11, -3, 3, 21] || 4 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -3, 3] || 4 9 || [ 11,-11, -1, 1, 21] || 5 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -1, 1] || 5 10 || [ 11,-11, -1, 1, 21] || 5 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -1, 1] || 5 ------------------------------------------------------------------------ Contents of nlo_7_p3.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.08358E-03 Squared matrix el. (prc) = 4.08358E-03 Event weight (ref) = 1.26569E+02 Event weight (prc) = 1.26569E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.08358E-03 sqme_ref* => 4.08358E-03 event_index* => 1 event_weight* => 1.26569E+02 event_weight_ref* => 1.26569E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 9.8408256E+01, 1.8165098E+02, 1.4077903E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-9.8408256E+01,-1.8165098E+02,-1.4077903E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.22190E-03 Squared matrix el. (prc) = 4.22190E-03 Event weight (ref) = 1.30782E+02 Event weight (prc) = 1.30782E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 6 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 6 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.22190E-03 sqme_ref* => 4.22190E-03 event_index* => 2 event_weight* => 1.30782E+02 event_weight_ref* => 1.30782E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.1286322E+02, 9.7428599E+01,-8.7732069E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.1286322E+02,-9.7428599E+01, 8.7732069E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 3 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 5.9262301E+01, 1.1991279E+02,-2.1120820E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-5.9262301E+01,-1.1991279E+02, 2.1120820E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 12 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 12 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-8.6412667E+01, 1.6275399E+02,-1.6894966E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 8.6412667E+01,-1.6275399E+02, 1.6894966E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.25951E-03 Squared matrix el. (prc) = 4.25951E-03 Event weight (ref) = 1.31947E+02 Event weight (prc) = 1.31947E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 15 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 15 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.25951E-03 sqme_ref* => 4.25951E-03 event_index* => 5 event_weight* => 1.31947E+02 event_weight_ref* => 1.31947E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 2.0159526E+02, 1.3452992E+02,-6.1327417E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-2.0159526E+02,-1.3452992E+02, 6.1327417E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-4.8740427E+00,-1.0688732E+02, 2.2594544E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 4.8740427E+00, 1.0688732E+02,-2.2594544E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 21 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 21 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.4549469E+01,-1.1200036E+02,-2.2215590E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.4549469E+01, 1.1200036E+02, 2.2215590E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.20249E-03 Squared matrix el. (prc) = 4.20249E-03 Event weight (ref) = 1.30180E+02 Event weight (prc) = 1.30180E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 24 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 24 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.20249E-03 sqme_ref* => 4.20249E-03 event_index* => 8 event_weight* => 1.30180E+02 event_weight_ref* => 1.30180E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-4.5418669E+01, 2.2544353E+02,-9.8042649E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 4.5418669E+01,-2.2544353E+02, 9.8042649E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.22672E-03 Squared matrix el. (prc) = 4.22672E-03 Event weight (ref) = 1.31006E+02 Event weight (prc) = 1.31006E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.22672E-03 sqme_ref* => 4.22672E-03 event_index* => 9 event_weight* => 1.31006E+02 event_weight_ref* => 1.31006E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.6634004E+02, 1.6619702E+02, 8.4909020E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.6634004E+02,-1.6619702E+02,-8.4909020E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.29218E-03 Squared matrix el. (prc) = 4.29218E-03 Event weight (ref) = 1.32959E+02 Event weight (prc) = 1.32959E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 30 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 30 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.29218E-03 sqme_ref* => 4.29218E-03 event_index* => 10 event_weight* => 1.32959E+02 event_weight_ref* => 1.32959E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-7.3495680E+01, 2.3878223E+02, 9.0240776E+00| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 7.3495680E+01,-2.3878223E+02,-9.0240776E+00| 0.0000000E+00| 4) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-quad/nlo_9.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-quad/nlo_9.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-quad/nlo_9.ref (revision 8760) @@ -1,4800 +1,4800 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true openmp_num_threads = 1 SM.ms => 0.00000E+00 SM.mc => 0.00000E+00 SM.mb => 0.00000E+00 SM.me => 0.00000E+00 [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) [user variable] elec = PDG(11, -11) $exclude_gauge_splittings = "t" $method = "dummy" $rng_method = "rng_stream" $integration_method = "vamp2" sqrts = 1.30000E+04 ?combined_nlo_integration = false ?use_vamp_equivalences = false seed = 3991 n_events = 2 $sample_normalization = "sigma" ?unweighted = false ?negative_weights = true ?keep_failed_events = true ?fixed_order_nlo_events = true ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false | Process library 'nlo_9_lib': recorded process 'nlo_9_p1' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3991 | Initializing integration for process nlo_9_p1: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Initialized builtin PDF CTEQ6L | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p1' | Library name = 'nlo_9_lib' | Process index = 1 | Process components: | 1: 'nlo_9_p1_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy] | 2: 'nlo_9_p1_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p1_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p1_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p1_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 4 dimensions | Integrator: Write grid header and grids to 'nlo_9_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 96 1.827E+07 7.39E+06 40.46 3.96 4.1 |-----------------------------------------------------------------------------| 1 96 1.827E+07 7.39E+06 40.46 3.96 4.1 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.827E+07 7.39E+06 40.46 0.00 4.1 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| | Starting simulation for process 'nlo_9_p1' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3992 | Events: writing to ASCII file 'nlo_9_p1.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p1.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p2' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3993 | Initializing integration for process nlo_9_p2: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p2.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p2' | Library name = 'nlo_9_lib' | Process index = 2 | Process components: | 1: 'nlo_9_p2_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p2_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [dummy], [real] | 3: 'nlo_9_p2_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p2_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p2_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 7 dimensions | Integrator: Write grid header and grids to 'nlo_9_p2.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p2.m2.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.432E+10 7.73E+09 53.98 5.40 5.0 |-----------------------------------------------------------------------------| 1 100 1.432E+10 7.73E+09 53.98 5.40 5.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.432E+10 7.73E+09 53.98 0.00 5.0 |=============================================================================| | Starting simulation for process 'nlo_9_p2' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3994 | Events: writing to ASCII file 'nlo_9_p2.debug' | Events: generating 8 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p2.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p3' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3995 | Initializing integration for process nlo_9_p3: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p3.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p3' | Library name = 'nlo_9_lib' | Process index = 3 | Process components: | 1: 'nlo_9_p3_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p3_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p3_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy], [virtual] | 4: 'nlo_9_p3_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p3_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 4 dimensions | Integrator: Write grid header and grids to 'nlo_9_p3.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p3.m3.vg2'. | VAMP2: set chain: use chained weights. 1 96 1.148E+05 9.41E+04 81.94 8.03 2.6 |-----------------------------------------------------------------------------| 1 96 1.148E+05 9.41E+04 81.94 8.03 2.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.148E+05 9.41E+04 81.94 0.00 2.6 |=============================================================================| | Starting simulation for process 'nlo_9_p3' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3996 | Events: writing to ASCII file 'nlo_9_p3.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p3.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p4' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3997 | Initializing integration for process nlo_9_p4: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p4.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p4.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p4' | Library name = 'nlo_9_lib' | Process index = 4 | Process components: | 1: 'nlo_9_p4_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p4_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p4_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p4_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p4_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p4' part 'dglap' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: Write grid header and grids to 'nlo_9_p4.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p4.m4.vg2'. | VAMP2: set chain: use chained weights. 1 100 2.155E+08 2.04E+08 94.81 9.48 2.1 |-----------------------------------------------------------------------------| 1 100 2.155E+08 2.04E+08 94.81 9.48 2.1 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.155E+08 2.04E+08 94.81 0.00 2.1 |=============================================================================| | Starting simulation for process 'nlo_9_p4' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3998 | Events: writing to ASCII file 'nlo_9_p4.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p4.debug' | There were no errors and 4 warning(s). | WHIZARD run finished. |=============================================================================| Contents of nlo_9_p1.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.70571E+04 Squared matrix el. (prc) = 3.70571E+04 Event weight (ref) = 2.59265E+07 Event weight (prc) = 2.59265E+07 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 3270494107.0, 1218490942.0, 3220277207.0, 2821320218.0, 4220147848.0, 1218259235.0, ] Beginning substream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Initial stream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 870276730.0, 1525774502.0, 3988227742.0, 3787208568.0, 2984262882.0, 2541051477.0, ] Beginning substream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Initial stream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.48247E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p1" process_num_id* => [unknown integer] sqme* => 3.70571E+04 sqme_ref* => 3.70571E+04 event_index* => 1 event_weight* => 2.59265E+07 event_weight_ref* => 2.59265E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-2|-6.8868056E+00; 0.0000000E+00, 0.0000000E+00,-6.8868056E+00| 0.0000000E+00| 3) 4 prt(i:2|-3.2641096E+02; 0.0000000E+00, 0.0000000E+00, 3.2641096E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4931132E+03; 0.0000000E+00, 0.0000000E+00, 6.4931132E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.1735890E+03; 0.0000000E+00, 0.0000000E+00,-6.1735890E+03| 0.0000000E+00| 6) 7 prt(o:11| 6.6717870E+01; 3.6985611E+01, 7.0258495E-01,-5.5523374E+01| 0.0000000E+00| 7) 8 prt(o:-11| 2.6657990E+02;-3.6985611E+01,-7.0258495E-01,-2.6400078E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 6.87216E-01 Squared matrix el. (prc) = 6.87216E-01 Event weight (ref) = 2.69210E+03 Event weight (prc) = 2.69210E+03 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 1817174340.0, 4169406181.0, 394187331.0, 860033000.0, 2212227538.0, 3653581942.0, ] Beginning substream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Initial stream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 976955966.0, 3946182281.0, 2474115998.0, 1111192673.0, 3759619853.0, 3640289132.0, ] Beginning substream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Initial stream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(1) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(1) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 2.19506E+03 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p1" process_num_id* => [unknown integer] sqme* => 6.87216E-01 sqme_ref* => 6.87216E-01 event_index* => 2 event_weight* => 2.69210E+03 event_weight_ref* => 2.69210E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-1|-3.8204346E+02; 0.0000000E+00, 0.0000000E+00,-3.8204346E+02| 0.0000000E+00| 3) 4 prt(i:1|-3.1529664E+03; 0.0000000E+00, 0.0000000E+00, 3.1529664E+03| 0.0000000E+00| 4) 5 prt(o:92| 6.1179565E+03; 0.0000000E+00, 0.0000000E+00, 6.1179565E+03| 0.0000000E+00| 5) 6 prt(o:-92| 3.3470336E+03; 0.0000000E+00, 0.0000000E+00,-3.3470336E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.1875968E+03;-8.3458144E+02, 6.3031503E+02,-1.9213944E+03| 0.0000000E+00| 7) 8 prt(o:-11| 1.3474130E+03; 8.3458144E+02,-6.3031503E+02,-8.4952849E+02| 0.0000000E+00| 8) ======================================================================== Contents of nlo_9_p2.debug: Total number of regions: 30 alr || flst_real || i_real || em || mul || nreg || ftuples || flst_born || i_born 1 || [ -4, 4, 11,-11, 21] || 1 || 0 || 1 || 1 || {(0,5)} || [ -4, 4, 11,-11] || 1 2 || [ -4, 21, 11,-11, -4] || 2 || 2 || 1 || 1 || {(2,5)} || [ -4, 4, 11,-11] || 1 3 || [ -2, 2, 11,-11, 21] || 3 || 0 || 1 || 1 || {(0,5)} || [ -2, 2, 11,-11] || 2 4 || [ -2, 21, 11,-11, -2] || 4 || 2 || 1 || 1 || {(2,5)} || [ -2, 2, 11,-11] || 2 5 || [ 2, -2, 11,-11, 21] || 5 || 0 || 1 || 1 || {(0,5)} || [ 2, -2, 11,-11] || 3 6 || [ 2, 21, 11,-11, 2] || 6 || 2 || 1 || 1 || {(2,5)} || [ 2, -2, 11,-11] || 3 7 || [ 4, -4, 11,-11, 21] || 7 || 0 || 1 || 1 || {(0,5)} || [ 4, -4, 11,-11] || 4 8 || [ 4, 21, 11,-11, 4] || 8 || 2 || 1 || 1 || {(2,5)} || [ 4, -4, 11,-11] || 4 9 || [ -5, 5, 11,-11, 21] || 9 || 0 || 1 || 1 || {(0,5)} || [ -5, 5, 11,-11] || 5 10 || [ -5, 21, 11,-11, -5] || 10 || 2 || 1 || 1 || {(2,5)} || [ -5, 5, 11,-11] || 5 11 || [ -3, 3, 11,-11, 21] || 11 || 0 || 1 || 1 || {(0,5)} || [ -3, 3, 11,-11] || 6 12 || [ -3, 21, 11,-11, -3] || 12 || 2 || 1 || 1 || {(2,5)} || [ -3, 3, 11,-11] || 6 13 || [ -1, 1, 11,-11, 21] || 13 || 0 || 1 || 1 || {(0,5)} || [ -1, 1, 11,-11] || 7 14 || [ -1, 21, 11,-11, -1] || 14 || 2 || 1 || 1 || {(2,5)} || [ -1, 1, 11,-11] || 7 15 || [ 1, -1, 11,-11, 21] || 15 || 0 || 1 || 1 || {(0,5)} || [ 1, -1, 11,-11] || 8 16 || [ 1, 21, 11,-11, 1] || 16 || 2 || 1 || 1 || {(2,5)} || [ 1, -1, 11,-11] || 8 17 || [ 3, -3, 11,-11, 21] || 17 || 0 || 1 || 1 || {(0,5)} || [ 3, -3, 11,-11] || 9 18 || [ 3, 21, 11,-11, 3] || 18 || 2 || 1 || 1 || {(2,5)} || [ 3, -3, 11,-11] || 9 19 || [ 5, -5, 11,-11, 21] || 19 || 0 || 1 || 1 || {(0,5)} || [ 5, -5, 11,-11] || 10 20 || [ 5, 21, 11,-11, 5] || 20 || 2 || 1 || 1 || {(2,5)} || [ 5, -5, 11,-11] || 10 21 || [ 21, -4, 11,-11, -4] || 21 || 1 || 1 || 1 || {(1,5)} || [ 4, -4, 11,-11] || 4 22 || [ 21, -2, 11,-11, -2] || 22 || 1 || 1 || 1 || {(1,5)} || [ 2, -2, 11,-11] || 3 23 || [ 21, 2, 11,-11, 2] || 23 || 1 || 1 || 1 || {(1,5)} || [ -2, 2, 11,-11] || 2 24 || [ 21, 4, 11,-11, 4] || 24 || 1 || 1 || 1 || {(1,5)} || [ -4, 4, 11,-11] || 1 25 || [ 21, -5, 11,-11, -5] || 25 || 1 || 1 || 1 || {(1,5)} || [ 5, -5, 11,-11] || 10 26 || [ 21, -3, 11,-11, -3] || 26 || 1 || 1 || 1 || {(1,5)} || [ 3, -3, 11,-11] || 9 27 || [ 21, -1, 11,-11, -1] || 27 || 1 || 1 || 1 || {(1,5)} || [ 1, -1, 11,-11] || 8 28 || [ 21, 1, 11,-11, 1] || 28 || 1 || 1 || 1 || {(1,5)} || [ -1, 1, 11,-11] || 7 29 || [ 21, 3, 11,-11, 3] || 29 || 1 || 1 || 1 || {(1,5)} || [ -3, 3, 11,-11] || 6 30 || [ 21, 5, 11,-11, 5] || 30 || 1 || 1 || 1 || {(1,5)} || [ -5, 5, 11,-11] || 5 ------------------------------------------------------------------------ ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 7.40062E+03 Event weight (ref) = 1.00516E+09 Event weight (prc) = 8.95289E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864435E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.30010E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 7.40062E+03 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 8.95289E+05 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-6.3427874E+00; 0.0000000E+00, 0.0000000E+00,-6.3427874E+00| 0.0000000E+00| 3) 4 prt(i:4|-3.4090636E+02; 0.0000000E+00, 0.0000000E+00, 3.4090636E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4936572E+03; 0.0000000E+00, 0.0000000E+00, 6.4936572E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.1590936E+03; 0.0000000E+00, 0.0000000E+00,-6.1590936E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.5798314E+01; 1.2978902E+01,-2.2934559E+01,-2.4229598E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1145084E+02;-1.2978902E+01, 2.2934559E+01,-3.1033398E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 2.16231E+05 Event weight (ref) = 1.00516E+09 Event weight (prc) = 2.61585E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864435E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 2.16231E+05 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 2.61585E+07 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-1|-6.3910148E+00; 0.0000000E+00, 0.0000000E+00,-6.3910148E+00| 0.0000000E+00| 3) 4 prt(i:1|-4.3483007E+02; 0.0000000E+00, 0.0000000E+00, 4.3483007E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.0651699E+03; 0.0000000E+00, 0.0000000E+00,-6.0651699E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393841E+01; 1.1353673E+01,-2.4091464E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600053E+01, 2.1780555E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:21| 9.3653318E+01; 3.2463798E+00, 2.3109086E+00,-9.3568503E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 1.85537E+06 Event weight (ref) = 1.00516E+09 Event weight (prc) = 2.24453E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864435E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 1.85537E+06 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 2.24453E+08 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:1|-6.3910148E+00; 0.0000000E+00, 0.0000000E+00,-6.3910148E+00| 0.0000000E+00| 3) 4 prt(i:21|-4.3483007E+02; 0.0000000E+00, 0.0000000E+00, 4.3483007E+02| 0.0000000E+00| 4) 5 prt(o:-92| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:93| 6.0651699E+03; 0.0000000E+00, 0.0000000E+00,-6.0651699E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393841E+01; 1.1353673E+01,-2.4091464E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600053E+01, 2.1780555E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:1| 9.3653318E+01; 3.2463798E+00, 2.3109086E+00,-9.3568503E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 6.22986E+06 Event weight (ref) = 1.00516E+09 Event weight (prc) = 7.53657E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864435E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.22986E+06 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 7.53657E+08 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:21|-6.3910148E+00; 0.0000000E+00, 0.0000000E+00,-6.3910148E+00| 0.0000000E+00| 3) 4 prt(i:2|-4.3483007E+02; 0.0000000E+00, 0.0000000E+00, 4.3483007E+02| 0.0000000E+00| 4) 5 prt(o:93| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.0651699E+03; 0.0000000E+00, 0.0000000E+00,-6.0651699E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393841E+01; 1.1353673E+01,-2.4091464E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600053E+01, 2.1780555E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:2| 9.3653318E+01; 3.2463798E+00, 2.3109086E+00,-9.3568503E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = -7.22695E+03 Event weight (ref) = 3.07001E+08 Event weight (prc) = -2.81358E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066983E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.11989E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => -7.22695E+03 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => -2.81358E+05 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-1.0203303E+03; 0.0000000E+00, 0.0000000E+00,-1.0203303E+03| 0.0000000E+00| 3) 4 prt(i:4|-2.0378805E+00; 0.0000000E+00, 0.0000000E+00, 2.0378805E+00| 0.0000000E+00| 4) 5 prt(o:92| 5.4796697E+03; 0.0000000E+00, 0.0000000E+00, 5.4796697E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4979621E+03; 0.0000000E+00, 0.0000000E+00,-6.4979621E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.8155129E+02;-2.0762780E+01, 3.5003646E+01, 2.7859430E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4081694E+02; 2.0762780E+01,-3.5003646E+01, 7.3969817E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = 2.23960E+05 Event weight (ref) = 3.07001E+08 Event weight (prc) = 8.71918E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066983E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 2.23960E+05 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => 8.71918E+06 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:2|-1.0761179E+03; 0.0000000E+00, 0.0000000E+00,-1.0761179E+03| 0.0000000E+00| 3) 4 prt(i:-2|-2.1012438E+00; 0.0000000E+00, 0.0000000E+00, 2.1012438E+00| 0.0000000E+00| 4) 5 prt(o:-92| 5.4238821E+03; 0.0000000E+00, 0.0000000E+00, 5.4238821E+03| 0.0000000E+00| 5) 6 prt(o:92| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797004E+02;-2.2099732E+01, 3.3747855E+01, 2.7502732E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523148E+02; 1.9415336E+01,-3.6269293E+01, 7.4409511E+02| 0.0000000E+00| 8) 9 prt(o:21| 5.5017596E+01; 2.6843964E+00, 2.5214378E+00, 5.4894192E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = 6.98237E+06 Event weight (ref) = 3.07001E+08 Event weight (prc) = 2.71836E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066983E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.98237E+06 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => 2.71836E+08 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:1|-1.0761179E+03; 0.0000000E+00, 0.0000000E+00,-1.0761179E+03| 0.0000000E+00| 3) 4 prt(i:21|-2.1012438E+00; 0.0000000E+00, 0.0000000E+00, 2.1012438E+00| 0.0000000E+00| 4) 5 prt(o:-92| 5.4238821E+03; 0.0000000E+00, 0.0000000E+00, 5.4238821E+03| 0.0000000E+00| 5) 6 prt(o:93| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797004E+02;-2.2099732E+01, 3.3747855E+01, 2.7502732E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523148E+02; 1.9415336E+01,-3.6269293E+01, 7.4409511E+02| 0.0000000E+00| 8) 9 prt(o:1| 5.5017596E+01; 2.6843964E+00, 2.5214378E+00, 5.4894192E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = 6.86507E+05 Event weight (ref) = 3.07001E+08 Event weight (prc) = 2.67269E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066983E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.86507E+05 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => 2.67269E+07 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:21|-1.0761179E+03; 0.0000000E+00, 0.0000000E+00,-1.0761179E+03| 0.0000000E+00| 3) 4 prt(i:-1|-2.1012438E+00; 0.0000000E+00, 0.0000000E+00, 2.1012438E+00| 0.0000000E+00| 4) 5 prt(o:93| 5.4238821E+03; 0.0000000E+00, 0.0000000E+00, 5.4238821E+03| 0.0000000E+00| 5) 6 prt(o:92| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797004E+02;-2.2099732E+01, 3.3747855E+01, 2.7502732E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523148E+02; 1.9415336E+01,-3.6269293E+01, 7.4409511E+02| 0.0000000E+00| 8) 9 prt(o:-1| 5.5017596E+01; 2.6843964E+00, 2.5214378E+00, 5.4894192E+01| 0.0000000E+00| 9) ======================================================================== Contents of nlo_9_p3.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.12930E+01 Squared matrix el. (prc) = 2.12930E+01 Event weight (ref) = 6.36286E+03 Event weight (prc) = 6.36286E+03 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 6 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 2596865362.0, 2097861302.0, 1710419373.0, 4132755378.0, 3334395289.0, 3898036172.0, ] Beginning substream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Initial stream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-2) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 2690940837.0, 944023296.0, 3856628408.0, 3483223282.0, 1004971824.0, 2058251242.0, ] Beginning substream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Initial stream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.44812E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p3" process_num_id* => [unknown integer] sqme* => 2.12930E+01 sqme_ref* => 2.12930E+01 event_index* => 1 event_weight* => 6.36286E+03 event_weight_ref* => 6.36286E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-2.1850027E+03; 0.0000000E+00, 0.0000000E+00,-2.1850027E+03| 0.0000000E+00| 3) 4 prt(i:4|-1.0213593E+00; 0.0000000E+00, 0.0000000E+00, 1.0213593E+00| 0.0000000E+00| 4) 5 prt(o:92| 4.3149973E+03; 0.0000000E+00, 0.0000000E+00, 4.3149973E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4989786E+03; 0.0000000E+00, 0.0000000E+00,-6.4989786E+03| 0.0000000E+00| 6) 7 prt(o:11| 1.9276312E+03; 2.5248333E+01,-1.7044627E+01, 1.9273905E+03| 0.0000000E+00| 7) 8 prt(o:-11| 2.5839283E+02;-2.5248333E+01, 1.7044627E+01, 2.5659084E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.24170E+01 Squared matrix el. (prc) = 4.24170E+01 Event weight (ref) = 1.65951E+03 Event weight (prc) = 1.65951E+03 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 6 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 1150698303.0, 3394442877.0, 1602037449.0, 443345876.0, 714281248.0, 3904759980.0, ] Beginning substream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Initial stream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 845567059.0, 1878523320.0, 621290442.0, 2282089536.0, 2749647619.0, 2527962339.0, ] Beginning substream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Initial stream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.09908E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p3" process_num_id* => [unknown integer] sqme* => 4.24170E+01 sqme_ref* => 4.24170E+01 event_index* => 2 event_weight* => 1.65951E+03 event_weight_ref* => 1.65951E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-5.4466623E+01; 0.0000000E+00, 0.0000000E+00,-5.4466623E+01| 0.0000000E+00| 3) 4 prt(i:4|-3.8001808E+01; 0.0000000E+00, 0.0000000E+00, 3.8001808E+01| 0.0000000E+00| 4) 5 prt(o:92| 6.4455334E+03; 0.0000000E+00, 0.0000000E+00, 6.4455334E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4619982E+03; 0.0000000E+00, 0.0000000E+00,-6.4619982E+03| 0.0000000E+00| 6) 7 prt(o:11| 5.1146524E+01;-2.4957136E+01,-2.6645778E+01, 3.5820536E+01| 0.0000000E+00| 7) 8 prt(o:-11| 4.1321907E+01; 2.4957136E+01, 2.6645778E+01,-1.9355720E+01| 0.0000000E+00| 8) ======================================================================== Contents of nlo_9_p4.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.05161E-13 Squared matrix el. (prc) = 1.05161E-13 Event weight (ref) = 7.75946E-13 Event weight (prc) = 7.75946E-13 ------------------------------------------------------------------------ Selected MCI group = 4 Selected term = 7 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 112567446.0, 2537546482.0, 955490456.0, 493528515.0, 744046788.0, 3090452419.0, ] Beginning substream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Initial stream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 1453789347.0, 653147693.0, 3790828741.0, 3331230639.0, 15326295.0, 3964323346.0, ] Beginning substream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Initial stream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.25213E+04 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p4" process_num_id* => [unknown integer] sqme* => 1.05161E-13 sqme_ref* => 1.05161E-13 event_index* => 1 event_weight* => 7.75946E-13 event_weight_ref* => 7.75946E-13 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-6.2455844E+03; 0.0000000E+00, 0.0000000E+00,-6.2455844E+03| 0.0000000E+00| 3) 4 prt(i:4|-6.2757411E+03; 0.0000000E+00, 0.0000000E+00, 6.2757411E+03| 0.0000000E+00| 4) 5 prt(o:92| 2.5441558E+02; 0.0000000E+00, 0.0000000E+00, 2.5441558E+02| 0.0000000E+00| 5) 6 prt(o:-92| 2.2425890E+02; 0.0000000E+00, 0.0000000E+00,-2.2425890E+02| 0.0000000E+00| 6) 7 prt(o:11| 6.2672848E+03;-1.9090987E+02, 5.6213367E+03,-2.7645949E+03| 0.0000000E+00| 7) 8 prt(o:-11| 6.2540408E+03; 1.9090987E+02,-5.6213367E+03, 2.7344382E+03| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.58498E-02 Squared matrix el. (prc) = 7.58498E-02 Event weight (ref) = 7.08197E+01 Event weight (prc) = 7.08197E+01 ------------------------------------------------------------------------ Selected MCI group = 4 Selected term = 7 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 2964943828.0, 3006961225.0, 2205962508.0, 235002314.0, 4260252546.0, 4030348999.0, ] Beginning substream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Initial stream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-2) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 2927356149.0, 2992177383.0, 3989844751.0, 720065746.0, 2244661502.0, 4119271164.0, ] Beginning substream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Initial stream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 3.47756E+03 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p4" process_num_id* => [unknown integer] sqme* => 7.58498E-02 sqme_ref* => 7.58498E-02 event_index* => 2 event_weight* => 7.08197E+01 event_weight_ref* => 7.08197E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-2.6130095E+03; 0.0000000E+00, 0.0000000E+00,-2.6130095E+03| 0.0000000E+00| 3) 4 prt(i:4|-1.1570394E+03; 0.0000000E+00, 0.0000000E+00, 1.1570394E+03| 0.0000000E+00| 4) 5 prt(o:92| 3.8869905E+03; 0.0000000E+00, 0.0000000E+00, 3.8869905E+03| 0.0000000E+00| 5) 6 prt(o:-92| 5.3429606E+03; 0.0000000E+00, 0.0000000E+00,-5.3429606E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.5040593E+03; 7.8357558E+02, 4.7248514E+02, 2.3308968E+03| 0.0000000E+00| 7) 8 prt(o:-11| 1.2659896E+03;-7.8357558E+02,-4.7248514E+02,-8.7492676E+02| 0.0000000E+00| 8) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-ext/openloops_3.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-ext/openloops_3.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-ext/openloops_3.ref (revision 8760) @@ -1,1186 +1,1186 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true $method = "openloops" openmp_num_threads = 1 ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true seed = 2222 sqrts = 5.00000E+02 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false ?fixed_order_nlo_events = true ?negative_weights = true ?unweighted = false SM.mtop => 1.73200E+02 SM.wtop => 0.00000E+00 | Process library 'openloops_3_lib': recorded process 'openloops_3_p1' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2222 | Initializing integration for process openloops_3_p1: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p1' | Library name = 'openloops_3_lib' | Process index = 1 | Process components: | 1: 'openloops_3_p1_i1': e+, e- => t, tbar [openloops] | 2: 'openloops_3_p1_i2': e+, e- => t, tbar, gl [inactive], [real] | 3: 'openloops_3_p1_i3': e+, e- => t, tbar [inactive], [virtual] | 4: 'openloops_3_p1_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 6.257E+02 2.89E+01 4.61 0.46 55.5 |-----------------------------------------------------------------------------| 1 100 6.257E+02 2.89E+01 4.61 0.46 55.5 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 6.257E+02 2.89E+01 4.61 0.00 55.5 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p1' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p1.m1.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2223 | Events: writing to ASCII file 'openloops_3_p1.debug' | Events: generating 1 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p1.debug' seed = 3333 | Process library 'openloops_3_lib': unloading | Process library 'openloops_3_lib': open | Process library 'openloops_3_lib': recorded process 'openloops_3_p2' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 3333 | Initializing integration for process openloops_3_p2: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p2.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p2' | Library name = 'openloops_3_lib' | Process index = 2 | Process components: | 1: 'openloops_3_p2_i1': e+, e- => t, tbar [inactive] | 2: 'openloops_3_p2_i2': e+, e- => t, tbar, gl [openloops], [real] | 3: 'openloops_3_p2_i3': e+, e- => t, tbar [inactive], [virtual] | 4: 'openloops_3_p2_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -7.301E+01 4.28E+00 5.86 0.59 39.2 |-----------------------------------------------------------------------------| 1 100 -7.301E+01 4.28E+00 5.86 0.59 39.2 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 -7.301E+01 4.28E+00 5.86 0.00 0.0 |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p2' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p2.m2.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 3334 | Events: writing to ASCII file 'openloops_3_p2.debug' | Events: generating 3 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p2.debug' seed = 4444 | Process library 'openloops_3_lib': unloading | Process library 'openloops_3_lib': open | Process library 'openloops_3_lib': recorded process 'openloops_3_p3' | Integrate: current process library needs compilation | Process library 'openloops_3_lib': compiling ... | Process library 'openloops_3_lib': writing makefile | Process library 'openloops_3_lib': removing old files | Process library 'openloops_3_lib': writing driver | Process library 'openloops_3_lib': creating source code | Process library 'openloops_3_lib': compiling sources | Process library 'openloops_3_lib': linking | Process library 'openloops_3_lib': loading | Process library 'openloops_3_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 4444 | Initializing integration for process openloops_3_p3: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_3_p3.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_3_p3' | Library name = 'openloops_3_lib' | Process index = 3 | Process components: | 1: 'openloops_3_p3_i1': e+, e- => t, tbar [inactive] | 2: 'openloops_3_p3_i2': e+, e- => t, tbar, gl [inactive], [real] | 3: 'openloops_3_p3_i3': e+, e- => t, tbar [openloops], [virtual] | 4: 'openloops_3_p3_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_3_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.387E+02 7.85E+00 5.66 0.57 44.8 |-----------------------------------------------------------------------------| 1 100 1.387E+02 7.85E+00 5.66 0.57 44.8 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.387E+02 7.85E+00 5.66 0.00 44.8 |=============================================================================| n_events = 1 | Starting simulation for process 'openloops_3_p3' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | Simulate: using integration grids from file 'openloops_3_p3.m3.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 4445 | Events: writing to ASCII file 'openloops_3_p3.debug' | Events: generating 1 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'openloops_3_p3.debug' | There were no errors and 3 warning(s). | WHIZARD run finished. |=============================================================================| ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.66014E-02 Squared matrix el. (prc) = 2.66014E-02 Event weight (ref) = 5.94404E+02 Event weight (prc) = 5.94404E+02 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p1' TAO random-number generator: seed = 145620996 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p1' TAO random-number generator: seed = 145620997 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -3.093375E+01 1.729251E+02 -4.051886E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 3.093375E+01 -1.729251E+02 4.051886E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p1" process_num_id* => [unknown integer] sqme* => 2.66014E-02 sqme_ref* => 2.66014E-02 event_index* => 1 event_weight* => 5.94404E+02 event_weight_ref* => 5.94404E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02;-3.0933754E+01, 1.7292509E+02,-4.0518856E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02; 3.0933754E+01,-1.7292509E+02, 4.0518856E+01| 2.9998240E+04| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = -5.17360E-03 Event weight (ref) = -9.77307E+01 Event weight (prc) = -1.15603E+02 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034761903E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888583E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = 7.697588E+01 4.999534E+01 9.008653E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => -5.17360E-03 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => -1.15603E+02 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02; 1.6597780E+02, 4.6491044E+01,-5.2836666E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02;-1.6597780E+02,-4.6491044E+01, 5.2836666E+01| 2.9998240E+04| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = 4.96367E-04 Event weight (ref) = -9.77307E+01 Event weight (prc) = 1.10912E+01 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034761903E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888583E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = 7.697588E+01 4.999534E+01 9.008653E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => 4.96367E-04 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => 1.10912E+01 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 1.8711951E+02; 4.8885826E+01,-1.4740977E+01,-4.9074934E+01| 2.9998240E+04| 3) 4 prt(o:-6| 2.2065264E+02;-1.2586171E+02,-3.5254367E+01, 4.0066281E+01| 2.9998240E+04| 4) 5 prt(o:21| 9.2227854E+01; 7.6975885E+01, 4.9995344E+01, 9.0086533E+00| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = -4.37375E-03 Squared matrix el. (prc) = 3.03476E-04 Event weight (ref) = -9.77307E+01 Event weight (prc) = 6.78112E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431492 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p2' TAO random-number generator: seed = 218431493 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 3.034761903E-04 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = 1.659778E+02 4.649104E+01 -5.283667E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = -1.659778E+02 -4.649104E+01 5.283667E+01 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 1.871195E+02 P = 4.888583E+01 -1.474098E+01 -4.907493E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.206526E+02 P = -1.258617E+02 -3.525437E+01 4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = 7.697588E+01 4.999534E+01 9.008653E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(6) E = 2.206526E+02 P = 1.258617E+02 3.525437E+01 -4.006628E+01 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 1.871195E+02 P = -6.823954E+01 9.319923E+00 -1.649161E+01 T = 2.999824000E+04 Parents: 1 2 Particle 5 [o] f(21) E = 9.222785E+01 P = -5.762217E+01 -4.457429E+01 5.655790E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "openloops_3_p2" process_num_id* => [unknown integer] sqme* => 3.03476E-04 sqme_ref* => -4.37375E-03 event_index* => 1 event_weight* => 6.78112E+00 event_weight_ref* => -9.77307E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.2065264E+02; 1.2586171E+02, 3.5254367E+01,-4.0066281E+01| 2.9998240E+04| 3) 4 prt(o:-6| 1.8711951E+02;-6.8239543E+01, 9.3199232E+00,-1.6491614E+01| 2.9998240E+04| 4) 5 prt(o:21| 9.2227854E+01;-5.7622167E+01,-4.4574291E+01, 5.6557895E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.22409E-02 Squared matrix el. (prc) = 1.22409E-02 Event weight (ref) = 2.73522E+02 Event weight (prc) = 2.73522E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'openloops_3_p3' TAO random-number generator: seed = 291241988 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'openloops_3_p3' TAO random-number generator: seed = 291241989 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(6) E = 2.500000E+02 P = -9.602929E+01 1.904619E+01 -1.513849E+02 T = 2.999824000E+04 Parents: 1 2 Particle 4 [o] f(-6) E = 2.500000E+02 P = 9.602929E+01 -1.904619E+01 1.513849E+02 T = 2.999824000E+04 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "openloops_3_p3" process_num_id* => [unknown integer] sqme* => 1.22409E-02 sqme_ref* => 1.22409E-02 event_index* => 1 event_weight* => 2.73522E+02 event_weight_ref* => 2.73522E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:6| 2.5000000E+02;-9.6029292E+01, 1.9046186E+01,-1.5138487E+02| 2.9998240E+04| 3) 4 prt(o:-6| 2.5000000E+02; 9.6029292E+01,-1.9046186E+01, 1.5138487E+02| 2.9998240E+04| 4) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-ext/nlo_7.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-ext/nlo_7.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-ext/nlo_7.ref (revision 8760) @@ -1,8792 +1,8792 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true openmp_num_threads = 1 SM.ms => 0.00000E+00 SM.mc => 0.00000E+00 SM.mb => 0.00000E+00 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $method = "dummy" ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true sqrts = 5.00000E+02 jet_algorithm = 2 jet_r = 5.00000E-01 seed = 1558 n_events = 10 $sample_normalization = "sigma" ?unweighted = false ?negative_weights = true ?keep_failed_events = true ?fixed_order_nlo_events = true ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false | Process library 'nlo_7_lib': recorded process 'nlo_7_p1' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1558 | Initializing integration for process nlo_7_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p1' | Library name = 'nlo_7_lib' | Process index = 1 | Process components: | 1: 'nlo_7_p1_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [dummy] | 2: 'nlo_7_p1_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_7_p1_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [virtual] | 4: 'nlo_7_p1_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.054E+05 7.27E+03 6.90 0.69 68.0 |-----------------------------------------------------------------------------| 1 100 1.054E+05 7.27E+03 6.90 0.69 68.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.054E+05 7.27E+03 6.90 0.00 68.0 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| | Starting simulation for process 'nlo_7_p1' | Simulate: using integration grids from file 'nlo_7_p1.m1.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1559 | Events: writing to ASCII file 'nlo_7_p1.debug' | Events: generating 10 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p1.debug' | Process library 'nlo_7_lib': unloading | Process library 'nlo_7_lib': open | Process library 'nlo_7_lib': recorded process 'nlo_7_p2' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1560 | Initializing integration for process nlo_7_p2: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p2.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p2' | Library name = 'nlo_7_lib' | Process index = 2 | Process components: | 1: 'nlo_7_p2_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive] | 2: 'nlo_7_p2_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [dummy], [real] | 3: 'nlo_7_p2_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [virtual] | 4: 'nlo_7_p2_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.817E+07 6.57E+06 36.18 3.62 5.2 |-----------------------------------------------------------------------------| 1 100 1.817E+07 6.57E+06 36.18 3.62 5.2 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.817E+07 6.57E+06 36.18 0.00 5.2 |=============================================================================| | Starting simulation for process 'nlo_7_p2' | Simulate: using integration grids from file 'nlo_7_p2.m2.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1561 | Events: writing to ASCII file 'nlo_7_p2.debug' | Events: generating 30 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p2.debug' | Process library 'nlo_7_lib': unloading | Process library 'nlo_7_lib': open | Process library 'nlo_7_lib': recorded process 'nlo_7_p3' | Integrate: current process library needs compilation | Process library 'nlo_7_lib': compiling ... | Process library 'nlo_7_lib': writing makefile | Process library 'nlo_7_lib': removing old files | Process library 'nlo_7_lib': writing driver | Process library 'nlo_7_lib': creating source code | Process library 'nlo_7_lib': compiling sources | Process library 'nlo_7_lib': linking | Process library 'nlo_7_lib': loading | Process library 'nlo_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1562 | Initializing integration for process nlo_7_p3: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 5.1099700E-04 GeV) | e+ (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_7_p3.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_7_p3' | Library name = 'nlo_7_lib' | Process index = 3 | Process components: | 1: 'nlo_7_p3_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive] | 2: 'nlo_7_p3_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_7_p3_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [dummy], [virtual] | 4: 'nlo_7_p3_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_7_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 7.843E+01 6.45E+00 8.22 0.82 59.0 |-----------------------------------------------------------------------------| 1 100 7.843E+01 6.45E+00 8.22 0.82 59.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 7.843E+01 6.45E+00 8.22 0.00 59.0 |=============================================================================| | Starting simulation for process 'nlo_7_p3' | Simulate: using integration grids from file 'nlo_7_p3.m3.vg' | Simulate: activating fixed-order NLO events | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1563 | Events: writing to ASCII file 'nlo_7_p3.debug' | Events: generating 10 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_7_p3.debug' | WHIZARD run finished. |=============================================================================| Contents of nlo_7_p1.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.303033E+02 2.009312E+01 -9.516652E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.303033E+02 -2.009312E+01 9.516652E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 1 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.5000000E+02; 2.3030328E+02, 2.0093120E+01,-9.5166522E+01| 0.0000000E+00| 3) 4 prt(o:2| 2.5000000E+02;-2.3030328E+02,-2.0093120E+01, 9.5166522E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 6 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 6 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.190015E+02 -1.602555E+01 -1.195053E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.190015E+02 1.602555E+01 1.195053E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 2 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-2.1900152E+02,-1.6025552E+01,-1.1950530E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 2.1900152E+02, 1.6025552E+01, 1.1950530E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 1.148880E+02 -1.015189E+02 -1.974706E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -1.148880E+02 1.015189E+02 1.974706E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 3 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-5| 2.5000000E+02; 1.1488797E+02,-1.0151895E+02,-1.9747065E+02| 0.0000000E+00| 3) 4 prt(o:5| 2.5000000E+02;-1.1488797E+02, 1.0151895E+02, 1.9747065E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 12 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 12 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -8.092247E+01 7.810847E+01 -2.232725E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 8.092247E+01 -7.810847E+01 2.232725E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-8.0922467E+01, 7.8108474E+01,-2.2327253E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 8.0922467E+01,-7.8108474E+01, 2.2327253E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 15 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 15 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = 2.172182E+02 6.866419E+01 1.029634E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = -2.172182E+02 -6.866419E+01 -1.029634E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 5 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.5000000E+02; 2.1721823E+02, 6.8664192E+01, 1.0296343E+02| 0.0000000E+00| 3) 4 prt(o:2| 2.5000000E+02;-2.1721823E+02,-6.8664192E+01,-1.0296343E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.718836E+02 -1.435798E+02 1.110896E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.718836E+02 1.435798E+02 -1.110896E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 6 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-1.7188357E+02,-1.4357975E+02, 1.1108958E+02| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 1.7188357E+02, 1.4357975E+02,-1.1108958E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 21 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 21 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.858836E+02 1.515349E+02 7.060076E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.858836E+02 -1.515349E+02 -7.060076E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 7 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.8588362E+02, 1.5153486E+02, 7.0600756E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.8588362E+02,-1.5153486E+02,-7.0600756E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 24 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 24 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -1.380982E+02 -1.987471E+02 6.267765E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 1.380982E+02 1.987471E+02 -6.267765E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 8 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-1| 2.5000000E+02;-1.3809822E+02,-1.9874706E+02, 6.2677654E+01| 0.0000000E+00| 3) 4 prt(o:1| 2.5000000E+02; 1.3809822E+02, 1.9874706E+02,-6.2677654E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = -2.233159E+02 -3.624658E+01 1.063777E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = 2.233159E+02 3.624658E+01 -1.063777E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 9 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-3| 2.5000000E+02;-2.2331587E+02,-3.6246582E+01, 1.0637766E+02| 0.0000000E+00| 3) 4 prt(o:3| 2.5000000E+02; 2.2331587E+02, 3.6246582E+01,-1.0637766E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 5.00000E+00 Squared matrix el. (prc) = 5.00000E+00 Event weight (ref) = 1.54929E+05 Event weight (prc) = 1.54929E+05 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105092 calls = 30 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p1' TAO random-number generator: seed = 102105093 calls = 30 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = 7.669623E+01 1.946583E+02 1.368424E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = -7.669623E+01 -1.946583E+02 -1.368424E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p1" process_num_id* => [unknown integer] sqme* => 5.00000E+00 sqme_ref* => 5.00000E+00 event_index* => 10 event_weight* => 1.54929E+05 event_weight_ref* => 1.54929E+05 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-5| 2.5000000E+02; 7.6696234E+01, 1.9465831E+02, 1.3684236E+02| 0.0000000E+00| 3) 4 prt(o:5| 2.5000000E+02;-7.6696234E+01,-1.9465831E+02,-1.3684236E+02| 0.0000000E+00| 4) ======================================================================== Contents of nlo_7_p2.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.43649E+00 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.69268E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358864E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104539E+01 P = -8.581748E+00 2.829877E+01 9.452491E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608388E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.43649E+00 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.69268E+04 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.7405031E+01, 2.2771282E+02,-6.8229998E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.7405031E+01,-2.2771282E+02, 6.8229998E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.34436E+03 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.51997E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358864E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104539E+01 P = -8.581748E+00 2.829877E+01 9.452491E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608388E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34436E+03 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.51997E+07 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 3.1045389E+01;-8.5817480E+00, 2.8298767E+01, 9.4524908E+00| 0.0000000E+00| 3) 4 prt(o:2| 2.4414255E+02;-7.5591448E+01,-2.2237756E+02, 6.6631385E+01| 0.0000000E+00| 4) 5 prt(o:21| 2.2481206E+02; 8.4173196E+01, 1.9407879E+02,-7.6083875E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.69015E+03 Squared matrix el. (prc) = 1.34436E+03 Event weight (ref) = 5.04264E+07 Event weight (prc) = 2.51997E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.344358864E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.740503E+01 2.277128E+02 -6.823000E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.740503E+01 -2.277128E+02 6.823000E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 3.104539E+01 P = -8.581748E+00 2.829877E+01 9.452491E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.441426E+02 P = -7.559145E+01 -2.223776E+02 6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = 8.417320E+01 1.940788E+02 -7.608388E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.441426E+02 P = 7.559145E+01 2.223776E+02 -6.663138E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 3.104539E+01 P = 1.133141E+01 -2.020972E+01 2.066356E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 2.248121E+02 P = -8.692286E+01 -2.021678E+02 4.596782E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34436E+03 sqme_ref* => 2.69015E+03 event_index* => 1 event_weight* => 2.51997E+07 event_weight_ref* => 5.04264E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4414255E+02; 7.5591448E+01, 2.2237756E+02,-6.6631385E+01| 0.0000000E+00| 3) 4 prt(o:4| 3.1045389E+01; 1.1331410E+01,-2.0209717E+01, 2.0663560E+01| 0.0000000E+00| 4) 5 prt(o:21| 2.2481206E+02;-8.6922858E+01,-2.0216784E+02, 4.5967825E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 2.04961E+00 Event weight (ref) = 1.22098E+08 Event weight (prc) = 1.83043E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365136459E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534399E+00 -6.315655E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = -1.140192E+01 2.199270E+01 -4.000800E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 2.04961E+00 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 1.83043E+05 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.2470250E+02, 2.0311083E+01,-1.0768586E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.2470250E+02,-2.0311083E+01, 1.0768586E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 1.36514E+03 Event weight (ref) = 1.22098E+08 Event weight (prc) = 1.21915E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365136459E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534399E+00 -6.315655E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = -1.140192E+01 2.199270E+01 -4.000800E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.36514E+03 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 1.21915E+08 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-2| 2.1343993E+02;-2.0386621E+02,-2.5343987E+00,-6.3156555E+01| 0.0000000E+00| 3) 4 prt(o:2| 2.3950348E+02; 2.1526813E+02,-1.9458300E+01, 1.0316455E+02| 0.0000000E+00| 4) 5 prt(o:21| 4.7056589E+01;-1.1401918E+01, 2.1992698E+01,-4.0008000E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.36719E+03 Squared matrix el. (prc) = 1.36514E+03 Event weight (ref) = 1.22098E+08 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-2) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.365136459E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.247025E+02 2.031108E+01 -1.076859E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.247025E+02 -2.031108E+01 1.076859E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-2) E = 2.134399E+02 P = -2.038662E+02 -2.534399E+00 -6.315655E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(2) E = 2.395035E+02 P = 2.152681E+02 -1.945830E+01 1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = -1.140192E+01 2.199270E+01 -4.000800E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.395035E+02 P = -2.152681E+02 1.945830E+01 -1.031646E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.134399E+02 P = 1.778159E+02 4.889109E+00 1.179584E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.705659E+01 P = 3.745220E+01 -2.434741E+01 -1.479389E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.36514E+03 sqme_ref* => 1.36719E+03 event_index* => 2 event_weight* => 0.00000E+00 event_weight_ref* => 1.22098E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.3950348E+02;-2.1526813E+02, 1.9458300E+01,-1.0316455E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.1343993E+02; 1.7781593E+02, 4.8891091E+00, 1.1795845E+02| 0.0000000E+00| 4) 5 prt(o:21| 4.7056589E+01; 3.7452196E+01,-2.4347409E+01,-1.4793894E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50428E+02 Squared matrix el. (prc) = 1.34286E+00 Event weight (ref) = 4.69422E+06 Event weight (prc) = 2.51716E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636844E+01 -2.180363E+02 -8.844250E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161621E+01 2.197846E+02 8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = -4.752234E+00 -1.748261E+00 -1.660102E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.34286E+00 sqme_ref* => 2.50428E+02 event_index* => 3 event_weight* => 2.51716E+04 event_weight_ref* => 4.69422E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.2322269E+01,-2.2195145E+02,-8.9482095E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.2322269E+01, 2.2195145E+02, 8.9482095E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50428E+02 Squared matrix el. (prc) = 1.24543E+02 Event weight (ref) = 4.69422E+06 Event weight (prc) = 2.33452E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636844E+01 -2.180363E+02 -8.844250E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161621E+01 2.197846E+02 8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = -4.752234E+00 -1.748261E+00 -1.660102E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.24543E+02 sqme_ref* => 2.50428E+02 event_index* => 3 event_weight* => 2.33452E+06 event_weight_ref* => 4.69422E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4737434E+02; 7.6368444E+01,-2.1803635E+02,-8.8442500E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4755933E+02;-7.1616210E+01, 2.1978461E+02, 8.8608510E+01| 0.0000000E+00| 4) 5 prt(o:21| 5.0663301E+00;-4.7522336E+00,-1.7482611E+00,-1.6601021E-01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.50428E+02 Squared matrix el. (prc) = 1.24543E+02 Event weight (ref) = 4.69422E+06 Event weight (prc) = 2.33452E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.232227E+01 -2.219514E+02 -8.948209E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.232227E+01 2.219514E+02 8.948209E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.473743E+02 P = 7.636844E+01 -2.180363E+02 -8.844250E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.475593E+02 P = -7.161621E+01 2.197846E+02 8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = -4.752234E+00 -1.748261E+00 -1.660102E-01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.475593E+02 P = 7.161621E+01 -2.197846E+02 -8.860851E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.473743E+02 P = -7.634914E+01 2.179771E+02 8.860503E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 5.066330E+00 P = 4.732932E+00 1.807497E+00 3.480879E-03 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.24543E+02 sqme_ref* => 2.50428E+02 event_index* => 3 event_weight* => 2.33452E+06 event_weight_ref* => 4.69422E+06 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4755933E+02; 7.1616210E+01,-2.1978461E+02,-8.8608510E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4737434E+02;-7.6349142E+01, 2.1797711E+02, 8.8605029E+01| 0.0000000E+00| 4) 5 prt(o:21| 5.0663301E+00; 4.7329318E+00, 1.8074970E+00, 3.4808792E-03| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746688E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -2.435277E+01 -1.603512E+01 9.468480E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.3221583E+02,-2.5714252E+00, 2.1216117E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.3221583E+02, 2.5714252E+00,-2.1216117E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746688E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -2.435277E+01 -1.603512E+01 9.468480E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.7450549E+02; 1.4409898E+02, 1.3706217E+01, 9.7466877E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.2642183E+02;-1.1974620E+02, 2.3289073E+00,-1.9215168E+02| 0.0000000E+00| 4) 5 prt(o:21| 9.9072675E+01;-2.4352772E+01,-1.6035124E+01, 9.4684805E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 36 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 36 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.322158E+02 -2.571425E+00 2.121612E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.322158E+02 2.571425E+00 -2.121612E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.745055E+02 P = 1.440990E+02 1.370622E+01 9.746688E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.264218E+02 P = -1.197462E+02 2.328907E+00 -1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -2.435277E+01 -1.603512E+01 9.468480E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.264218E+02 P = 1.197462E+02 -2.328907E+00 1.921517E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.745055E+02 P = -2.449134E+01 -1.603243E+01 -1.720329E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 9.907268E+01 P = -9.525486E+01 1.836134E+01 -2.011883E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.2642183E+02; 1.1974620E+02,-2.3289073E+00, 1.9215168E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.7450549E+02;-2.4491339E+01,-1.6032429E+01,-1.7203285E+02| 0.0000000E+00| 4) 5 prt(o:21| 9.9072675E+01;-9.5254864E+01, 1.8361336E+01,-2.0118828E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624320E+02 P = 1.138997E+02 6.273779E+01 9.733942E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = 5.289584E+01 4.378007E+01 5.487409E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.6701515E+02, 1.0665808E+02, 1.5241389E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.6701515E+02,-1.0665808E+02,-1.5241389E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624320E+02 P = 1.138997E+02 6.273779E+01 9.733942E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = 5.289584E+01 4.378007E+01 5.487409E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.6243197E+02; 1.1389974E+02, 6.2737795E+01, 9.7339424E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4967133E+02;-1.6679558E+02,-1.0651786E+02,-1.5221351E+02| 0.0000000E+00| 4) 5 prt(o:21| 8.7896698E+01; 5.2895836E+01, 4.3780068E+01, 5.4874089E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 45 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 45 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.245425045E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.670151E+02 1.066581E+02 1.524139E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.670151E+02 -1.066581E+02 -1.524139E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.624320E+02 P = 1.138997E+02 6.273779E+01 9.733942E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.496713E+02 P = -1.667956E+02 -1.065179E+02 -1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = 5.289584E+01 4.378007E+01 5.487409E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.496713E+02 P = 1.667956E+02 1.065179E+02 1.522135E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.624320E+02 P = -1.118934E+02 -6.145653E+01 -1.004346E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 8.789670E+01 P = -5.490216E+01 -4.506133E+01 -5.177894E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 5 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4967133E+02; 1.6679558E+02, 1.0651786E+02, 1.5221351E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.6243197E+02;-1.1189342E+02,-6.1456531E+01,-1.0043457E+02| 0.0000000E+00| 4) 5 prt(o:21| 8.7896698E+01;-5.4902158E+01,-4.5061332E+01,-5.1778943E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 3.89002E-01 Event weight (ref) = 7.29176E+03 Event weight (prc) = 7.29176E+03 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825239683E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284390E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072803E+02 P = -1.303455E+02 -1.319191E+02 9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 1.906577E+00 -3.645817E+01 3.067713E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 3.89002E-01 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 7.29176E+03 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.5720930E+02, 1.5910720E+02,-1.1166976E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.5720930E+02,-1.5910720E+02, 1.1166976E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 1.82524E+02 Event weight (ref) = 7.29176E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825239683E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284390E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072803E+02 P = -1.303455E+02 -1.319191E+02 9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 1.906577E+00 -3.645817E+01 3.067713E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.82524E+02 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4503411E+02; 1.2843896E+02, 1.6837730E+02,-1.2326488E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.0728026E+02;-1.3034554E+02,-1.3191913E+02, 9.2587754E+01| 0.0000000E+00| 4) 5 prt(o:21| 4.7685630E+01; 1.9065767E+00,-3.6458169E+01, 3.0677127E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.89002E-01 Squared matrix el. (prc) = 1.82524E+02 Event weight (ref) = 7.29176E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 54 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 54 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.825239683E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.572093E+02 1.591072E+02 -1.116698E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.572093E+02 -1.591072E+02 1.116698E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.450341E+02 P = 1.284390E+02 1.683773E+02 -1.232649E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.072803E+02 P = -1.303455E+02 -1.319191E+02 9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 1.906577E+00 -3.645817E+01 3.067713E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.072803E+02 P = 1.303455E+02 1.319191E+02 -9.258775E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.450341E+02 P = -1.387748E+02 -1.788379E+02 9.380970E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 4.768563E+01 P = 8.429272E+00 4.691880E+01 -1.221951E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.82524E+02 sqme_ref* => 3.89002E-01 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 7.29176E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.0728026E+02; 1.3034554E+02, 1.3191913E+02,-9.2587754E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4503411E+02;-1.3877481E+02,-1.7883793E+02, 9.3809705E+01| 0.0000000E+00| 4) 5 prt(o:21| 4.7685630E+01; 8.4292718E+00, 4.6918797E+01,-1.2219511E+00| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 8.24902E-01 Event weight (ref) = 1.54626E+04 Event weight (prc) = 1.54626E+04 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688750E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763859E+00 -8.718463E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101356E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981894E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 8.24902E-01 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 1.54626E+04 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.2301966E+01,-2.2379372E+02, 1.0917415E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.2301966E+01, 2.2379372E+02,-1.0917415E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 4.70269E+03 Event weight (ref) = 1.54626E+04 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688750E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763859E+00 -8.718463E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101356E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981894E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 4.70269E+03 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.0673038E+02;-9.7638590E+00,-8.7184634E+01,-6.0785524E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1013565E+02; 1.8745753E+01, 1.8810815E+02,-9.1765521E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.8313397E+02;-8.9818936E+00,-1.0092352E+02, 1.5255105E+02| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.24902E-01 Squared matrix el. (prc) = 4.70269E+03 Event weight (ref) = 1.54626E+04 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 63 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 63 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688750E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.230197E+01 -2.237937E+02 1.091741E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.230197E+01 2.237937E+02 -1.091741E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.067304E+02 P = -9.763859E+00 -8.718463E+01 -6.078552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.101356E+02 P = 1.874575E+01 1.881082E+02 -9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = -8.981894E+00 -1.009235E+02 1.525510E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.101356E+02 P = -1.874575E+01 -1.881082E+02 9.176552E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.067304E+02 P = 1.710021E+00 6.366723E+00 -1.065266E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.831340E+02 P = 1.703573E+01 1.817414E+02 1.476107E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 4.70269E+03 sqme_ref* => 8.24902E-01 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 1.54626E+04 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1013565E+02;-1.8745753E+01,-1.8810815E+02, 9.1765521E+01| 0.0000000E+00| 3) 4 prt(o:4| 1.0673038E+02; 1.7100212E+00, 6.3667233E+00,-1.0652659E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.8313397E+02; 1.7035731E+01, 1.8174143E+02, 1.4761067E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688750E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473681E+01 2.000447E+02 -5.273248E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708635E+01 P = -2.761834E+01 -5.055249E+01 7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541757E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 7.1117985E+01, 1.3017405E+02,-2.0123854E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-7.1117985E+01,-1.3017405E+02, 2.0123854E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688750E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473681E+01 2.000447E+02 -5.273248E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708635E+01 P = -2.761834E+01 -5.055249E+01 7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541757E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1996406E+02;-7.4736813E+01, 2.0004470E+02,-5.2732481E+01| 0.0000000E+00| 3) 4 prt(o:4| 9.7086346E+01;-2.7618341E+01,-5.0552492E+01, 7.8150056E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.8294959E+02; 1.0235515E+02,-1.4949221E+02,-2.5417575E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 72 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 72 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 4.702688750E+03 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 7.111799E+01 1.301741E+02 -2.012385E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -7.111799E+01 -1.301741E+02 2.012385E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.199641E+02 P = -7.473681E+01 2.000447E+02 -5.273248E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 9.708635E+01 P = -2.761834E+01 -5.055249E+01 7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = 1.023552E+02 -1.494922E+02 -2.541757E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 9.708635E+01 P = 2.761834E+01 5.055249E+01 -7.815006E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.199641E+02 P = 1.373975E+02 -8.535081E+01 1.490683E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.829496E+02 P = -1.650159E+02 3.479831E+01 -7.091821E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 8 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 9.7086346E+01; 2.7618341E+01, 5.0552492E+01,-7.8150056E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1996406E+02; 1.3739753E+02,-8.5350807E+01, 1.4906827E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.8294959E+02;-1.6501587E+02, 3.4798315E+01,-7.0918215E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.58453E-01 Event weight (ref) = 2.97017E+03 Event weight (prc) = 2.97017E+03 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691046E+02 -5.336321E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544066E+01 -1.134704E+02 4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536293E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.58453E-01 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 2.97017E+03 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-1.3197112E+02, 1.9849802E+02,-7.5380093E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 1.3197112E+02,-1.9849802E+02, 7.5380093E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.08776E+02 Event weight (ref) = 2.97017E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691046E+02 -5.336321E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544066E+01 -1.134704E+02 4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536293E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.08776E+02 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 0.00000E+00 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.4620692E+02;-1.7080359E+02, 1.6910456E+02,-5.3363212E+01| 0.0000000E+00| 3) 4 prt(o:4| 1.4291130E+02; 7.5440660E+01,-1.1347044E+02, 4.3090669E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.1088177E+02; 9.5362927E+01,-5.5634116E+01, 1.0272543E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.58453E-01 Squared matrix el. (prc) = 1.08776E+02 Event weight (ref) = 2.97017E+03 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 81 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 81 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -1.319711E+02 1.984980E+02 -7.538009E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 1.319711E+02 -1.984980E+02 7.538009E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.462069E+02 P = -1.708036E+02 1.691046E+02 -5.336321E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.429113E+02 P = 7.544066E+01 -1.134704E+02 4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = 9.536293E+01 -5.563412E+01 1.027254E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.429113E+02 P = -7.544066E+01 1.134704E+02 -4.309067E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.462069E+02 P = 1.640946E+02 -1.590135E+02 9.168156E+01 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.108818E+02 P = -8.865393E+01 4.554310E+01 -4.859089E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 1.08776E+02 sqme_ref* => 1.58453E-01 event_index* => 9 event_weight* => 0.00000E+00 event_weight_ref* => 2.97017E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.4291130E+02;-7.5440660E+01, 1.1347044E+02,-4.3090669E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.4620692E+02; 1.6409459E+02,-1.5901354E+02, 9.1681560E+01| 0.0000000E+00| 4) 5 prt(o:21| 1.1088177E+02;-8.8653929E+01, 4.5543100E+01,-4.8590891E+01| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686716E+01 1.081329E+02 -9.603933E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016601E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 8.7439956E+00, 8.9899620E+01,-2.3311285E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-8.7439956E+00,-8.9899620E+01, 2.3311285E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686716E+01 1.081329E+02 -9.603933E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016601E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 1.5540321E+02;-5.6867161E+01, 1.0813292E+02,-9.6039332E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.1681660E+02;-7.5833736E+00,-7.7966919E+01, 2.0217094E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.2778019E+02; 6.4450535E+01,-3.0166005E+01,-1.0613161E+02| 0.0000000E+00| 5) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 4 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236164 calls = 90 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p2' TAO random-number generator: seed = 102236165 calls = 90 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 1.087758565E+02 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 8.743996E+00 8.989962E+01 -2.331129E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -8.743996E+00 -8.989962E+01 2.331129E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 1.554032E+02 P = -5.686716E+01 1.081329E+02 -9.603933E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.168166E+02 P = -7.583374E+00 -7.796692E+01 2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = 6.445054E+01 -3.016601E+01 -1.061316E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 5 Particle 3 [o] f(-4) E = 2.168166E+02 P = 7.583374E+00 7.796692E+01 -2.021709E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 1.554032E+02 P = 6.779379E+01 4.206951E+00 1.397729E+02 T = 0.000000000E+00 Parents: 1 2 Particle 5 [o] f(21) E = 1.277802E+02 P = -7.537716E+01 -8.217387E+01 6.239805E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 3 n_tot* => 5 $process_id* => "nlo_7_p2" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 10 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.1681660E+02; 7.5833736E+00, 7.7966919E+01,-2.0217094E+02| 0.0000000E+00| 3) 4 prt(o:4| 1.5540321E+02; 6.7793786E+01, 4.2069508E+00, 1.3977289E+02| 0.0000000E+00| 4) 5 prt(o:21| 1.2778019E+02;-7.5377159E+01,-8.2173870E+01, 6.2398052E+01| 0.0000000E+00| 5) ======================================================================== Total number of regions: 10 alr || flst_real || i_real || em || mul || nreg || ftuples || flst_born || i_born 1 || [ 11,-11, -4, 4, 21] || 1 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -4, 4] || 1 2 || [ 11,-11, -4, 4, 21] || 1 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -4, 4] || 1 3 || [ 11,-11, -2, 2, 21] || 2 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -2, 2] || 2 4 || [ 11,-11, -2, 2, 21] || 2 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -2, 2] || 2 5 || [ 11,-11, -5, 5, 21] || 3 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -5, 5] || 3 6 || [ 11,-11, -5, 5, 21] || 3 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -5, 5] || 3 7 || [ 11,-11, -3, 3, 21] || 4 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -3, 3] || 4 8 || [ 11,-11, -3, 3, 21] || 4 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -3, 3] || 4 9 || [ 11,-11, -1, 1, 21] || 5 || 3 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -1, 1] || 5 10 || [ 11,-11, -1, 1, 21] || 5 || 4 || 1 || 2 || {(3,5),(4,5)} || [ 11,-11, -1, 1] || 5 ------------------------------------------------------------------------ Contents of nlo_7_p3.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.08358E-03 Squared matrix el. (prc) = 4.08358E-03 Event weight (ref) = 1.26569E+02 Event weight (prc) = 1.26569E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 3 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 3 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 9.840826E+01 1.816510E+02 1.407790E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -9.840826E+01 -1.816510E+02 -1.407790E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.08358E-03 sqme_ref* => 4.08358E-03 event_index* => 1 event_weight* => 1.26569E+02 event_weight_ref* => 1.26569E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 9.8408256E+01, 1.8165098E+02, 1.4077903E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-9.8408256E+01,-1.8165098E+02,-1.4077903E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.22190E-03 Squared matrix el. (prc) = 4.22190E-03 Event weight (ref) = 1.30782E+02 Event weight (prc) = 1.30782E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 6 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-5) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(5) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 6 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.128632E+02 9.742860E+01 -8.773207E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.128632E+02 -9.742860E+01 8.773207E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.22190E-03 sqme_ref* => 4.22190E-03 event_index* => 2 event_weight* => 1.30782E+02 event_weight_ref* => 1.30782E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.1286322E+02, 9.7428599E+01,-8.7732069E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.1286322E+02,-9.7428599E+01, 8.7732069E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #3 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 9 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 9 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 5.926230E+01 1.199128E+02 -2.112082E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -5.926230E+01 -1.199128E+02 2.112082E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 3 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 5.9262301E+01, 1.1991279E+02,-2.1120820E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-5.9262301E+01,-1.1991279E+02, 2.1120820E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #4 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 12 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 12 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -8.641267E+01 1.627540E+02 -1.689497E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 8.641267E+01 -1.627540E+02 1.689497E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 4 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-8.6412667E+01, 1.6275399E+02,-1.6894966E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 8.6412667E+01,-1.6275399E+02, 1.6894966E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #5 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.25951E-03 Squared matrix el. (prc) = 4.25951E-03 Event weight (ref) = 1.31947E+02 Event weight (prc) = 1.31947E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 15 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 15 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 2.015953E+02 1.345299E+02 -6.132742E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -2.015953E+02 -1.345299E+02 6.132742E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.25951E-03 sqme_ref* => 4.25951E-03 event_index* => 5 event_weight* => 1.31947E+02 event_weight_ref* => 1.31947E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 2.0159526E+02, 1.3452992E+02,-6.1327417E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-2.0159526E+02,-1.3452992E+02, 6.1327417E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #6 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 18 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 18 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.874043E+00 -1.068873E+02 2.259454E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.874043E+00 1.068873E+02 -2.259454E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 6 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-4.8740427E+00,-1.0688732E+02, 2.2594544E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 4.8740427E+00, 1.0688732E+02,-2.2594544E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #7 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 0.00000E+00 Squared matrix el. (prc) = 0.00000E+00 Event weight (ref) = 0.00000E+00 Event weight (prc) = 0.00000E+00 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 21 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 21 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -2.454947E+01 -1.120004E+02 -2.221559E+02 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 2.454947E+01 1.120004E+02 2.221559E+02 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 0.00000E+00 sqme_ref* => 0.00000E+00 event_index* => 7 event_weight* => 0.00000E+00 event_weight_ref* => 0.00000E+00 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-2.4549469E+01,-1.1200036E+02,-2.2215590E+02| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 2.4549469E+01, 1.1200036E+02, 2.2215590E+02| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #8 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.20249E-03 Squared matrix el. (prc) = 4.20249E-03 Event weight (ref) = 1.30180E+02 Event weight (prc) = 1.30180E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 24 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 24 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -4.541867E+01 2.254435E+02 -9.804265E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 4.541867E+01 -2.254435E+02 9.804265E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.20249E-03 sqme_ref* => 4.20249E-03 event_index* => 8 event_weight* => 1.30180E+02 event_weight_ref* => 1.30180E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-4.5418669E+01, 2.2544353E+02,-9.8042649E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 4.5418669E+01,-2.2544353E+02, 9.8042649E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #9 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.22672E-03 Squared matrix el. (prc) = 4.22672E-03 Event weight (ref) = 1.31006E+02 Event weight (prc) = 1.31006E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 27 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-3) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(3) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 27 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = 1.663400E+02 1.661970E+02 8.490902E+01 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = -1.663400E+02 -1.661970E+02 -8.490902E+01 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.22672E-03 sqme_ref* => 4.22672E-03 event_index* => 9 event_weight* => 1.31006E+02 event_weight_ref* => 1.31006E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02; 1.6634004E+02, 1.6619702E+02, 8.4909020E+01| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02;-1.6634004E+02,-1.6619702E+02,-8.4909020E+01| 0.0000000E+00| 4) ======================================================================== ======================================================================== Event #10 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.29218E-03 Squared matrix el. (prc) = 4.29218E-03 Event weight (ref) = 1.32959E+02 Event weight (prc) = 1.32959E+02 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 5 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367236 calls = 30 Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-1) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(1) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_7_p3' TAO random-number generator: seed = 102367237 calls = 30 Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [i] f(11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 2 [i] f(-11) E = 2.500000E+02 P = 0.000000E+00 0.000000E+00 -2.500000E+02 T = 2.611179340E-07 Children: 3 4 Particle 3 [o] f(-4) E = 2.500000E+02 P = -7.349568E+01 2.387822E+02 9.024078E+00 T = 0.000000000E+00 Parents: 1 2 Particle 4 [o] f(4) E = 2.500000E+02 P = 7.349568E+01 -2.387822E+02 -9.024078E+00 T = 0.000000000E+00 Parents: 1 2 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 5.00000E+02 sqrts_hat* => 5.00000E+02 n_in* => 2 n_out* => 2 n_tot* => 4 $process_id* => "nlo_7_p3" process_num_id* => [unknown integer] sqme* => 4.29218E-03 sqme_ref* => 4.29218E-03 event_index* => 10 event_weight* => 1.32959E+02 event_weight_ref* => 1.32959E+02 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(i:11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00,-2.5000000E+02| 2.6111793E-07| 1) 2 prt(i:-11|-2.5000000E+02; 0.0000000E+00, 0.0000000E+00, 2.5000000E+02| 2.6111793E-07| 2) 3 prt(o:-4| 2.5000000E+02;-7.3495680E+01, 2.3878223E+02, 9.0240776E+00| 0.0000000E+00| 3) 4 prt(o:4| 2.5000000E+02; 7.3495680E+01,-2.3878223E+02,-9.0240776E+00| 0.0000000E+00| 4) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output-ext/nlo_9.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output-ext/nlo_9.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output-ext/nlo_9.ref (revision 8760) @@ -1,4800 +1,4800 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true openmp_num_threads = 1 SM.ms => 0.00000E+00 SM.mc => 0.00000E+00 SM.mb => 0.00000E+00 SM.me => 0.00000E+00 [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) [user variable] elec = PDG(11, -11) $exclude_gauge_splittings = "t" $method = "dummy" $rng_method = "rng_stream" $integration_method = "vamp2" sqrts = 1.30000E+04 ?combined_nlo_integration = false ?use_vamp_equivalences = false seed = 3991 n_events = 2 $sample_normalization = "sigma" ?unweighted = false ?negative_weights = true ?keep_failed_events = true ?fixed_order_nlo_events = true ?debug_decay = false ?debug_process = false ?debug_verbose = false ?sample_pacify = true ?write_raw = false | Process library 'nlo_9_lib': recorded process 'nlo_9_p1' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3991 | Initializing integration for process nlo_9_p1: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Initialized builtin PDF CTEQ6L | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p1' | Library name = 'nlo_9_lib' | Process index = 1 | Process components: | 1: 'nlo_9_p1_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy] | 2: 'nlo_9_p1_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p1_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p1_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p1_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 4 dimensions | Integrator: Write grid header and grids to 'nlo_9_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 96 1.827E+07 7.39E+06 40.46 3.96 4.1 |-----------------------------------------------------------------------------| 1 96 1.827E+07 7.39E+06 40.46 3.96 4.1 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.827E+07 7.39E+06 40.46 0.00 4.1 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| | Starting simulation for process 'nlo_9_p1' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3992 | Events: writing to ASCII file 'nlo_9_p1.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p1.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p2' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3993 | Initializing integration for process nlo_9_p2: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p2.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p2' | Library name = 'nlo_9_lib' | Process index = 2 | Process components: | 1: 'nlo_9_p2_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p2_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [dummy], [real] | 3: 'nlo_9_p2_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p2_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p2_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 7 dimensions | Integrator: Write grid header and grids to 'nlo_9_p2.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p2.m2.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.432E+10 7.73E+09 53.98 5.40 5.0 |-----------------------------------------------------------------------------| 1 100 1.432E+10 7.73E+09 53.98 5.40 5.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.432E+10 7.73E+09 53.98 0.00 5.0 |=============================================================================| | Starting simulation for process 'nlo_9_p2' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3994 | Events: writing to ASCII file 'nlo_9_p2.debug' | Events: generating 8 weighted, unpolarized NLO events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p2.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p3' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3995 | Initializing integration for process nlo_9_p3: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p3.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p3.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p3' | Library name = 'nlo_9_lib' | Process index = 3 | Process components: | 1: 'nlo_9_p3_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p3_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p3_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy], [virtual] | 4: 'nlo_9_p3_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p3_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p3' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 4 dimensions | Integrator: Write grid header and grids to 'nlo_9_p3.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p3.m3.vg2'. | VAMP2: set chain: use chained weights. 1 96 1.148E+05 9.41E+04 81.94 8.03 2.6 |-----------------------------------------------------------------------------| 1 96 1.148E+05 9.41E+04 81.94 8.03 2.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.148E+05 9.41E+04 81.94 0.00 2.6 |=============================================================================| | Starting simulation for process 'nlo_9_p3' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3996 | Events: writing to ASCII file 'nlo_9_p3.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p3.debug' | Process library 'nlo_9_lib': unloading | Process library 'nlo_9_lib': open | Process library 'nlo_9_lib': recorded process 'nlo_9_p4' | Integrate: current process library needs compilation | Process library 'nlo_9_lib': compiling ... | Process library 'nlo_9_lib': writing makefile | Process library 'nlo_9_lib': removing old files | Process library 'nlo_9_lib': writing driver | Process library 'nlo_9_lib': creating source code | Process library 'nlo_9_lib': compiling sources | Process library 'nlo_9_lib': linking | Process library 'nlo_9_lib': loading | Process library 'nlo_9_lib': ... success. | Integrate: compilation done | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3997 | Initializing integration for process nlo_9_p4: | Beam structure: p, p => pdf_builtin | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p4.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_9_p4.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_9_p4' | Library name = 'nlo_9_lib' | Process index = 4 | Process components: | 1: 'nlo_9_p4_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive] | 2: 'nlo_9_p4_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [inactive], [real] | 3: 'nlo_9_p4_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [virtual] | 4: 'nlo_9_p4_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [inactive], [subtraction] | 5: 'nlo_9_p4_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => e-, e+ [dummy], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Beam structure: pdf_builtin, none => none, pdf_builtin | Beam structure: 2 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_9_p4' part 'dglap' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: Write grid header and grids to 'nlo_9_p4.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_9_p4.m4.vg2'. | VAMP2: set chain: use chained weights. 1 100 2.155E+08 2.04E+08 94.81 9.48 2.1 |-----------------------------------------------------------------------------| 1 100 2.155E+08 2.04E+08 94.81 9.48 2.1 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.155E+08 2.04E+08 94.81 0.00 2.1 |=============================================================================| | Starting simulation for process 'nlo_9_p4' | Simulate: activating fixed-order NLO events | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 3998 | Events: writing to ASCII file 'nlo_9_p4.debug' | Events: generating 2 weighted, unpolarized events ... | Events: event normalization mode 'sigma' | ... event sample complete. | Events: closing ASCII file 'nlo_9_p4.debug' | There were no errors and 4 warning(s). | WHIZARD run finished. |=============================================================================| Contents of nlo_9_p1.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 3.70571E+04 Squared matrix el. (prc) = 3.70571E+04 Event weight (ref) = 2.59265E+07 Event weight (prc) = 2.59265E+07 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 3270494107.0, 1218490942.0, 3220277207.0, 2821320218.0, 4220147848.0, 1218259235.0, ] Beginning substream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Initial stream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 870276730.0, 1525774502.0, 3988227742.0, 3787208568.0, 2984262882.0, 2541051477.0, ] Beginning substream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Initial stream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.886806E+00 P = 0.000000E+00 0.000000E+00 6.886806E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.264110E+02 P = 0.000000E+00 0.000000E+00 -3.264110E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493113E+03 P = 0.000000E+00 0.000000E+00 6.493113E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.173589E+03 P = 0.000000E+00 0.000000E+00 -6.173589E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.671787E+01 P = 3.698561E+01 7.025850E-01 -5.552337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.665799E+02 P = -3.698561E+01 -7.025850E-01 -2.640008E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.48247E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p1" process_num_id* => [unknown integer] sqme* => 3.70571E+04 sqme_ref* => 3.70571E+04 event_index* => 1 event_weight* => 2.59265E+07 event_weight_ref* => 2.59265E+07 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-2|-6.8868056E+00; 0.0000000E+00, 0.0000000E+00,-6.8868056E+00| 0.0000000E+00| 3) 4 prt(i:2|-3.2641096E+02; 0.0000000E+00, 0.0000000E+00, 3.2641096E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4931132E+03; 0.0000000E+00, 0.0000000E+00, 6.4931132E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.1735890E+03; 0.0000000E+00, 0.0000000E+00,-6.1735890E+03| 0.0000000E+00| 6) 7 prt(o:11| 6.6717870E+01; 3.6985611E+01, 7.0258495E-01,-5.5523374E+01| 0.0000000E+00| 7) 8 prt(o:-11| 2.6657990E+02;-3.6985611E+01,-7.0258495E-01,-2.6400078E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 6.87216E-01 Squared matrix el. (prc) = 6.87216E-01 Event weight (ref) = 2.69210E+03 Event weight (prc) = 2.69210E+03 ------------------------------------------------------------------------ Selected MCI group = 1 Selected term = 1 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 1817174340.0, 4169406181.0, 394187331.0, 860033000.0, 2212227538.0, 3653581942.0, ] Beginning substream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Initial stream = [ 4226523048.0, 3065015250.0, 1182429328.0, 1392969535.0, 3625333239.0, 3251691171.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p1' RNG Stream generator Current position = [ 976955966.0, 3946182281.0, 2474115998.0, 1111192673.0, 3759619853.0, 3640289132.0, ] Beginning substream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Initial stream = [ 3013866238.0, 581103679.0, 3358998661.0, 3484764854.0, 532756457.0, 2693721620.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(1) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 3.820435E+02 P = 0.000000E+00 0.000000E+00 3.820435E+02 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(1) E = 3.152966E+03 P = 0.000000E+00 0.000000E+00 -3.152966E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.117957E+03 P = 0.000000E+00 0.000000E+00 6.117957E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 3.347034E+03 P = 0.000000E+00 0.000000E+00 -3.347034E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.187597E+03 P = -8.345814E+02 6.303150E+02 -1.921394E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.347413E+03 P = 8.345814E+02 -6.303150E+02 -8.495285E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 2.19506E+03 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p1" process_num_id* => [unknown integer] sqme* => 6.87216E-01 sqme_ref* => 6.87216E-01 event_index* => 2 event_weight* => 2.69210E+03 event_weight_ref* => 2.69210E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-1|-3.8204346E+02; 0.0000000E+00, 0.0000000E+00,-3.8204346E+02| 0.0000000E+00| 3) 4 prt(i:1|-3.1529664E+03; 0.0000000E+00, 0.0000000E+00, 3.1529664E+03| 0.0000000E+00| 4) 5 prt(o:92| 6.1179565E+03; 0.0000000E+00, 0.0000000E+00, 6.1179565E+03| 0.0000000E+00| 5) 6 prt(o:-92| 3.3470336E+03; 0.0000000E+00, 0.0000000E+00,-3.3470336E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.1875968E+03;-8.3458144E+02, 6.3031503E+02,-1.9213944E+03| 0.0000000E+00| 7) 8 prt(o:-11| 1.3474130E+03; 8.3458144E+02,-6.3031503E+02,-8.4952849E+02| 0.0000000E+00| 8) ======================================================================== Contents of nlo_9_p2.debug: Total number of regions: 30 alr || flst_real || i_real || em || mul || nreg || ftuples || flst_born || i_born 1 || [ -4, 4, 11,-11, 21] || 1 || 0 || 1 || 1 || {(0,5)} || [ -4, 4, 11,-11] || 1 2 || [ -4, 21, 11,-11, -4] || 2 || 2 || 1 || 1 || {(2,5)} || [ -4, 4, 11,-11] || 1 3 || [ -2, 2, 11,-11, 21] || 3 || 0 || 1 || 1 || {(0,5)} || [ -2, 2, 11,-11] || 2 4 || [ -2, 21, 11,-11, -2] || 4 || 2 || 1 || 1 || {(2,5)} || [ -2, 2, 11,-11] || 2 5 || [ 2, -2, 11,-11, 21] || 5 || 0 || 1 || 1 || {(0,5)} || [ 2, -2, 11,-11] || 3 6 || [ 2, 21, 11,-11, 2] || 6 || 2 || 1 || 1 || {(2,5)} || [ 2, -2, 11,-11] || 3 7 || [ 4, -4, 11,-11, 21] || 7 || 0 || 1 || 1 || {(0,5)} || [ 4, -4, 11,-11] || 4 8 || [ 4, 21, 11,-11, 4] || 8 || 2 || 1 || 1 || {(2,5)} || [ 4, -4, 11,-11] || 4 9 || [ -5, 5, 11,-11, 21] || 9 || 0 || 1 || 1 || {(0,5)} || [ -5, 5, 11,-11] || 5 10 || [ -5, 21, 11,-11, -5] || 10 || 2 || 1 || 1 || {(2,5)} || [ -5, 5, 11,-11] || 5 11 || [ -3, 3, 11,-11, 21] || 11 || 0 || 1 || 1 || {(0,5)} || [ -3, 3, 11,-11] || 6 12 || [ -3, 21, 11,-11, -3] || 12 || 2 || 1 || 1 || {(2,5)} || [ -3, 3, 11,-11] || 6 13 || [ -1, 1, 11,-11, 21] || 13 || 0 || 1 || 1 || {(0,5)} || [ -1, 1, 11,-11] || 7 14 || [ -1, 21, 11,-11, -1] || 14 || 2 || 1 || 1 || {(2,5)} || [ -1, 1, 11,-11] || 7 15 || [ 1, -1, 11,-11, 21] || 15 || 0 || 1 || 1 || {(0,5)} || [ 1, -1, 11,-11] || 8 16 || [ 1, 21, 11,-11, 1] || 16 || 2 || 1 || 1 || {(2,5)} || [ 1, -1, 11,-11] || 8 17 || [ 3, -3, 11,-11, 21] || 17 || 0 || 1 || 1 || {(0,5)} || [ 3, -3, 11,-11] || 9 18 || [ 3, 21, 11,-11, 3] || 18 || 2 || 1 || 1 || {(2,5)} || [ 3, -3, 11,-11] || 9 19 || [ 5, -5, 11,-11, 21] || 19 || 0 || 1 || 1 || {(0,5)} || [ 5, -5, 11,-11] || 10 20 || [ 5, 21, 11,-11, 5] || 20 || 2 || 1 || 1 || {(2,5)} || [ 5, -5, 11,-11] || 10 21 || [ 21, -4, 11,-11, -4] || 21 || 1 || 1 || 1 || {(1,5)} || [ 4, -4, 11,-11] || 4 22 || [ 21, -2, 11,-11, -2] || 22 || 1 || 1 || 1 || {(1,5)} || [ 2, -2, 11,-11] || 3 23 || [ 21, 2, 11,-11, 2] || 23 || 1 || 1 || 1 || {(1,5)} || [ -2, 2, 11,-11] || 2 24 || [ 21, 4, 11,-11, 4] || 24 || 1 || 1 || 1 || {(1,5)} || [ -4, 4, 11,-11] || 1 25 || [ 21, -5, 11,-11, -5] || 25 || 1 || 1 || 1 || {(1,5)} || [ 5, -5, 11,-11] || 10 26 || [ 21, -3, 11,-11, -3] || 26 || 1 || 1 || 1 || {(1,5)} || [ 3, -3, 11,-11] || 9 27 || [ 21, -1, 11,-11, -1] || 27 || 1 || 1 || 1 || {(1,5)} || [ 1, -1, 11,-11] || 8 28 || [ 21, 1, 11,-11, 1] || 28 || 1 || 1 || 1 || {(1,5)} || [ -1, 1, 11,-11] || 7 29 || [ 21, 3, 11,-11, 3] || 29 || 1 || 1 || 1 || {(1,5)} || [ -3, 3, 11,-11] || 6 30 || [ 21, 5, 11,-11, 5] || 30 || 1 || 1 || 1 || {(1,5)} || [ -5, 5, 11,-11] || 5 ------------------------------------------------------------------------ ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 7.40062E+03 Event weight (ref) = 1.00516E+09 Event weight (prc) = 8.95289E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864437E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.30010E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 7.40062E+03 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 8.95289E+05 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-6.3427874E+00; 0.0000000E+00, 0.0000000E+00,-6.3427874E+00| 0.0000000E+00| 3) 4 prt(i:4|-3.4090636E+02; 0.0000000E+00, 0.0000000E+00, 3.4090636E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4936572E+03; 0.0000000E+00, 0.0000000E+00, 6.4936572E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.1590936E+03; 0.0000000E+00, 0.0000000E+00,-6.1590936E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.5798314E+01; 1.2978902E+01,-2.2934559E+01,-2.4229598E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1145084E+02;-1.2978902E+01, 2.2934559E+01,-3.1033398E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 2.16231E+05 Event weight (ref) = 1.00516E+09 Event weight (prc) = 2.61585E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864437E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 2.16231E+05 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 2.61585E+07 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-1|-6.3910148E+00; 0.0000000E+00, 0.0000000E+00,-6.3910148E+00| 0.0000000E+00| 3) 4 prt(i:1|-4.3483007E+02; 0.0000000E+00, 0.0000000E+00, 4.3483007E+02| 0.0000000E+00| 4) 5 prt(o:92| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.0651699E+03; 0.0000000E+00, 0.0000000E+00,-6.0651699E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393841E+01; 1.1353673E+01,-2.4091464E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600053E+01, 2.1780555E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:21| 9.3653318E+01; 3.2463798E+00, 2.3109086E+00,-9.3568503E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 1.85537E+06 Event weight (ref) = 1.00516E+09 Event weight (prc) = 2.24453E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864437E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 1.85537E+06 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 2.24453E+08 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:1|-6.3910148E+00; 0.0000000E+00, 0.0000000E+00,-6.3910148E+00| 0.0000000E+00| 3) 4 prt(i:21|-4.3483007E+02; 0.0000000E+00, 0.0000000E+00, 4.3483007E+02| 0.0000000E+00| 4) 5 prt(o:-92| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:93| 6.0651699E+03; 0.0000000E+00, 0.0000000E+00,-6.0651699E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393841E+01; 1.1353673E+01,-2.4091464E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600053E+01, 2.1780555E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:1| 9.3653318E+01; 3.2463798E+00, 2.3109086E+00,-9.3568503E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 8.30886E+06 Squared matrix el. (prc) = 6.22986E+06 Event weight (ref) = 1.00516E+09 Event weight (prc) = 7.53657E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 2125751043.0, 3119684730.0, 3239440115.0, 2925436940.0, 1582887005.0, 7211591.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-3) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(3) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1930342972.0, 3957482835.0, 230286771.0, 1399951024.0, 1008217281.0, 1436520322.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.229864437E+06 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.342787E+00 P = 0.000000E+00 0.000000E+00 6.342787E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.409064E+02 P = 0.000000E+00 0.000000E+00 -3.409064E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.493657E+03 P = 0.000000E+00 0.000000E+00 6.493657E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.159094E+03 P = 0.000000E+00 0.000000E+00 -6.159094E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.579831E+01 P = 1.297890E+01 -2.293456E+01 -2.422960E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.114508E+02 P = -1.297890E+01 2.293456E+01 -3.103340E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(1) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 6.391015E+00 P = 0.000000E+00 0.000000E+00 6.391015E+00 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(2) E = 4.348301E+02 P = 0.000000E+00 0.000000E+00 -4.348301E+02 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 6.493609E+03 P = 0.000000E+00 0.000000E+00 6.493609E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.065170E+03 P = 0.000000E+00 0.000000E+00 -6.065170E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 3.639384E+01 P = 1.135367E+01 -2.409146E+01 -2.480337E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 3.111739E+02 P = -1.460005E+01 2.178056E+01 -3.100672E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(2) E = 9.365332E+01 P = 3.246380E+00 2.310909E+00 -9.356850E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.05433E+02 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.22986E+06 sqme_ref* => 8.30886E+06 event_index* => 1 event_weight* => 7.53657E+08 event_weight_ref* => 1.00516E+09 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:21|-6.3910148E+00; 0.0000000E+00, 0.0000000E+00,-6.3910148E+00| 0.0000000E+00| 3) 4 prt(i:2|-4.3483007E+02; 0.0000000E+00, 0.0000000E+00, 4.3483007E+02| 0.0000000E+00| 4) 5 prt(o:93| 6.4936090E+03; 0.0000000E+00, 0.0000000E+00, 6.4936090E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.0651699E+03; 0.0000000E+00, 0.0000000E+00,-6.0651699E+03| 0.0000000E+00| 6) 7 prt(o:11| 3.6393841E+01; 1.1353673E+01,-2.4091464E+01,-2.4803370E+01| 0.0000000E+00| 7) 8 prt(o:-11| 3.1117393E+02;-1.4600053E+01, 2.1780555E+01,-3.1006718E+02| 0.0000000E+00| 8) 9 prt(o:2| 9.3653318E+01; 3.2463798E+00, 2.3109086E+00,-9.3568503E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = -7.22695E+03 Event weight (ref) = 3.07001E+08 Event weight (prc) = -2.81358E+05 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066989E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.11989E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => -7.22695E+03 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => -2.81358E+05 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-1.0203303E+03; 0.0000000E+00, 0.0000000E+00,-1.0203303E+03| 0.0000000E+00| 3) 4 prt(i:4|-2.0378805E+00; 0.0000000E+00, 0.0000000E+00, 2.0378805E+00| 0.0000000E+00| 4) 5 prt(o:92| 5.4796697E+03; 0.0000000E+00, 0.0000000E+00, 5.4796697E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4979621E+03; 0.0000000E+00, 0.0000000E+00,-6.4979621E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.8155129E+02;-2.0762780E+01, 3.5003646E+01, 2.7859430E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4081694E+02; 2.0762780E+01,-3.5003646E+01, 7.3969817E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = 2.23960E+05 Event weight (ref) = 3.07001E+08 Event weight (prc) = 8.71918E+06 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066989E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 2.23960E+05 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => 8.71918E+06 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:2|-1.0761179E+03; 0.0000000E+00, 0.0000000E+00,-1.0761179E+03| 0.0000000E+00| 3) 4 prt(i:-2|-2.1012438E+00; 0.0000000E+00, 0.0000000E+00, 2.1012438E+00| 0.0000000E+00| 4) 5 prt(o:-92| 5.4238821E+03; 0.0000000E+00, 0.0000000E+00, 5.4238821E+03| 0.0000000E+00| 5) 6 prt(o:92| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797004E+02;-2.2099732E+01, 3.3747855E+01, 2.7502732E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523148E+02; 1.9415336E+01,-3.6269293E+01, 7.4409511E+02| 0.0000000E+00| 8) 9 prt(o:21| 5.5017596E+01; 2.6843964E+00, 2.5214379E+00, 5.4894192E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = 6.98237E+06 Event weight (ref) = 3.07001E+08 Event weight (prc) = 2.71836E+08 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066989E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.98237E+06 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => 2.71836E+08 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:1|-1.0761179E+03; 0.0000000E+00, 0.0000000E+00,-1.0761179E+03| 0.0000000E+00| 3) 4 prt(i:21|-2.1012438E+00; 0.0000000E+00, 0.0000000E+00, 2.1012438E+00| 0.0000000E+00| 4) 5 prt(o:-92| 5.4238821E+03; 0.0000000E+00, 0.0000000E+00, 5.4238821E+03| 0.0000000E+00| 5) 6 prt(o:93| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797004E+02;-2.2099732E+01, 3.3747855E+01, 2.7502732E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523148E+02; 1.9415336E+01,-3.6269293E+01, 7.4409511E+02| 0.0000000E+00| 8) 9 prt(o:1| 5.5017596E+01; 2.6843964E+00, 2.5214379E+00, 5.4894192E+01| 0.0000000E+00| 9) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.88561E+06 Squared matrix el. (prc) = 6.86507E+05 Event weight (ref) = 3.07001E+08 Event weight (prc) = 2.67269E+07 ------------------------------------------------------------------------ Selected MCI group = 2 Selected term = 5 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 3744648883.0, 3101498919.0, 3140563258.0, 3989000131.0, 1600404546.0, 3801299494.0, ] Beginning substream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Initial stream = [ 4251240501.0, 2108766020.0, 3246026613.0, 1344164347.0, 2774833281.0, 3776333211.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p2' RNG Stream generator Current position = [ 1641581573.0, 2692482027.0, 733933807.0, 3381237756.0, 3242070282.0, 2443650744.0, ] Beginning substream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Initial stream = [ 3454451130.0, 4092915208.0, 285007697.0, 627160781.0, 3409592340.0, 357657504.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 6.865066989E+05 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 1.020330E+03 P = 0.000000E+00 0.000000E+00 1.020330E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 2.037880E+00 P = 0.000000E+00 0.000000E+00 -2.037880E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 5.479670E+03 P = 0.000000E+00 0.000000E+00 5.479670E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.497962E+03 P = 0.000000E+00 0.000000E+00 -6.497962E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.815513E+02 P = -2.076278E+01 3.500365E+01 2.785943E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.408169E+02 P = 2.076278E+01 -3.500365E+01 7.396982E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-2) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(21) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(21) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(-92*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(93*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(21) E = 1.076118E+03 P = 0.000000E+00 0.000000E+00 1.076118E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 9 Particle 4 [i] f(-1) E = 2.101244E+00 P = 0.000000E+00 0.000000E+00 -2.101244E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 9 Particle 5 [x] f(93*) E = 5.423882E+03 P = 0.000000E+00 0.000000E+00 5.423882E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.497899E+03 P = 0.000000E+00 0.000000E+00 -6.497899E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.779700E+02 P = -2.209973E+01 3.374786E+01 2.750273E+02 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 7.452315E+02 P = 1.941534E+01 -3.626929E+01 7.440951E+02 T = 0.000000000E+00 Parents: 3 4 Particle 9 [o] f(-1) E = 5.501760E+01 P = 2.684396E+00 2.521438E+00 5.489419E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.51039E+01 n_in* => 2 n_out* => 5 n_tot* => 7 $process_id* => "nlo_9_p2" process_num_id* => [unknown integer] sqme* => 6.86507E+05 sqme_ref* => 7.88561E+06 event_index* => 2 event_weight* => 2.67269E+07 event_weight_ref* => 3.07001E+08 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:21|-1.0761179E+03; 0.0000000E+00, 0.0000000E+00,-1.0761179E+03| 0.0000000E+00| 3) 4 prt(i:-1|-2.1012438E+00; 0.0000000E+00, 0.0000000E+00, 2.1012438E+00| 0.0000000E+00| 4) 5 prt(o:93| 5.4238821E+03; 0.0000000E+00, 0.0000000E+00, 5.4238821E+03| 0.0000000E+00| 5) 6 prt(o:92| 6.4978988E+03; 0.0000000E+00, 0.0000000E+00,-6.4978988E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.7797004E+02;-2.2099732E+01, 3.3747855E+01, 2.7502732E+02| 0.0000000E+00| 7) 8 prt(o:-11| 7.4523148E+02; 1.9415336E+01,-3.6269293E+01, 7.4409511E+02| 0.0000000E+00| 8) 9 prt(o:-1| 5.5017596E+01; 2.6843964E+00, 2.5214379E+00, 5.4894192E+01| 0.0000000E+00| 9) ======================================================================== Contents of nlo_9_p3.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 2.12930E+01 Squared matrix el. (prc) = 2.12930E+01 Event weight (ref) = 6.36286E+03 Event weight (prc) = 6.36286E+03 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 6 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 2596865362.0, 2097861302.0, 1710419373.0, 4132755378.0, 3334395289.0, 3898036172.0, ] Beginning substream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Initial stream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-2) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 2690940837.0, 944023296.0, 3856628408.0, 3483223282.0, 1004971824.0, 2058251242.0, ] Beginning substream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Initial stream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.185003E+03 P = 0.000000E+00 0.000000E+00 2.185003E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.021359E+00 P = 0.000000E+00 0.000000E+00 -1.021359E+00 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 4.314997E+03 P = 0.000000E+00 0.000000E+00 4.314997E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.498979E+03 P = 0.000000E+00 0.000000E+00 -6.498979E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 1.927631E+03 P = 2.524833E+01 -1.704463E+01 1.927390E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 2.583928E+02 P = -2.524833E+01 1.704463E+01 2.565908E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.44812E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p3" process_num_id* => [unknown integer] sqme* => 2.12930E+01 sqme_ref* => 2.12930E+01 event_index* => 1 event_weight* => 6.36286E+03 event_weight_ref* => 6.36286E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-2.1850027E+03; 0.0000000E+00, 0.0000000E+00,-2.1850027E+03| 0.0000000E+00| 3) 4 prt(i:4|-1.0213593E+00; 0.0000000E+00, 0.0000000E+00, 1.0213593E+00| 0.0000000E+00| 4) 5 prt(o:92| 4.3149973E+03; 0.0000000E+00, 0.0000000E+00, 4.3149973E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4989786E+03; 0.0000000E+00, 0.0000000E+00,-6.4989786E+03| 0.0000000E+00| 6) 7 prt(o:11| 1.9276312E+03; 2.5248333E+01,-1.7044627E+01, 1.9273905E+03| 0.0000000E+00| 7) 8 prt(o:-11| 2.5839283E+02;-2.5248333E+01, 1.7044627E+01, 2.5659084E+02| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 4.24170E+01 Squared matrix el. (prc) = 4.24170E+01 Event weight (ref) = 1.65951E+03 Event weight (prc) = 1.65951E+03 ------------------------------------------------------------------------ Selected MCI group = 3 Selected term = 6 Selected channel = 2 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 1150698303.0, 3394442877.0, 1602037449.0, 443345876.0, 714281248.0, 3904759980.0, ] Beginning substream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Initial stream = [ 4275957954.0, 1152516790.0, 1014656811.0, 1295359159.0, 1924333323.0, 6030808.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(1) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-1) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p3' RNG Stream generator Current position = [ 845567059.0, 1878523320.0, 621290442.0, 2282089536.0, 2749647619.0, 2527962339.0, ] Beginning substream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Initial stream = [ 3895036022.0, 3309759650.0, 1505983820.0, 2064501151.0, 1991483780.0, 2316537831.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 5.446662E+01 P = 0.000000E+00 0.000000E+00 5.446662E+01 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 3.800181E+01 P = 0.000000E+00 0.000000E+00 -3.800181E+01 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 6.445533E+03 P = 0.000000E+00 0.000000E+00 6.445533E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 6.461998E+03 P = 0.000000E+00 0.000000E+00 -6.461998E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 5.114652E+01 P = -2.495714E+01 -2.664578E+01 3.582054E+01 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 4.132191E+01 P = 2.495714E+01 2.664578E+01 -1.935572E+01 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 9.09908E+01 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p3" process_num_id* => [unknown integer] sqme* => 4.24170E+01 sqme_ref* => 4.24170E+01 event_index* => 2 event_weight* => 1.65951E+03 event_weight_ref* => 1.65951E+03 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-5.4466623E+01; 0.0000000E+00, 0.0000000E+00,-5.4466623E+01| 0.0000000E+00| 3) 4 prt(i:4|-3.8001808E+01; 0.0000000E+00, 0.0000000E+00, 3.8001808E+01| 0.0000000E+00| 4) 5 prt(o:92| 6.4455334E+03; 0.0000000E+00, 0.0000000E+00, 6.4455334E+03| 0.0000000E+00| 5) 6 prt(o:-92| 6.4619982E+03; 0.0000000E+00, 0.0000000E+00,-6.4619982E+03| 0.0000000E+00| 6) 7 prt(o:11| 5.1146524E+01;-2.4957136E+01,-2.6645778E+01, 3.5820536E+01| 0.0000000E+00| 7) 8 prt(o:-11| 4.1321907E+01; 2.4957136E+01, 2.6645778E+01,-1.9355720E+01| 0.0000000E+00| 8) ======================================================================== Contents of nlo_9_p4.debug: ======================================================================== Event #1 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 1.05161E-13 Squared matrix el. (prc) = 1.05161E-13 Event weight (ref) = 7.75946E-13 Event weight (prc) = 7.75946E-13 ------------------------------------------------------------------------ Selected MCI group = 4 Selected term = 7 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 112567446.0, 2537546482.0, 955490456.0, 493528515.0, 744046788.0, 3090452419.0, ] Beginning substream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Initial stream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-2) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(2) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 1453789347.0, 653147693.0, 3790828741.0, 3331230639.0, 15326295.0, 3964323346.0, ] Beginning substream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Initial stream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 6.245584E+03 P = 0.000000E+00 0.000000E+00 6.245584E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 6.275741E+03 P = 0.000000E+00 0.000000E+00 -6.275741E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 2.544156E+02 P = 0.000000E+00 0.000000E+00 2.544156E+02 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 2.242589E+02 P = 0.000000E+00 0.000000E+00 -2.242589E+02 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 6.267285E+03 P = -1.909099E+02 5.621337E+03 -2.764595E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 6.254041E+03 P = 1.909099E+02 -5.621337E+03 2.734438E+03 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 1.25213E+04 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p4" process_num_id* => [unknown integer] sqme* => 1.05161E-13 sqme_ref* => 1.05161E-13 event_index* => 1 event_weight* => 7.75946E-13 event_weight_ref* => 7.75946E-13 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-6.2455844E+03; 0.0000000E+00, 0.0000000E+00,-6.2455844E+03| 0.0000000E+00| 3) 4 prt(i:4|-6.2757411E+03; 0.0000000E+00, 0.0000000E+00, 6.2757411E+03| 0.0000000E+00| 4) 5 prt(o:92| 2.5441558E+02; 0.0000000E+00, 0.0000000E+00, 2.5441558E+02| 0.0000000E+00| 5) 6 prt(o:-92| 2.2425890E+02; 0.0000000E+00, 0.0000000E+00,-2.2425890E+02| 0.0000000E+00| 6) 7 prt(o:11| 6.2672848E+03;-1.9090987E+02, 5.6213367E+03,-2.7645949E+03| 0.0000000E+00| 7) 8 prt(o:-11| 6.2540408E+03; 1.9090987E+02,-5.6213367E+03, 2.7344382E+03| 0.0000000E+00| 8) ======================================================================== ======================================================================== Event #2 ------------------------------------------------------------------------ Unweighted = F Normalization = 'sigma' Helicity handling = drop Keep correlations = F ------------------------------------------------------------------------ Squared matrix el. (ref) = 7.58498E-02 Squared matrix el. (prc) = 7.58498E-02 Event weight (ref) = 7.08197E+01 Event weight (prc) = 7.08197E+01 ------------------------------------------------------------------------ Selected MCI group = 4 Selected term = 7 Selected channel = 1 ------------------------------------------------------------------------ Passed selection = T Reweighting factor = 1.00000E+00 Analysis flag = T ======================================================================== Event transform: trivial (hard process) ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 2964943828.0, 3006961225.0, 2205962508.0, 235002314.0, 4260252546.0, 4030348999.0, ] Beginning substream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Initial stream = [ 5708320.0, 196267560.0, 3078254096.0, 1246553971.0, 1073833365.0, 530672848.0, ] Number of tries = 1 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(2) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(-2) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(-92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 ======================================================================== ======================================================================== Event transform: NLO ------------------------------------------------------------------------ Associated process: 'nlo_9_p4' RNG Stream generator Current position = [ 2927356149.0, 2992177383.0, 3989844751.0, 720065746.0, 2244661502.0, 4119271164.0, ] Beginning substream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Initial stream = [ 40653827.0, 2526604092.0, 2726959943.0, 3501841521.0, 573375220.0, 4275418158.0, ] Number of tries = 0 ------------------------------------------------------------------------ Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 sqme_rad = 0.000000000E+00 i_evaluation = 0 ------------------------------------------------------------------------ Radiated particle sets: Particle set: ------------------------------------------------------------------------ Particle 1 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 6.500000E+03 T = 0.000000000E+00 Children: 3 5 Particle 2 [b] f(2212) E = 6.500000E+03 P = 0.000000E+00 0.000000E+00 -6.500000E+03 T = 0.000000000E+00 Children: 4 6 Particle 3 [i] f(-4) E = 2.613009E+03 P = 0.000000E+00 0.000000E+00 2.613009E+03 T = 0.000000000E+00 Parents: 1 Children: 7 8 Particle 4 [i] f(4) E = 1.157039E+03 P = 0.000000E+00 0.000000E+00 -1.157039E+03 T = 0.000000000E+00 Parents: 2 Children: 7 8 Particle 5 [x] f(92*) E = 3.886991E+03 P = 0.000000E+00 0.000000E+00 3.886991E+03 T = 0.000000000E+00 Parents: 1 Particle 6 [x] f(-92*) E = 5.342961E+03 P = 0.000000E+00 0.000000E+00 -5.342961E+03 T = 0.000000000E+00 Parents: 2 Particle 7 [o] f(11) E = 2.504059E+03 P = 7.835756E+02 4.724851E+02 2.330897E+03 T = 0.000000000E+00 Parents: 3 4 Particle 8 [o] f(-11) E = 1.265990E+03 P = -7.835756E+02 -4.724851E+02 -8.749268E+02 T = 0.000000000E+00 Parents: 3 4 ------------------------------------------------------------------------ ======================================================================== Local variables: ------------------------------------------------------------------------ sqrts* = 1.30000E+04 sqrts_hat* => 3.47756E+03 n_in* => 2 n_out* => 4 n_tot* => 6 $process_id* => "nlo_9_p4" process_num_id* => [unknown integer] sqme* => 7.58498E-02 sqme_ref* => 7.58498E-02 event_index* => 2 event_weight* => 7.08197E+01 event_weight_ref* => 7.08197E+01 event_excess* => 0.00000E+00 ------------------------------------------------------------------------ subevent: 1 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00,-6.5000000E+03| 0.0000000E+00| 1) 2 prt(b:2212|-6.5000000E+03; 0.0000000E+00, 0.0000000E+00, 6.5000000E+03| 0.0000000E+00| 2) 3 prt(i:-4|-2.6130095E+03; 0.0000000E+00, 0.0000000E+00,-2.6130095E+03| 0.0000000E+00| 3) 4 prt(i:4|-1.1570394E+03; 0.0000000E+00, 0.0000000E+00, 1.1570394E+03| 0.0000000E+00| 4) 5 prt(o:92| 3.8869905E+03; 0.0000000E+00, 0.0000000E+00, 3.8869905E+03| 0.0000000E+00| 5) 6 prt(o:-92| 5.3429606E+03; 0.0000000E+00, 0.0000000E+00,-5.3429606E+03| 0.0000000E+00| 6) 7 prt(o:11| 2.5040593E+03; 7.8357558E+02, 4.7248514E+02, 2.3308968E+03| 0.0000000E+00| 7) 8 prt(o:-11| 1.2659896E+03;-7.8357558E+02,-4.7248514E+02,-8.7492676E+02| 0.0000000E+00| 8) ======================================================================== Index: trunk/share/tests/functional_tests/ref-output/openloops_5.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output/openloops_5.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output/openloops_5.ref (revision 8760) @@ -1,414 +1,414 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true $loop_me_method = "openloops" $real_tree_me_method = "openloops" $correlation_me_method = "openloops" openmp_num_threads = 1 ?use_vamp_equivalences = false ?alphas_is_fixed = true ?alphas_from_mz = false SM.alphas => 1.17800E-01 SM.ms => 0.00000E+00 SM.mc => 0.00000E+00 SM.mb => 0.00000E+00 | Process library 'openloops_5_lib': recorded process 'openloops_5_p1_nlo' | Process library 'openloops_5_lib': recorded process 'openloops_5_p2_nlo' | Process library 'openloops_5_lib': recorded process 'openloops_5_p3_nlo' | Process library 'openloops_5_lib': recorded process 'openloops_5_p4_nlo' sqrts = 5.00000E+02 tolerance = 1.00000E-03 seed = 0 | Integrate: current process library needs compilation | Process library 'openloops_5_lib': compiling ... | Process library 'openloops_5_lib': writing makefile | Process library 'openloops_5_lib': removing old files | Process library 'openloops_5_lib': writing driver | Process library 'openloops_5_lib': creating source code | Process library 'openloops_5_lib': compiling sources | Process library 'openloops_5_lib': linking | Process library 'openloops_5_lib': loading | Process library 'openloops_5_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_5_p1_nlo: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p1_nlo.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p1_nlo.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_5_p1_nlo' | Library name = 'openloops_5_lib' | Process index = 1 | Process components: | 1: 'openloops_5_p1_nlo_i1': e+, e- => d:dbar:s:sbar:b:bbar, d:dbar:s:sbar:b:bbar [omega] | 2: 'openloops_5_p1_nlo_i2': e+, e- => d:dbar:s:sbar:b:bbar, d:dbar:s:sbar:b:bbar, gl [openloops], [real] | 3: 'openloops_5_p1_nlo_i3': e+, e- => d:dbar:s:sbar:b:bbar, d:dbar:s:sbar:b:bbar [openloops], [virtual] | 4: 'openloops_5_p1_nlo_i4': e+, e- => d:dbar:s:sbar:b:bbar, d:dbar:s:sbar:b:bbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_5_p1_nlo' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.123E+03 8.53E+01 7.59 0.76 36.1 |-----------------------------------------------------------------------------| 1 100 1.123E+03 8.53E+01 7.59 0.76 36.1 |=============================================================================| | Starting integration for process 'openloops_5_p1_nlo' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 8.711E+01 8.27E+00 9.49 0.95 20.2 |-----------------------------------------------------------------------------| 1 100 8.711E+01 8.27E+00 9.49 0.95 20.2 |=============================================================================| | Starting integration for process 'openloops_5_p1_nlo' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -4.462E+01 3.24E+00 7.27 0.73 40.0 |-----------------------------------------------------------------------------| 1 100 -4.462E+01 3.24E+00 7.27 0.73 40.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.166E+03 8.58E+01 7.36 0.00 32.9 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 3.7824 +- 0.84124 ) % +| ( 3.78 +- 0.84 ) % |=============================================================================| seed = 0 | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_5_p2_nlo: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p2_nlo.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p2_nlo.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_5_p2_nlo' | Library name = 'openloops_5_lib' | Process index = 2 | Process components: | 1: 'openloops_5_p2_nlo_i1': e+, e- => dbar, d [omega] | 2: 'openloops_5_p2_nlo_i2': e+, e- => dbar, d, gl [openloops], [real] | 3: 'openloops_5_p2_nlo_i3': e+, e- => dbar, d [openloops], [virtual] | 4: 'openloops_5_p2_nlo_i4': e+, e- => dbar, d [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_5_p2_nlo' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 3.744E+02 2.84E+01 7.59 0.76 36.1 |-----------------------------------------------------------------------------| 1 100 3.744E+02 2.84E+01 7.59 0.76 36.1 |=============================================================================| | Starting integration for process 'openloops_5_p2_nlo' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.904E+01 2.76E+00 9.49 0.95 20.2 |-----------------------------------------------------------------------------| 1 100 2.904E+01 2.76E+00 9.49 0.95 20.2 |=============================================================================| | Starting integration for process 'openloops_5_p2_nlo' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.487E+01 1.08E+00 7.27 0.73 40.0 |-----------------------------------------------------------------------------| 1 100 -1.487E+01 1.08E+00 7.27 0.73 40.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 3.886E+02 2.86E+01 7.36 0.00 32.9 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 3.7824 +- 0.84124 ) % +| ( 3.78 +- 0.84 ) % |=============================================================================| seed = 0 | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_5_p3_nlo: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p3_nlo.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p3_nlo.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_5_p3_nlo' | Library name = 'openloops_5_lib' | Process index = 3 | Process components: | 1: 'openloops_5_p3_nlo_i1': e+, e- => sbar, s [omega] | 2: 'openloops_5_p3_nlo_i2': e+, e- => sbar, s, gl [openloops], [real] | 3: 'openloops_5_p3_nlo_i3': e+, e- => sbar, s [openloops], [virtual] | 4: 'openloops_5_p3_nlo_i4': e+, e- => sbar, s [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_5_p3_nlo' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 3.744E+02 2.84E+01 7.59 0.76 36.1 |-----------------------------------------------------------------------------| 1 100 3.744E+02 2.84E+01 7.59 0.76 36.1 |=============================================================================| | Starting integration for process 'openloops_5_p3_nlo' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.904E+01 2.76E+00 9.49 0.95 20.2 |-----------------------------------------------------------------------------| 1 100 2.904E+01 2.76E+00 9.49 0.95 20.2 |=============================================================================| | Starting integration for process 'openloops_5_p3_nlo' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.487E+01 1.08E+00 7.27 0.73 40.0 |-----------------------------------------------------------------------------| 1 100 -1.487E+01 1.08E+00 7.27 0.73 40.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 3.886E+02 2.86E+01 7.36 0.00 32.9 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 3.7824 +- 0.84124 ) % +| ( 3.78 +- 0.84 ) % |=============================================================================| seed = 0 | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_5_p4_nlo: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p4_nlo.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_5_p4_nlo.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_5_p4_nlo' | Library name = 'openloops_5_lib' | Process index = 4 | Process components: | 1: 'openloops_5_p4_nlo_i1': e+, e- => bbar, b [omega] | 2: 'openloops_5_p4_nlo_i2': e+, e- => bbar, b, gl [openloops], [real] | 3: 'openloops_5_p4_nlo_i3': e+, e- => bbar, b [openloops], [virtual] | 4: 'openloops_5_p4_nlo_i4': e+, e- => bbar, b [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_5_p4_nlo' part 'born' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 3.744E+02 2.84E+01 7.59 0.76 36.1 |-----------------------------------------------------------------------------| 1 100 3.744E+02 2.84E+01 7.59 0.76 36.1 |=============================================================================| | Starting integration for process 'openloops_5_p4_nlo' part 'real' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.904E+01 2.76E+00 9.49 0.95 20.2 |-----------------------------------------------------------------------------| 1 100 2.904E+01 2.76E+00 9.49 0.95 20.2 |=============================================================================| | Starting integration for process 'openloops_5_p4_nlo' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.487E+01 1.08E+00 7.27 0.73 40.0 |-----------------------------------------------------------------------------| 1 100 -1.487E+01 1.08E+00 7.27 0.73 40.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 3.886E+02 2.86E+01 7.36 0.00 32.9 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 3.7824 +- 0.84124 ) % +| ( 3.78 +- 0.84 ) % |=============================================================================| | expect: success | Summary of value checks: | Failures: 0 / Total: 1 | There were no errors and 4 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/functional_tests/ref-output/nlo_2.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output/nlo_2.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output/nlo_2.ref (revision 8760) @@ -1,116 +1,116 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true $loop_me_method = "dummy" openmp_num_threads = 1 SM.wtop => 0.00000E+00 SM.mtop => 1.75000E+02 ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true | Process library 'nlo_2_lib': recorded process 'nlo_2_p1' seed = 2222 sqrts = 5.00000E+02 error_threshold = 1.00000E-05 | Integrate: current process library needs compilation | Process library 'nlo_2_lib': compiling ... | Process library 'nlo_2_lib': writing makefile | Process library 'nlo_2_lib': removing old files | Process library 'nlo_2_lib': writing driver | Process library 'nlo_2_lib': creating source code | Process library 'nlo_2_lib': compiling sources | Process library 'nlo_2_lib': linking | Process library 'nlo_2_lib': loading | Process library 'nlo_2_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2222 | Initializing integration for process nlo_2_p1: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 5.1099700E-04 GeV) | e- (mass = 5.1099700E-04 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_2_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_2_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_2_p1' | Library name = 'nlo_2_lib' | Process index = 1 | Process components: | 1: 'nlo_2_p1_i1': e+, e- => t, tbar [omega] | 2: 'nlo_2_p1_i2': e+, e- => t, tbar, gl [omega], [real] | 3: 'nlo_2_p1_i3': e+, e- => t, tbar [dummy], [virtual] | 4: 'nlo_2_p1_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'nlo_2_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 6.198E+02 2.83E+01 4.56 0.46 55.8 |-----------------------------------------------------------------------------| 1 100 6.198E+02 2.83E+01 4.56 0.46 55.8 |=============================================================================| | Starting integration for process 'nlo_2_p1' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -7.272E+01 4.21E+00 5.79 0.58 43.6 |-----------------------------------------------------------------------------| 1 100 -7.272E+01 4.21E+00 5.79 0.58 43.6 |=============================================================================| | Starting integration for process 'nlo_2_p1' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.999E+01 0.00E+00 0.00 0.00 100.0 |-----------------------------------------------------------------------------| 1 100 1.999E+01 0.00E+00 0.00 0.00 100.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 5.670E+02 2.86E+01 5.04 0.00 50.1 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -8.5087 +- 0.78265 ) % +| ( -8.51 +- 0.78 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Total number of regions: 2 alr || flst_real || i_real || em || mul || nreg || ftuples || flst_born || i_born 1 || [-11, 11, 6, -6, 21] || 1 || 3 || 1 || 2 || {(3,5),(4,5)} || [-11, 11, 6, -6] || 1 2 || [-11, 11, 6, -6, 21] || 1 || 4 || 1 || 2 || {(3,5),(4,5)} || [-11, 11, 6, -6] || 1 ------------------------------------------------------------------------ Index: trunk/share/tests/functional_tests/ref-output/recola_7.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output/recola_7.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output/recola_7.ref (revision 8760) @@ -1,134 +1,134 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true SM.mW => 8.03760E+01 SM.mZ => 9.11876E+01 SM.GF => 1.16637E-05 SM.wZ => 2.49520E+00 SM.wW => 2.12400E+00 SM.mmu => 0.00000E+00 SM.me => 0.00000E+00 SM.mc => 0.00000E+00 SM.ms => 0.00000E+00 SM.wtop => 0.00000E+00 SM.mtop => 1.75000E+02 $method = "recola" openmp_num_threads = 1 ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alpha_power = 2 alphas_power = 0 | Process library 'recola_7_lib': recorded process 'recola_7_p1' seed = 7777 sqrts = 5.00000E+02 | Integrate: current process library needs compilation | Process library 'recola_7_lib': compiling ... | Process library 'recola_7_lib': writing makefile | Process library 'recola_7_lib': removing old files | Process library 'recola_7_lib': writing driver | Process library 'recola_7_lib': creating source code | Process library 'recola_7_lib': compiling sources | Process library 'recola_7_lib': linking | Process library 'recola_7_lib': loading | Process library 'recola_7_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 7777 | Initializing integration for process recola_7_p1: | Recola: registering processes for 'recola_7_p1_BORN' | Recola: process #1: e+ e- -> t t~ (LO) | Recola: preparing processes for integration | Recola: registering processes for 'recola_7_p1_REAL' | Recola: process #2: e+ e- -> t t~ g (LO) | Recola: preparing processes for integration | Recola: registering processes for 'recola_7_p1_LOOP' | Recola: process #3: e+ e- -> t t~ (NLO) | Recola: preparing processes for integration | Recola: registering processes for 'recola_7_p1_SUB' | Recola: process #4: e+ e- -> t t~ (LO) | Recola: preparing processes for integration | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'recola_7_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'recola_7_p1.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'recola_7_p1' | Library name = 'recola_7_lib' | Process index = 1 | Process components: | 1: 'recola_7_p1_i1': e+, e- => t, tbar [recola] | 2: 'recola_7_p1_i2': e+, e- => t, tbar, gl [recola], [real] | 3: 'recola_7_p1_i3': e+, e- => t, tbar [recola], [virtual] | 4: 'recola_7_p1_i4': e+, e- => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'recola_7_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 5.071E+02 2.64E+01 5.21 0.52 45.6 |-----------------------------------------------------------------------------| 1 100 5.071E+02 2.64E+01 5.21 0.52 45.6 |=============================================================================| | Starting integration for process 'recola_7_p1' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -7.761E+01 4.10E+00 5.28 0.53 43.0 |-----------------------------------------------------------------------------| 1 100 -7.761E+01 4.10E+00 5.28 0.53 43.0 |=============================================================================| | Starting integration for process 'recola_7_p1' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.388E+02 7.64E+00 5.51 0.55 45.4 |-----------------------------------------------------------------------------| 1 100 1.388E+02 7.64E+00 5.51 0.55 45.4 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 5.683E+02 2.78E+01 4.90 0.00 40.1 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 12.0634 +- 1.82163 ) % +| ( 12.06 +- 1.82 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/functional_tests/ref-output/openloops_4.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output/openloops_4.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output/openloops_4.ref (revision 8760) @@ -1,722 +1,722 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true openmp_num_threads = 1 ?use_vamp_equivalences = false ?openloops_use_cms = false SM.mW => 7.00000E+01 SM.mZ => 9.00000E+01 SM.GF => 1.50000E-05 SM.wZ => 1.00000E+00 SM.wW => 3.00000E+00 alpha_em 0.0130713 [user variable] alpha_em_inverse = 7.65037E+01 SM.mmu => 0.00000E+00 SM.me => 0.00000E+00 SM.mc => 0.00000E+00 SM.ms => 0.00000E+00 ?alphas_is_fixed = true ?alphas_from_mz = false ?alphas_from_lambda_qcd = false SM.alphas => 2.00000E-01 alpha_power = 2 alphas_power = 0 $loop_me_method = "openloops" sqrts = 5.00000E+02 tolerance = 1.00000E-03 $born_me_method = "omega" $real_tree_me_method = "omega" $correlation_me_method = "omega" | Process library 'openloops_4_lib': recorded process 'openloops_4_omomom' seed = 0 | Integrate: current process library needs compilation | Process library 'openloops_4_lib': compiling ... | Process library 'openloops_4_lib': writing makefile | Process library 'openloops_4_lib': removing old files | Process library 'openloops_4_lib': writing driver | Process library 'openloops_4_lib': creating source code | Process library 'openloops_4_lib': compiling sources | Process library 'openloops_4_lib': linking | Process library 'openloops_4_lib': loading | Process library 'openloops_4_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_4_omomom: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_omomom.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_omomom.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_4_omomom' | Library name = 'openloops_4_lib' | Process index = 1 | Process components: | 1: 'openloops_4_omomom_i1': e+, e- => u, ubar [omega] | 2: 'openloops_4_omomom_i2': e+, e- => u, ubar, gl [omega], [real] | 3: 'openloops_4_omomom_i3': e+, e- => u, ubar [openloops], [virtual] | 4: 'openloops_4_omomom_i4': e+, e- => u, ubar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'openloops_4_omomom' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |-----------------------------------------------------------------------------| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |=============================================================================| | Starting integration for process 'openloops_4_omomom' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |-----------------------------------------------------------------------------| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |=============================================================================| | Starting integration for process 'openloops_4_omomom' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |-----------------------------------------------------------------------------| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.902E+03 1.10E+02 5.79 0.00 34.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 6.1438 +- 1.27004 ) % +| ( 6.14 +- 1.27 ) % |=============================================================================| integral(openloops_4_omomom) = 1.90204E+03 error(openloops_4_omomom) = 1.10105E+02 [user variable] reference_integral = 1.90204E+03 $born_me_method = "openloops" $real_tree_me_method = "omega" $correlation_me_method = "omega" | Process library 'openloops_4_lib': unloading | Process library 'openloops_4_lib': open | Process library 'openloops_4_lib': recorded process 'openloops_4_olomom' seed = 0 | Integrate: current process library needs compilation | Process library 'openloops_4_lib': compiling ... | Process library 'openloops_4_lib': writing makefile | Process library 'openloops_4_lib': removing old files | Process library 'openloops_4_lib': writing driver | Process library 'openloops_4_lib': creating source code | Process library 'openloops_4_lib': compiling sources | Process library 'openloops_4_lib': linking | Process library 'openloops_4_lib': loading | Process library 'openloops_4_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_4_olomom: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_olomom.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_olomom.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_4_olomom' | Library name = 'openloops_4_lib' | Process index = 2 | Process components: | 1: 'openloops_4_olomom_i1': e+, e- => u, ubar [openloops] | 2: 'openloops_4_olomom_i2': e+, e- => u, ubar, gl [omega], [real] | 3: 'openloops_4_olomom_i3': e+, e- => u, ubar [openloops], [virtual] | 4: 'openloops_4_olomom_i4': e+, e- => u, ubar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'openloops_4_olomom' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |-----------------------------------------------------------------------------| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |=============================================================================| | Starting integration for process 'openloops_4_olomom' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |-----------------------------------------------------------------------------| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |=============================================================================| | Starting integration for process 'openloops_4_olomom' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |-----------------------------------------------------------------------------| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.902E+03 1.10E+02 5.79 0.00 34.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 6.1438 +- 1.27004 ) % +| ( 6.14 +- 1.27 ) % |=============================================================================| integral(openloops_4_olomom) = 1.90204E+03 error(openloops_4_olomom) = 1.10105E+02 | expect: success $born_me_method = "omega" $real_tree_me_method = "openloops" $correlation_me_method = "omega" | Process library 'openloops_4_lib': unloading | Process library 'openloops_4_lib': open | Process library 'openloops_4_lib': recorded process 'openloops_4_omolom' seed = 0 | Integrate: current process library needs compilation | Process library 'openloops_4_lib': compiling ... | Process library 'openloops_4_lib': writing makefile | Process library 'openloops_4_lib': removing old files | Process library 'openloops_4_lib': writing driver | Process library 'openloops_4_lib': creating source code | Process library 'openloops_4_lib': compiling sources | Process library 'openloops_4_lib': linking | Process library 'openloops_4_lib': loading | Process library 'openloops_4_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_4_omolom: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_omolom.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_omolom.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_4_omolom' | Library name = 'openloops_4_lib' | Process index = 3 | Process components: | 1: 'openloops_4_omolom_i1': e+, e- => u, ubar [omega] | 2: 'openloops_4_omolom_i2': e+, e- => u, ubar, gl [openloops], [real] | 3: 'openloops_4_omolom_i3': e+, e- => u, ubar [openloops], [virtual] | 4: 'openloops_4_omolom_i4': e+, e- => u, ubar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'openloops_4_omolom' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |-----------------------------------------------------------------------------| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |=============================================================================| | Starting integration for process 'openloops_4_omolom' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |-----------------------------------------------------------------------------| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |=============================================================================| | Starting integration for process 'openloops_4_omolom' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |-----------------------------------------------------------------------------| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.902E+03 1.10E+02 5.79 0.00 34.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 6.1438 +- 1.27004 ) % +| ( 6.14 +- 1.27 ) % |=============================================================================| integral(openloops_4_omolom) = 1.90204E+03 error(openloops_4_omolom) = 1.10105E+02 | expect: success $born_me_method = "omega" $real_tree_me_method = "omega" $correlation_me_method = "openloops" | Process library 'openloops_4_lib': unloading | Process library 'openloops_4_lib': open | Process library 'openloops_4_lib': recorded process 'openloops_4_omomol' seed = 0 | Integrate: current process library needs compilation | Process library 'openloops_4_lib': compiling ... | Process library 'openloops_4_lib': writing makefile | Process library 'openloops_4_lib': removing old files | Process library 'openloops_4_lib': writing driver | Process library 'openloops_4_lib': creating source code | Process library 'openloops_4_lib': compiling sources | Process library 'openloops_4_lib': linking | Process library 'openloops_4_lib': loading | Process library 'openloops_4_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_4_omomol: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_omomol.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_omomol.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_4_omomol' | Library name = 'openloops_4_lib' | Process index = 4 | Process components: | 1: 'openloops_4_omomol_i1': e+, e- => u, ubar [omega] | 2: 'openloops_4_omomol_i2': e+, e- => u, ubar, gl [omega], [real] | 3: 'openloops_4_omomol_i3': e+, e- => u, ubar [openloops], [virtual] | 4: 'openloops_4_omomol_i4': e+, e- => u, ubar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'openloops_4_omomol' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |-----------------------------------------------------------------------------| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |=============================================================================| | Starting integration for process 'openloops_4_omomol' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |-----------------------------------------------------------------------------| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |=============================================================================| | Starting integration for process 'openloops_4_omomol' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |-----------------------------------------------------------------------------| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.902E+03 1.10E+02 5.79 0.00 34.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 6.1438 +- 1.27004 ) % +| ( 6.14 +- 1.27 ) % |=============================================================================| integral(openloops_4_omomol) = 1.90204E+03 error(openloops_4_omomol) = 1.10105E+02 | expect: success $born_me_method = "openloops" $real_tree_me_method = "openloops" $correlation_me_method = "openloops" | Process library 'openloops_4_lib': unloading | Process library 'openloops_4_lib': open | Process library 'openloops_4_lib': recorded process 'openloops_4_ololol' seed = 0 | Integrate: current process library needs compilation | Process library 'openloops_4_lib': compiling ... | Process library 'openloops_4_lib': writing makefile | Process library 'openloops_4_lib': removing old files | Process library 'openloops_4_lib': writing driver | Process library 'openloops_4_lib': creating source code | Process library 'openloops_4_lib': compiling sources | Process library 'openloops_4_lib': linking | Process library 'openloops_4_lib': loading | Process library 'openloops_4_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_4_ololol: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_ololol.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_ololol.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_4_ololol' | Library name = 'openloops_4_lib' | Process index = 5 | Process components: | 1: 'openloops_4_ololol_i1': e+, e- => u, ubar [openloops] | 2: 'openloops_4_ololol_i2': e+, e- => u, ubar, gl [openloops], [real] | 3: 'openloops_4_ololol_i3': e+, e- => u, ubar [openloops], [virtual] | 4: 'openloops_4_ololol_i4': e+, e- => u, ubar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'openloops_4_ololol' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |-----------------------------------------------------------------------------| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |=============================================================================| | Starting integration for process 'openloops_4_ololol' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |-----------------------------------------------------------------------------| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |=============================================================================| | Starting integration for process 'openloops_4_ololol' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |-----------------------------------------------------------------------------| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.902E+03 1.10E+02 5.79 0.00 34.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 6.1438 +- 1.27004 ) % +| ( 6.14 +- 1.27 ) % |=============================================================================| integral(openloops_4_ololol) = 1.90204E+03 error(openloops_4_ololol) = 1.10105E+02 | expect: success | Switching to model 'SM_tt_threshold' SM_tt_threshold.sqrtsstepsize => 1.00000E-01 SM_tt_threshold.sqrtsmin => 4.99900E+02 SM_tt_threshold.sqrtsmax => 5.00100E+02 SM_tt_threshold.mW => 7.00000E+01 SM_tt_threshold.mZ => 9.00000E+01 SM_tt_threshold.wZ => 1.00000E+00 SM_tt_threshold.wW => 3.00000E+00 SM_tt_threshold.alpha_em_i => 7.65037E+01 SM_tt_threshold.mmu => 0.00000E+00 SM_tt_threshold.me => 0.00000E+00 SM_tt_threshold.mc => 0.00000E+00 SM_tt_threshold.ms => 0.00000E+00 ?alphas_is_fixed = true ?alphas_from_mz = false ?alphas_from_lambda_qcd = false SM_tt_threshold.alphas => 2.00000E-01 | Process library 'openloops_4_lib': unloading | Process library 'openloops_4_lib': open | Process library 'openloops_4_lib': recorded process 'openloops_4_threshold' seed = 0 | Integrate: current process library needs compilation | Process library 'openloops_4_lib': compiling ... | Process library 'openloops_4_lib': writing makefile | Process library 'openloops_4_lib': removing old files | Process library 'openloops_4_lib': writing driver | Process library 'openloops_4_lib': creating source code | Process library 'openloops_4_lib': compiling sources | Process library 'openloops_4_lib': linking | Process library 'openloops_4_lib': loading | Process library 'openloops_4_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process openloops_4_threshold: | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 5.000000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_threshold.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_4_threshold.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'openloops_4_threshold' | Library name = 'openloops_4_lib' | Process index = 6 | Process components: | 1: 'openloops_4_threshold_i1': e+, e- => u, ubar [openloops] | 2: 'openloops_4_threshold_i2': e+, e- => u, ubar, gl [openloops], [real] | 3: 'openloops_4_threshold_i3': e+, e- => u, ubar [openloops], [virtual] | 4: 'openloops_4_threshold_i4': e+, e- => u, ubar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 2 channels, 2 dimensions | Phase space: found 2 channels, collected in 2 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'openloops_4_threshold' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |-----------------------------------------------------------------------------| 1 100 1.792E+03 1.08E+02 6.02 0.60 41.2 |=============================================================================| | Starting integration for process 'openloops_4_threshold' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |-----------------------------------------------------------------------------| 1 100 2.253E+02 2.07E+01 9.18 0.92 20.0 |=============================================================================| | Starting integration for process 'openloops_4_threshold' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 2 chains, 2 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |-----------------------------------------------------------------------------| 1 100 -1.152E+02 6.79E+00 5.89 0.59 39.6 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.902E+03 1.10E+02 5.79 0.00 34.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 6.1438 +- 1.27004 ) % +| ( 6.14 +- 1.27 ) % |=============================================================================| integral(openloops_4_threshold) = 1.90204E+03 error(openloops_4_threshold) = 1.10105E+02 | expect: success | Summary of value checks: | Failures: 0 / Total: 5 | There were no errors and 6 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/functional_tests/ref-output/openloops_6.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output/openloops_6.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output/openloops_6.ref (revision 8760) @@ -1,325 +1,325 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true $loop_me_method = "openloops" openmp_num_threads = 1 SM.wtop => 0.00000E+00 SM.wW => 0.00000E+00 SM.mb => 4.20000E+00 alpha_power = 1 ?use_vamp_equivalences = false ?alphas_is_fixed = false ?alphas_from_mz = true error_threshold = 1.00000E-08 seed = 1111 | Process library 'openloops_6_lib': recorded process 'openloops_6_p0' | Integrate: current process library needs compilation | Process library 'openloops_6_lib': compiling ... | Process library 'openloops_6_lib': writing makefile | Process library 'openloops_6_lib': removing old files | Process library 'openloops_6_lib': writing driver | Process library 'openloops_6_lib': creating source code | Process library 'openloops_6_lib': compiling sources | Process library 'openloops_6_lib': linking | Process library 'openloops_6_lib': loading | Process library 'openloops_6_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 1111 | Initializing integration for process openloops_6_p0: | Beam structure: [any particles] | Beam data (decay): | t (mass = 1.7310000E+02 GeV) | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_6_p0.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_6_p0.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [decay]: 'openloops_6_p0' | Library name = 'openloops_6_lib' | Process index = 1 | Process components: | 1: 'openloops_6_p0_i1': t => W+, b [omega] | 2: 'openloops_6_p0_i2': t => W+, b, gl [omega], [real] | 3: 'openloops_6_p0_i3': t => W+, b [openloops], [virtual] | 4: 'openloops_6_p0_i4': t => W+, b [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_6_p0' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.495E+00 0.00E+00 0.00 0.00 100.0 |-----------------------------------------------------------------------------| 1 100 1.495E+00 0.00E+00 0.00 0.00 100.0 |=============================================================================| | Starting integration for process 'openloops_6_p0' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -4.234E-01 2.94E-02 6.94 0.69 27.7 |-----------------------------------------------------------------------------| 1 100 -4.234E-01 2.94E-02 6.94 0.69 27.7 |=============================================================================| | Starting integration for process 'openloops_6_p0' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.761E-01 0.00E+00 0.00 0.00 100.0 |-----------------------------------------------------------------------------| 1 100 2.761E-01 0.00E+00 0.00 0.00 100.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.348E+00 2.94E-02 2.18 0.00 76.1 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -9.8465 +- 1.96394 ) % +| ( -9.85 +- 1.96 ) % |=============================================================================| [user variable] res_0 = 1.34806E+00 seed = 2222 | Process library 'openloops_6_lib': unloading | Process library 'openloops_6_lib': open | Process library 'openloops_6_lib': recorded process 'openloops_6_p1' | Integrate: current process library needs compilation | Process library 'openloops_6_lib': compiling ... | Process library 'openloops_6_lib': writing makefile | Process library 'openloops_6_lib': removing old files | Process library 'openloops_6_lib': writing driver | Process library 'openloops_6_lib': creating source code | Process library 'openloops_6_lib': compiling sources | Process library 'openloops_6_lib': linking | Process library 'openloops_6_lib': loading | Process library 'openloops_6_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 2222 | Initializing integration for process openloops_6_p1: | Beam structure: t | polarization (beam 1): | @(+1: +1: ( 1.000000000000E+00, 0.000000000000E+00)) | polarization degree = 1.0000000 | Beam data (decay): | t (mass = 1.7310000E+02 GeV) polarized | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_6_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_6_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [decay]: 'openloops_6_p1' | Library name = 'openloops_6_lib' | Process index = 2 | Process components: | 1: 'openloops_6_p1_i1': t => W+, b [omega] | 2: 'openloops_6_p1_i2': t => W+, b, gl [omega], [real] | 3: 'openloops_6_p1_i3': t => W+, b [openloops], [virtual] | 4: 'openloops_6_p1_i4': t => W+, b [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_6_p1' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.590E+00 3.44E-02 2.17 0.22 76.3 |-----------------------------------------------------------------------------| 1 100 1.590E+00 3.44E-02 2.17 0.22 76.3 |=============================================================================| | Starting integration for process 'openloops_6_p1' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -3.944E-01 2.71E-02 6.87 0.69 37.1 |-----------------------------------------------------------------------------| 1 100 -3.944E-01 2.71E-02 6.87 0.69 37.1 |=============================================================================| | Starting integration for process 'openloops_6_p1' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.803E-01 5.47E-03 1.95 0.20 76.0 |-----------------------------------------------------------------------------| 1 100 2.803E-01 5.47E-03 1.95 0.20 76.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.476E+00 4.41E-02 2.99 0.00 60.2 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -7.1780 +- 1.74505 ) % +| ( -7.18 +- 1.75 ) % |=============================================================================| [user variable] res_1 = 1.47555E+00 seed = 3333 | Process library 'openloops_6_lib': unloading | Process library 'openloops_6_lib': open | Process library 'openloops_6_lib': recorded process 'openloops_6_p2' | Integrate: current process library needs compilation | Process library 'openloops_6_lib': compiling ... | Process library 'openloops_6_lib': writing makefile | Process library 'openloops_6_lib': removing old files | Process library 'openloops_6_lib': writing driver | Process library 'openloops_6_lib': creating source code | Process library 'openloops_6_lib': compiling sources | Process library 'openloops_6_lib': linking | Process library 'openloops_6_lib': loading | Process library 'openloops_6_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 3333 | Initializing integration for process openloops_6_p2: | Beam structure: t | polarization (beam 1): | @(-1: -1: ( 1.000000000000E+00, 0.000000000000E+00)) | polarization degree = 1.0000000 | Beam data (decay): | t (mass = 1.7310000E+02 GeV) polarized | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_6_p2.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'openloops_6_p2.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [decay]: 'openloops_6_p2' | Library name = 'openloops_6_lib' | Process index = 3 | Process components: | 1: 'openloops_6_p2_i1': t => W+, b [omega] | 2: 'openloops_6_p2_i2': t => W+, b, gl [omega], [real] | 3: 'openloops_6_p2_i3': t => W+, b [openloops], [virtual] | 4: 'openloops_6_p2_i4': t => W+, b [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'openloops_6_p2' part 'born' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 1.505E+00 3.49E-02 2.32 0.23 72.1 |-----------------------------------------------------------------------------| 1 100 1.505E+00 3.49E-02 2.32 0.23 72.1 |=============================================================================| | Starting integration for process 'openloops_6_p2' part 'real' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 -4.603E-01 3.06E-02 6.65 0.67 35.3 |-----------------------------------------------------------------------------| 1 100 -4.603E-01 3.06E-02 6.65 0.67 35.3 |=============================================================================| | Starting integration for process 'openloops_6_p2' part 'virtual' | Integrate: iterations = 1:100 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 100 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 100 2.766E-01 5.84E-03 2.11 0.21 74.2 |-----------------------------------------------------------------------------| 1 100 2.766E-01 5.84E-03 2.11 0.21 74.2 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[GeV] Error[GeV] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.321E+00 4.68E-02 3.54 0.00 53.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-12.2037 +- 2.09046 ) % +| ( -12.20 +- 2.09 ) % |=============================================================================| [user variable] res_2 = 1.32132E+00 tolerance = 1.00000E-01 | expect: success | Summary of value checks: | Failures: 0 / Total: 1 | There were no errors and 3 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/functional_tests/ref-output/user_prc_threshold_1.ref =================================================================== --- trunk/share/tests/functional_tests/ref-output/user_prc_threshold_1.ref (revision 8759) +++ trunk/share/tests/functional_tests/ref-output/user_prc_threshold_1.ref (revision 8760) @@ -1,491 +1,491 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false ?pacify = true ?use_vamp_equivalences = false openmp_num_threads = 1 | Switching to model 'SM_tt_threshold' SM_tt_threshold.sqrtsmin => 3.50000E+02 SM_tt_threshold.sqrtsmax => 3.50000E+02 SM_tt_threshold.sqrtsstepsize => 0.00000E+00 SM_tt_threshold.m1S => 1.72000E+02 SM_tt_threshold.mZ => 9.11880E+01 SM_tt_threshold.mW => 8.04190E+01 SM_tt_threshold.mb => 4.20000E+00 SM_tt_threshold.alphas => 1.18000E-01 SM_tt_threshold.alpha_em_i => 1.25924E+02 SM_tt_threshold.m1S => 1.72000E+02 phs_t_channel = 0 SM_tt_threshold.nrqcd_order => 1.00000E+00 SM_tt_threshold.sh => 1.00000E+00 SM_tt_threshold.sf => 1.00000E+00 SM_tt_threshold.Vtb => 1.00000E+00 SM_tt_threshold.FF => 1.00000E+00 SM_tt_threshold.mpole_fixed => 1.00000E+00 SM_tt_threshold.offshell_strategy => 4.00000E+00 SM_tt_threshold.me => 0.00000E+00 sqrts = 3.50000E+02 [user variable] num_diff = 1.00000E-03 seed = 0 $restrictions = "3+5~t && 4+6~tbar" | Process library 'user_prc_threshold_1_lib': recorded process 'user_prc_threshold_1_p1' | Integrate: current process library needs compilation | Process library 'user_prc_threshold_1_lib': compiling ... | Process library 'user_prc_threshold_1_lib': writing makefile | Process library 'user_prc_threshold_1_lib': removing old files | Process library 'user_prc_threshold_1_lib': writing driver | Process library 'user_prc_threshold_1_lib': creating source code | Process library 'user_prc_threshold_1_lib': compiling sources | Process library 'user_prc_threshold_1_lib': linking | Process library 'user_prc_threshold_1_lib': loading | Process library 'user_prc_threshold_1_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process user_prc_threshold_1_p1: | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Scanning from 350.000 GeV to 350.000 GeV in steps of 0.000 GeV | 100.0% | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 3.500000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'user_prc_threshold_1_p1.i1.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'user_prc_threshold_1_p1' | Library name = 'user_prc_threshold_1_lib' | Process index = 1 | Process components: | 1: 'user_prc_threshold_1_p1_i1': e+, e- => W+, W-, b, bbar [omega] | ------------------------------------------------------------------------ | Phase space: 15 channels, 8 dimensions | Phase space: found 15 channels, collected in 6 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'user_prc_threshold_1_p1' | Integrate: iterations = 1:200 | Integrator: 6 chains, 15 channels, 8 dimensions | Integrator: 200 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 195 7.811E+02 1.52E+02 19.42 2.71 28.7 |-----------------------------------------------------------------------------| 1 195 7.811E+02 1.52E+02 19.42 2.71 28.7 |=============================================================================| seed = 0 | Process library 'user_prc_threshold_1_lib': unloading | Process library 'user_prc_threshold_1_lib': open | Process library 'user_prc_threshold_1_lib': recorded process 'user_prc_threshold_1_p2' | Integrate: current process library needs compilation | Process library 'user_prc_threshold_1_lib': compiling ... | Process library 'user_prc_threshold_1_lib': writing makefile | Process library 'user_prc_threshold_1_lib': removing old files | Process library 'user_prc_threshold_1_lib': writing driver | Process library 'user_prc_threshold_1_lib': creating source code | Process library 'user_prc_threshold_1_lib': compiling sources | Process library 'user_prc_threshold_1_lib': linking | Process library 'user_prc_threshold_1_lib': loading | Process library 'user_prc_threshold_1_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process user_prc_threshold_1_p2: | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Opening grid file: SM_tt_threshold.grid | Threshold setup unchanged: reusing existing threshold grid. | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 3.500000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'user_prc_threshold_1_p2.i1.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'user_prc_threshold_1_p2' | Library name = 'user_prc_threshold_1_lib' | Process index = 2 | Process components: | 1: 'user_prc_threshold_1_p2_i1': e+, e- => t, tbar [omega] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'user_prc_threshold_1_p2' | Integrate: iterations = 1:200 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 200 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 200 5.568E+02 4.28E-01 0.08 0.01 80.9 |-----------------------------------------------------------------------------| 1 200 5.568E+02 4.28E-01 0.08 0.01 80.9 |=============================================================================| seed = 0 $method = "threshold" | Process library 'user_prc_threshold_1_lib': unloading | Process library 'user_prc_threshold_1_lib': open | Process library 'user_prc_threshold_1_lib': recorded process 'user_prc_threshold_1_p5' | Integrate: current process library needs compilation | Process library 'user_prc_threshold_1_lib': compiling ... | Process library 'user_prc_threshold_1_lib': writing makefile | Process library 'user_prc_threshold_1_lib': removing old files | Process library 'user_prc_threshold_1_lib': writing driver | Process library 'user_prc_threshold_1_lib': creating source code | Process library 'user_prc_threshold_1_lib': compiling sources | Process library 'user_prc_threshold_1_lib': linking | Process library 'user_prc_threshold_1_lib': loading | Loaded extra threshold functions | Process library 'user_prc_threshold_1_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process user_prc_threshold_1_p5: | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Opening grid file: SM_tt_threshold.grid | Threshold setup unchanged: reusing existing threshold grid. | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 3.500000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'user_prc_threshold_1_p5.i1.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'user_prc_threshold_1_p5' | Library name = 'user_prc_threshold_1_lib' | Process index = 3 | Process components: | 1: 'user_prc_threshold_1_p5_i1': e+, e- => t, tbar [threshold] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'user_prc_threshold_1_p5' | Integrate: iterations = 1:200 | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: 200 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 200 5.568E+02 4.28E-01 0.08 0.01 80.9 |-----------------------------------------------------------------------------| 1 200 5.568E+02 4.28E-01 0.08 0.01 80.9 |=============================================================================| tolerance = 1.00000E-04 | expect: success seed = 0 $born_me_method = "threshold" $loop_me_method = "threshold" $correlation_me_method = "threshold" $real_tree_me_method = "threshold" $restrictions = "3+5~t && 4+6~tbar" | Process library 'user_prc_threshold_1_lib': unloading | Process library 'user_prc_threshold_1_lib': open | Process library 'user_prc_threshold_1_lib': recorded process 'user_prc_threshold_1_p6' | Integrate: current process library needs compilation | Process library 'user_prc_threshold_1_lib': compiling ... | Process library 'user_prc_threshold_1_lib': writing makefile | Process library 'user_prc_threshold_1_lib': removing old files | Process library 'user_prc_threshold_1_lib': writing driver | Process library 'user_prc_threshold_1_lib': creating source code | Process library 'user_prc_threshold_1_lib': compiling sources | Process library 'user_prc_threshold_1_lib': linking | Process library 'user_prc_threshold_1_lib': loading | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Process library 'user_prc_threshold_1_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process user_prc_threshold_1_p6: | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Opening grid file: SM_tt_threshold.grid | Threshold setup unchanged: reusing existing threshold grid. | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Opening grid file: SM_tt_threshold.grid | Threshold setup unchanged: reusing existing threshold grid. | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Opening grid file: SM_tt_threshold.grid | Threshold setup unchanged: reusing existing threshold grid. | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 3.500000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'user_prc_threshold_1_p6.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'user_prc_threshold_1_p6.i3.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'user_prc_threshold_1_p6' | Library name = 'user_prc_threshold_1_lib' | Process index = 4 | Process components: | 1: 'user_prc_threshold_1_p6_i1': e+, e- => W+, W-, b, bbar [threshold] | 2: 'user_prc_threshold_1_p6_i2': e+, e- => W+, W-, b, bbar, gl [inactive], [real] | 3: 'user_prc_threshold_1_p6_i3': e+, e- => W+, W-, b, bbar [inactive], [virtual] | 4: 'user_prc_threshold_1_p6_i4': e+, e- => W+, W-, b, bbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 15 channels, 8 dimensions | Phase space: found 15 channels, collected in 6 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 15 channels, 11 dimensions | Phase space: found 15 channels, collected in 6 groves. | Phase space: no equivalences between channels used. | Phase space: wood | Phase space: 15 channels, 8 dimensions | Phase space: found 15 channels, collected in 6 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'user_prc_threshold_1_p6' part 'born' | Integrate: iterations = 1:200 | Integrator: 6 chains, 15 channels, 8 dimensions | Integrator: 200 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 195 7.811E+02 1.52E+02 19.42 2.71 28.7 |-----------------------------------------------------------------------------| 1 195 7.811E+02 1.52E+02 19.42 2.71 28.7 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 7.811E+02 1.52E+02 19.42 0.00 28.7 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.0000 +- 0.00000 ) % +| ( 0.00 +- 0.00 ) % |=============================================================================| tolerance = 1.00000E-04 | expect: success $method = "threshold" seed = 0 | Process library 'user_prc_threshold_1_lib': unloading | Process library 'user_prc_threshold_1_lib': open | Process library 'user_prc_threshold_1_lib': recorded process 'user_prc_threshold_1_sig_thr' SM_tt_threshold.offshell_strategy => 0.00000E+00 | Integrate: current process library needs compilation | Process library 'user_prc_threshold_1_lib': compiling ... | Process library 'user_prc_threshold_1_lib': writing makefile | Process library 'user_prc_threshold_1_lib': removing old files | Process library 'user_prc_threshold_1_lib': writing driver | Process library 'user_prc_threshold_1_lib': creating source code | Process library 'user_prc_threshold_1_lib': compiling sources | Process library 'user_prc_threshold_1_lib': linking | Process library 'user_prc_threshold_1_lib': loading | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Process library 'user_prc_threshold_1_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process user_prc_threshold_1_sig_thr: | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Opening grid file: SM_tt_threshold.grid | Threshold setup unchanged: reusing existing threshold grid. | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 3.500000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'user_prc_threshold_1_sig_thr.i1.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'user_prc_threshold_1_sig_thr' | Library name = 'user_prc_threshold_1_lib' | Process index = 5 | Process components: | 1: 'user_prc_threshold_1_sig_thr_i1': e+, e- => W+, W-, b, bbar [threshold] | ------------------------------------------------------------------------ | Phase space: 15 channels, 8 dimensions | Phase space: found 15 channels, collected in 6 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'user_prc_threshold_1_sig_thr' | Integrate: iterations = 1:200 | Integrator: 6 chains, 15 channels, 8 dimensions | Integrator: 200 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 195 7.811E+02 1.52E+02 19.42 2.71 28.7 |-----------------------------------------------------------------------------| 1 195 7.811E+02 1.52E+02 19.42 2.71 28.7 |=============================================================================| tolerance = 1.00000E-03 | expect: success seed = 0 | Process library 'user_prc_threshold_1_lib': unloading | Process library 'user_prc_threshold_1_lib': open | Process library 'user_prc_threshold_1_lib': recorded process 'user_prc_threshold_1_factorized' SM_tt_threshold.offshell_strategy => 2.00000E+00 | Integrate: current process library needs compilation | Process library 'user_prc_threshold_1_lib': compiling ... | Process library 'user_prc_threshold_1_lib': writing makefile | Process library 'user_prc_threshold_1_lib': removing old files | Process library 'user_prc_threshold_1_lib': writing driver | Process library 'user_prc_threshold_1_lib': creating source code | Process library 'user_prc_threshold_1_lib': compiling sources | Process library 'user_prc_threshold_1_lib': linking | Process library 'user_prc_threshold_1_lib': loading | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Loaded extra threshold functions | Process library 'user_prc_threshold_1_lib': ... success. | Integrate: compilation done | RNG: Initializing TAO random-number generator | RNG: Setting seed for random-number generator to 0 | Initializing integration for process user_prc_threshold_1_factorized: | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | Initialize e+e- => ttbar threshold resummation: | Use analytic (LL) or TOPPIK (NLL) form factors for ttA/ttZ vector | and axial vector couplings (S/P-wave) in the threshold region. | Cf. threshold shapes from A. Hoang et al.: [arXiv:hep-ph/0107144], | [arXiv:1309.6323]. | Numerical NLL solutions calculated with TOPPIK [arXiv:hep-ph/9904468] | by M. Jezabek, T. Teubner. | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | | Opening grid file: SM_tt_threshold.grid | Threshold setup unchanged: reusing existing threshold grid. | Beam structure: [any particles] | Beam data (collision): | e+ (mass = 0.0000000E+00 GeV) | e- (mass = 0.0000000E+00 GeV) | sqrts = 3.500000000000E+02 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'user_prc_threshold_1_factorized.i1.phs' | ------------------------------------------------------------------------ | Process [scattering]: 'user_prc_threshold_1_factorized' | Library name = 'user_prc_threshold_1_lib' | Process index = 6 | Process components: | 1: 'user_prc_threshold_1_factorized_i1': e+, e- => W+, W-, b, bbar [threshold] | ------------------------------------------------------------------------ | Phase space: 15 channels, 8 dimensions | Phase space: found 15 channels, collected in 6 groves. | Phase space: no equivalences between channels used. | Phase space: wood Warning: No cuts have been defined. | Starting integration for process 'user_prc_threshold_1_factorized' | Integrate: iterations = 1:200 | Integrator: 6 chains, 15 channels, 8 dimensions | Integrator: 200 initial calls, 20 bins, stratified = T | Integrator: VAMP |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 195 7.681E+02 1.49E+02 19.44 2.72 28.8 |-----------------------------------------------------------------------------| 1 195 7.681E+02 1.49E+02 19.44 2.72 28.8 |=============================================================================| tolerance = 2.79506E+01 | expect: success | Summary of value checks: | Failures: 0 / Total: 4 | There were no errors and 6 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eejjj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eejjj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eejjj.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 1 | Process library 'nlo_eejjj_lib': recorded process 'nlo_eejjj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eejjj_lib': compiling ... | Process library 'nlo_eejjj_lib': writing makefile | Process library 'nlo_eejjj_lib': removing old files | Process library 'nlo_eejjj_lib': writing driver | Process library 'nlo_eejjj_lib': creating source code | Process library 'nlo_eejjj_lib': compiling sources | Process library 'nlo_eejjj_lib': linking | Process library 'nlo_eejjj_lib': loading | Process library 'nlo_eejjj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eejjj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_eejjj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eejjj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eejjj_p1' | Library name = 'nlo_eejjj_lib' | Process index = 1 | Process components: | 1: 'nlo_eejjj_p1_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eejjj_p1_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eejjj_p1_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eejjj_p1_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 2 equivalences between channels. | Phase space: wood | Phase space: 2 channels, 8 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 2 equivalences between channels. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 2 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eejjj_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 2 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eejjj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eejjj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 100 4.0193681E+02 1.37E+02 34.00 3.40* 7.11 |-----------------------------------------------------------------------------| 1 100 4.0193681E+02 1.37E+02 34.00 3.40 7.11 |=============================================================================| | Starting integration for process 'nlo_eejjj_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 2 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eejjj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eejjj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.0017265E+02 3.44E+01 34.33 3.43* 6.20 |-----------------------------------------------------------------------------| 1 100 1.0017265E+02 3.44E+01 34.33 3.43 6.20 |=============================================================================| | Starting integration for process 'nlo_eejjj_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 2 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eejjj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eejjj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 100 -3.1346969E+01 1.48E+01 47.08 4.71* 4.27 |-----------------------------------------------------------------------------| 1 100 -3.1346969E+01 1.48E+01 47.08 4.71 4.27 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 4.7076249E+02 1.42E+02 30.10 0.00* 6.48 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 17.1235 +- 10.98137 ) % +| ( 17.12 +- 10.98 ) % |=============================================================================| | There were no errors and 2 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4j.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4j.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4j.ref (revision 8760) @@ -1,177 +1,177 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 2 $restrictions = "!W+:W-" | Process library 'nlo_ee4j_lib': recorded process 'nlo_ee4j_p1' | Integrate: current process library needs compilation | Process library 'nlo_ee4j_lib': compiling ... | Process library 'nlo_ee4j_lib': writing makefile | Process library 'nlo_ee4j_lib': removing old files | Process library 'nlo_ee4j_lib': writing driver | Process library 'nlo_ee4j_lib': creating source code | Process library 'nlo_ee4j_lib': compiling sources | Process library 'nlo_ee4j_lib': linking | Process library 'nlo_ee4j_lib': loading | Process library 'nlo_ee4j_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_ee4j_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. Warning: Intermediate decay of zero-width particle W- may be possible. Warning: Intermediate decay of zero-width particle W+ may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee4j_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee4j_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_ee4j_p1' | Library name = 'nlo_ee4j_lib' | Process index = 1 | Process components: | 1: 'nlo_ee4j_p1_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_ee4j_p1_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_ee4j_p1_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_ee4j_p1_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 48 channels, 8 dimensions | Phase space: found 48 channels, collected in 5 groves. | Phase space: Using 320 equivalences between channels. | Phase space: wood | Phase space: 48 channels, 11 dimensions | Phase space: found 48 channels, collected in 5 groves. | Phase space: Using 320 equivalences between channels. | Phase space: wood | Phase space: 48 channels, 8 dimensions | Phase space: found 48 channels, collected in 5 groves. | Phase space: Using 320 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_ee4j_p1' part 'born' | Integrate: iterations = 1:480:"gw" | Integrator: 5 chains, 48 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4j_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 480 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4j_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 494 8.8893730E+01 4.52E+01 50.81 11.29* 12.59 |-----------------------------------------------------------------------------| 1 494 8.8893730E+01 4.52E+01 50.81 11.29 12.59 |=============================================================================| | Starting integration for process 'nlo_ee4j_p1' part 'real' | Integrate: iterations = 1:480:"gw" | Integrator: 5 chains, 48 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4j_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 480 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4j_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 494 4.2862344E+01 1.13E+01 26.34 5.85* 14.36 |-----------------------------------------------------------------------------| 1 494 4.2862344E+01 1.13E+01 26.34 5.85 14.36 |=============================================================================| | Starting integration for process 'nlo_ee4j_p1' part 'virtual' | Integrate: iterations = 1:480:"gw" | Integrator: 5 chains, 48 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4j_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 480 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4j_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 488 -2.3587867E+01 9.36E+00 39.69 8.77* 10.96 |-----------------------------------------------------------------------------| 1 488 -2.3587867E+01 9.36E+00 39.69 8.77 10.96 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.0816821E+02 4.75E+01 43.91 0.00* 10.77 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 21.6826 +- 19.83813 ) % +| ( 21.68 +- 19.84 ) % |=============================================================================| | There were no errors and 4 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppllll_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppllll_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppllll_ew.ref (revision 8760) @@ -1,219 +1,219 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' ?pacify = true [user variable] jet = PDG(11, -11, 13, -13, 22, 2, -2, 1, -1, 3, -3, 4, -4, 5, -5) SM.wtop => 1.36918E+00 SM.mZ => 9.11535E+01 SM.mW => 8.03578E+01 SM.wZ => 2.49457E+00 SM.wW => 2.08899E+00 alpha_power = 4 alphas_power = 0 $nlo_correction_type = "EW" seed = 1 | Process library 'nlo_ppllll_ew_lib': recorded process 'ppllll_ew' | Integrate: current process library needs compilation | Process library 'nlo_ppllll_ew_lib': compiling ... | Process library 'nlo_ppllll_ew_lib': writing makefile | Process library 'nlo_ppllll_ew_lib': removing old files | Process library 'nlo_ppllll_ew_lib': writing driver | Process library 'nlo_ppllll_ew_lib': creating source code | Process library 'nlo_ppllll_ew_lib': compiling sources | Process library 'nlo_ppllll_ew_lib': linking | Process library 'nlo_ppllll_ew_lib': loading | Process library 'nlo_ppllll_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process ppllll_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'ppllll_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppllll_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppllll_ew' | Library name = 'nlo_ppllll_ew_lib' | Process index = 1 | Process components: | 1: 'ppllll_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, mu-, mu+ [openloops] | 2: 'ppllll_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => e-, e+, mu-, mu+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'ppllll_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, mu-, mu+ [openloops], [virtual] | 4: 'ppllll_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, mu-, mu+ [inactive], [subtraction] | 5: 'ppllll_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, mu-, mu+ [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 143 channels, 8 dimensions | Phase space: found 143 channels, collected in 24 groves. | Phase space: Using 227 equivalences between channels. | Phase space: wood | Phase space: 143 channels, 11 dimensions | Phase space: found 143 channels, collected in 24 groves. | Phase space: Using 227 equivalences between channels. | Phase space: wood | Phase space: 143 channels, 8 dimensions | Phase space: found 143 channels, collected in 24 groves. | Phase space: Using 227 equivalences between channels. | Phase space: wood | Phase space: 143 channels, 9 dimensions | Phase space: found 143 channels, collected in 24 groves. | Phase space: Using 227 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 2 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'ppllll_ew' part 'born' | Integrate: iterations = 1:1500:"gw" | Integrator: 24 chains, 143 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppllll_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppllll_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 1602 1.302E+00 8.96E-01 68.80 27.54 10.0 |-----------------------------------------------------------------------------| 1 1602 1.302E+00 8.96E-01 68.80 27.54 10.0 |=============================================================================| | Starting integration for process 'ppllll_ew' part 'real' | Integrate: iterations = 1:1500:"gw" | Integrator: 24 chains, 143 channels, 13 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppllll_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppllll_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 1578 1.281E-03 1.18E-02 920.11 365.50 19.7 |-----------------------------------------------------------------------------| 1 1578 1.281E-03 1.18E-02 920.11 365.50 19.7 |=============================================================================| | Starting integration for process 'ppllll_ew' part 'virtual' | Integrate: iterations = 1:1500:"gw" | Integrator: 24 chains, 143 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppllll_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppllll_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 1538 -3.197E-01 1.85E-01 57.89 22.70 10.3 |-----------------------------------------------------------------------------| 1 1538 -3.197E-01 1.85E-01 57.89 22.70 10.3 |=============================================================================| | Starting integration for process 'ppllll_ew' part 'dglap' | Integrate: iterations = 1:1500:"gw" | Integrator: 24 chains, 143 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppllll_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppllll_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 1594 2.655E-03 1.40E-03 52.58 20.99 10.5 |-----------------------------------------------------------------------------| 1 1594 2.655E-03 1.40E-03 52.58 20.99 10.5 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 9.858E-01 9.15E-01 92.77 0.00 7.6 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-24.2634 +- 21.94944 ) % +| ( -24.26 +- 21.95 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphee_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphee_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphee_ew.ref (revision 8760) @@ -1,215 +1,215 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' SM.wtop => 1.369180000000E+00 SM.mZ => 9.115347000000E+01 SM.mW => 8.035785000000E+01 SM.wZ => 2.494566000000E+00 SM.wW => 2.088994000000E+00 alpha_power = 3 alphas_power = 0 $nlo_correction_type = "EW" seed = 1 | Process library 'nlo_pphee_ew_lib': recorded process 'pphee_ew' | Integrate: current process library needs compilation | Process library 'nlo_pphee_ew_lib': compiling ... | Process library 'nlo_pphee_ew_lib': writing makefile | Process library 'nlo_pphee_ew_lib': removing old files | Process library 'nlo_pphee_ew_lib': writing driver | Process library 'nlo_pphee_ew_lib': creating source code | Process library 'nlo_pphee_ew_lib': compiling sources | Process library 'nlo_pphee_ew_lib': linking | Process library 'nlo_pphee_ew_lib': loading | Process library 'nlo_pphee_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process pphee_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'pphee_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'pphee_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'pphee_ew' | Library name = 'nlo_pphee_ew_lib' | Process index = 1 | Process components: | 1: 'pphee_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, H [openloops] | 2: 'pphee_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => e-, e+, H, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'pphee_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, H [openloops], [virtual] | 4: 'pphee_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, H [inactive], [subtraction] | 5: 'pphee_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+, H [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 14 channels, 5 dimensions | Phase space: found 14 channels, collected in 8 groves. | Phase space: Using 26 equivalences between channels. | Phase space: wood | Phase space: 14 channels, 8 dimensions | Phase space: found 14 channels, collected in 8 groves. | Phase space: Using 26 equivalences between channels. | Phase space: wood | Phase space: 14 channels, 5 dimensions | Phase space: found 14 channels, collected in 8 groves. | Phase space: Using 26 equivalences between channels. | Phase space: wood | Phase space: 14 channels, 6 dimensions | Phase space: found 14 channels, collected in 8 groves. | Phase space: Using 26 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'pphee_ew' part 'born' | Integrate: iterations = 1:500:"gw" | Integrator: 8 chains, 14 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphee_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphee_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 502 6.2743298E-02 3.24E-02 51.68 11.58* 2.81 |-----------------------------------------------------------------------------| 1 502 6.2743298E-02 3.24E-02 51.68 11.58 2.81 |=============================================================================| | Starting integration for process 'pphee_ew' part 'real' | Integrate: iterations = 1:500:"gw" | Integrator: 8 chains, 14 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphee_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphee_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 499 -2.7800382E-01 2.26E-01 81.15 18.13* 3.33 |-----------------------------------------------------------------------------| 1 499 -2.7800382E-01 2.26E-01 81.15 18.13 3.33 |=============================================================================| | Starting integration for process 'pphee_ew' part 'virtual' | Integrate: iterations = 1:500:"gw" | Integrator: 8 chains, 14 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphee_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphee_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 493 -7.5191672E-01 6.38E-01 84.79 18.83* 3.05 |-----------------------------------------------------------------------------| 1 493 -7.5191672E-01 6.38E-01 84.79 18.83 3.05 |=============================================================================| | Starting integration for process 'pphee_ew' part 'dglap' | Integrate: iterations = 1:500:"gw" | Integrator: 8 chains, 14 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphee_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphee_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 500 -3.1893821E-03 2.48E-02 778.29 174.03* 6.26 |-----------------------------------------------------------------------------| 1 500 -3.1893821E-03 2.48E-02 778.29 174.03 6.26 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 -9.7036662E-01 6.78E-01 69.82 0.00* -43.53 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (******** +- ********* ) % +| (******* +- ****** ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppllnn_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppllnn_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppllnn_ew.ref (revision 8760) @@ -1,217 +1,217 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' SM.wtop => 1.369180000000E+00 SM.mZ => 9.115347000000E+01 SM.mW => 8.035785000000E+01 SM.wZ => 2.494566000000E+00 SM.wW => 2.088994000000E+00 alpha_power = 4 alphas_power = 0 $nlo_correction_type = "EW" seed = 1 | Process library 'nlo_ppllnn_ew_lib': recorded process 'drellyNLO' | Integrate: current process library needs compilation | Process library 'nlo_ppllnn_ew_lib': compiling ... | Process library 'nlo_ppllnn_ew_lib': writing makefile | Process library 'nlo_ppllnn_ew_lib': removing old files | Process library 'nlo_ppllnn_ew_lib': writing driver | Process library 'nlo_ppllnn_ew_lib': creating source code | Process library 'nlo_ppllnn_ew_lib': compiling sources | Process library 'nlo_ppllnn_ew_lib': linking | Process library 'nlo_ppllnn_ew_lib': loading | Process library 'nlo_ppllnn_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process drellyNLO: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'drellyNLO.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'drellyNLO.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'drellyNLO' | Library name = 'nlo_ppllnn_ew_lib' | Process index = 1 | Process components: | 1: 'drellyNLO_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e+, nue, mu-, numubar [openloops] | 2: 'drellyNLO_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => e+, nue, mu-, numubar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'drellyNLO_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e+, nue, mu-, numubar [openloops], [virtual] | 4: 'drellyNLO_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e+, nue, mu-, numubar [inactive], [subtraction] | 5: 'drellyNLO_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e+, nue, mu-, numubar [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 81 channels, 8 dimensions | Phase space: found 81 channels, collected in 26 groves. | Phase space: Using 109 equivalences between channels. | Phase space: wood | Phase space: 81 channels, 11 dimensions | Phase space: found 81 channels, collected in 26 groves. | Phase space: Using 109 equivalences between channels. | Phase space: wood | Phase space: 81 channels, 8 dimensions | Phase space: found 81 channels, collected in 26 groves. | Phase space: Using 109 equivalences between channels. | Phase space: wood | Phase space: 81 channels, 9 dimensions | Phase space: found 81 channels, collected in 26 groves. | Phase space: Using 109 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 2 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'drellyNLO' part 'born' | Integrate: iterations = 1:1000:"gw" | Integrator: 26 chains, 81 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'drellyNLO.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'drellyNLO.m1.vg2'. | VAMP2: set chain: use chained weights. 1 1029 1.7082321E+02 1.71E+02 99.82 32.02* 8.34 |-----------------------------------------------------------------------------| 1 1029 1.7082321E+02 1.71E+02 99.82 32.02 8.34 |=============================================================================| | Starting integration for process 'drellyNLO' part 'real' | Integrate: iterations = 1:1000:"gw" | Integrator: 26 chains, 81 channels, 13 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'drellyNLO.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'drellyNLO.m2.vg2'. | VAMP2: set chain: use chained weights. 1 1019 1.9915628E+01 2.92E+01 146.72 46.84* 10.72 |-----------------------------------------------------------------------------| 1 1019 1.9915628E+01 2.92E+01 146.72 46.84 10.72 |=============================================================================| | Starting integration for process 'drellyNLO' part 'virtual' | Integrate: iterations = 1:1000:"gw" | Integrator: 26 chains, 81 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'drellyNLO.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'drellyNLO.m3.vg2'. | VAMP2: set chain: use chained weights. 1 1030 -1.2539877E+01 8.69E+00 69.32 22.25* 8.51 |-----------------------------------------------------------------------------| 1 1030 -1.2539877E+01 8.69E+00 69.32 22.25 8.51 |=============================================================================| | Starting integration for process 'drellyNLO' part 'dglap' | Integrate: iterations = 1:1000:"gw" | Integrator: 26 chains, 81 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'drellyNLO.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'drellyNLO.m4.vg2'. | VAMP2: set chain: use chained weights. 1 1018 4.0168989E+01 4.13E+01 102.85 32.82* 8.39 |-----------------------------------------------------------------------------| 1 1018 4.0168989E+01 4.13E+01 102.85 32.82 8.39 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.1836795E+02 1.78E+02 81.55 0.00* 8.05 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 27.8327 +- 40.93079 ) % +| ( 27.83 +- 40.93 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzw.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzw.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzw.ref (revision 8760) @@ -1,209 +1,209 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $negative_sf = "positive" [user variable] Wpm = PDG(24, -24) $lhapdf_file = "MSTW2008nlo68cl" sqrts = 1.300000000000E+04 alpha_power = 2 alphas_power = 0 ?alphas_from_mz = false ?alphas_from_lhapdf = true ?combined_nlo_integration = false | Process library 'nlo_ppzw_lib': recorded process 'nlo_ppzw_p1' | Integrate: current process library needs compilation | Process library 'nlo_ppzw_lib': compiling ... | Process library 'nlo_ppzw_lib': writing makefile | Process library 'nlo_ppzw_lib': removing old files | Process library 'nlo_ppzw_lib': writing driver | Process library 'nlo_ppzw_lib': creating source code | Process library 'nlo_ppzw_lib': compiling sources | Process library 'nlo_ppzw_lib': linking | Process library 'nlo_ppzw_lib': loading | Process library 'nlo_ppzw_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_ppzw_p1: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ppzw_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ppzw_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_ppzw_p1' | Library name = 'nlo_ppzw_lib' | Process index = 1 | Process components: | 1: 'nlo_ppzw_p1_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, W+:W- [openloops] | 2: 'nlo_ppzw_p1_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => Z, W+:W-, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_ppzw_p1_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, W+:W- [openloops], [virtual] | 4: 'nlo_ppzw_p1_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, W+:W- [inactive], [subtraction] | 5: 'nlo_ppzw_p1_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, W+:W- [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 5 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 5 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 5 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 5 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 3 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 5 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_ppzw_p1' part 'born' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzw_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzw_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 448 2.2318426E+04 9.44E+03 42.30 8.95* 1.61 |-----------------------------------------------------------------------------| 1 448 2.2318426E+04 9.44E+03 42.30 8.95 1.61 |=============================================================================| | Starting integration for process 'nlo_ppzw_p1' part 'real' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzw_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzw_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 500 7.4808395E+03 5.59E+03 74.76 16.72* 1.83 |-----------------------------------------------------------------------------| 1 500 7.4808395E+03 5.59E+03 74.76 16.72 1.83 |=============================================================================| | Starting integration for process 'nlo_ppzw_p1' part 'virtual' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzw_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzw_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 478 7.1479170E+03 2.34E+03 32.73 7.16* 2.24 |-----------------------------------------------------------------------------| 1 478 7.1479170E+03 2.34E+03 32.73 7.16 2.24 |=============================================================================| | Starting integration for process 'nlo_ppzw_p1' part 'dglap' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzw_p1.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzw_p1.m4.vg2'. | VAMP2: set chain: use chained weights. 1 416 9.3555985E+02 6.77E+02 72.34 14.75* 2.55 |-----------------------------------------------------------------------------| 1 416 9.3555985E+02 6.77E+02 72.34 14.75 2.55 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 3.7882742E+04 1.12E+04 29.67 0.00* 1.76 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 69.7375 +- 40.21210 ) % +| ( 69.74 +- 40.21 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4t.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4t.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4t.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 2 | Process library 'nlo_ee4t_lib': recorded process 'nlo_ee4t_p1' | Integrate: current process library needs compilation | Process library 'nlo_ee4t_lib': compiling ... | Process library 'nlo_ee4t_lib': writing makefile | Process library 'nlo_ee4t_lib': removing old files | Process library 'nlo_ee4t_lib': writing driver | Process library 'nlo_ee4t_lib': creating source code | Process library 'nlo_ee4t_lib': compiling sources | Process library 'nlo_ee4t_lib': linking | Process library 'nlo_ee4t_lib': loading | Process library 'nlo_ee4t_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_ee4t_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee4t_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee4t_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_ee4t_p1' | Library name = 'nlo_ee4t_lib' | Process index = 1 | Process components: | 1: 'nlo_ee4t_p1_i1': e-, e+ => t, tbar, t, tbar [openloops] | 2: 'nlo_ee4t_p1_i2': e-, e+ => t, tbar, t, tbar, gl [openloops], [real] | 3: 'nlo_ee4t_p1_i3': e-, e+ => t, tbar, t, tbar [openloops], [virtual] | 4: 'nlo_ee4t_p1_i4': e-, e+ => t, tbar, t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 16 channels, 8 dimensions | Phase space: found 16 channels, collected in 2 groves. | Phase space: Using 96 equivalences between channels. | Phase space: wood | Phase space: 16 channels, 11 dimensions | Phase space: found 16 channels, collected in 2 groves. | Phase space: Using 96 equivalences between channels. | Phase space: wood | Phase space: 16 channels, 8 dimensions | Phase space: found 16 channels, collected in 2 groves. | Phase space: Using 96 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_ee4t_p1' part 'born' | Integrate: iterations = 1:160:"gw" | Integrator: 2 chains, 16 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4t_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 160 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4t_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 160 6.3704751E-04 7.16E-05 11.24 1.42* 28.70 |-----------------------------------------------------------------------------| 1 160 6.3704751E-04 7.16E-05 11.24 1.42 28.70 |=============================================================================| | Starting integration for process 'nlo_ee4t_p1' part 'real' | Integrate: iterations = 1:160:"gw" | Integrator: 2 chains, 16 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4t_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 160 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4t_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 160 -2.0914858E-04 2.29E-05 10.94 1.38* 29.07 |-----------------------------------------------------------------------------| 1 160 -2.0914858E-04 2.29E-05 10.94 1.38 29.07 |=============================================================================| | Starting integration for process 'nlo_ee4t_p1' part 'virtual' | Integrate: iterations = 1:160:"gw" | Integrator: 2 chains, 16 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4t_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 160 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4t_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 160 7.0389404E-04 7.85E-05 11.15 1.41* 28.03 |-----------------------------------------------------------------------------| 1 160 7.0389404E-04 7.85E-05 11.15 1.41 28.03 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.1317930E-03 1.09E-04 9.60 0.00* 23.92 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 77.6623 +- 15.52148 ) % +| ( 77.66 +- 15.52 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eett.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eett.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eett.ref (revision 8760) @@ -1,172 +1,172 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 0 | Process library 'nlo_eett_lib': recorded process 'nlo_eett_p1' | Integrate: current process library needs compilation | Process library 'nlo_eett_lib': compiling ... | Process library 'nlo_eett_lib': writing makefile | Process library 'nlo_eett_lib': removing old files | Process library 'nlo_eett_lib': writing driver | Process library 'nlo_eett_lib': creating source code | Process library 'nlo_eett_lib': compiling sources | Process library 'nlo_eett_lib': linking | Process library 'nlo_eett_lib': loading | Process library 'nlo_eett_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eett_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eett_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eett_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eett_p1' | Library name = 'nlo_eett_lib' | Process index = 1 | Process components: | 1: 'nlo_eett_p1_i1': e-, e+ => t, tbar [openloops] | 2: 'nlo_eett_p1_i2': e-, e+ => t, tbar, gl [openloops], [real] | 3: 'nlo_eett_p1_i3': e-, e+ => t, tbar [openloops], [virtual] | 4: 'nlo_eett_p1_i4': e-, e+ => t, tbar [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_eett_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eett_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eett_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 98 1.6780255E+02 1.83E+00 1.09 0.11* 41.44 |-----------------------------------------------------------------------------| 1 98 1.6780255E+02 1.83E+00 1.09 0.11 41.44 |=============================================================================| | Starting integration for process 'nlo_eett_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eett_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eett_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 96 -4.2905273E+01 2.30E+00 5.37 0.53* 30.26 |-----------------------------------------------------------------------------| 1 96 -4.2905273E+01 2.30E+00 5.37 0.53 30.26 |=============================================================================| | Starting integration for process 'nlo_eett_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eett_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eett_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 98 4.8853813E+01 6.76E-01 1.38 0.14* 35.70 |-----------------------------------------------------------------------------| 1 98 4.8853813E+01 6.76E-01 1.38 0.14 35.70 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.7375109E+02 3.02E+00 1.74 0.00* 32.07 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 3.5450 +- 1.43164 ) % +| ( 3.54 +- 1.43 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzz.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzz.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzz.ref (revision 8760) @@ -1,208 +1,208 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $negative_sf = "positive" $lhapdf_file = "MSTW2008nlo68cl" sqrts = 1.300000000000E+04 alpha_power = 2 alphas_power = 0 ?alphas_from_mz = false ?alphas_from_lhapdf = true ?combined_nlo_integration = false | Process library 'nlo_ppzz_lib': recorded process 'nlo_ppzz_p1' | Integrate: current process library needs compilation | Process library 'nlo_ppzz_lib': compiling ... | Process library 'nlo_ppzz_lib': writing makefile | Process library 'nlo_ppzz_lib': removing old files | Process library 'nlo_ppzz_lib': writing driver | Process library 'nlo_ppzz_lib': creating source code | Process library 'nlo_ppzz_lib': compiling sources | Process library 'nlo_ppzz_lib': linking | Process library 'nlo_ppzz_lib': loading | Process library 'nlo_ppzz_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_ppzz_p1: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ppzz_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ppzz_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_ppzz_p1' | Library name = 'nlo_ppzz_lib' | Process index = 1 | Process components: | 1: 'nlo_ppzz_p1_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, Z [openloops] | 2: 'nlo_ppzz_p1_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => Z, Z, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_ppzz_p1_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, Z [openloops], [virtual] | 4: 'nlo_ppzz_p1_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, Z [inactive], [subtraction] | 5: 'nlo_ppzz_p1_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z, Z [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 2 groves. | Phase space: Using 18 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 5 dimensions | Phase space: found 5 channels, collected in 2 groves. | Phase space: Using 18 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 2 groves. | Phase space: Using 18 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 3 dimensions | Phase space: found 5 channels, collected in 2 groves. | Phase space: Using 18 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_ppzz_p1' part 'born' | Integrate: iterations = 1:500:"gw" | Integrator: 2 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzz_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzz_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 480 5.2493104E+03 2.54E+03 48.41 10.61* 1.46 |-----------------------------------------------------------------------------| 1 480 5.2493104E+03 2.54E+03 48.41 10.61 1.46 |=============================================================================| | Starting integration for process 'nlo_ppzz_p1' part 'real' | Integrate: iterations = 1:500:"gw" | Integrator: 2 chains, 5 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzz_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzz_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 501 -6.0423038E+02 4.35E+02 72.02 16.12* 2.04 |-----------------------------------------------------------------------------| 1 501 -6.0423038E+02 4.35E+02 72.02 16.12 2.04 |=============================================================================| | Starting integration for process 'nlo_ppzz_p1' part 'virtual' | Integrate: iterations = 1:500:"gw" | Integrator: 2 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzz_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzz_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 477 1.5233944E+03 5.05E+02 33.15 7.24* 1.88 |-----------------------------------------------------------------------------| 1 477 1.5233944E+03 5.05E+02 33.15 7.24 1.88 |=============================================================================| | Starting integration for process 'nlo_ppzz_p1' part 'dglap' | Integrate: iterations = 1:500:"gw" | Integrator: 2 chains, 5 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ppzz_p1.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ppzz_p1.m4.vg2'. | VAMP2: set chain: use chained weights. 1 384 4.2945688E+02 2.21E+02 51.39 10.07* 2.06 |-----------------------------------------------------------------------------| 1 384 4.2945688E+02 2.21E+02 51.39 10.07 2.06 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 6.5979313E+03 2.64E+03 39.96 0.00* 1.43 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 25.6914 +- 18.26611 ) % +| ( 25.69 +- 18.27 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetth.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetth.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetth.ref (revision 8760) @@ -1,172 +1,172 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 3 alphas_power = 0 | Process library 'nlo_eetth_lib': recorded process 'nlo_eetth_p1' | Integrate: current process library needs compilation | Process library 'nlo_eetth_lib': compiling ... | Process library 'nlo_eetth_lib': writing makefile | Process library 'nlo_eetth_lib': removing old files | Process library 'nlo_eetth_lib': writing driver | Process library 'nlo_eetth_lib': creating source code | Process library 'nlo_eetth_lib': compiling sources | Process library 'nlo_eetth_lib': linking | Process library 'nlo_eetth_lib': loading | Process library 'nlo_eetth_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eetth_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetth_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetth_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eetth_p1' | Library name = 'nlo_eetth_lib' | Process index = 1 | Process components: | 1: 'nlo_eetth_p1_i1': e-, e+ => t, tbar, H [openloops] | 2: 'nlo_eetth_p1_i2': e-, e+ => t, tbar, H, gl [openloops], [real] | 3: 'nlo_eetth_p1_i3': e-, e+ => t, tbar, H [openloops], [virtual] | 4: 'nlo_eetth_p1_i4': e-, e+ => t, tbar, H [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 3 channels, 5 dimensions | Phase space: found 3 channels, collected in 1 grove. | Phase space: Using 3 equivalences between channels. | Phase space: wood | Phase space: 3 channels, 8 dimensions | Phase space: found 3 channels, collected in 1 grove. | Phase space: Using 3 equivalences between channels. | Phase space: wood | Phase space: 3 channels, 5 dimensions | Phase space: found 3 channels, collected in 1 grove. | Phase space: Using 3 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_eetth_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 3 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetth_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetth_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 99 2.0104544E+00 1.47E-01 7.33 0.73* 30.49 |-----------------------------------------------------------------------------| 1 99 2.0104544E+00 1.47E-01 7.33 0.73 30.49 |=============================================================================| | Starting integration for process 'nlo_eetth_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 3 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetth_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetth_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 99 -4.0829431E-01 4.05E-02 9.92 0.99* 23.34 |-----------------------------------------------------------------------------| 1 99 -4.0829431E-01 4.05E-02 9.92 0.99 23.34 |=============================================================================| | Starting integration for process 'nlo_eetth_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 3 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetth_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetth_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 99 3.0647296E-01 1.98E-02 6.46 0.64* 34.90 |-----------------------------------------------------------------------------| 1 99 3.0647296E-01 1.98E-02 6.46 0.64 34.90 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.9086331E+00 1.54E-01 8.07 0.00* 25.54 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -5.0646 +- 2.27315 ) % +| ( -5.06 +- 2.27 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4tj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4tj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee4tj.ref (revision 8760) @@ -1,173 +1,173 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 3 | Process library 'nlo_ee4tj_lib': recorded process 'nlo_ee4tj_p1' | Integrate: current process library needs compilation | Process library 'nlo_ee4tj_lib': compiling ... | Process library 'nlo_ee4tj_lib': writing makefile | Process library 'nlo_ee4tj_lib': removing old files | Process library 'nlo_ee4tj_lib': writing driver | Process library 'nlo_ee4tj_lib': creating source code | Process library 'nlo_ee4tj_lib': compiling sources | Process library 'nlo_ee4tj_lib': linking | Process library 'nlo_ee4tj_lib': loading | Process library 'nlo_ee4tj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_ee4tj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee4tj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee4tj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_ee4tj_p1' | Library name = 'nlo_ee4tj_lib' | Process index = 1 | Process components: | 1: 'nlo_ee4tj_p1_i1': e-, e+ => t, tbar, t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_ee4tj_p1_i2': e-, e+ => t, tbar, t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_ee4tj_p1_i3': e-, e+ => t, tbar, t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_ee4tj_p1_i4': e-, e+ => t, tbar, t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 64 channels, 11 dimensions | Phase space: found 64 channels, collected in 2 groves. | Phase space: Using 384 equivalences between channels. | Phase space: wood | Phase space: 64 channels, 14 dimensions | Phase space: found 64 channels, collected in 2 groves. | Phase space: Using 384 equivalences between channels. | Phase space: wood | Phase space: 64 channels, 11 dimensions | Phase space: found 64 channels, collected in 2 groves. | Phase space: Using 384 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_ee4tj_p1' part 'born' | Integrate: iterations = 1:640:"gw" | Integrator: 2 chains, 64 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4tj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 640 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4tj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 640 3.3015681E-05 6.26E-06 18.95 4.80* 12.71 |-----------------------------------------------------------------------------| 1 640 3.3015681E-05 6.26E-06 18.95 4.80 12.71 |=============================================================================| | Starting integration for process 'nlo_ee4tj_p1' part 'real' | Integrate: iterations = 1:640:"gw" | Integrator: 2 chains, 64 channels, 14 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4tj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 640 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4tj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 640 -6.1255904E-06 3.37E-06 55.00 13.91* 16.23 |-----------------------------------------------------------------------------| 1 640 -6.1255904E-06 3.37E-06 55.00 13.91 16.23 |=============================================================================| | Starting integration for process 'nlo_ee4tj_p1' part 'virtual' | Integrate: iterations = 1:640:"gw" | Integrator: 2 chains, 64 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee4tj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 640 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee4tj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 640 2.5286924E-05 4.40E-06 17.39 4.40* 12.13 |-----------------------------------------------------------------------------| 1 640 2.5286924E-05 4.40E-06 17.39 4.40 12.13 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 5.2177015E-05 8.36E-06 16.02 0.00* 11.14 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 58.0371 +- 20.06396 ) % +| ( 58.04 +- 20.06 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettj.ref (revision 8760) @@ -1,171 +1,171 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 1 | Process library 'nlo_eettj_lib': recorded process 'nlo_eettj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettj_lib': compiling ... | Process library 'nlo_eettj_lib': writing makefile | Process library 'nlo_eettj_lib': removing old files | Process library 'nlo_eettj_lib': writing driver | Process library 'nlo_eettj_lib': creating source code | Process library 'nlo_eettj_lib': compiling sources | Process library 'nlo_eettj_lib': linking | Process library 'nlo_eettj_lib': loading | Process library 'nlo_eettj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettj_p1' | Library name = 'nlo_eettj_lib' | Process index = 1 | Process components: | 1: 'nlo_eettj_p1_i1': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eettj_p1_i2': e-, e+ => t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eettj_p1_i3': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eettj_p1_i4': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 2 equivalences between channels. | Phase space: wood | Phase space: 2 channels, 8 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 2 equivalences between channels. | Phase space: wood | Phase space: 2 channels, 5 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 2 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eettj_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 2 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 100 4.4113189E+01 8.43E+00 19.11 1.91* 11.29 |-----------------------------------------------------------------------------| 1 100 4.4113189E+01 8.43E+00 19.11 1.91 11.29 |=============================================================================| | Starting integration for process 'nlo_eettj_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 2 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 100 -1.0155418E+01 7.25E+00 71.36 7.14* 8.97 |-----------------------------------------------------------------------------| 1 100 -1.0155418E+01 7.25E+00 71.36 7.14 8.97 |=============================================================================| | Starting integration for process 'nlo_eettj_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 2 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.0827676E+01 3.35E+00 30.98 3.10* 5.85 |-----------------------------------------------------------------------------| 1 100 1.0827676E+01 3.35E+00 30.98 3.10 5.85 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 4.4785447E+01 1.16E+01 25.93 0.00* 7.78 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 1.5239 +- 18.10505 ) % +| ( 1.52 +- 18.11 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettww.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettww.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettww.ref (revision 8760) @@ -1,172 +1,172 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 4 alphas_power = 0 | Process library 'nlo_eettww_lib': recorded process 'nlo_eettww_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettww_lib': compiling ... | Process library 'nlo_eettww_lib': writing makefile | Process library 'nlo_eettww_lib': removing old files | Process library 'nlo_eettww_lib': writing driver | Process library 'nlo_eettww_lib': creating source code | Process library 'nlo_eettww_lib': compiling sources | Process library 'nlo_eettww_lib': linking | Process library 'nlo_eettww_lib': loading | Process library 'nlo_eettww_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettww_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettww_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettww_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettww_p1' | Library name = 'nlo_eettww_lib' | Process index = 1 | Process components: | 1: 'nlo_eettww_p1_i1': e-, e+ => t, tbar, W+, W- [openloops] | 2: 'nlo_eettww_p1_i2': e-, e+ => t, tbar, W+, W-, gl [openloops], [real] | 3: 'nlo_eettww_p1_i3': e-, e+ => t, tbar, W+, W- [openloops], [virtual] | 4: 'nlo_eettww_p1_i4': e-, e+ => t, tbar, W+, W- [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 8 channels, 8 dimensions | Phase space: found 8 channels, collected in 3 groves. | Phase space: Using 8 equivalences between channels. | Phase space: wood | Phase space: 8 channels, 11 dimensions | Phase space: found 8 channels, collected in 3 groves. | Phase space: Using 8 equivalences between channels. | Phase space: wood | Phase space: 8 channels, 8 dimensions | Phase space: found 8 channels, collected in 3 groves. | Phase space: Using 8 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_eettww_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 3 chains, 8 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettww_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettww_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.6643469E-01 5.55E-02 33.34 3.33* 10.69 |-----------------------------------------------------------------------------| 1 100 1.6643469E-01 5.55E-02 33.34 3.33 10.69 |=============================================================================| | Starting integration for process 'nlo_eettww_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 3 chains, 8 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettww_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettww_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 102 -3.0683483E-02 1.20E-02 39.14 3.95* 10.91 |-----------------------------------------------------------------------------| 1 102 -3.0683483E-02 1.20E-02 39.14 3.95 10.91 |=============================================================================| | Starting integration for process 'nlo_eettww_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 3 chains, 8 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettww_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettww_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 100 8.9943033E-02 2.32E-02 25.84 2.58* 14.23 |-----------------------------------------------------------------------------| 1 100 8.9943033E-02 2.32E-02 25.84 2.58 14.23 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.2569424E-01 6.13E-02 27.18 0.00* 10.31 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 35.6053 +- 19.69732 ) % +| ( 35.61 +- 19.70 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthh.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthh.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthh.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 4 alphas_power = 0 | Process library 'nlo_eetthh_lib': recorded process 'nlo_eetthh_p1' | Integrate: current process library needs compilation | Process library 'nlo_eetthh_lib': compiling ... | Process library 'nlo_eetthh_lib': writing makefile | Process library 'nlo_eetthh_lib': removing old files | Process library 'nlo_eetthh_lib': writing driver | Process library 'nlo_eetthh_lib': creating source code | Process library 'nlo_eetthh_lib': compiling sources | Process library 'nlo_eetthh_lib': linking | Process library 'nlo_eetthh_lib': loading | Process library 'nlo_eetthh_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eetthh_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthh_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthh_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eetthh_p1' | Library name = 'nlo_eetthh_lib' | Process index = 1 | Process components: | 1: 'nlo_eetthh_p1_i1': e-, e+ => t, tbar, H, H [openloops] | 2: 'nlo_eetthh_p1_i2': e-, e+ => t, tbar, H, H, gl [openloops], [real] | 3: 'nlo_eetthh_p1_i3': e-, e+ => t, tbar, H, H [openloops], [virtual] | 4: 'nlo_eetthh_p1_i4': e-, e+ => t, tbar, H, H [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 12 channels, 8 dimensions | Phase space: found 12 channels, collected in 1 grove. | Phase space: Using 24 equivalences between channels. | Phase space: wood | Phase space: 12 channels, 11 dimensions | Phase space: found 12 channels, collected in 1 grove. | Phase space: Using 24 equivalences between channels. | Phase space: wood | Phase space: 12 channels, 8 dimensions | Phase space: found 12 channels, collected in 1 grove. | Phase space: Using 24 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_eetthh_p1' part 'born' | Integrate: iterations = 1:120:"gw" | Integrator: 1 chains, 12 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthh_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 120 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthh_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 120 1.4402584E-02 1.91E-03 13.28 1.45* 25.31 |-----------------------------------------------------------------------------| 1 120 1.4402584E-02 1.91E-03 13.28 1.45 25.31 |=============================================================================| | Starting integration for process 'nlo_eetthh_p1' part 'real' | Integrate: iterations = 1:120:"gw" | Integrator: 1 chains, 12 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthh_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 120 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthh_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 120 -2.7756784E-03 4.27E-04 15.39 1.69* 25.07 |-----------------------------------------------------------------------------| 1 120 -2.7756784E-03 4.27E-04 15.39 1.69 25.07 |=============================================================================| | Starting integration for process 'nlo_eetthh_p1' part 'virtual' | Integrate: iterations = 1:120:"gw" | Integrator: 1 chains, 12 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthh_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 120 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthh_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 120 8.0975983E-04 1.36E-04 16.78 1.84* 23.76 |-----------------------------------------------------------------------------| 1 120 8.0975983E-04 1.36E-04 16.78 1.84 23.76 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.2436666E-02 1.96E-03 15.80 0.00* 20.62 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-13.6498 +- 3.60157 ) % +| ( -13.65 +- 3.60 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppwhh_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppwhh_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppwhh_ew.ref (revision 8760) @@ -1,211 +1,211 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' alpha_power = 3 alphas_power = 0 seed = 1 $nlo_correction_type = "EW" | Process library 'nlo_ppwhh_ew_lib': recorded process 'ppwhh_ew' | Integrate: current process library needs compilation | Process library 'nlo_ppwhh_ew_lib': compiling ... | Process library 'nlo_ppwhh_ew_lib': writing makefile | Process library 'nlo_ppwhh_ew_lib': removing old files | Process library 'nlo_ppwhh_ew_lib': writing driver | Process library 'nlo_ppwhh_ew_lib': creating source code | Process library 'nlo_ppwhh_ew_lib': compiling sources | Process library 'nlo_ppwhh_ew_lib': linking | Process library 'nlo_ppwhh_ew_lib': loading | Process library 'nlo_ppwhh_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process ppwhh_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppwhh_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppwhh_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppwhh_ew' | Library name = 'nlo_ppwhh_ew_lib' | Process index = 1 | Process components: | 1: 'ppwhh_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, H, W+ [openloops] | 2: 'ppwhh_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => H, H, W+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'ppwhh_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, H, W+ [openloops], [virtual] | 4: 'ppwhh_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, H, W+ [inactive], [subtraction] | 5: 'ppwhh_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, H, W+ [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 23 channels, 5 dimensions | Phase space: found 23 channels, collected in 5 groves. | Phase space: Using 70 equivalences between channels. | Phase space: wood | Phase space: 23 channels, 8 dimensions | Phase space: found 23 channels, collected in 5 groves. | Phase space: Using 70 equivalences between channels. | Phase space: wood | Phase space: 23 channels, 5 dimensions | Phase space: found 23 channels, collected in 5 groves. | Phase space: Using 70 equivalences between channels. | Phase space: wood | Phase space: 23 channels, 6 dimensions | Phase space: found 23 channels, collected in 5 groves. | Phase space: Using 70 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'ppwhh_ew' part 'born' | Integrate: iterations = 1:300:"gw" | Integrator: 5 chains, 23 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwhh_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwhh_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 300 2.5544525E-01 8.71E-02 34.11 5.91* 8.83 |-----------------------------------------------------------------------------| 1 300 2.5544525E-01 8.71E-02 34.11 5.91 8.83 |=============================================================================| | Starting integration for process 'ppwhh_ew' part 'real' | Integrate: iterations = 1:300:"gw" | Integrator: 5 chains, 23 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwhh_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwhh_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 300 2.6651386E-04 7.59E-04 284.73 49.32* 15.90 |-----------------------------------------------------------------------------| 1 300 2.6651386E-04 7.59E-04 284.73 49.32 15.90 |=============================================================================| | Starting integration for process 'ppwhh_ew' part 'virtual' | Integrate: iterations = 1:300:"gw" | Integrator: 5 chains, 23 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwhh_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwhh_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 295 -5.6309985E-02 1.57E-02 27.86 4.79* 10.44 |-----------------------------------------------------------------------------| 1 295 -5.6309985E-02 1.57E-02 27.86 4.79 10.44 |=============================================================================| | Starting integration for process 'ppwhh_ew' part 'dglap' | Integrate: iterations = 1:300:"gw" | Integrator: 5 chains, 23 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwhh_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwhh_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 296 2.7986734E-04 2.33E-04 83.32 14.33* 11.26 |-----------------------------------------------------------------------------| 1 296 2.7986734E-04 2.33E-04 83.32 14.33 11.26 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.9968165E-01 8.85E-02 44.34 0.00* 6.89 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-21.8300 +- 9.65811 ) % +| ( -21.83 +- 9.66 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthj.ref (revision 8760) @@ -1,171 +1,171 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 3 alphas_power = 1 | Process library 'nlo_eetthj_lib': recorded process 'nlo_eetthj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eetthj_lib': compiling ... | Process library 'nlo_eetthj_lib': writing makefile | Process library 'nlo_eetthj_lib': removing old files | Process library 'nlo_eetthj_lib': writing driver | Process library 'nlo_eetthj_lib': creating source code | Process library 'nlo_eetthj_lib': compiling sources | Process library 'nlo_eetthj_lib': linking | Process library 'nlo_eetthj_lib': loading | Process library 'nlo_eetthj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eetthj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eetthj_p1' | Library name = 'nlo_eetthj_lib' | Process index = 1 | Process components: | 1: 'nlo_eetthj_p1_i1': e-, e+ => t, tbar, H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eetthj_p1_i2': e-, e+ => t, tbar, H, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eetthj_p1_i3': e-, e+ => t, tbar, H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eetthj_p1_i4': e-, e+ => t, tbar, H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 6 channels, 8 dimensions | Phase space: found 6 channels, collected in 1 grove. | Phase space: Using 6 equivalences between channels. | Phase space: wood | Phase space: 6 channels, 11 dimensions | Phase space: found 6 channels, collected in 1 grove. | Phase space: Using 6 equivalences between channels. | Phase space: wood | Phase space: 6 channels, 8 dimensions | Phase space: found 6 channels, collected in 1 grove. | Phase space: Using 6 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eetthj_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 6 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 102 2.1971622E-01 5.21E-02 23.71 2.39* 12.91 |-----------------------------------------------------------------------------| 1 102 2.1971622E-01 5.21E-02 23.71 2.39 12.91 |=============================================================================| | Starting integration for process 'nlo_eetthj_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 6 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 102 4.1144864E-03 2.13E-02 517.36 52.25* 17.05 |-----------------------------------------------------------------------------| 1 102 4.1144864E-03 2.13E-02 517.36 52.25 17.05 |=============================================================================| | Starting integration for process 'nlo_eetthj_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 6 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 102 1.7075037E-02 5.97E-03 34.97 3.53* 9.79 |-----------------------------------------------------------------------------| 1 102 1.7075037E-02 5.97E-03 34.97 3.53 9.79 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.4090574E-01 5.66E-02 23.49 0.00* 12.67 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 9.6440 +- 10.31875 ) % +| ( 9.64 +- 10.32 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettjj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettjj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettjj.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 2 | Process library 'nlo_eettjj_lib': recorded process 'nlo_eettjj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettjj_lib': compiling ... | Process library 'nlo_eettjj_lib': writing makefile | Process library 'nlo_eettjj_lib': removing old files | Process library 'nlo_eettjj_lib': writing driver | Process library 'nlo_eettjj_lib': creating source code | Process library 'nlo_eettjj_lib': compiling sources | Process library 'nlo_eettjj_lib': linking | Process library 'nlo_eettjj_lib': loading | Process library 'nlo_eettjj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettjj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettjj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettjj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettjj_p1' | Library name = 'nlo_eettjj_lib' | Process index = 1 | Process components: | 1: 'nlo_eettjj_p1_i1': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eettjj_p1_i2': e-, e+ => t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eettjj_p1_i3': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eettjj_p1_i4': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 18 channels, 8 dimensions | Phase space: found 18 channels, collected in 5 groves. | Phase space: Using 24 equivalences between channels. | Phase space: wood | Phase space: 18 channels, 11 dimensions | Phase space: found 18 channels, collected in 5 groves. | Phase space: Using 24 equivalences between channels. | Phase space: wood | Phase space: 18 channels, 8 dimensions | Phase space: found 18 channels, collected in 5 groves. | Phase space: Using 24 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eettjj_p1' part 'born' | Integrate: iterations = 1:180:"gw" | Integrator: 5 chains, 18 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettjj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 180 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettjj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 190 1.4441407E+01 7.60E+00 52.64 7.26* 11.58 |-----------------------------------------------------------------------------| 1 190 1.4441407E+01 7.60E+00 52.64 7.26 11.58 |=============================================================================| | Starting integration for process 'nlo_eettjj_p1' part 'real' | Integrate: iterations = 1:180:"gw" | Integrator: 5 chains, 18 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettjj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 180 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettjj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 190 -2.3800632E+00 3.08E+00 129.59 17.86* 14.83 |-----------------------------------------------------------------------------| 1 190 -2.3800632E+00 3.08E+00 129.59 17.86 14.83 |=============================================================================| | Starting integration for process 'nlo_eettjj_p1' part 'virtual' | Integrate: iterations = 1:180:"gw" | Integrator: 5 chains, 18 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettjj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 180 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettjj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 184 6.3942161E-01 5.43E-01 84.96 11.52* 19.91 |-----------------------------------------------------------------------------| 1 184 6.3942161E-01 5.43E-01 84.96 11.52 19.91 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.2700765E+01 8.22E+00 64.73 0.00* 9.92 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-12.0531 +- 22.59596 ) % +| ( -12.05 +- 22.60 ) % |=============================================================================| | There were no errors and 2 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzzz_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzzz_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppzzz_ew.ref (revision 8760) @@ -1,211 +1,211 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' alpha_power = 3 alphas_power = 0 seed = 1 $nlo_correction_type = "EW" | Process library 'nlo_ppzzz_ew_lib': recorded process 'ppzzz_ew' | Integrate: current process library needs compilation | Process library 'nlo_ppzzz_ew_lib': compiling ... | Process library 'nlo_ppzzz_ew_lib': writing makefile | Process library 'nlo_ppzzz_ew_lib': removing old files | Process library 'nlo_ppzzz_ew_lib': writing driver | Process library 'nlo_ppzzz_ew_lib': creating source code | Process library 'nlo_ppzzz_ew_lib': compiling sources | Process library 'nlo_ppzzz_ew_lib': linking | Process library 'nlo_ppzzz_ew_lib': loading | Process library 'nlo_ppzzz_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process ppzzz_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppzzz_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppzzz_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppzzz_ew' | Library name = 'nlo_ppzzz_ew_lib' | Process index = 1 | Process components: | 1: 'ppzzz_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z, Z, Z [openloops] | 2: 'ppzzz_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => Z, Z, Z, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'ppzzz_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z, Z, Z [openloops], [virtual] | 4: 'ppzzz_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z, Z, Z [inactive], [subtraction] | 5: 'ppzzz_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z, Z, Z [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 27 channels, 5 dimensions | Phase space: found 27 channels, collected in 4 groves. | Phase space: Using 234 equivalences between channels. | Phase space: wood | Phase space: 27 channels, 8 dimensions | Phase space: found 27 channels, collected in 4 groves. | Phase space: Using 234 equivalences between channels. | Phase space: wood | Phase space: 27 channels, 5 dimensions | Phase space: found 27 channels, collected in 4 groves. | Phase space: Using 234 equivalences between channels. | Phase space: wood | Phase space: 27 channels, 6 dimensions | Phase space: found 27 channels, collected in 4 groves. | Phase space: Using 234 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'ppzzz_ew' part 'born' | Integrate: iterations = 1:300:"gw" | Integrator: 4 chains, 27 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppzzz_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppzzz_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 309 7.1197555E+00 3.58E+00 50.35 8.85* 9.29 |-----------------------------------------------------------------------------| 1 309 7.1197555E+00 3.58E+00 50.35 8.85 9.29 |=============================================================================| | Starting integration for process 'ppzzz_ew' part 'real' | Integrate: iterations = 1:300:"gw" | Integrator: 4 chains, 27 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppzzz_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppzzz_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 297 5.8296043E-04 1.84E-03 315.79 54.42* 16.46 |-----------------------------------------------------------------------------| 1 297 5.8296043E-04 1.84E-03 315.79 54.42 16.46 |=============================================================================| | Starting integration for process 'ppzzz_ew' part 'virtual' | Integrate: iterations = 1:300:"gw" | Integrator: 4 chains, 27 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppzzz_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppzzz_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 303 -1.4904616E+00 4.76E-01 31.95 5.56* 12.22 |-----------------------------------------------------------------------------| 1 303 -1.4904616E+00 4.76E-01 31.95 5.56 12.22 |=============================================================================| | Starting integration for process 'ppzzz_ew' part 'dglap' | Integrate: iterations = 1:300:"gw" | Integrator: 4 chains, 27 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppzzz_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppzzz_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 297 3.4187166E-03 7.69E-03 224.94 38.77* 15.95 |-----------------------------------------------------------------------------| 1 297 3.4187166E-03 7.69E-03 224.94 38.77 15.95 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 5.6332956E+00 3.62E+00 64.19 0.00* 7.35 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-20.8780 +- 12.45889 ) % +| ( -20.88 +- 12.46 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee5j.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee5j.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ee5j.ref (revision 8760) @@ -1,177 +1,177 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 3 $restrictions = "!W+:W-" | Process library 'nlo_ee5j_lib': recorded process 'nlo_ee5j_p1' | Integrate: current process library needs compilation | Process library 'nlo_ee5j_lib': compiling ... | Process library 'nlo_ee5j_lib': writing makefile | Process library 'nlo_ee5j_lib': removing old files | Process library 'nlo_ee5j_lib': writing driver | Process library 'nlo_ee5j_lib': creating source code | Process library 'nlo_ee5j_lib': compiling sources | Process library 'nlo_ee5j_lib': linking | Process library 'nlo_ee5j_lib': loading | Process library 'nlo_ee5j_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_ee5j_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. Warning: Intermediate decay of zero-width particle W- may be possible. Warning: Intermediate decay of zero-width particle W+ may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee5j_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_ee5j_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_ee5j_p1' | Library name = 'nlo_ee5j_lib' | Process index = 1 | Process components: | 1: 'nlo_ee5j_p1_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_ee5j_p1_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_ee5j_p1_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_ee5j_p1_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 104 channels, 11 dimensions | Phase space: found 104 channels, collected in 3 groves. | Phase space: Using 672 equivalences between channels. | Phase space: wood | Phase space: 104 channels, 14 dimensions | Phase space: found 104 channels, collected in 3 groves. | Phase space: Using 672 equivalences between channels. | Phase space: wood | Phase space: 104 channels, 11 dimensions | Phase space: found 104 channels, collected in 3 groves. | Phase space: Using 672 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_ee5j_p1' part 'born' | Integrate: iterations = 1:1040:"gw" | Integrator: 3 chains, 104 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee5j_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1040 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee5j_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 1040 1.8756860E+01 9.19E+00 49.00 15.80* 10.03 |-----------------------------------------------------------------------------| 1 1040 1.8756860E+01 9.19E+00 49.00 15.80 10.03 |=============================================================================| | Starting integration for process 'nlo_ee5j_p1' part 'real' | Integrate: iterations = 1:1040:"gw" | Integrator: 3 chains, 104 channels, 14 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee5j_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1040 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee5j_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 1040 1.4196379E+01 4.65E+00 32.75 10.56* 12.25 |-----------------------------------------------------------------------------| 1 1040 1.4196379E+01 4.65E+00 32.75 10.56 12.25 |=============================================================================| | Starting integration for process 'nlo_ee5j_p1' part 'virtual' | Integrate: iterations = 1:1040:"gw" | Integrator: 3 chains, 104 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_ee5j_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1040 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_ee5j_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 1040 -4.8314113E+01 4.40E+01 90.98 29.34* 10.14 |-----------------------------------------------------------------------------| 1 1040 -4.8314113E+01 4.40E+01 90.98 29.34 10.14 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 -1.5360874E+01 4.51E+01 293.90 0.00* -5.07 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (******** +- 251.94021 ) % +| (-181.89 +- 251.94 ) % |=============================================================================| | There were no errors and 4 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppww_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppww_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppww_ew.ref (revision 8760) @@ -1,213 +1,213 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' ?pacify = true SM.wtop => 1.44262E+00 alpha_power = 2 alphas_power = 0 seed = 1 $nlo_correction_type = "EW" | Process library 'nlo_ppww_ew_lib': recorded process 'ppww_ew' | Integrate: current process library needs compilation | Process library 'nlo_ppww_ew_lib': compiling ... | Process library 'nlo_ppww_ew_lib': writing makefile | Process library 'nlo_ppww_ew_lib': removing old files | Process library 'nlo_ppww_ew_lib': writing driver | Process library 'nlo_ppww_ew_lib': creating source code | Process library 'nlo_ppww_ew_lib': compiling sources | Process library 'nlo_ppww_ew_lib': linking | Process library 'nlo_ppww_ew_lib': loading | Process library 'nlo_ppww_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process ppww_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppww_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppww_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppww_ew' | Library name = 'nlo_ppww_ew_lib' | Process index = 1 | Process components: | 1: 'ppww_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => W+, W- [openloops] | 2: 'ppww_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => W+, W-, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'ppww_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => W+, W- [openloops], [virtual] | 4: 'ppww_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => W+, W- [inactive], [subtraction] | 5: 'ppww_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => W+, W- [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 9 channels, 2 dimensions | Phase space: found 9 channels, collected in 4 groves. | Phase space: Using 13 equivalences between channels. | Phase space: wood | Phase space: 9 channels, 5 dimensions | Phase space: found 9 channels, collected in 4 groves. | Phase space: Using 13 equivalences between channels. | Phase space: wood | Phase space: 9 channels, 2 dimensions | Phase space: found 9 channels, collected in 4 groves. | Phase space: Using 13 equivalences between channels. | Phase space: wood | Phase space: 9 channels, 3 dimensions | Phase space: found 9 channels, collected in 4 groves. | Phase space: Using 13 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'ppww_ew' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 4 chains, 9 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppww_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppww_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 102 3.866E+03 2.67E+03 68.93 6.96 9.4 |-----------------------------------------------------------------------------| 1 102 3.866E+03 2.67E+03 68.93 6.96 9.4 |=============================================================================| | Starting integration for process 'ppww_ew' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 4 chains, 9 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppww_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppww_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 104 4.876E+02 3.14E+02 64.41 6.57 12.3 |-----------------------------------------------------------------------------| 1 104 4.876E+02 3.14E+02 64.41 6.57 12.3 |=============================================================================| | Starting integration for process 'ppww_ew' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 4 chains, 9 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppww_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppww_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 102 -1.057E+03 8.01E+02 75.81 7.66 9.2 |-----------------------------------------------------------------------------| 1 102 -1.057E+03 8.01E+02 75.81 7.66 9.2 |=============================================================================| | Starting integration for process 'ppww_ew' part 'dglap' | Integrate: iterations = 1:100:"gw" | Integrator: 4 chains, 9 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppww_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppww_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 100 3.576E+02 2.17E+02 60.64 6.06 10.0 |-----------------------------------------------------------------------------| 1 100 3.576E+02 2.17E+02 60.64 6.06 10.0 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 3.655E+03 2.81E+03 76.86 0.00 7.5 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -5.4737 +- 23.25963 ) % +| ( -5.47 +- 23.26 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettz.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettz.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettz.ref (revision 8760) @@ -1,172 +1,172 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 3 alphas_power = 0 | Process library 'nlo_eettz_lib': recorded process 'nlo_eettz_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettz_lib': compiling ... | Process library 'nlo_eettz_lib': writing makefile | Process library 'nlo_eettz_lib': removing old files | Process library 'nlo_eettz_lib': writing driver | Process library 'nlo_eettz_lib': creating source code | Process library 'nlo_eettz_lib': compiling sources | Process library 'nlo_eettz_lib': linking | Process library 'nlo_eettz_lib': loading | Process library 'nlo_eettz_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettz_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettz_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettz_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettz_p1' | Library name = 'nlo_eettz_lib' | Process index = 1 | Process components: | 1: 'nlo_eettz_p1_i1': e-, e+ => t, tbar, Z [openloops] | 2: 'nlo_eettz_p1_i2': e-, e+ => t, tbar, Z, gl [openloops], [real] | 3: 'nlo_eettz_p1_i3': e-, e+ => t, tbar, Z [openloops], [virtual] | 4: 'nlo_eettz_p1_i4': e-, e+ => t, tbar, Z [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 7 channels, 5 dimensions | Phase space: found 7 channels, collected in 3 groves. | Phase space: Using 11 equivalences between channels. | Phase space: wood | Phase space: 7 channels, 8 dimensions | Phase space: found 7 channels, collected in 3 groves. | Phase space: Using 11 equivalences between channels. | Phase space: wood | Phase space: 7 channels, 5 dimensions | Phase space: found 7 channels, collected in 3 groves. | Phase space: Using 11 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_eettz_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 3 chains, 7 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettz_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettz_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 99 4.9357132E+00 5.64E-01 11.42 1.14* 30.10 |-----------------------------------------------------------------------------| 1 99 4.9357132E+00 5.64E-01 11.42 1.14 30.10 |=============================================================================| | Starting integration for process 'nlo_eettz_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 3 chains, 7 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettz_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettz_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 100 -1.0739389E+00 1.17E-01 10.89 1.09* 33.33 |-----------------------------------------------------------------------------| 1 100 -1.0739389E+00 1.17E-01 10.89 1.09 33.33 |=============================================================================| | Starting integration for process 'nlo_eettz_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 3 chains, 7 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettz_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettz_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.2315981E+00 1.19E-01 9.66 0.97* 31.96 |-----------------------------------------------------------------------------| 1 100 1.2315981E+00 1.19E-01 9.66 0.97 31.96 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 5.0933723E+00 5.88E-01 11.54 0.00* 25.15 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 3.1943 +- 3.40114 ) % +| ( 3.19 +- 3.40 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthjj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthjj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthjj.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 3 alphas_power = 2 | Process library 'nlo_eetthjj_lib': recorded process 'nlo_eetthjj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eetthjj_lib': compiling ... | Process library 'nlo_eetthjj_lib': writing makefile | Process library 'nlo_eetthjj_lib': removing old files | Process library 'nlo_eetthjj_lib': writing driver | Process library 'nlo_eetthjj_lib': creating source code | Process library 'nlo_eetthjj_lib': compiling sources | Process library 'nlo_eetthjj_lib': linking | Process library 'nlo_eetthjj_lib': loading | Process library 'nlo_eetthjj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eetthjj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthjj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthjj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eetthjj_p1' | Library name = 'nlo_eetthjj_lib' | Process index = 1 | Process components: | 1: 'nlo_eetthjj_p1_i1': e-, e+ => t, tbar, H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eetthjj_p1_i2': e-, e+ => t, tbar, H, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eetthjj_p1_i3': e-, e+ => t, tbar, H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eetthjj_p1_i4': e-, e+ => t, tbar, H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 38 channels, 11 dimensions | Phase space: found 38 channels, collected in 2 groves. | Phase space: Using 46 equivalences between channels. | Phase space: wood | Phase space: 38 channels, 14 dimensions | Phase space: found 38 channels, collected in 2 groves. | Phase space: Using 46 equivalences between channels. | Phase space: wood | Phase space: 38 channels, 11 dimensions | Phase space: found 38 channels, collected in 2 groves. | Phase space: Using 46 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eetthjj_p1' part 'born' | Integrate: iterations = 1:380:"gw" | Integrator: 2 chains, 38 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthjj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 380 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthjj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 380 3.7100749E-02 1.38E-02 37.19 7.25* 12.21 |-----------------------------------------------------------------------------| 1 380 3.7100749E-02 1.38E-02 37.19 7.25 12.21 |=============================================================================| | Starting integration for process 'nlo_eetthjj_p1' part 'real' | Integrate: iterations = 1:380:"gw" | Integrator: 2 chains, 38 channels, 14 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthjj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 380 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthjj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 380 -1.9179941E-02 3.91E-02 203.68 39.70* 14.90 |-----------------------------------------------------------------------------| 1 380 -1.9179941E-02 3.91E-02 203.68 39.70 14.90 |=============================================================================| | Starting integration for process 'nlo_eetthjj_p1' part 'virtual' | Integrate: iterations = 1:380:"gw" | Integrator: 2 chains, 38 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthjj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 380 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthjj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 380 1.2177497E-03 1.19E-03 97.87 19.08* 16.77 |-----------------------------------------------------------------------------| 1 380 1.2177497E-03 1.19E-03 97.87 19.08 16.77 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.9138558E-02 4.14E-02 216.57 0.00* 6.15 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-48.4146 +- 106.87174 ) % +| ( -48.41 +- 106.87 ) % |=============================================================================| | There were no errors and 2 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettjjj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettjjj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettjjj.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 3 | Process library 'nlo_eettjjj_lib': recorded process 'nlo_eettjjj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettjjj_lib': compiling ... | Process library 'nlo_eettjjj_lib': writing makefile | Process library 'nlo_eettjjj_lib': removing old files | Process library 'nlo_eettjjj_lib': writing driver | Process library 'nlo_eettjjj_lib': creating source code | Process library 'nlo_eettjjj_lib': compiling sources | Process library 'nlo_eettjjj_lib': linking | Process library 'nlo_eettjjj_lib': loading | Process library 'nlo_eettjjj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettjjj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettjjj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettjjj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettjjj_p1' | Library name = 'nlo_eettjjj_lib' | Process index = 1 | Process components: | 1: 'nlo_eettjjj_p1_i1': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eettjjj_p1_i2': e-, e+ => t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eettjjj_p1_i3': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eettjjj_p1_i4': e-, e+ => t, tbar, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 78 channels, 11 dimensions | Phase space: found 78 channels, collected in 5 groves. | Phase space: Using 94 equivalences between channels. | Phase space: wood | Phase space: 78 channels, 14 dimensions | Phase space: found 78 channels, collected in 5 groves. | Phase space: Using 94 equivalences between channels. | Phase space: wood | Phase space: 78 channels, 11 dimensions | Phase space: found 78 channels, collected in 5 groves. | Phase space: Using 94 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eettjjj_p1' part 'born' | Integrate: iterations = 1:780:"gw" | Integrator: 5 chains, 78 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettjjj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 780 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettjjj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 812 2.4856807E+00 1.74E+00 69.90 19.92* 10.65 |-----------------------------------------------------------------------------| 1 812 2.4856807E+00 1.74E+00 69.90 19.92 10.65 |=============================================================================| | Starting integration for process 'nlo_eettjjj_p1' part 'real' | Integrate: iterations = 1:780:"gw" | Integrator: 5 chains, 78 channels, 14 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettjjj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 780 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettjjj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 836 1.7244363E-01 1.91E-01 110.52 31.95* 15.43 |-----------------------------------------------------------------------------| 1 836 1.7244363E-01 1.91E-01 110.52 31.95 15.43 |=============================================================================| | Starting integration for process 'nlo_eettjjj_p1' part 'virtual' | Integrate: iterations = 1:780:"gw" | Integrator: 5 chains, 78 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettjjj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 780 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettjjj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 812 3.7292135E-02 3.13E-02 84.06 23.95* 16.46 |-----------------------------------------------------------------------------| 1 812 3.7292135E-02 3.13E-02 84.06 23.95 16.46 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.6954165E+00 1.75E+00 64.86 0.00* 10.92 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 8.4378 +- 9.75505 ) % +| ( 8.44 +- 9.76 ) % |=============================================================================| | There were no errors and 2 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptttt.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptttt.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptttt.ref (revision 8760) @@ -1,210 +1,210 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $negative_sf = "positive" $lhapdf_file = "MSTW2008nlo68cl" sqrts = 1.300000000000E+04 alpha_power = 0 alphas_power = 4 ?alphas_from_mz = false ?alphas_from_lhapdf = true ?combined_nlo_integration = false | Process library 'nlo_pptttt_lib': recorded process 'nlo_pptttt_p1' | Integrate: current process library needs compilation | Process library 'nlo_pptttt_lib': compiling ... | Process library 'nlo_pptttt_lib': writing makefile | Process library 'nlo_pptttt_lib': removing old files | Process library 'nlo_pptttt_lib': writing driver | Process library 'nlo_pptttt_lib': creating source code | Process library 'nlo_pptttt_lib': compiling sources | Process library 'nlo_pptttt_lib': linking | Process library 'nlo_pptttt_lib': loading | Process library 'nlo_pptttt_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_pptttt_p1: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_pptttt_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... failed. Increasing phs_off_shell ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_pptttt_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_pptttt_p1' | Library name = 'nlo_pptttt_lib' | Process index = 1 | Process components: | 1: 'nlo_pptttt_p1_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => t, tbar, t, tbar [openloops] | 2: 'nlo_pptttt_p1_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => t, tbar, t, tbar, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_pptttt_p1_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => t, tbar, t, tbar [openloops], [virtual] | 4: 'nlo_pptttt_p1_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => t, tbar, t, tbar [inactive], [subtraction] | 5: 'nlo_pptttt_p1_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => t, tbar, t, tbar [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 128 channels, 8 dimensions | Phase space: found 128 channels, collected in 4 groves. | Phase space: Using 672 equivalences between channels. | Phase space: wood | Phase space: 128 channels, 11 dimensions | Phase space: found 128 channels, collected in 4 groves. | Phase space: Using 672 equivalences between channels. | Phase space: wood | Phase space: 128 channels, 8 dimensions | Phase space: found 128 channels, collected in 4 groves. | Phase space: Using 672 equivalences between channels. | Phase space: wood | Phase space: 128 channels, 9 dimensions | Phase space: found 128 channels, collected in 4 groves. | Phase space: Using 672 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_pptttt_p1' part 'born' | Integrate: iterations = 1:2000:"gw" | Integrator: 4 chains, 128 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_pptttt_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 2000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_pptttt_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 1984 7.3169590E+00 3.56E+00 48.70 21.69* 6.96 |-----------------------------------------------------------------------------| 1 1984 7.3169590E+00 3.56E+00 48.70 21.69 6.96 |=============================================================================| | Starting integration for process 'nlo_pptttt_p1' part 'real' | Integrate: iterations = 1:2000:"gw" | Integrator: 4 chains, 128 channels, 13 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_pptttt_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 2000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_pptttt_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 1992 1.2530138E-01 4.52E-01 360.86 161.06* 12.03 |-----------------------------------------------------------------------------| 1 1992 1.2530138E-01 4.52E-01 360.86 161.06 12.03 |=============================================================================| | Starting integration for process 'nlo_pptttt_p1' part 'virtual' | Integrate: iterations = 1:2000:"gw" | Integrator: 4 chains, 128 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_pptttt_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 2000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_pptttt_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 2000 5.4971119E+00 1.46E+00 26.47 11.84* 6.76 |-----------------------------------------------------------------------------| 1 2000 5.4971119E+00 1.46E+00 26.47 11.84 6.76 |=============================================================================| | Starting integration for process 'nlo_pptttt_p1' part 'dglap' | Integrate: iterations = 1:2000:"gw" | Integrator: 4 chains, 128 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_pptttt_p1.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 2000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_pptttt_p1.m4.vg2'. | VAMP2: set chain: use chained weights. 1 1976 1.9642699E+00 1.07E+00 54.45 24.21* 7.80 |-----------------------------------------------------------------------------| 1 1976 1.9642699E+00 1.07E+00 54.45 24.21 7.80 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.4903642E+01 4.02E+00 26.98 0.00* 7.01 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (103.6863 +- 56.54290 ) % +| ( 103.69 +- 56.54 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthz.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthz.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eetthz.ref (revision 8760) @@ -1,172 +1,172 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 4 alphas_power = 0 | Process library 'nlo_eetthz_lib': recorded process 'nlo_eetthz_p1' | Integrate: current process library needs compilation | Process library 'nlo_eetthz_lib': compiling ... | Process library 'nlo_eetthz_lib': writing makefile | Process library 'nlo_eetthz_lib': removing old files | Process library 'nlo_eetthz_lib': writing driver | Process library 'nlo_eetthz_lib': creating source code | Process library 'nlo_eetthz_lib': compiling sources | Process library 'nlo_eetthz_lib': linking | Process library 'nlo_eetthz_lib': loading | Process library 'nlo_eetthz_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eetthz_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthz_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eetthz_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eetthz_p1' | Library name = 'nlo_eetthz_lib' | Process index = 1 | Process components: | 1: 'nlo_eetthz_p1_i1': e-, e+ => t, tbar, H, Z [openloops] | 2: 'nlo_eetthz_p1_i2': e-, e+ => t, tbar, H, Z, gl [openloops], [real] | 3: 'nlo_eetthz_p1_i3': e-, e+ => t, tbar, H, Z [openloops], [virtual] | 4: 'nlo_eetthz_p1_i4': e-, e+ => t, tbar, H, Z [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 6 channels, 8 dimensions | Phase space: found 6 channels, collected in 1 grove. | Phase space: Using 12 equivalences between channels. | Phase space: wood | Phase space: 6 channels, 11 dimensions | Phase space: found 6 channels, collected in 1 grove. | Phase space: Using 12 equivalences between channels. | Phase space: wood | Phase space: 6 channels, 8 dimensions | Phase space: found 6 channels, collected in 1 grove. | Phase space: Using 12 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_eetthz_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 6 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthz_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthz_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 102 2.7683185E-02 8.29E-03 29.94 3.02* 10.86 |-----------------------------------------------------------------------------| 1 102 2.7683185E-02 8.29E-03 29.94 3.02 10.86 |=============================================================================| | Starting integration for process 'nlo_eetthz_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 6 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthz_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthz_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 102 -7.9626362E-03 2.24E-03 28.07 2.84* 11.01 |-----------------------------------------------------------------------------| 1 102 -7.9626362E-03 2.24E-03 28.07 2.84 11.01 |=============================================================================| | Starting integration for process 'nlo_eetthz_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 6 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eetthz_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eetthz_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 102 1.2424068E-02 2.92E-03 23.48 2.37* 12.29 |-----------------------------------------------------------------------------| 1 102 1.2424068E-02 2.92E-03 23.48 2.37 12.29 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 3.2144617E-02 9.07E-03 28.21 0.00* 9.03 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 16.1160 +- 14.12548 ) % +| ( 16.12 +- 14.13 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppwzh_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppwzh_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppwzh_ew.ref (revision 8760) @@ -1,211 +1,211 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' alpha_power = 3 alphas_power = 0 seed = 1 $nlo_correction_type = "EW" | Process library 'nlo_ppwzh_ew_lib': recorded process 'ppwzh_ew' | Integrate: current process library needs compilation | Process library 'nlo_ppwzh_ew_lib': compiling ... | Process library 'nlo_ppwzh_ew_lib': writing makefile | Process library 'nlo_ppwzh_ew_lib': removing old files | Process library 'nlo_ppwzh_ew_lib': writing driver | Process library 'nlo_ppwzh_ew_lib': creating source code | Process library 'nlo_ppwzh_ew_lib': compiling sources | Process library 'nlo_ppwzh_ew_lib': linking | Process library 'nlo_ppwzh_ew_lib': loading | Process library 'nlo_ppwzh_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process ppwzh_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppwzh_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppwzh_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppwzh_ew' | Library name = 'nlo_ppwzh_ew_lib' | Process index = 1 | Process components: | 1: 'ppwzh_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z, W- [openloops] | 2: 'ppwzh_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => H, Z, W-, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'ppwzh_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z, W- [openloops], [virtual] | 4: 'ppwzh_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z, W- [inactive], [subtraction] | 5: 'ppwzh_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z, W- [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 27 channels, 5 dimensions | Phase space: found 27 channels, collected in 8 groves. | Phase space: Using 35 equivalences between channels. | Phase space: wood | Phase space: 27 channels, 8 dimensions | Phase space: found 27 channels, collected in 8 groves. | Phase space: Using 35 equivalences between channels. | Phase space: wood | Phase space: 27 channels, 5 dimensions | Phase space: found 27 channels, collected in 8 groves. | Phase space: Using 35 equivalences between channels. | Phase space: wood | Phase space: 27 channels, 6 dimensions | Phase space: found 27 channels, collected in 8 groves. | Phase space: Using 35 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'ppwzh_ew' part 'born' | Integrate: iterations = 1:300:"gw" | Integrator: 8 chains, 27 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwzh_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwzh_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 298 2.8920044E+00 1.57E+00 54.42 9.40* 9.49 |-----------------------------------------------------------------------------| 1 298 2.8920044E+00 1.57E+00 54.42 9.40 9.49 |=============================================================================| | Starting integration for process 'ppwzh_ew' part 'real' | Integrate: iterations = 1:300:"gw" | Integrator: 8 chains, 27 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwzh_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwzh_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 326 2.3756250E-02 1.54E-02 64.77 11.70* 9.73 |-----------------------------------------------------------------------------| 1 326 2.3756250E-02 1.54E-02 64.77 11.70 9.73 |=============================================================================| | Starting integration for process 'ppwzh_ew' part 'virtual' | Integrate: iterations = 1:300:"gw" | Integrator: 8 chains, 27 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwzh_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwzh_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 298 -8.4482656E-02 3.79E-02 44.87 7.75* 10.17 |-----------------------------------------------------------------------------| 1 298 -8.4482656E-02 3.79E-02 44.87 7.75 10.17 |=============================================================================| | Starting integration for process 'ppwzh_ew' part 'dglap' | Integrate: iterations = 1:300:"gw" | Integrator: 8 chains, 27 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppwzh_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 300 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppwzh_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 298 3.0648229E-03 2.48E-03 81.04 13.99* 10.46 |-----------------------------------------------------------------------------| 1 298 3.0648229E-03 2.48E-03 81.04 13.99 10.46 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.8343428E+00 1.57E+00 55.55 0.00* 9.21 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -1.9938 +- 1.78502 ) % +| ( -1.99 +- 1.79 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppz_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppz_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppz_ew.ref (revision 8760) @@ -1,212 +1,212 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' ?pacify = true alpha_power = 1 alphas_power = 0 seed = 1 $nlo_correction_type = "EW" | Process library 'nlo_ppz_ew_lib': recorded process 'ppz_ew' | Integrate: current process library needs compilation | Process library 'nlo_ppz_ew_lib': compiling ... | Process library 'nlo_ppz_ew_lib': writing makefile | Process library 'nlo_ppz_ew_lib': removing old files | Process library 'nlo_ppz_ew_lib': writing driver | Process library 'nlo_ppz_ew_lib': creating source code | Process library 'nlo_ppz_ew_lib': compiling sources | Process library 'nlo_ppz_ew_lib': linking | Process library 'nlo_ppz_ew_lib': loading | Process library 'nlo_ppz_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process ppz_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppz_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppz_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppz_ew' | Library name = 'nlo_ppz_ew_lib' | Process index = 1 | Process components: | 1: 'ppz_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z [openloops] | 2: 'ppz_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => Z, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'ppz_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z [openloops], [virtual] | 4: 'ppz_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z [inactive], [subtraction] | 5: 'ppz_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => Z [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 1 channels, 0 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 3 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 0 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 1 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'ppz_ew' part 'born' | Integrate: iterations = 1:1000:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 800 4.357E+07 8.60E+04 0.20 0.06 68.9 |-----------------------------------------------------------------------------| 1 800 4.357E+07 8.60E+04 0.20 0.06 68.9 |=============================================================================| | Starting integration for process 'ppz_ew' part 'real' | Integrate: iterations = 1:1000:"gw" | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 972 3.628E+03 2.03E+02 5.59 1.74 26.4 |-----------------------------------------------------------------------------| 1 972 3.628E+03 2.03E+02 5.59 1.74 26.4 |=============================================================================| | Starting integration for process 'ppz_ew' part 'virtual' | Integrate: iterations = 1:1000:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 800 -2.735E+05 4.84E+02 0.18 0.05 70.0 |-----------------------------------------------------------------------------| 1 800 -2.735E+05 4.84E+02 0.18 0.05 70.0 |=============================================================================| | Starting integration for process 'ppz_ew' part 'dglap' | Integrate: iterations = 1:1000:"gw" | Integrator: 1 chains, 1 channels, 3 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 1000 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 686 9.804E+04 2.34E+03 2.38 0.62 11.4 |-----------------------------------------------------------------------------| 1 686 9.804E+04 2.34E+03 2.38 0.62 11.4 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 4.340E+07 8.60E+04 0.20 0.00 67.6 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -0.3943 +- 0.00555 ) % +| ( -0.39 +- 0.01 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzj.ref (revision 8760) @@ -1,171 +1,171 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 3 alphas_power = 1 | Process library 'nlo_eettzj_lib': recorded process 'nlo_eettzj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettzj_lib': compiling ... | Process library 'nlo_eettzj_lib': writing makefile | Process library 'nlo_eettzj_lib': removing old files | Process library 'nlo_eettzj_lib': writing driver | Process library 'nlo_eettzj_lib': creating source code | Process library 'nlo_eettzj_lib': compiling sources | Process library 'nlo_eettzj_lib': linking | Process library 'nlo_eettzj_lib': loading | Process library 'nlo_eettzj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettzj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettzj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettzj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettzj_p1' | Library name = 'nlo_eettzj_lib' | Process index = 1 | Process components: | 1: 'nlo_eettzj_p1_i1': e-, e+ => t, tbar, Z, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eettzj_p1_i2': e-, e+ => t, tbar, Z, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eettzj_p1_i3': e-, e+ => t, tbar, Z, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eettzj_p1_i4': e-, e+ => t, tbar, Z, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 14 channels, 8 dimensions | Phase space: found 14 channels, collected in 3 groves. | Phase space: Using 22 equivalences between channels. | Phase space: wood | Phase space: 14 channels, 11 dimensions | Phase space: found 14 channels, collected in 3 groves. | Phase space: Using 22 equivalences between channels. | Phase space: wood | Phase space: 14 channels, 8 dimensions | Phase space: found 14 channels, collected in 3 groves. | Phase space: Using 22 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eettzj_p1' part 'born' | Integrate: iterations = 1:140:"gw" | Integrator: 3 chains, 14 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 140 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 140 3.2668638E-01 6.72E-02 20.56 2.43* 16.87 |-----------------------------------------------------------------------------| 1 140 3.2668638E-01 6.72E-02 20.56 2.43 16.87 |=============================================================================| | Starting integration for process 'nlo_eettzj_p1' part 'real' | Integrate: iterations = 1:140:"gw" | Integrator: 3 chains, 14 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 140 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 140 5.0632195E-02 8.19E-02 161.77 19.14* 20.75 |-----------------------------------------------------------------------------| 1 140 5.0632195E-02 8.19E-02 161.77 19.14 20.75 |=============================================================================| | Starting integration for process 'nlo_eettzj_p1' part 'virtual' | Integrate: iterations = 1:140:"gw" | Integrator: 3 chains, 14 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 140 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 148 8.2763934E-02 1.97E-02 23.80 2.90* 18.23 |-----------------------------------------------------------------------------| 1 148 8.2763934E-02 1.97E-02 23.80 2.90 18.23 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 4.6008251E-01 1.08E-01 23.42 0.00* 17.47 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 40.8331 +- 27.11890 ) % +| ( 40.83 +- 27.12 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppw.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppw.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppw.ref (revision 8760) @@ -1,225 +1,225 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) [user variable] Wpm = PDG(24, -24) $exclude_gauge_splittings = "t" $negative_sf = "positive" $lhapdf_file = "MSTW2008nlo68cl" sqrts = 1.300000000000E+04 alpha_power = 1 alphas_power = 0 ?alphas_from_mz = false ?alphas_from_lhapdf = true ?combined_nlo_integration = false relative_error_goal = 4.000000000000E-03 | Process library 'nlo_ppw_lib': recorded process 'ppw' | Integrate: current process library needs compilation | Process library 'nlo_ppw_lib': compiling ... | Process library 'nlo_ppw_lib': writing makefile | Process library 'nlo_ppw_lib': removing old files | Process library 'nlo_ppw_lib': writing driver | Process library 'nlo_ppw_lib': creating source code | Process library 'nlo_ppw_lib': compiling sources | Process library 'nlo_ppw_lib': linking | Process library 'nlo_ppw_lib': loading | Process library 'nlo_ppw_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process ppw: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppw.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppw.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppw' | Library name = 'nlo_ppw_lib' | Process index = 1 | Process components: | 1: 'ppw_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => W+:W- [openloops] | 2: 'ppw_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => W+:W-, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'ppw_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => W+:W- [openloops], [virtual] | 4: 'ppw_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => W+:W- [inactive], [subtraction] | 5: 'ppw_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => W+:W- [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 2 channels, 0 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 4 equivalences between channels. | Phase space: wood | Phase space: 2 channels, 3 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 4 equivalences between channels. | Phase space: wood | Phase space: 2 channels, 0 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 4 equivalences between channels. | Phase space: wood | Phase space: 2 channels, 1 dimensions | Phase space: found 2 channels, collected in 1 grove. | Phase space: Using 4 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'ppw' part 'born' | Integrate: iterations = 5:100:"gw" | Integrator: 1 chains, 2 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppw.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppw.m1.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.4010570E+08 3.16E+06 2.26 0.23* 73.87 2 100 1.3863990E+08 3.83E+06 2.76 0.28 65.10 3 100 1.3632383E+08 3.63E+06 2.67 0.27* 70.50 4 100 1.4252454E+08 2.24E+06 1.57 0.16* 73.08 5 100 1.4081748E+08 2.99E+06 2.12 0.21 68.62 |-----------------------------------------------------------------------------| 5 500 1.4041796E+08 1.34E+06 0.96 0.21 68.62 0.60 5 |=============================================================================| | Starting integration for process 'ppw' part 'real' | Integrate: iterations = 5:100:"gw" | Integrator: 1 chains, 2 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppw.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppw.m2.vg2'. | VAMP2: set chain: use chained weights. 1 100 9.8853129E+06 1.38E+06 13.94 1.39* 29.20 2 100 8.2275778E+06 1.61E+06 19.52 1.95 26.00 3 100 9.7328215E+06 1.75E+06 17.96 1.80* 32.55 4 100 1.2215379E+07 1.17E+06 9.60 0.96* 35.14 5 100 1.1251738E+07 1.05E+06 9.37 0.94* 32.78 |-----------------------------------------------------------------------------| 5 500 1.0662861E+07 5.91E+05 5.54 1.24 32.78 1.24 5 |=============================================================================| | Starting integration for process 'ppw' part 'virtual' | Integrate: iterations = 5:100:"gw" | Integrator: 1 chains, 2 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppw.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppw.m3.vg2'. | VAMP2: set chain: use chained weights. 1 100 1.0997093E+07 2.83E+05 2.58 0.26* 72.55 2 100 1.1192063E+07 2.52E+05 2.25 0.22* 64.96 3 100 1.0848472E+07 2.43E+05 2.24 0.22* 74.22 4 100 1.1283361E+07 4.51E+05 4.00 0.40 39.48 5 100 1.0974889E+07 3.40E+05 3.10 0.31* 66.97 |-----------------------------------------------------------------------------| 5 500 1.1027461E+07 1.31E+05 1.18 0.26 66.97 0.33 5 |=============================================================================| | Starting integration for process 'ppw' part 'dglap' | Integrate: iterations = 5:100:"gw" | Integrator: 1 chains, 2 channels, 3 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppw.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppw.m4.vg2'. | VAMP2: set chain: use chained weights. 1 96 1.6843581E+07 5.54E+06 32.92 3.23* 14.38 2 96 2.3578182E+07 3.57E+06 15.13 1.48* 46.89 3 96 2.2694833E+07 2.92E+06 12.86 1.26* 52.16 4 96 1.6804304E+07 2.90E+06 17.23 1.69 47.56 5 96 1.3640601E+07 3.28E+06 24.07 2.36 46.62 |-----------------------------------------------------------------------------| 5 480 1.8919194E+07 1.51E+06 7.96 1.74 46.62 1.66 5 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.8102747E+08 2.11E+06 1.16 0.00* 61.53 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 28.9205 +- 1.18881 ) % +| ( 28.92 +- 1.19 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphjj_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphjj_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphjj_ew.ref (revision 8760) @@ -1,219 +1,219 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' [user variable] j = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) SM.wtop => 1.369180000000E+00 SM.mZ => 9.115347000000E+01 SM.mW => 8.035785000000E+01 SM.wZ => 2.494566000000E+00 SM.wW => 2.088994000000E+00 alpha_power = 3 alphas_power = 0 $nlo_correction_type = "EW" seed = 1 $restrictions = "^[c:b,cbar:bbar,H]" | Process library 'nlo_pphjj_ew_lib': recorded process 'pphjj_ew' | Integrate: current process library needs compilation | Process library 'nlo_pphjj_ew_lib': compiling ... | Process library 'nlo_pphjj_ew_lib': writing makefile | Process library 'nlo_pphjj_ew_lib': removing old files | Process library 'nlo_pphjj_ew_lib': writing driver | Process library 'nlo_pphjj_ew_lib': creating source code | Process library 'nlo_pphjj_ew_lib': compiling sources | Process library 'nlo_pphjj_ew_lib': linking | Process library 'nlo_pphjj_ew_lib': loading | Process library 'nlo_pphjj_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process pphjj_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'pphjj_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'pphjj_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'pphjj_ew' | Library name = 'nlo_pphjj_ew_lib' | Process index = 1 | Process components: | 1: 'pphjj_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [openloops] | 2: 'pphjj_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => H, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A:d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A:d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A:d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A, e-:mu-:tau-:d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A, e+:mu+:tau+:d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'pphjj_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [openloops], [virtual] | 4: 'pphjj_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [inactive], [subtraction] | 5: 'pphjj_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 58 channels, 5 dimensions | Phase space: found 58 channels, collected in 18 groves. | Phase space: Using 180 equivalences between channels. | Phase space: wood | Phase space: 58 channels, 8 dimensions | Phase space: found 58 channels, collected in 18 groves. | Phase space: Using 180 equivalences between channels. | Phase space: wood | Phase space: 58 channels, 5 dimensions | Phase space: found 58 channels, collected in 18 groves. | Phase space: Using 180 equivalences between channels. | Phase space: wood | Phase space: 58 channels, 6 dimensions | Phase space: found 58 channels, collected in 18 groves. | Phase space: Using 180 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'pphjj_ew' part 'born' | Integrate: iterations = 1:600:"gw" | Integrator: 18 chains, 58 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphjj_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 600 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphjj_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 623 1.3011454E+02 5.18E+01 39.78 9.93* 10.90 |-----------------------------------------------------------------------------| 1 623 1.3011454E+02 5.18E+01 39.78 9.93 10.90 |=============================================================================| | Starting integration for process 'pphjj_ew' part 'real' | Integrate: iterations = 1:600:"gw" | Integrator: 18 chains, 58 channels, 10 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphjj_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 600 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphjj_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 647 -2.7833842E+00 9.64E+00 346.33 88.09* 17.89 |-----------------------------------------------------------------------------| 1 647 -2.7833842E+00 9.64E+00 346.33 88.09 17.89 |=============================================================================| | Starting integration for process 'pphjj_ew' part 'virtual' | Integrate: iterations = 1:600:"gw" | Integrator: 18 chains, 58 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphjj_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 600 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphjj_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 606 -1.1323805E+02 6.76E+01 59.67 14.69* 11.07 |-----------------------------------------------------------------------------| 1 606 -1.1323805E+02 6.76E+01 59.67 14.69 11.07 |=============================================================================| | Starting integration for process 'pphjj_ew' part 'dglap' | Integrate: iterations = 1:600:"gw" | Integrator: 18 chains, 58 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphjj_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 600 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphjj_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 624 -1.0811901E+00 1.19E+00 110.10 27.50* 14.40 |-----------------------------------------------------------------------------| 1 624 -1.0811901E+00 1.19E+00 110.10 27.50 14.40 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 1.3011919E+01 8.57E+01 658.40 0.00* 1.09 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-89.9996 +- 63.51795 ) % +| ( -90.00 +- 63.52 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptj_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptj_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_pptj_ew.ref (revision 8760) @@ -1,215 +1,215 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' [user variable] j = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) SM.mZ => 9.115347000000E+01 SM.mW => 8.035785000000E+01 SM.wZ => 2.494566000000E+00 SM.wW => 2.088994000000E+00 alpha_power = 2 alphas_power = 0 $nlo_correction_type = "EW" seed = 1 | Process library 'nlo_pptj_ew_lib': recorded process 'pptj_ew' | Integrate: current process library needs compilation | Process library 'nlo_pptj_ew_lib': compiling ... | Process library 'nlo_pptj_ew_lib': writing makefile | Process library 'nlo_pptj_ew_lib': removing old files | Process library 'nlo_pptj_ew_lib': writing driver | Process library 'nlo_pptj_ew_lib': creating source code | Process library 'nlo_pptj_ew_lib': compiling sources | Process library 'nlo_pptj_ew_lib': linking | Process library 'nlo_pptj_ew_lib': loading | Process library 'nlo_pptj_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process pptj_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'pptj_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'pptj_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'pptj_ew' | Library name = 'nlo_pptj_ew_lib' | Process index = 1 | Process components: | 1: 'pptj_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [openloops] | 2: 'pptj_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A:dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => t, e-:mu-:tau-:d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A, e+:mu+:tau+:d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'pptj_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [openloops], [virtual] | 4: 'pptj_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [inactive], [subtraction] | 5: 'pptj_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => t, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 5 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 3 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'pptj_ew' part 'born' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pptj_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pptj_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 480 4.8309710E+04 1.61E+04 33.24 7.28* 1.68 |-----------------------------------------------------------------------------| 1 480 4.8309710E+04 1.61E+04 33.24 7.28 1.68 |=============================================================================| | Starting integration for process 'pptj_ew' part 'real' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pptj_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pptj_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 499 7.9265439E+02 1.01E+03 127.21 28.42* 1.62 |-----------------------------------------------------------------------------| 1 499 7.9265439E+02 1.01E+03 127.21 28.42 1.62 |=============================================================================| | Starting integration for process 'pptj_ew' part 'virtual' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pptj_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pptj_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 464 -1.7044741E+03 5.18E+02 30.37 6.54* 2.91 |-----------------------------------------------------------------------------| 1 464 -1.7044741E+03 5.18E+02 30.37 6.54 2.91 |=============================================================================| | Starting integration for process 'pptj_ew' part 'dglap' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pptj_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pptj_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 405 1.7131231E+02 9.63E+01 56.24 11.32* 1.65 |-----------------------------------------------------------------------------| 1 405 1.7131231E+02 9.63E+01 56.24 11.32 1.65 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 4.7569202E+04 1.61E+04 33.84 0.00* 1.62 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -1.5328 +- 2.40925 ) % +| ( -1.53 +- 2.41 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppz.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppz.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppz.ref (revision 8760) @@ -1,208 +1,208 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $negative_sf = "positive" $lhapdf_file = "MSTW2008nlo68cl" sqrts = 1.300000000000E+04 alpha_power = 1 alphas_power = 0 ?alphas_from_mz = false ?alphas_from_lhapdf = true ?combined_nlo_integration = false relative_error_goal = 4.000000000000E-03 | Process library 'nlo_ppz_lib': recorded process 'ppz' | Integrate: current process library needs compilation | Process library 'nlo_ppz_lib': compiling ... | Process library 'nlo_ppz_lib': writing makefile | Process library 'nlo_ppz_lib': removing old files | Process library 'nlo_ppz_lib': writing driver | Process library 'nlo_ppz_lib': creating source code | Process library 'nlo_ppz_lib': compiling sources | Process library 'nlo_ppz_lib': linking | Process library 'nlo_ppz_lib': loading | Process library 'nlo_ppz_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process ppz: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppz.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppz.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppz' | Library name = 'nlo_ppz_lib' | Process index = 1 | Process components: | 1: 'ppz_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z [openloops] | 2: 'ppz_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:gl => Z, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'ppz_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z [openloops], [virtual] | 4: 'ppz_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z [inactive], [subtraction] | 5: 'ppz_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl => Z [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 1 channels, 0 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 3 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 0 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 1 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'ppz' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz.m1.vg2'. | VAMP2: set chain: use chained weights. 1 98 4.2228581E+07 6.40E+05 1.52 0.15* 69.02 |-----------------------------------------------------------------------------| 1 98 4.2228581E+07 6.40E+05 1.52 0.15 69.02 |=============================================================================| | Starting integration for process 'ppz' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz.m2.vg2'. | VAMP2: set chain: use chained weights. 1 96 3.2494859E+06 5.20E+05 16.01 1.57* 29.99 |-----------------------------------------------------------------------------| 1 96 3.2494859E+06 5.20E+05 16.01 1.57 29.99 |=============================================================================| | Starting integration for process 'ppz' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz.m3.vg2'. | VAMP2: set chain: use chained weights. 1 98 3.3188407E+06 5.09E+04 1.53 0.15* 69.37 |-----------------------------------------------------------------------------| 1 98 3.3188407E+06 5.09E+04 1.53 0.15 69.37 |=============================================================================| | Starting integration for process 'ppz' part 'dglap' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 3 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppz.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppz.m4.vg2'. | VAMP2: set chain: use chained weights. 1 81 7.2848842E+06 1.05E+06 14.43 1.30* 22.84 |-----------------------------------------------------------------------------| 1 81 7.2848842E+06 1.05E+06 14.43 1.30 22.84 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 5.6081792E+07 1.34E+06 2.38 0.00* 51.60 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 32.8053 +- 2.82358 ) % +| ( 32.81 +- 2.82 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettwjj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettwjj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettwjj.ref (revision 8760) @@ -1,178 +1,178 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 3 alphas_power = 2 [user variable] W = PDG(24, -24) mult_call_real = 2.000000000000E+00 | Process library 'nlo_eettwjj_lib': recorded process 'nlo_eettwjj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettwjj_lib': compiling ... | Process library 'nlo_eettwjj_lib': writing makefile | Process library 'nlo_eettwjj_lib': removing old files | Process library 'nlo_eettwjj_lib': writing driver | Process library 'nlo_eettwjj_lib': creating source code | Process library 'nlo_eettwjj_lib': compiling sources | Process library 'nlo_eettwjj_lib': linking | Process library 'nlo_eettwjj_lib': loading | Process library 'nlo_eettwjj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettwjj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle W+ may be possible. Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. Warning: Intermediate decay of zero-width particle W- may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettwjj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettwjj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettwjj_p1' | Library name = 'nlo_eettwjj_lib' | Process index = 1 | Process components: | 1: 'nlo_eettwjj_p1_i1': e-, e+ => t, tbar, W+:W-, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eettwjj_p1_i2': e-, e+ => t, tbar, W+:W-, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eettwjj_p1_i3': e-, e+ => t, tbar, W+:W-, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eettwjj_p1_i4': e-, e+ => t, tbar, W+:W-, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 4 channels, 11 dimensions | Phase space: found 4 channels, collected in 1 grove. | Phase space: Using 4 equivalences between channels. | Phase space: wood | Phase space: 4 channels, 14 dimensions | Phase space: found 4 channels, collected in 1 grove. | Phase space: Using 4 equivalences between channels. | Phase space: wood | Phase space: 4 channels, 11 dimensions | Phase space: found 4 channels, collected in 1 grove. | Phase space: Using 4 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eettwjj_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 4 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettwjj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettwjj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 100 7.2691124E-05 7.38E-05 101.49 10.15* 4.00 |-----------------------------------------------------------------------------| 1 100 7.2691124E-05 7.38E-05 101.49 10.15 4.00 |=============================================================================| | Starting integration for process 'nlo_eettwjj_p1' part 'real' | Integrate: iterations = 1:200:"gw" | Integrator: 1 chains, 4 channels, 14 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettwjj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 200 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettwjj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 200 -6.7419305E-05 2.46E-04 364.49 51.55* 3.42 |-----------------------------------------------------------------------------| 1 200 -6.7419305E-05 2.46E-04 364.49 51.55 3.42 |=============================================================================| | Starting integration for process 'nlo_eettwjj_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 4 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettwjj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettwjj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 100 4.5824693E-03 4.65E-03 101.41 10.14* 4.00 |-----------------------------------------------------------------------------| 1 100 4.5824693E-03 4.65E-03 101.41 10.14 4.00 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 4.5877411E-03 4.65E-03 101.45 0.00* 3.94 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (******** +- ********* ) % +| (6211.28 +- ****** ) % |=============================================================================| | There were no errors and 4 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphz_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphz_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_pphz_ew.ref (revision 8760) @@ -1,211 +1,211 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' seed = 1 alpha_power = 2 alphas_power = 0 $nlo_correction_type = "EW" | Process library 'nlo_pphz_ew_lib': recorded process 'pphz_ew' | Integrate: current process library needs compilation | Process library 'nlo_pphz_ew_lib': compiling ... | Process library 'nlo_pphz_ew_lib': writing makefile | Process library 'nlo_pphz_ew_lib': removing old files | Process library 'nlo_pphz_ew_lib': writing driver | Process library 'nlo_pphz_ew_lib': creating source code | Process library 'nlo_pphz_ew_lib': compiling sources | Process library 'nlo_pphz_ew_lib': linking | Process library 'nlo_pphz_ew_lib': loading | Process library 'nlo_pphz_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process pphz_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'pphz_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'pphz_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'pphz_ew' | Library name = 'nlo_pphz_ew_lib' | Process index = 1 | Process components: | 1: 'pphz_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z [openloops] | 2: 'pphz_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => H, Z, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'pphz_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z [openloops], [virtual] | 4: 'pphz_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z [inactive], [subtraction] | 5: 'pphz_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => H, Z [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 5 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 2 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Phase space: 5 channels, 3 dimensions | Phase space: found 5 channels, collected in 3 groves. | Phase space: Using 9 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 1 channels, 2 dimensions Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'pphz_ew' part 'born' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphz_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphz_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 464 3.2608263E+02 1.34E+02 41.01 8.83* 1.37 |-----------------------------------------------------------------------------| 1 464 3.2608263E+02 1.34E+02 41.01 8.83 1.37 |=============================================================================| | Starting integration for process 'pphz_ew' part 'real' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphz_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphz_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 500 -1.1101044E-01 6.50E-02 58.58 13.10* 1.39 |-----------------------------------------------------------------------------| 1 500 -1.1101044E-01 6.50E-02 58.58 13.10 1.39 |=============================================================================| | Starting integration for process 'pphz_ew' part 'virtual' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphz_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphz_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 418 -3.0231328E+01 1.68E+01 55.47 11.34* 1.32 |-----------------------------------------------------------------------------| 1 418 -3.0231328E+01 1.68E+01 55.47 11.34 1.32 |=============================================================================| | Starting integration for process 'pphz_ew' part 'dglap' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 5 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'pphz_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'pphz_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 431 5.6133671E-01 3.78E-01 67.41 14.00* 1.51 |-----------------------------------------------------------------------------| 1 431 5.6133671E-01 3.78E-01 67.41 14.00 1.51 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 2.9630163E+02 1.35E+02 45.49 0.00* 1.24 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( -9.1330 +- 6.36356 ) % +| ( -9.13 +- 6.36 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eejj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eejj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eejj.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 2 alphas_power = 0 | Process library 'nlo_eejj_lib': recorded process 'nlo_eejj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eejj_lib': compiling ... | Process library 'nlo_eejj_lib': writing makefile | Process library 'nlo_eejj_lib': removing old files | Process library 'nlo_eejj_lib': writing driver | Process library 'nlo_eejj_lib': creating source code | Process library 'nlo_eejj_lib': compiling sources | Process library 'nlo_eejj_lib': linking | Process library 'nlo_eejj_lib': loading | Process library 'nlo_eejj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eejj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_eejj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eejj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eejj_p1' | Library name = 'nlo_eejj_lib' | Process index = 1 | Process components: | 1: 'nlo_eejj_p1_i1': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eejj_p1_i2': e-, e+ => d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eejj_p1_i3': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eejj_p1_i4': e-, e+ => u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 5 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Phase space: 1 channels, 2 dimensions | Phase space: found 1 channel, collected in 1 grove. | Phase space: Using 1 equivalence between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eejj_p1' part 'born' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eejj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eejj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 98 6.2062491E+02 5.03E+00 0.81 0.08* 37.53 |-----------------------------------------------------------------------------| 1 98 6.2062491E+02 5.03E+00 0.81 0.08 37.53 |=============================================================================| | Starting integration for process 'nlo_eejj_p1' part 'real' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eejj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eejj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 96 3.2589839E+01 6.75E+00 20.71 2.03* 8.16 |-----------------------------------------------------------------------------| 1 96 3.2589839E+01 6.75E+00 20.71 2.03 8.16 |=============================================================================| | Starting integration for process 'nlo_eejj_p1' part 'virtual' | Integrate: iterations = 1:100:"gw" | Integrator: 1 chains, 1 channels, 2 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eejj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 100 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eejj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 98 -2.0692689E+01 3.90E-01 1.88 0.19* 28.35 |-----------------------------------------------------------------------------| 1 98 -2.0692689E+01 3.90E-01 1.88 0.19 28.35 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 6.3252206E+02 8.43E+00 1.33 0.00* 30.80 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 1.9170 +- 1.08920 ) % +| ( 1.92 +- 1.09 ) % |=============================================================================| | There were no errors and 2 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzjj.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzjj.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzjj.ref (revision 8760) @@ -1,174 +1,174 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 3 alphas_power = 2 | Process library 'nlo_eettzjj_lib': recorded process 'nlo_eettzjj_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettzjj_lib': compiling ... | Process library 'nlo_eettzjj_lib': writing makefile | Process library 'nlo_eettzjj_lib': removing old files | Process library 'nlo_eettzjj_lib': writing driver | Process library 'nlo_eettzjj_lib': creating source code | Process library 'nlo_eettzjj_lib': compiling sources | Process library 'nlo_eettzjj_lib': linking | Process library 'nlo_eettzjj_lib': loading | Process library 'nlo_eettzjj_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettzjj_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... Warning: Intermediate decay of zero-width particle Z may be possible. Warning: Intermediate decay of zero-width particle H may be possible. | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettzjj_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettzjj_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettzjj_p1' | Library name = 'nlo_eettzjj_lib' | Process index = 1 | Process components: | 1: 'nlo_eettzjj_p1_i1': e-, e+ => t, tbar, Z, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops] | 2: 'nlo_eettzjj_p1_i2': e-, e+ => t, tbar, Z, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:gl [openloops], [real] | 3: 'nlo_eettzjj_p1_i3': e-, e+ => t, tbar, Z, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [openloops], [virtual] | 4: 'nlo_eettzjj_p1_i4': e-, e+ => t, tbar, Z, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:gl [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 94 channels, 11 dimensions | Phase space: found 94 channels, collected in 7 groves. | Phase space: Using 146 equivalences between channels. | Phase space: wood | Phase space: 94 channels, 14 dimensions | Phase space: found 94 channels, collected in 7 groves. | Phase space: Using 146 equivalences between channels. | Phase space: wood | Phase space: 94 channels, 11 dimensions | Phase space: found 94 channels, collected in 7 groves. | Phase space: Using 146 equivalences between channels. | Phase space: wood | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'nlo_eettzjj_p1' part 'born' | Integrate: iterations = 1:940:"gw" | Integrator: 7 chains, 94 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzjj_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 940 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzjj_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 970 7.0600481E-02 2.23E-02 31.55 9.82* 11.13 |-----------------------------------------------------------------------------| 1 970 7.0600481E-02 2.23E-02 31.55 9.82 11.13 |=============================================================================| | Starting integration for process 'nlo_eettzjj_p1' part 'real' | Integrate: iterations = 1:940:"gw" | Integrator: 7 chains, 94 channels, 14 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzjj_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 940 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzjj_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 970 -2.6270605E-02 4.96E-02 188.73 58.78* 15.57 |-----------------------------------------------------------------------------| 1 970 -2.6270605E-02 4.96E-02 188.73 58.78 15.57 |=============================================================================| | Starting integration for process 'nlo_eettzjj_p1' part 'virtual' | Integrate: iterations = 1:940:"gw" | Integrator: 7 chains, 94 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzjj_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 940 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzjj_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 980 6.3218338E-03 2.91E-03 46.03 14.41* 12.01 |-----------------------------------------------------------------------------| 1 980 6.3218338E-03 2.91E-03 46.03 14.41 12.01 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 5.0651710E-02 5.44E-02 107.46 0.00* 7.37 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| (-28.2559 +- 70.91089 ) % +| ( -28.26 +- 70.91 ) % |=============================================================================| | There were no errors and 2 warning(s). | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppee_ew.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppee_ew.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_ppee_ew.ref (revision 8760) @@ -1,215 +1,215 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22, 11, -11, 13, -13, 12, -12, 14, -14) [user variable] pr = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 22) [user variable] leptons = PDG(11, -11, 13, -13, 15, -15) $exclude_gauge_splittings = "t" | Switching to model 'SM', scheme 'Complex_Mass_Scheme' $blha_ew_scheme = "GF" SM.mZ => 9.118760000000E+01 SM.mW => 8.038500000000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.733400000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 0.000000000000E+00 alpha_power = 2 alphas_power = 0 alphas_nf = 5 alphas_order = 2 ?alphas_is_fixed = false ?alphas_from_mz = false ?alphas_from_lhapdf = true ?alphas_from_lambda_qcd = false SM.alphas => 1.180000000000E-01 $method = "openloops" ?openloops_use_cms = true $integration_method = "vamp2" $rng_method = "rng_stream" openmp_num_threads = 1 ?omega_openmp = false sqrts = 1.300000000000E+04 $lhapdf_file = "LUXqed_plus_PDF4LHC15_nnlo_100" photon_rec_r0 = 1.000000000000E-01 jet_algorithm = 2 jet_r = 4.000000000000E-01 | End of included 'nlo_settings_ew.sin' SM.wtop => 1.369180000000E+00 SM.mZ => 9.115347000000E+01 SM.mW => 8.035785000000E+01 SM.wZ => 2.494566000000E+00 SM.wW => 2.088994000000E+00 alpha_power = 2 alphas_power = 0 $nlo_correction_type = "EW" seed = 1 | Process library 'nlo_ppee_ew_lib': recorded process 'ppee_ew' | Integrate: current process library needs compilation | Process library 'nlo_ppee_ew_lib': compiling ... | Process library 'nlo_ppee_ew_lib': writing makefile | Process library 'nlo_ppee_ew_lib': removing old files | Process library 'nlo_ppee_ew_lib': writing driver | Process library 'nlo_ppee_ew_lib': creating source code | Process library 'nlo_ppee_ew_lib': compiling sources | Process library 'nlo_ppee_ew_lib': linking | Process library 'nlo_ppee_ew_lib': loading | Process library 'nlo_ppee_ew_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 1 | Initializing integration for process ppee_ew: | Beam structure: p, p => lhapdf | Beam data (collision): | p (mass = 0.0000000E+00 GeV) | p (mass = 0.0000000E+00 GeV) | sqrts = 1.300000000000E+04 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppee_ew.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'ppee_ew.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'ppee_ew' | Library name = 'nlo_ppee_ew_lib' | Process index = 1 | Process components: | 1: 'ppee_ew_i1': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+ [openloops] | 2: 'ppee_ew_i2': dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A, dbar:d:ubar:u:sbar:s:cbar:c:bbar:b:A => e-, e+, d:dbar:u:ubar:s:sbar:c:cbar:b:bbar:A [openloops], [real] | 3: 'ppee_ew_i3': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+ [openloops], [virtual] | 4: 'ppee_ew_i4': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+ [inactive], [subtraction] | 5: 'ppee_ew_i5': u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A, u:ubar:d:dbar:s:sbar:c:cbar:b:bbar:A => e-, e+ [openloops], [dglap] | ------------------------------------------------------------------------ | Phase space: 6 channels, 2 dimensions | Phase space: found 6 channels, collected in 3 groves. | Phase space: Using 10 equivalences between channels. | Phase space: wood | Phase space: 6 channels, 5 dimensions | Phase space: found 6 channels, collected in 3 groves. | Phase space: Using 10 equivalences between channels. | Phase space: wood | Phase space: 6 channels, 2 dimensions | Phase space: found 6 channels, collected in 3 groves. | Phase space: Using 10 equivalences between channels. | Phase space: wood | Phase space: 6 channels, 3 dimensions | Phase space: found 6 channels, collected in 3 groves. | Phase space: Using 10 equivalences between channels. | Phase space: wood | Beam structure: lhapdf, none => none, lhapdf | Beam structure: 2 channels, 2 dimensions | Applying user-defined cuts. | Using user-defined general scale. | Starting integration for process 'ppee_ew' part 'born' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 6 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppee_ew.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppee_ew.m1.vg2'. | VAMP2: set chain: use chained weights. 1 381 6.4505582E+05 1.13E+05 17.57 3.43* 15.21 |-----------------------------------------------------------------------------| 1 381 6.4505582E+05 1.13E+05 17.57 3.43 15.21 |=============================================================================| | Starting integration for process 'ppee_ew' part 'real' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 6 channels, 7 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppee_ew.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppee_ew.m2.vg2'. | VAMP2: set chain: use chained weights. 1 397 5.8552031E+03 1.16E+04 198.71 39.59* 4.15 |-----------------------------------------------------------------------------| 1 397 5.8552031E+03 1.16E+04 198.71 39.59 4.15 |=============================================================================| | Starting integration for process 'ppee_ew' part 'virtual' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 6 channels, 4 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppee_ew.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppee_ew.m3.vg2'. | VAMP2: set chain: use chained weights. 1 460 -5.8863656E+03 1.29E+03 22.00 4.72* 14.09 |-----------------------------------------------------------------------------| 1 460 -5.8863656E+03 1.29E+03 22.00 4.72 14.09 |=============================================================================| | Starting integration for process 'ppee_ew' part 'dglap' | Integrate: iterations = 1:500:"gw" | Integrator: 3 chains, 6 channels, 5 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'ppee_ew.m4.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 500 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'ppee_ew.m4.vg2'. | VAMP2: set chain: use chained weights. 1 482 1.8170762E+03 6.34E+02 34.88 7.66* 6.22 |-----------------------------------------------------------------------------| 1 482 1.8170762E+03 6.34E+02 34.88 7.66 6.22 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 6.4684173E+05 1.14E+05 17.61 0.00* 14.66 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 0.2769 +- 1.81818 ) % +| ( 0.28 +- 1.82 ) % |=============================================================================| | WHIZARD run finished. |=============================================================================| Index: trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzz.ref =================================================================== --- trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzz.ref (revision 8759) +++ trunk/share/tests/ext_tests_nlo/ref-output/nlo_eettzz.ref (revision 8760) @@ -1,172 +1,172 @@ ?openmp_logging = false ?vis_history = false ?integration_timer = false openmp_num_threads = 1 ?debug_decay = false ?debug_process = false ?debug_verbose = false ?write_raw = false | Switching to model 'SM', scheme 'GF_MW_MZ' $blha_ew_scheme = "alpha_qed" SM.mZ => 9.118800000000E+01 SM.mW => 8.041900200000E+01 SM.mH => 1.250000000000E+02 SM.GF => 1.166390000000E-05 SM.wZ => 0.000000000000E+00 SM.wtop => 0.000000000000E+00 SM.wW => 0.000000000000E+00 SM.wH => 0.000000000000E+00 SM.ms => 0.000000000000E+00 SM.mc => 0.000000000000E+00 SM.mb => 0.000000000000E+00 SM.mtop => 1.732000000000E+02 SM.me => 0.000000000000E+00 SM.mmu => 0.000000000000E+00 SM.mtau => 1.777000000000E+00 SM.alphas => 1.180000000000E-01 ?alphas_is_fixed = false ?alphas_from_mz = true ?alphas_from_lambda_qcd = false alphas_nf = 5 alphas_order = 2 [user variable] jet = PDG(2, -2, 1, -1, 3, -3, 4, -4, 5, -5, 21) $exclude_gauge_splittings = "t" $method = "openloops" seed = 8131 sqrts = 1.000000000000E+03 jet_algorithm = 2 jet_r = 5.000000000000E-01 $integration_method = "vamp2" $rng_method = "rng_stream" | End of included 'nlo_settings.sin' alpha_power = 4 alphas_power = 0 | Process library 'nlo_eettzz_lib': recorded process 'nlo_eettzz_p1' | Integrate: current process library needs compilation | Process library 'nlo_eettzz_lib': compiling ... | Process library 'nlo_eettzz_lib': writing makefile | Process library 'nlo_eettzz_lib': removing old files | Process library 'nlo_eettzz_lib': writing driver | Process library 'nlo_eettzz_lib': creating source code | Process library 'nlo_eettzz_lib': compiling sources | Process library 'nlo_eettzz_lib': linking | Process library 'nlo_eettzz_lib': loading | Process library 'nlo_eettzz_lib': ... success. | Integrate: compilation done | QCD alpha: using a running strong coupling | RNG: Initializing RNG Stream random-number generator | RNG: Setting seed for random-number generator to 8131 | Initializing integration for process nlo_eettzz_p1: | Beam structure: [any particles] | Beam data (collision): | e- (mass = 0.0000000E+00 GeV) | e+ (mass = 0.0000000E+00 GeV) | sqrts = 1.000000000000E+03 GeV | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettzz_p1.i1.phs' | Phase space: generating configuration ... | Phase space: ... success. | Phase space: writing configuration file 'nlo_eettzz_p1.i3.phs' | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | One-Loop-Provider: Using OpenLoops | Loading library: [...] | ------------------------------------------------------------------------ | Process [scattering]: 'nlo_eettzz_p1' | Library name = 'nlo_eettzz_lib' | Process index = 1 | Process components: | 1: 'nlo_eettzz_p1_i1': e-, e+ => t, tbar, Z, Z [openloops] | 2: 'nlo_eettzz_p1_i2': e-, e+ => t, tbar, Z, Z, gl [openloops], [real] | 3: 'nlo_eettzz_p1_i3': e-, e+ => t, tbar, Z, Z [openloops], [virtual] | 4: 'nlo_eettzz_p1_i4': e-, e+ => t, tbar, Z, Z [inactive], [subtraction] | ------------------------------------------------------------------------ | Phase space: 20 channels, 8 dimensions | Phase space: found 20 channels, collected in 3 groves. | Phase space: Using 64 equivalences between channels. | Phase space: wood | Phase space: 20 channels, 11 dimensions | Phase space: found 20 channels, collected in 3 groves. | Phase space: Using 64 equivalences between channels. | Phase space: wood | Phase space: 20 channels, 8 dimensions | Phase space: found 20 channels, collected in 3 groves. | Phase space: Using 64 equivalences between channels. | Phase space: wood Warning: No cuts have been defined. | Using user-defined general scale. | Starting integration for process 'nlo_eettzz_p1' part 'born' | Integrate: iterations = 1:200:"gw" | Integrator: 3 chains, 20 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzz_p1.m1.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 200 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzz_p1.m1.vg2'. | VAMP2: set chain: use chained weights. 1 200 4.0872323E-02 9.12E-03 22.31 3.16* 15.41 |-----------------------------------------------------------------------------| 1 200 4.0872323E-02 9.12E-03 22.31 3.16 15.41 |=============================================================================| | Starting integration for process 'nlo_eettzz_p1' part 'real' | Integrate: iterations = 1:200:"gw" | Integrator: 3 chains, 20 channels, 11 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzz_p1.m2.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 200 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzz_p1.m2.vg2'. | VAMP2: set chain: use chained weights. 1 200 -1.4381791E-02 4.73E-03 32.86 4.65* 14.22 |-----------------------------------------------------------------------------| 1 200 -1.4381791E-02 4.73E-03 32.86 4.65 14.22 |=============================================================================| | Starting integration for process 'nlo_eettzz_p1' part 'virtual' | Integrate: iterations = 1:200:"gw" | Integrator: 3 chains, 20 channels, 8 dimensions | Integrator: Using VAMP2 channel equivalences | Integrator: Write grid header and grids to 'nlo_eettzz_p1.m3.vg2' | Integrator: Grid checkpoint after each iteration | Integrator: 200 initial calls, 20 max. bins, stratified = T | Integrator: VAMP2 |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| | VAMP2: Initialize new grids and write to file 'nlo_eettzz_p1.m3.vg2'. | VAMP2: set chain: use chained weights. 1 204 1.6832366E-02 3.67E-03 21.78 3.11* 15.60 |-----------------------------------------------------------------------------| 1 204 1.6832366E-02 3.67E-03 21.78 3.11 15.60 |=============================================================================| | Integrate: sum of all components |=============================================================================| | It Calls Integral[fb] Error[fb] Err[%] Acc Eff[%] Chi2 N[It] | |=============================================================================| 1 0 4.3322897E-02 1.09E-02 25.17 0.00* 11.61 | NLO Correction: [O(alpha_s+1)/O(alpha_s)] -| ( 5.9957 +- 14.69597 ) % +| ( 6.00 +- 14.70 ) % |=============================================================================| | There were no errors and 1 warning(s). | WHIZARD run finished. |=============================================================================|